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

Pinecone.Search

Description

Search

Synopsis

Main types

data SearchWithVector Source #

Request body for /query

Instances

Instances details
FromJSON SearchWithVector Source # 
Instance details

Defined in Pinecone.Search

ToJSON SearchWithVector Source # 
Instance details

Defined in Pinecone.Search

Generic SearchWithVector Source # 
Instance details

Defined in Pinecone.Search

Associated Types

type Rep SearchWithVector :: Type -> Type #

Show SearchWithVector Source # 
Instance details

Defined in Pinecone.Search

Eq SearchWithVector Source # 
Instance details

Defined in Pinecone.Search

type Rep SearchWithVector Source # 
Instance details

Defined in Pinecone.Search

data Matches Source #

Response body for /query

Constructors

Matches 

Fields

Instances

Instances details
FromJSON Matches Source # 
Instance details

Defined in Pinecone.Search

ToJSON Matches Source # 
Instance details

Defined in Pinecone.Search

Generic Matches Source # 
Instance details

Defined in Pinecone.Search

Associated Types

type Rep Matches :: Type -> Type #

Methods

from :: Matches -> Rep Matches x #

to :: Rep Matches x -> Matches #

Show Matches Source # 
Instance details

Defined in Pinecone.Search

Eq Matches Source # 
Instance details

Defined in Pinecone.Search

Methods

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

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

type Rep Matches Source # 
Instance details

Defined in Pinecone.Search

type Rep Matches = D1 ('MetaData "Matches" "Pinecone.Search" "pinecone-1.0.0-Ex4c0YruToKASgnObHGBW7" 'False) (C1 ('MetaCons "Matches" 'PrefixI 'True) (S1 ('MetaSel ('Just "matches") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Vector Match)) :*: (S1 ('MetaSel ('Just "namespace") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Namespace) :*: S1 ('MetaSel ('Just "usage") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Usage))))

data SearchWithText Source #

A search request for records in a specific namespace.

Constructors

SearchWithText 

Fields

Instances

Instances details
FromJSON SearchWithText Source # 
Instance details

Defined in Pinecone.Search

ToJSON SearchWithText Source # 
Instance details

Defined in Pinecone.Search

Generic SearchWithText Source # 
Instance details

Defined in Pinecone.Search

Associated Types

type Rep SearchWithText :: Type -> Type #

Show SearchWithText Source # 
Instance details

Defined in Pinecone.Search

Eq SearchWithText Source # 
Instance details

Defined in Pinecone.Search

type Rep SearchWithText Source # 
Instance details

Defined in Pinecone.Search

type Rep SearchWithText = D1 ('MetaData "SearchWithText" "Pinecone.Search" "pinecone-1.0.0-Ex4c0YruToKASgnObHGBW7" 'False) (C1 ('MetaCons "SearchWithText" 'PrefixI 'True) (S1 ('MetaSel ('Just "query") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Query) :*: (S1 ('MetaSel ('Just "fields") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe (Vector Text))) :*: S1 ('MetaSel ('Just "rerank") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe Rerank)))))

data Hits Source #

A successful search namespace response.

Constructors

Hits 

Fields

Instances

Instances details
FromJSON Hits Source # 
Instance details

Defined in Pinecone.Search

ToJSON Hits Source # 
Instance details

Defined in Pinecone.Search

Generic Hits Source # 
Instance details

Defined in Pinecone.Search

Associated Types

type Rep Hits :: Type -> Type #

Methods

from :: Hits -> Rep Hits x #

to :: Rep Hits x -> Hits #

Show Hits Source # 
Instance details

Defined in Pinecone.Search

Methods

showsPrec :: Int -> Hits -> ShowS #

show :: Hits -> String #

showList :: [Hits] -> ShowS #

Eq Hits Source # 
Instance details

Defined in Pinecone.Search

Methods

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

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

type Rep Hits Source # 
Instance details

Defined in Pinecone.Search

type Rep Hits = D1 ('MetaData "Hits" "Pinecone.Search" "pinecone-1.0.0-Ex4c0YruToKASgnObHGBW7" 'False) (C1 ('MetaCons "Hits" 'PrefixI 'True) (S1 ('MetaSel ('Just "usage") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Usage) :*: S1 ('MetaSel ('Just "hits") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Vector Hit))))

Other types

data Match Source #

Match for a vector

Constructors

Match 

Instances

Instances details
FromJSON Match Source # 
Instance details

Defined in Pinecone.Search

ToJSON Match Source # 
Instance details

Defined in Pinecone.Search

Generic Match Source # 
Instance details

Defined in Pinecone.Search

Associated Types

type Rep Match :: Type -> Type #

Methods

from :: Match -> Rep Match x #

to :: Rep Match x -> Match #

Show Match Source # 
Instance details

Defined in Pinecone.Search

Methods

showsPrec :: Int -> Match -> ShowS #

show :: Match -> String #

showList :: [Match] -> ShowS #

Eq Match Source # 
Instance details

Defined in Pinecone.Search

Methods

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

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

type Rep Match Source # 
Instance details

Defined in Pinecone.Search

data Query Source #

The query inputs to search with

Constructors

Query 

Instances

Instances details
FromJSON Query Source # 
Instance details

Defined in Pinecone.Search

ToJSON Query Source # 
Instance details

Defined in Pinecone.Search

Generic Query Source # 
Instance details

Defined in Pinecone.Search

Associated Types

type Rep Query :: Type -> Type #

Methods

from :: Query -> Rep Query x #

to :: Rep Query x -> Query #

Show Query Source # 
Instance details

Defined in Pinecone.Search

Methods

showsPrec :: Int -> Query -> ShowS #

show :: Query -> String #

showList :: [Query] -> ShowS #

Eq Query Source # 
Instance details

Defined in Pinecone.Search

Methods

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

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

type Rep Query Source # 
Instance details

Defined in Pinecone.Search

data VectorQuery Source #

Vector query

Constructors

VectorQuery 

Fields

Instances

Instances details
FromJSON VectorQuery Source # 
Instance details

Defined in Pinecone.Search

ToJSON VectorQuery Source # 
Instance details

Defined in Pinecone.Search

Generic VectorQuery Source # 
Instance details

Defined in Pinecone.Search

Associated Types

type Rep VectorQuery :: Type -> Type #

Show VectorQuery Source # 
Instance details

Defined in Pinecone.Search

Eq VectorQuery Source # 
Instance details

Defined in Pinecone.Search

type Rep VectorQuery Source # 
Instance details

Defined in Pinecone.Search

type Rep VectorQuery = D1 ('MetaData "VectorQuery" "Pinecone.Search" "pinecone-1.0.0-Ex4c0YruToKASgnObHGBW7" 'False) (C1 ('MetaCons "VectorQuery" 'PrefixI 'True) (S1 ('MetaSel ('Just "values") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe (Vector Double))) :*: (S1 ('MetaSel ('Just "sparse_values") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe (Vector Double))) :*: S1 ('MetaSel ('Just "sparse_indices") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe (Vector Natural))))))

data Rerank Source #

Parameters for reranking the initial search results

Constructors

Rerank 

Instances

Instances details
FromJSON Rerank Source # 
Instance details

Defined in Pinecone.Search

ToJSON Rerank Source # 
Instance details

Defined in Pinecone.Search

Generic Rerank Source # 
Instance details

Defined in Pinecone.Search

Associated Types

type Rep Rerank :: Type -> Type #

Methods

from :: Rerank -> Rep Rerank x #

to :: Rep Rerank x -> Rerank #

Show Rerank Source # 
Instance details

Defined in Pinecone.Search

Eq Rerank Source # 
Instance details

Defined in Pinecone.Search

Methods

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

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

type Rep Rerank Source # 
Instance details

Defined in Pinecone.Search

data Hit Source #

Hit for the search document request

Constructors

Hit 

Fields

Instances

Instances details
FromJSON Hit Source # 
Instance details

Defined in Pinecone.Search

ToJSON Hit Source # 
Instance details

Defined in Pinecone.Search

Generic Hit Source # 
Instance details

Defined in Pinecone.Search

Associated Types

type Rep Hit :: Type -> Type #

Methods

from :: Hit -> Rep Hit x #

to :: Rep Hit x -> Hit #

Show Hit Source # 
Instance details

Defined in Pinecone.Search

Methods

showsPrec :: Int -> Hit -> ShowS #

show :: Hit -> String #

showList :: [Hit] -> ShowS #

Eq Hit Source # 
Instance details

Defined in Pinecone.Search

Methods

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

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

type Rep Hit Source # 
Instance details

Defined in Pinecone.Search

type Rep Hit = D1 ('MetaData "Hit" "Pinecone.Search" "pinecone-1.0.0-Ex4c0YruToKASgnObHGBW7" 'False) (C1 ('MetaCons "Hit" 'PrefixI 'True) (S1 ('MetaSel ('Just "_id") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Text) :*: (S1 ('MetaSel ('Just "_score") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Double) :*: S1 ('MetaSel ('Just "fields") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Value))))

data Usage Source #

Usage

Instances

Instances details
FromJSON Usage Source # 
Instance details

Defined in Pinecone.Search

ToJSON Usage Source # 
Instance details

Defined in Pinecone.Search

Generic Usage Source # 
Instance details

Defined in Pinecone.Search

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.Search

Methods

showsPrec :: Int -> Usage -> ShowS #

show :: Usage -> String #

showList :: [Usage] -> ShowS #

Eq Usage Source # 
Instance details

Defined in Pinecone.Search

Methods

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

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

type Rep Usage Source # 
Instance details

Defined in Pinecone.Search

type Rep Usage = D1 ('MetaData "Usage" "Pinecone.Search" "pinecone-1.0.0-Ex4c0YruToKASgnObHGBW7" 'False) (C1 ('MetaCons "Usage" 'PrefixI 'True) (S1 ('MetaSel ('Just "read_units") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe Natural)) :*: (S1 ('MetaSel ('Just "embed_total_tokens") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe Natural)) :*: S1 ('MetaSel ('Just "rerank_units") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe Natural)))))

Servant

type API = ("query" :> (ReqBody '[JSON] SearchWithVector :> Post '[JSON] Matches)) :<|> ("records" :> ("namespaces" :> (Capture "namespace" Namespace :> ("search" :> (ReqBody '[JSON] SearchWithText :> Post '[JSON] Hits))))) Source #

Servant API