pinecone-1.0.0: Servant bindings to Pinecone
Safe HaskellSafe-Inferred
LanguageHaskell2010

Pinecone.Indexes

Description

Indexes

Synopsis

Main types

newtype Index Source #

The name of the index

Constructors

Index 

Fields

Instances

Instances details
FromJSON Index Source # 
Instance details

Defined in Pinecone.Indexes

ToJSON Index Source # 
Instance details

Defined in Pinecone.Indexes

IsString Index Source # 
Instance details

Defined in Pinecone.Indexes

Methods

fromString :: String -> Index #

Show Index Source # 
Instance details

Defined in Pinecone.Indexes

Methods

showsPrec :: Int -> Index -> ShowS #

show :: Index -> String #

showList :: [Index] -> ShowS #

Eq Index Source # 
Instance details

Defined in Pinecone.Indexes

Methods

(==) :: Index -> Index -> Bool #

(/=) :: Index -> Index -> Bool #

ToHttpApiData Index Source # 
Instance details

Defined in Pinecone.Indexes

newtype Host Source #

The host for the index

Constructors

Host 

Fields

Instances

Instances details
FromJSON Host Source # 
Instance details

Defined in Pinecone.Indexes

ToJSON Host Source # 
Instance details

Defined in Pinecone.Indexes

IsString Host Source # 
Instance details

Defined in Pinecone.Indexes

Methods

fromString :: String -> Host #

Show Host Source # 
Instance details

Defined in Pinecone.Indexes

Methods

showsPrec :: Int -> Host -> ShowS #

show :: Host -> String #

showList :: [Host] -> ShowS #

Eq Host Source # 
Instance details

Defined in Pinecone.Indexes

Methods

(==) :: Host -> Host -> Bool #

(/=) :: Host -> Host -> Bool #

ToHttpApiData Host Source # 
Instance details

Defined in Pinecone.Indexes

data IndexModels Source #

The list of indexes that exist in the project

Constructors

IndexModels 

Fields

Instances

Instances details
FromJSON IndexModels Source # 
Instance details

Defined in Pinecone.Indexes

ToJSON IndexModels Source # 
Instance details

Defined in Pinecone.Indexes

Generic IndexModels Source # 
Instance details

Defined in Pinecone.Indexes

Associated Types

type Rep IndexModels :: Type -> Type #

Show IndexModels Source # 
Instance details

Defined in Pinecone.Indexes

Eq IndexModels Source # 
Instance details

Defined in Pinecone.Indexes

type Rep IndexModels Source # 
Instance details

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

Instances

Instances details
FromJSON IndexModel Source # 
Instance details

Defined in Pinecone.Indexes

ToJSON IndexModel Source # 
Instance details

Defined in Pinecone.Indexes

Generic IndexModel Source # 
Instance details

Defined in Pinecone.Indexes

Associated Types

type Rep IndexModel :: Type -> Type #

Show IndexModel Source # 
Instance details

Defined in Pinecone.Indexes

Eq IndexModel Source # 
Instance details

Defined in Pinecone.Indexes

type Rep IndexModel Source # 
Instance details

Defined in Pinecone.Indexes

data CreateIndex Source #

The desired configuration for the index

Instances

Instances details
FromJSON CreateIndex Source # 
Instance details

Defined in Pinecone.Indexes

ToJSON CreateIndex Source # 
Instance details

Defined in Pinecone.Indexes

Generic CreateIndex Source # 
Instance details

Defined in Pinecone.Indexes

Associated Types

type Rep CreateIndex :: Type -> Type #

Show CreateIndex Source # 
Instance details

Defined in Pinecone.Indexes

Eq CreateIndex Source # 
Instance details

Defined in Pinecone.Indexes

type Rep CreateIndex Source # 
Instance details

Defined in Pinecone.Indexes

data CreateIndexWithEmbedding Source #

The desired configuration for the index and associated embedding model

Instances

Instances details
FromJSON CreateIndexWithEmbedding Source # 
Instance details

Defined in Pinecone.Indexes

ToJSON CreateIndexWithEmbedding Source # 
Instance details

Defined in Pinecone.Indexes

Generic CreateIndexWithEmbedding Source # 
Instance details

Defined in Pinecone.Indexes

Associated Types

type Rep CreateIndexWithEmbedding :: Type -> Type #

Show CreateIndexWithEmbedding Source # 
Instance details

Defined in Pinecone.Indexes

Eq CreateIndexWithEmbedding Source # 
Instance details

Defined in Pinecone.Indexes

type Rep CreateIndexWithEmbedding Source # 
Instance details

Defined in Pinecone.Indexes

data ConfigureIndex Source #

The desired pod size and replica configuration for the index

Instances

Instances details
FromJSON ConfigureIndex Source # 
Instance details

Defined in Pinecone.Indexes

ToJSON ConfigureIndex Source # 
Instance details

Defined in Pinecone.Indexes

Generic ConfigureIndex Source # 
Instance details

Defined in Pinecone.Indexes

Associated Types

type Rep ConfigureIndex :: Type -> Type #

Show ConfigureIndex Source # 
Instance details

Defined in Pinecone.Indexes

Eq ConfigureIndex Source # 
Instance details

Defined in Pinecone.Indexes

type Rep ConfigureIndex Source # 
Instance details

Defined in Pinecone.Indexes

type Rep ConfigureIndex = D1 ('MetaData "ConfigureIndex" "Pinecone.Indexes" "pinecone-1.0.0-Ex4c0YruToKASgnObHGBW7" 'False) (C1 ('MetaCons "ConfigureIndex" 'PrefixI 'True) ((S1 ('MetaSel ('Just "spec") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe Spec)) :*: S1 ('MetaSel ('Just "deletion_protection") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe DeletionProtection))) :*: (S1 ('MetaSel ('Just "tags") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe (Map Text Text))) :*: S1 ('MetaSel ('Just "embed") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe EmbedRequest)))))

data GetIndexStats Source #

Request body for /describe_index_stats

Constructors

GetIndexStats 

Fields

Instances

Instances details
FromJSON GetIndexStats Source # 
Instance details

Defined in Pinecone.Indexes

ToJSON GetIndexStats Source # 
Instance details

Defined in Pinecone.Indexes

Generic GetIndexStats Source # 
Instance details

Defined in Pinecone.Indexes

Associated Types

type Rep GetIndexStats :: Type -> Type #

Show GetIndexStats Source # 
Instance details

Defined in Pinecone.Indexes

Eq GetIndexStats Source # 
Instance details

Defined in Pinecone.Indexes

type Rep GetIndexStats Source # 
Instance details

Defined in Pinecone.Indexes

type Rep GetIndexStats = D1 ('MetaData "GetIndexStats" "Pinecone.Indexes" "pinecone-1.0.0-Ex4c0YruToKASgnObHGBW7" 'False) (C1 ('MetaCons "GetIndexStats" 'PrefixI 'True) (S1 ('MetaSel ('Just "filter") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe Filter))))

data IndexStats Source #

Response body for /describe_index_stats

Instances

Instances details
FromJSON IndexStats Source # 
Instance details

Defined in Pinecone.Indexes

ToJSON IndexStats Source # 
Instance details

Defined in Pinecone.Indexes

Generic IndexStats Source # 
Instance details

Defined in Pinecone.Indexes

Associated Types

type Rep IndexStats :: Type -> Type #

Show IndexStats Source # 
Instance details

Defined in Pinecone.Indexes

Eq IndexStats Source # 
Instance details

Defined in Pinecone.Indexes

type Rep IndexStats Source # 
Instance details

Defined in Pinecone.Indexes

Other types

data Metric Source #

The distance metric to be used for similarity search

Constructors

Cosine 
Euclidean 
DotProduct 

Instances

Instances details
FromJSON Metric Source # 
Instance details

Defined in Pinecone.Indexes

ToJSON Metric Source # 
Instance details

Defined in Pinecone.Indexes

Generic Metric Source # 
Instance details

Defined in Pinecone.Indexes

Associated Types

type Rep Metric :: Type -> Type #

Methods

from :: Metric -> Rep Metric x #

to :: Rep Metric x -> Metric #

Show Metric Source # 
Instance details

Defined in Pinecone.Indexes

Eq Metric Source # 
Instance details

Defined in Pinecone.Indexes

Methods

(==) :: Metric -> Metric -> Bool #

(/=) :: Metric -> Metric -> Bool #

type Rep Metric Source # 
Instance details

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)))

data Spec Source #

Spec object

Constructors

Spec 

Instances

Instances details
FromJSON Spec Source # 
Instance details

Defined in Pinecone.Indexes

ToJSON Spec Source # 
Instance details

Defined in Pinecone.Indexes

Generic Spec Source # 
Instance details

Defined in Pinecone.Indexes

Associated Types

type Rep Spec :: Type -> Type #

Methods

from :: Spec -> Rep Spec x #

to :: Rep Spec x -> Spec #

Show Spec Source # 
Instance details

Defined in Pinecone.Indexes

Methods

showsPrec :: Int -> Spec -> ShowS #

show :: Spec -> String #

showList :: [Spec] -> ShowS #

Eq Spec Source # 
Instance details

Defined in Pinecone.Indexes

Methods

(==) :: Spec -> Spec -> Bool #

(/=) :: Spec -> Spec -> Bool #

type Rep Spec Source # 
Instance details

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))))

data Pod Source #

Configuration needed to deploy a pod-based index.

Instances

Instances details
FromJSON Pod Source # 
Instance details

Defined in Pinecone.Indexes

ToJSON Pod Source # 
Instance details

Defined in Pinecone.Indexes

Generic Pod Source # 
Instance details

Defined in Pinecone.Indexes

Associated Types

type Rep Pod :: Type -> Type #

Methods

from :: Pod -> Rep Pod x #

to :: Rep Pod x -> Pod #

Show Pod Source # 
Instance details

Defined in Pinecone.Indexes

Methods

showsPrec :: Int -> Pod -> ShowS #

show :: Pod -> String #

showList :: [Pod] -> ShowS #

Eq Pod Source # 
Instance details

Defined in Pinecone.Indexes

Methods

(==) :: Pod -> Pod -> Bool #

(/=) :: Pod -> Pod -> Bool #

type Rep Pod Source # 
Instance details

Defined in Pinecone.Indexes

data PodType Source #

The type of pod to use

Constructors

PodType 

Fields

Instances

Instances details
FromJSON PodType Source # 
Instance details

Defined in Pinecone.Indexes

ToJSON PodType Source # 
Instance details

Defined in Pinecone.Indexes

Generic PodType Source # 
Instance details

Defined in Pinecone.Indexes

Associated Types

type Rep PodType :: Type -> Type #

Methods

from :: PodType -> Rep PodType x #

to :: Rep PodType x -> PodType #

Show PodType Source # 
Instance details

Defined in Pinecone.Indexes

Eq PodType Source # 
Instance details

Defined in Pinecone.Indexes

Methods

(==) :: PodType -> PodType -> Bool #

(/=) :: PodType -> PodType -> Bool #

type Rep PodType Source # 
Instance details

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)))

data Prefix Source #

The first component of a pod type

Constructors

S1 
P1 
P2 

Instances

Instances details
FromJSON Prefix Source # 
Instance details

Defined in Pinecone.Indexes

ToJSON Prefix Source # 
Instance details

Defined in Pinecone.Indexes

Generic Prefix Source # 
Instance details

Defined in Pinecone.Indexes

Associated Types

type Rep Prefix :: Type -> Type #

Methods

from :: Prefix -> Rep Prefix x #

to :: Rep Prefix x -> Prefix #

Show Prefix Source # 
Instance details

Defined in Pinecone.Indexes

Eq Prefix Source # 
Instance details

Defined in Pinecone.Indexes

Methods

(==) :: Prefix -> Prefix -> Bool #

(/=) :: Prefix -> Prefix -> Bool #

type Rep Prefix Source # 
Instance details

Defined in Pinecone.Indexes

type Rep Prefix = D1 ('MetaData "Prefix" "Pinecone.Indexes" "pinecone-1.0.0-Ex4c0YruToKASgnObHGBW7" 'False) (C1 ('MetaCons "S1" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "P1" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "P2" 'PrefixI 'False) (U1 :: Type -> Type)))

data Suffix Source #

The second component of a pod type

Constructors

X1 
X2 
X4 
X8 

Instances

Instances details
FromJSON Suffix Source # 
Instance details

Defined in Pinecone.Indexes

ToJSON Suffix Source # 
Instance details

Defined in Pinecone.Indexes

Generic Suffix Source # 
Instance details

Defined in Pinecone.Indexes

Associated Types

type Rep Suffix :: Type -> Type #

Methods

from :: Suffix -> Rep Suffix x #

to :: Rep Suffix x -> Suffix #

Show Suffix Source # 
Instance details

Defined in Pinecone.Indexes

Eq Suffix Source # 
Instance details

Defined in Pinecone.Indexes

Methods

(==) :: Suffix -> Suffix -> Bool #

(/=) :: Suffix -> Suffix -> Bool #

type Rep Suffix Source # 
Instance details

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 

Fields

Instances

Instances details
FromJSON MetadataConfig Source # 
Instance details

Defined in Pinecone.Indexes

ToJSON MetadataConfig Source # 
Instance details

Defined in Pinecone.Indexes

Generic MetadataConfig Source # 
Instance details

Defined in Pinecone.Indexes

Associated Types

type Rep MetadataConfig :: Type -> Type #

Show MetadataConfig Source # 
Instance details

Defined in Pinecone.Indexes

Eq MetadataConfig Source # 
Instance details

Defined in Pinecone.Indexes

type Rep MetadataConfig Source # 
Instance details

Defined in Pinecone.Indexes

type Rep MetadataConfig = D1 ('MetaData "MetadataConfig" "Pinecone.Indexes" "pinecone-1.0.0-Ex4c0YruToKASgnObHGBW7" 'False) (C1 ('MetaCons "MetadataConfig" 'PrefixI 'True) (S1 ('MetaSel ('Just "indexed") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe (Vector Text)))))

data Serverless Source #

Configuration needed to deploy a serverless index

Constructors

Serverless 

Fields

Instances

Instances details
FromJSON Serverless Source # 
Instance details

Defined in Pinecone.Indexes

ToJSON Serverless Source # 
Instance details

Defined in Pinecone.Indexes

Generic Serverless Source # 
Instance details

Defined in Pinecone.Indexes

Associated Types

type Rep Serverless :: Type -> Type #

Show Serverless Source # 
Instance details

Defined in Pinecone.Indexes

Eq Serverless Source # 
Instance details

Defined in Pinecone.Indexes

type Rep Serverless Source # 
Instance details

Defined in Pinecone.Indexes

type Rep Serverless = D1 ('MetaData "Serverless" "Pinecone.Indexes" "pinecone-1.0.0-Ex4c0YruToKASgnObHGBW7" 'False) (C1 ('MetaCons "Serverless" 'PrefixI 'True) (S1 ('MetaSel ('Just "cloud") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Cloud) :*: S1 ('MetaSel ('Just "region") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Text)))

data Cloud Source #

The public cloud where you would like your index hosted

Constructors

GCP 
AWS 
Azure 

Instances

Instances details
FromJSON Cloud Source # 
Instance details

Defined in Pinecone.Indexes

ToJSON Cloud Source # 
Instance details

Defined in Pinecone.Indexes

Generic Cloud Source # 
Instance details

Defined in Pinecone.Indexes

Associated Types

type Rep Cloud :: Type -> Type #

Methods

from :: Cloud -> Rep Cloud x #

to :: Rep Cloud x -> Cloud #

Show Cloud Source # 
Instance details

Defined in Pinecone.Indexes

Methods

showsPrec :: Int -> Cloud -> ShowS #

show :: Cloud -> String #

showList :: [Cloud] -> ShowS #

Eq Cloud Source # 
Instance details

Defined in Pinecone.Indexes

Methods

(==) :: Cloud -> Cloud -> Bool #

(/=) :: Cloud -> Cloud -> Bool #

type Rep Cloud Source # 
Instance details

Defined in Pinecone.Indexes

type Rep Cloud = D1 ('MetaData "Cloud" "Pinecone.Indexes" "pinecone-1.0.0-Ex4c0YruToKASgnObHGBW7" 'False) (C1 ('MetaCons "GCP" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "AWS" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "Azure" 'PrefixI 'False) (U1 :: Type -> Type)))

data Status Source #

Index status

Constructors

Status 

Fields

Instances

Instances details
FromJSON Status Source # 
Instance details

Defined in Pinecone.Indexes

ToJSON Status Source # 
Instance details

Defined in Pinecone.Indexes

Generic Status Source # 
Instance details

Defined in Pinecone.Indexes

Associated Types

type Rep Status :: Type -> Type #

Methods

from :: Status -> Rep Status x #

to :: Rep Status x -> Status #

Show Status Source # 
Instance details

Defined in Pinecone.Indexes

Eq Status Source # 
Instance details

Defined in Pinecone.Indexes

Methods

(==) :: Status -> Status -> Bool #

(/=) :: Status -> Status -> Bool #

type Rep Status Source # 
Instance details

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)))

data State Source #

Index state

Instances

Instances details
FromJSON State Source # 
Instance details

Defined in Pinecone.Indexes

ToJSON State Source # 
Instance details

Defined in Pinecone.Indexes

Generic State Source # 
Instance details

Defined in Pinecone.Indexes

Associated Types

type Rep State :: Type -> Type #

Methods

from :: State -> Rep State x #

to :: Rep State x -> State #

Show State Source # 
Instance details

Defined in Pinecone.Indexes

Methods

showsPrec :: Int -> State -> ShowS #

show :: State -> String #

showList :: [State] -> ShowS #

Eq State Source # 
Instance details

Defined in Pinecone.Indexes

Methods

(==) :: State -> State -> Bool #

(/=) :: State -> State -> Bool #

type Rep State Source # 
Instance details

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.

Constructors

Disabled 
Enabled 

Instances

Instances details
FromJSON DeletionProtection Source # 
Instance details

Defined in Pinecone.Indexes

ToJSON DeletionProtection Source # 
Instance details

Defined in Pinecone.Indexes

Generic DeletionProtection Source # 
Instance details

Defined in Pinecone.Indexes

Associated Types

type Rep DeletionProtection :: Type -> Type #

Show DeletionProtection Source # 
Instance details

Defined in Pinecone.Indexes

Eq DeletionProtection Source # 
Instance details

Defined in Pinecone.Indexes

type Rep DeletionProtection Source # 
Instance details

Defined in Pinecone.Indexes

type Rep DeletionProtection = D1 ('MetaData "DeletionProtection" "Pinecone.Indexes" "pinecone-1.0.0-Ex4c0YruToKASgnObHGBW7" 'False) (C1 ('MetaCons "Disabled" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "Enabled" 'PrefixI 'False) (U1 :: Type -> Type))

data EmbedRequest Source #

Specify the integrated inference embedding configuration for the index

Instances

Instances details
FromJSON EmbedRequest Source # 
Instance details

Defined in Pinecone.Indexes

ToJSON EmbedRequest Source # 
Instance details

Defined in Pinecone.Indexes

Generic EmbedRequest Source # 
Instance details

Defined in Pinecone.Indexes

Associated Types

type Rep EmbedRequest :: Type -> Type #

Show EmbedRequest Source # 
Instance details

Defined in Pinecone.Indexes

Eq EmbedRequest Source # 
Instance details

Defined in Pinecone.Indexes

type Rep EmbedRequest Source # 
Instance details

Defined in Pinecone.Indexes

type Rep EmbedRequest = D1 ('MetaData "EmbedRequest" "Pinecone.Indexes" "pinecone-1.0.0-Ex4c0YruToKASgnObHGBW7" 'False) (C1 ('MetaCons "EmbedRequest" 'PrefixI 'True) ((S1 ('MetaSel ('Just "model") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Text) :*: S1 ('MetaSel ('Just "metric") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe Metric))) :*: (S1 ('MetaSel ('Just "read_parameters") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe (Map Text Value))) :*: S1 ('MetaSel ('Just "write_parameters") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe (Map Text Value))))))

data EmbedResponse Source #

The embedding model and document fields mapped to embedding inputs

Instances

Instances details
FromJSON EmbedResponse Source # 
Instance details

Defined in Pinecone.Indexes

ToJSON EmbedResponse Source # 
Instance details

Defined in Pinecone.Indexes

Generic EmbedResponse Source # 
Instance details

Defined in Pinecone.Indexes

Associated Types

type Rep EmbedResponse :: Type -> Type #

Show EmbedResponse Source # 
Instance details

Defined in Pinecone.Indexes

Eq EmbedResponse Source # 
Instance details

Defined in Pinecone.Indexes

type Rep EmbedResponse Source # 
Instance details

Defined in Pinecone.Indexes

data Contents Source #

A summary of the contents of a namespace

Constructors

Contents 

Fields

Instances

Instances details
FromJSON Contents Source # 
Instance details

Defined in Pinecone.Indexes

ToJSON Contents Source # 
Instance details

Defined in Pinecone.Indexes

Generic Contents Source # 
Instance details

Defined in Pinecone.Indexes

Associated Types

type Rep Contents :: Type -> Type #

Methods

from :: Contents -> Rep Contents x #

to :: Rep Contents x -> Contents #

Show Contents Source # 
Instance details

Defined in Pinecone.Indexes

Eq Contents Source # 
Instance details

Defined in Pinecone.Indexes

type Rep Contents Source # 
Instance details

Defined in Pinecone.Indexes

type Rep Contents = D1 ('MetaData "Contents" "Pinecone.Indexes" "pinecone-1.0.0-Ex4c0YruToKASgnObHGBW7" 'False) (C1 ('MetaCons "Contents" 'PrefixI 'True) (S1 ('MetaSel ('Just "vectorCount") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Natural)))

API

type DataAPI = "describe_index_stats" :> (ReqBody '[JSON] GetIndexStats :> Post '[JSON] IndexStats) Source #

Data API