Safe Haskell | Safe-Inferred |
---|---|
Language | Haskell2010 |
Pinecone.Indexes
Contents
Description
Indexes
Synopsis
- newtype Index = Index {}
- newtype Host = Host {}
- data IndexModels = IndexModels {
- indexes :: Vector IndexModel
- data IndexModel = IndexModel {}
- data CreateIndex = CreateIndex {}
- _CreateIndex :: CreateIndex
- data CreateIndexWithEmbedding = CreateIndexWithEmbedding {}
- _CreateIndexWithEmbedding :: CreateIndexWithEmbedding
- data ConfigureIndex = ConfigureIndex {}
- _ConfigureIndex :: ConfigureIndex
- data GetIndexStats = GetIndexStats {}
- _GetIndexStats :: GetIndexStats
- data IndexStats = IndexStats {}
- data Metric
- data Spec = Spec {
- pod :: Maybe Pod
- serverless :: Maybe Serverless
- data Pod = Pod {}
- data PodType = PodType {}
- data Prefix
- data Suffix
- data MetadataConfig = MetadataConfig {}
- data Serverless = Serverless {}
- data Cloud
- data Status = Status {}
- data State
- data DeletionProtection
- data EmbedRequest = EmbedRequest {}
- data EmbedResponse = EmbedResponse {}
- data Contents = Contents {}
- type ControlAPI = "indexes" :> (Get '[JSON] IndexModels :<|> ((ReqBody '[JSON] CreateIndex :> Post '[JSON] IndexModel) :<|> (("create-for-model" :> (ReqBody '[JSON] CreateIndexWithEmbedding :> PostCreated '[JSON] IndexModel)) :<|> ((Capture "index_name" Index :> Get '[JSON] IndexModel) :<|> ((Capture "index_name" Index :> DeleteAccepted '[JSON] NoContent) :<|> (Capture "index_name" Index :> (ReqBody '[JSON] ConfigureIndex :> Patch '[JSON] IndexModel)))))))
- type DataAPI = "describe_index_stats" :> (ReqBody '[JSON] GetIndexStats :> Post '[JSON] IndexStats)
Main types
The name of the index
Instances
FromJSON Index Source # | |
Defined in Pinecone.Indexes | |
ToJSON Index Source # | |
IsString Index Source # | |
Defined in Pinecone.Indexes Methods fromString :: String -> Index # | |
Show Index Source # | |
Eq Index Source # | |
ToHttpApiData Index Source # | |
Defined in Pinecone.Indexes Methods toUrlPiece :: Index -> Text # toEncodedUrlPiece :: Index -> Builder # toHeader :: Index -> ByteString # toQueryParam :: Index -> Text # toEncodedQueryParam :: Index -> Builder # |
The host for the index
Instances
FromJSON Host Source # | |
Defined in Pinecone.Indexes | |
ToJSON Host Source # | |
IsString Host Source # | |
Defined in Pinecone.Indexes Methods fromString :: String -> Host # | |
Show Host Source # | |
Eq Host Source # | |
ToHttpApiData Host Source # | |
Defined in Pinecone.Indexes Methods toUrlPiece :: Host -> Text # toEncodedUrlPiece :: Host -> Builder # toHeader :: Host -> ByteString # toQueryParam :: Host -> Text # toEncodedQueryParam :: Host -> Builder # |
data IndexModels Source #
The list of indexes that exist in the project
Constructors
IndexModels | |
Fields
|
Instances
FromJSON IndexModels Source # | |
Defined in Pinecone.Indexes | |
ToJSON IndexModels Source # | |
Defined in Pinecone.Indexes Methods toJSON :: IndexModels -> Value # toEncoding :: IndexModels -> Encoding # toJSONList :: [IndexModels] -> Value # toEncodingList :: [IndexModels] -> Encoding # omitField :: IndexModels -> Bool # | |
Generic IndexModels Source # | |
Defined in Pinecone.Indexes Associated Types type Rep IndexModels :: Type -> Type # | |
Show IndexModels Source # | |
Defined in Pinecone.Indexes Methods showsPrec :: Int -> IndexModels -> ShowS # show :: IndexModels -> String # showList :: [IndexModels] -> ShowS # | |
Eq IndexModels Source # | |
Defined in Pinecone.Indexes | |
type Rep IndexModels Source # | |
Defined in Pinecone.Indexes type Rep IndexModels = D1 ('MetaData "IndexModels" "Pinecone.Indexes" "pinecone-1.0.0-Ex4c0YruToKASgnObHGBW7" 'False) (C1 ('MetaCons "IndexModels" 'PrefixI 'True) (S1 ('MetaSel ('Just "indexes") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Vector IndexModel)))) |
data IndexModel Source #
The IndexModel
describes the configuration and status of a Pinecone
index
Constructors
IndexModel | |
Instances
data CreateIndex Source #
The desired configuration for the index
Constructors
CreateIndex | |
Instances
_CreateIndex :: CreateIndex Source #
Default CreateIndex
data CreateIndexWithEmbedding Source #
The desired configuration for the index and associated embedding model
Constructors
CreateIndexWithEmbedding | |
Instances
data ConfigureIndex Source #
The desired pod size and replica configuration for the index
Constructors
ConfigureIndex | |
Fields
|
Instances
_ConfigureIndex :: ConfigureIndex Source #
Default ConfigureIndex
data GetIndexStats Source #
Request body for /describe_index_stats
Constructors
GetIndexStats | |
Instances
_GetIndexStats :: GetIndexStats Source #
Default GetIndexStats
data IndexStats Source #
Response body for /describe_index_stats
Constructors
IndexStats | |
Fields
|
Instances
Other types
The distance metric to be used for similarity search
Constructors
Cosine | |
Euclidean | |
DotProduct |
Instances
FromJSON Metric Source # | |
Defined in Pinecone.Indexes | |
ToJSON Metric Source # | |
Generic Metric Source # | |
Show Metric Source # | |
Eq Metric Source # | |
type Rep Metric Source # | |
Defined in Pinecone.Indexes type Rep Metric = D1 ('MetaData "Metric" "Pinecone.Indexes" "pinecone-1.0.0-Ex4c0YruToKASgnObHGBW7" 'False) (C1 ('MetaCons "Cosine" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "Euclidean" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "DotProduct" 'PrefixI 'False) (U1 :: Type -> Type))) |
Spec
object
Constructors
Spec | |
Fields
|
Instances
FromJSON Spec Source # | |
Defined in Pinecone.Indexes | |
ToJSON Spec Source # | |
Generic Spec Source # | |
Show Spec Source # | |
Eq Spec Source # | |
type Rep Spec Source # | |
Defined in Pinecone.Indexes type Rep Spec = D1 ('MetaData "Spec" "Pinecone.Indexes" "pinecone-1.0.0-Ex4c0YruToKASgnObHGBW7" 'False) (C1 ('MetaCons "Spec" 'PrefixI 'True) (S1 ('MetaSel ('Just "pod") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe Pod)) :*: S1 ('MetaSel ('Just "serverless") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe Serverless)))) |
Configuration needed to deploy a pod-based index.
Constructors
Pod | |
Fields
|
Instances
The type of pod to use
Instances
FromJSON PodType Source # | |
Defined in Pinecone.Indexes | |
ToJSON PodType Source # | |
Generic PodType Source # | |
Show PodType Source # | |
Eq PodType Source # | |
type Rep PodType Source # | |
Defined in Pinecone.Indexes type Rep PodType = D1 ('MetaData "PodType" "Pinecone.Indexes" "pinecone-1.0.0-Ex4c0YruToKASgnObHGBW7" 'False) (C1 ('MetaCons "PodType" 'PrefixI 'True) (S1 ('MetaSel ('Just "prefix") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Prefix) :*: S1 ('MetaSel ('Just "suffix") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Suffix))) |
The first component of a pod type
The second component of a pod type
Instances
FromJSON Suffix Source # | |
Defined in Pinecone.Indexes | |
ToJSON Suffix Source # | |
Generic Suffix Source # | |
Show Suffix Source # | |
Eq Suffix Source # | |
type Rep Suffix Source # | |
Defined in Pinecone.Indexes type Rep Suffix = D1 ('MetaData "Suffix" "Pinecone.Indexes" "pinecone-1.0.0-Ex4c0YruToKASgnObHGBW7" 'False) ((C1 ('MetaCons "X1" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "X2" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "X4" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "X8" 'PrefixI 'False) (U1 :: Type -> Type))) |
data MetadataConfig Source #
Configuration for the behavior of Pinecone's internal metadata index
Constructors
MetadataConfig | |
Instances
data Serverless Source #
Configuration needed to deploy a serverless index
Constructors
Serverless | |
Instances
The public cloud where you would like your index hosted
Index status
Instances
FromJSON Status Source # | |
Defined in Pinecone.Indexes | |
ToJSON Status Source # | |
Generic Status Source # | |
Show Status Source # | |
Eq Status Source # | |
type Rep Status Source # | |
Defined in Pinecone.Indexes type Rep Status = D1 ('MetaData "Status" "Pinecone.Indexes" "pinecone-1.0.0-Ex4c0YruToKASgnObHGBW7" 'False) (C1 ('MetaCons "Status" 'PrefixI 'True) (S1 ('MetaSel ('Just "ready") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Bool) :*: S1 ('MetaSel ('Just "state") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 State))) |
Index state
Constructors
Initializing | |
InitializationFailed | |
ScalingUp | |
ScalingDown | |
ScalingUpPodSize | |
ScalingDownPodSize | |
Terminating | |
Ready |
Instances
FromJSON State Source # | |
Defined in Pinecone.Indexes | |
ToJSON State Source # | |
Generic State Source # | |
Show State Source # | |
Eq State Source # | |
type Rep State Source # | |
Defined in Pinecone.Indexes type Rep State = D1 ('MetaData "State" "Pinecone.Indexes" "pinecone-1.0.0-Ex4c0YruToKASgnObHGBW7" 'False) (((C1 ('MetaCons "Initializing" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "InitializationFailed" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "ScalingUp" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "ScalingDown" 'PrefixI 'False) (U1 :: Type -> Type))) :+: ((C1 ('MetaCons "ScalingUpPodSize" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "ScalingDownPodSize" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "Terminating" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "Ready" 'PrefixI 'False) (U1 :: Type -> Type)))) |
data DeletionProtection Source #
Whether deletion protection is enabled/disabled for the index.
Instances
data EmbedRequest Source #
Specify the integrated inference embedding configuration for the index
Constructors
EmbedRequest | |
Instances
data EmbedResponse Source #
The embedding model and document fields mapped to embedding inputs
Constructors
EmbedResponse | |
Instances
A summary of the contents of a namespace
Constructors
Contents | |
Fields |
API
type ControlAPI = "indexes" :> (Get '[JSON] IndexModels :<|> ((ReqBody '[JSON] CreateIndex :> Post '[JSON] IndexModel) :<|> (("create-for-model" :> (ReqBody '[JSON] CreateIndexWithEmbedding :> PostCreated '[JSON] IndexModel)) :<|> ((Capture "index_name" Index :> Get '[JSON] IndexModel) :<|> ((Capture "index_name" Index :> DeleteAccepted '[JSON] NoContent) :<|> (Capture "index_name" Index :> (ReqBody '[JSON] ConfigureIndex :> Patch '[JSON] IndexModel))))))) Source #
Control API