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

Pinecone.Embed

Description

Embed

Synopsis

Main types

data GenerateVectors Source #

Generate embeddings for inputs

Constructors

GenerateVectors 

Fields

Instances

Instances details
FromJSON GenerateVectors Source # 
Instance details

Defined in Pinecone.Embed

ToJSON GenerateVectors Source # 
Instance details

Defined in Pinecone.Embed

Generic GenerateVectors Source # 
Instance details

Defined in Pinecone.Embed

Associated Types

type Rep GenerateVectors :: Type -> Type #

Show GenerateVectors Source # 
Instance details

Defined in Pinecone.Embed

Eq GenerateVectors Source # 
Instance details

Defined in Pinecone.Embed

type Rep GenerateVectors Source # 
Instance details

Defined in Pinecone.Embed

type Rep GenerateVectors = D1 ('MetaData "GenerateVectors" "Pinecone.Embed" "pinecone-1.0.0-Ex4c0YruToKASgnObHGBW7" 'False) (C1 ('MetaCons "GenerateVectors" 'PrefixI 'True) (S1 ('MetaSel ('Just "model") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Text) :*: (S1 ('MetaSel ('Just "inputs") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Vector Text)) :*: S1 ('MetaSel ('Just "parameters") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Map Text Scalar)))))

data Embeddings Source #

Embeddings generated for the input.

Constructors

Embeddings 

Fields

Instances

Instances details
FromJSON Embeddings Source # 
Instance details

Defined in Pinecone.Embed

ToJSON Embeddings Source # 
Instance details

Defined in Pinecone.Embed

Generic Embeddings Source # 
Instance details

Defined in Pinecone.Embed

Associated Types

type Rep Embeddings :: Type -> Type #

Show Embeddings Source # 
Instance details

Defined in Pinecone.Embed

Eq Embeddings Source # 
Instance details

Defined in Pinecone.Embed

type Rep Embeddings Source # 
Instance details

Defined in Pinecone.Embed

type Rep Embeddings = D1 ('MetaData "Embeddings" "Pinecone.Embed" "pinecone-1.0.0-Ex4c0YruToKASgnObHGBW7" 'False) (C1 ('MetaCons "Embeddings" 'PrefixI 'True) ((S1 ('MetaSel ('Just "model") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Text) :*: S1 ('MetaSel ('Just "vector_type") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 VectorType)) :*: (S1 ('MetaSel ('Just "data_") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Vector Embedding)) :*: S1 ('MetaSel ('Just "usage") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Usage))))

Other types

data Input Source #

Input to generate embedding for

Constructors

Input 

Fields

Instances

Instances details
FromJSON Input Source # 
Instance details

Defined in Pinecone.Embed

ToJSON Input Source # 
Instance details

Defined in Pinecone.Embed

Generic Input Source # 
Instance details

Defined in Pinecone.Embed

Associated Types

type Rep Input :: Type -> Type #

Methods

from :: Input -> Rep Input x #

to :: Rep Input x -> Input #

Show Input Source # 
Instance details

Defined in Pinecone.Embed

Methods

showsPrec :: Int -> Input -> ShowS #

show :: Input -> String #

showList :: [Input] -> ShowS #

Eq Input Source # 
Instance details

Defined in Pinecone.Embed

Methods

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

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

type Rep Input Source # 
Instance details

Defined in Pinecone.Embed

type Rep Input = D1 ('MetaData "Input" "Pinecone.Embed" "pinecone-1.0.0-Ex4c0YruToKASgnObHGBW7" 'False) (C1 ('MetaCons "Input" 'PrefixI 'True) (S1 ('MetaSel ('Just "text") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Text)))

data VectorType Source #

The index vector type

Constructors

Dense 
Sparse 

Instances

Instances details
FromJSON VectorType Source # 
Instance details

Defined in Pinecone.Embed

ToJSON VectorType Source # 
Instance details

Defined in Pinecone.Embed

Generic VectorType Source # 
Instance details

Defined in Pinecone.Embed

Associated Types

type Rep VectorType :: Type -> Type #

Show VectorType Source # 
Instance details

Defined in Pinecone.Embed

Eq VectorType Source # 
Instance details

Defined in Pinecone.Embed

type Rep VectorType Source # 
Instance details

Defined in Pinecone.Embed

type Rep VectorType = D1 ('MetaData "VectorType" "Pinecone.Embed" "pinecone-1.0.0-Ex4c0YruToKASgnObHGBW7" 'False) (C1 ('MetaCons "Dense" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "Sparse" 'PrefixI 'False) (U1 :: Type -> Type))

data Embedding Source #

An embedding generated for an input

Constructors

EmbeddingDense 

Fields

EmbeddingSparse 

Fields

Instances

Instances details
FromJSON Embedding Source # 
Instance details

Defined in Pinecone.Embed

ToJSON Embedding Source # 
Instance details

Defined in Pinecone.Embed

Generic Embedding Source # 
Instance details

Defined in Pinecone.Embed

Associated Types

type Rep Embedding :: Type -> Type #

Show Embedding Source # 
Instance details

Defined in Pinecone.Embed

Eq Embedding Source # 
Instance details

Defined in Pinecone.Embed

type Rep Embedding Source # 
Instance details

Defined in Pinecone.Embed

type Rep Embedding = D1 ('MetaData "Embedding" "Pinecone.Embed" "pinecone-1.0.0-Ex4c0YruToKASgnObHGBW7" 'False) (C1 ('MetaCons "EmbeddingDense" 'PrefixI 'True) (S1 ('MetaSel ('Just "values") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Vector Double))) :+: C1 ('MetaCons "EmbeddingSparse" 'PrefixI 'True) (S1 ('MetaSel ('Just "sparse_values") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Vector Double)) :*: (S1 ('MetaSel ('Just "sparse_indices") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Vector Natural)) :*: S1 ('MetaSel ('Just "sparse_tokens") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Vector Text)))))

data Usage Source #

Usage statistics for the model inference.

Constructors

Usage 

Instances

Instances details
FromJSON Usage Source # 
Instance details

Defined in Pinecone.Embed

ToJSON Usage Source # 
Instance details

Defined in Pinecone.Embed

Generic Usage Source # 
Instance details

Defined in Pinecone.Embed

Associated Types

type Rep Usage :: Type -> Type #

Methods

from :: Usage -> Rep Usage x #

to :: Rep Usage x -> Usage #

Show Usage Source # 
Instance details

Defined in Pinecone.Embed

Methods

showsPrec :: Int -> Usage -> ShowS #

show :: Usage -> String #

showList :: [Usage] -> ShowS #

Eq Usage Source # 
Instance details

Defined in Pinecone.Embed

Methods

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

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

type Rep Usage Source # 
Instance details

Defined in Pinecone.Embed

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

Servant

type API = "embed" :> (ReqBody '[JSON] GenerateVectors :> Post '[JSON] Embeddings) Source #

Servant API