module Pinecone.Vectors
(
Namespace(..)
, UpsertVectors(..)
, _UpsertVectors
, UpsertStats(..)
, Vectors(..)
, UpdateVector(..)
, _UpdateVector
, DeleteVectors(..)
, _DeleteVectors
, VectorIDs(..)
, Record(..)
, _Record
, VectorObject(..)
, SparseValues(..)
, Usage(..)
, API
) where
import Pinecone.Metadata (Filter, Scalar)
import Pinecone.Pagination (Pagination)
import Pinecone.Prelude
import Prelude hiding (id)
import qualified Data.Map as Map
newtype Namespace = Namespace{ Namespace -> Text
text :: Text }
deriving newtype (Namespace -> Namespace -> Bool
(Namespace -> Namespace -> Bool)
-> (Namespace -> Namespace -> Bool) -> Eq Namespace
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: Namespace -> Namespace -> Bool
== :: Namespace -> Namespace -> Bool
$c/= :: Namespace -> Namespace -> Bool
/= :: Namespace -> Namespace -> Bool
Eq, Maybe Namespace
Value -> Parser [Namespace]
Value -> Parser Namespace
(Value -> Parser Namespace)
-> (Value -> Parser [Namespace])
-> Maybe Namespace
-> FromJSON Namespace
forall a.
(Value -> Parser a)
-> (Value -> Parser [a]) -> Maybe a -> FromJSON a
$cparseJSON :: Value -> Parser Namespace
parseJSON :: Value -> Parser Namespace
$cparseJSONList :: Value -> Parser [Namespace]
parseJSONList :: Value -> Parser [Namespace]
$comittedField :: Maybe Namespace
omittedField :: Maybe Namespace
FromJSON, String -> Namespace
(String -> Namespace) -> IsString Namespace
forall a. (String -> a) -> IsString a
$cfromString :: String -> Namespace
fromString :: String -> Namespace
IsString, Int -> Namespace -> ShowS
[Namespace] -> ShowS
Namespace -> String
(Int -> Namespace -> ShowS)
-> (Namespace -> String)
-> ([Namespace] -> ShowS)
-> Show Namespace
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> Namespace -> ShowS
showsPrec :: Int -> Namespace -> ShowS
$cshow :: Namespace -> String
show :: Namespace -> String
$cshowList :: [Namespace] -> ShowS
showList :: [Namespace] -> ShowS
Show, Namespace -> Text
Namespace -> ByteString
Namespace -> Builder
(Namespace -> Text)
-> (Namespace -> Builder)
-> (Namespace -> ByteString)
-> (Namespace -> Text)
-> (Namespace -> Builder)
-> ToHttpApiData Namespace
forall a.
(a -> Text)
-> (a -> Builder)
-> (a -> ByteString)
-> (a -> Text)
-> (a -> Builder)
-> ToHttpApiData a
$ctoUrlPiece :: Namespace -> Text
toUrlPiece :: Namespace -> Text
$ctoEncodedUrlPiece :: Namespace -> Builder
toEncodedUrlPiece :: Namespace -> Builder
$ctoHeader :: Namespace -> ByteString
toHeader :: Namespace -> ByteString
$ctoQueryParam :: Namespace -> Text
toQueryParam :: Namespace -> Text
$ctoEncodedQueryParam :: Namespace -> Builder
toEncodedQueryParam :: Namespace -> Builder
ToHttpApiData, [Namespace] -> Value
[Namespace] -> Encoding
Namespace -> Bool
Namespace -> Value
Namespace -> Encoding
(Namespace -> Value)
-> (Namespace -> Encoding)
-> ([Namespace] -> Value)
-> ([Namespace] -> Encoding)
-> (Namespace -> Bool)
-> ToJSON Namespace
forall a.
(a -> Value)
-> (a -> Encoding)
-> ([a] -> Value)
-> ([a] -> Encoding)
-> (a -> Bool)
-> ToJSON a
$ctoJSON :: Namespace -> Value
toJSON :: Namespace -> Value
$ctoEncoding :: Namespace -> Encoding
toEncoding :: Namespace -> Encoding
$ctoJSONList :: [Namespace] -> Value
toJSONList :: [Namespace] -> Value
$ctoEncodingList :: [Namespace] -> Encoding
toEncodingList :: [Namespace] -> Encoding
$comitField :: Namespace -> Bool
omitField :: Namespace -> Bool
ToJSON)
data UpsertVectors = UpsertVectors
{ UpsertVectors -> Vector VectorObject
vectors :: Vector VectorObject
, UpsertVectors -> Maybe Namespace
namespace :: Maybe Namespace
} deriving stock (UpsertVectors -> UpsertVectors -> Bool
(UpsertVectors -> UpsertVectors -> Bool)
-> (UpsertVectors -> UpsertVectors -> Bool) -> Eq UpsertVectors
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: UpsertVectors -> UpsertVectors -> Bool
== :: UpsertVectors -> UpsertVectors -> Bool
$c/= :: UpsertVectors -> UpsertVectors -> Bool
/= :: UpsertVectors -> UpsertVectors -> Bool
Eq, (forall x. UpsertVectors -> Rep UpsertVectors x)
-> (forall x. Rep UpsertVectors x -> UpsertVectors)
-> Generic UpsertVectors
forall x. Rep UpsertVectors x -> UpsertVectors
forall x. UpsertVectors -> Rep UpsertVectors x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cfrom :: forall x. UpsertVectors -> Rep UpsertVectors x
from :: forall x. UpsertVectors -> Rep UpsertVectors x
$cto :: forall x. Rep UpsertVectors x -> UpsertVectors
to :: forall x. Rep UpsertVectors x -> UpsertVectors
Generic, Int -> UpsertVectors -> ShowS
[UpsertVectors] -> ShowS
UpsertVectors -> String
(Int -> UpsertVectors -> ShowS)
-> (UpsertVectors -> String)
-> ([UpsertVectors] -> ShowS)
-> Show UpsertVectors
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> UpsertVectors -> ShowS
showsPrec :: Int -> UpsertVectors -> ShowS
$cshow :: UpsertVectors -> String
show :: UpsertVectors -> String
$cshowList :: [UpsertVectors] -> ShowS
showList :: [UpsertVectors] -> ShowS
Show)
deriving anyclass (Maybe UpsertVectors
Value -> Parser [UpsertVectors]
Value -> Parser UpsertVectors
(Value -> Parser UpsertVectors)
-> (Value -> Parser [UpsertVectors])
-> Maybe UpsertVectors
-> FromJSON UpsertVectors
forall a.
(Value -> Parser a)
-> (Value -> Parser [a]) -> Maybe a -> FromJSON a
$cparseJSON :: Value -> Parser UpsertVectors
parseJSON :: Value -> Parser UpsertVectors
$cparseJSONList :: Value -> Parser [UpsertVectors]
parseJSONList :: Value -> Parser [UpsertVectors]
$comittedField :: Maybe UpsertVectors
omittedField :: Maybe UpsertVectors
FromJSON, [UpsertVectors] -> Value
[UpsertVectors] -> Encoding
UpsertVectors -> Bool
UpsertVectors -> Value
UpsertVectors -> Encoding
(UpsertVectors -> Value)
-> (UpsertVectors -> Encoding)
-> ([UpsertVectors] -> Value)
-> ([UpsertVectors] -> Encoding)
-> (UpsertVectors -> Bool)
-> ToJSON UpsertVectors
forall a.
(a -> Value)
-> (a -> Encoding)
-> ([a] -> Value)
-> ([a] -> Encoding)
-> (a -> Bool)
-> ToJSON a
$ctoJSON :: UpsertVectors -> Value
toJSON :: UpsertVectors -> Value
$ctoEncoding :: UpsertVectors -> Encoding
toEncoding :: UpsertVectors -> Encoding
$ctoJSONList :: [UpsertVectors] -> Value
toJSONList :: [UpsertVectors] -> Value
$ctoEncodingList :: [UpsertVectors] -> Encoding
toEncodingList :: [UpsertVectors] -> Encoding
$comitField :: UpsertVectors -> Bool
omitField :: UpsertVectors -> Bool
ToJSON)
_UpsertVectors :: UpsertVectors
_UpsertVectors :: UpsertVectors
_UpsertVectors = UpsertVectors
{ $sel:namespace:UpsertVectors :: Maybe Namespace
namespace = Maybe Namespace
forall a. Maybe a
Nothing
}
data UpsertStats = UpsertStats
{ UpsertStats -> Natural
upsertedCount :: Natural
} deriving stock (UpsertStats -> UpsertStats -> Bool
(UpsertStats -> UpsertStats -> Bool)
-> (UpsertStats -> UpsertStats -> Bool) -> Eq UpsertStats
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: UpsertStats -> UpsertStats -> Bool
== :: UpsertStats -> UpsertStats -> Bool
$c/= :: UpsertStats -> UpsertStats -> Bool
/= :: UpsertStats -> UpsertStats -> Bool
Eq, (forall x. UpsertStats -> Rep UpsertStats x)
-> (forall x. Rep UpsertStats x -> UpsertStats)
-> Generic UpsertStats
forall x. Rep UpsertStats x -> UpsertStats
forall x. UpsertStats -> Rep UpsertStats x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cfrom :: forall x. UpsertStats -> Rep UpsertStats x
from :: forall x. UpsertStats -> Rep UpsertStats x
$cto :: forall x. Rep UpsertStats x -> UpsertStats
to :: forall x. Rep UpsertStats x -> UpsertStats
Generic, Int -> UpsertStats -> ShowS
[UpsertStats] -> ShowS
UpsertStats -> String
(Int -> UpsertStats -> ShowS)
-> (UpsertStats -> String)
-> ([UpsertStats] -> ShowS)
-> Show UpsertStats
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> UpsertStats -> ShowS
showsPrec :: Int -> UpsertStats -> ShowS
$cshow :: UpsertStats -> String
show :: UpsertStats -> String
$cshowList :: [UpsertStats] -> ShowS
showList :: [UpsertStats] -> ShowS
Show)
deriving anyclass (Maybe UpsertStats
Value -> Parser [UpsertStats]
Value -> Parser UpsertStats
(Value -> Parser UpsertStats)
-> (Value -> Parser [UpsertStats])
-> Maybe UpsertStats
-> FromJSON UpsertStats
forall a.
(Value -> Parser a)
-> (Value -> Parser [a]) -> Maybe a -> FromJSON a
$cparseJSON :: Value -> Parser UpsertStats
parseJSON :: Value -> Parser UpsertStats
$cparseJSONList :: Value -> Parser [UpsertStats]
parseJSONList :: Value -> Parser [UpsertStats]
$comittedField :: Maybe UpsertStats
omittedField :: Maybe UpsertStats
FromJSON, [UpsertStats] -> Value
[UpsertStats] -> Encoding
UpsertStats -> Bool
UpsertStats -> Value
UpsertStats -> Encoding
(UpsertStats -> Value)
-> (UpsertStats -> Encoding)
-> ([UpsertStats] -> Value)
-> ([UpsertStats] -> Encoding)
-> (UpsertStats -> Bool)
-> ToJSON UpsertStats
forall a.
(a -> Value)
-> (a -> Encoding)
-> ([a] -> Value)
-> ([a] -> Encoding)
-> (a -> Bool)
-> ToJSON a
$ctoJSON :: UpsertStats -> Value
toJSON :: UpsertStats -> Value
$ctoEncoding :: UpsertStats -> Encoding
toEncoding :: UpsertStats -> Encoding
$ctoJSONList :: [UpsertStats] -> Value
toJSONList :: [UpsertStats] -> Value
$ctoEncodingList :: [UpsertStats] -> Encoding
toEncodingList :: [UpsertStats] -> Encoding
$comitField :: UpsertStats -> Bool
omitField :: UpsertStats -> Bool
ToJSON)
data Vectors = Vectors
{ Vectors -> Map Text VectorObject
vectors :: Map Text VectorObject
, Vectors -> Namespace
namespace :: Namespace
, Vectors -> Maybe Usage
usage :: Maybe Usage
} deriving stock (Vectors -> Vectors -> Bool
(Vectors -> Vectors -> Bool)
-> (Vectors -> Vectors -> Bool) -> Eq Vectors
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: Vectors -> Vectors -> Bool
== :: Vectors -> Vectors -> Bool
$c/= :: Vectors -> Vectors -> Bool
/= :: Vectors -> Vectors -> Bool
Eq, (forall x. Vectors -> Rep Vectors x)
-> (forall x. Rep Vectors x -> Vectors) -> Generic Vectors
forall x. Rep Vectors x -> Vectors
forall x. Vectors -> Rep Vectors x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cfrom :: forall x. Vectors -> Rep Vectors x
from :: forall x. Vectors -> Rep Vectors x
$cto :: forall x. Rep Vectors x -> Vectors
to :: forall x. Rep Vectors x -> Vectors
Generic, Int -> Vectors -> ShowS
[Vectors] -> ShowS
Vectors -> String
(Int -> Vectors -> ShowS)
-> (Vectors -> String) -> ([Vectors] -> ShowS) -> Show Vectors
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> Vectors -> ShowS
showsPrec :: Int -> Vectors -> ShowS
$cshow :: Vectors -> String
show :: Vectors -> String
$cshowList :: [Vectors] -> ShowS
showList :: [Vectors] -> ShowS
Show)
deriving anyclass (Maybe Vectors
Value -> Parser [Vectors]
Value -> Parser Vectors
(Value -> Parser Vectors)
-> (Value -> Parser [Vectors]) -> Maybe Vectors -> FromJSON Vectors
forall a.
(Value -> Parser a)
-> (Value -> Parser [a]) -> Maybe a -> FromJSON a
$cparseJSON :: Value -> Parser Vectors
parseJSON :: Value -> Parser Vectors
$cparseJSONList :: Value -> Parser [Vectors]
parseJSONList :: Value -> Parser [Vectors]
$comittedField :: Maybe Vectors
omittedField :: Maybe Vectors
FromJSON, [Vectors] -> Value
[Vectors] -> Encoding
Vectors -> Bool
Vectors -> Value
Vectors -> Encoding
(Vectors -> Value)
-> (Vectors -> Encoding)
-> ([Vectors] -> Value)
-> ([Vectors] -> Encoding)
-> (Vectors -> Bool)
-> ToJSON Vectors
forall a.
(a -> Value)
-> (a -> Encoding)
-> ([a] -> Value)
-> ([a] -> Encoding)
-> (a -> Bool)
-> ToJSON a
$ctoJSON :: Vectors -> Value
toJSON :: Vectors -> Value
$ctoEncoding :: Vectors -> Encoding
toEncoding :: Vectors -> Encoding
$ctoJSONList :: [Vectors] -> Value
toJSONList :: [Vectors] -> Value
$ctoEncodingList :: [Vectors] -> Encoding
toEncodingList :: [Vectors] -> Encoding
$comitField :: Vectors -> Bool
omitField :: Vectors -> Bool
ToJSON)
data UpdateVector = UpdateVector
{ UpdateVector -> Text
id :: Text
, UpdateVector -> Maybe (Vector Double)
values :: Maybe (Vector Double)
, UpdateVector -> Maybe SparseValues
sparseValues :: Maybe SparseValues
, UpdateVector -> Maybe (Map Text Scalar)
setMetadata :: Maybe (Map Text Scalar)
, UpdateVector -> Maybe Namespace
namespace :: Maybe Namespace
} deriving stock (UpdateVector -> UpdateVector -> Bool
(UpdateVector -> UpdateVector -> Bool)
-> (UpdateVector -> UpdateVector -> Bool) -> Eq UpdateVector
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: UpdateVector -> UpdateVector -> Bool
== :: UpdateVector -> UpdateVector -> Bool
$c/= :: UpdateVector -> UpdateVector -> Bool
/= :: UpdateVector -> UpdateVector -> Bool
Eq, (forall x. UpdateVector -> Rep UpdateVector x)
-> (forall x. Rep UpdateVector x -> UpdateVector)
-> Generic UpdateVector
forall x. Rep UpdateVector x -> UpdateVector
forall x. UpdateVector -> Rep UpdateVector x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cfrom :: forall x. UpdateVector -> Rep UpdateVector x
from :: forall x. UpdateVector -> Rep UpdateVector x
$cto :: forall x. Rep UpdateVector x -> UpdateVector
to :: forall x. Rep UpdateVector x -> UpdateVector
Generic, Int -> UpdateVector -> ShowS
[UpdateVector] -> ShowS
UpdateVector -> String
(Int -> UpdateVector -> ShowS)
-> (UpdateVector -> String)
-> ([UpdateVector] -> ShowS)
-> Show UpdateVector
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> UpdateVector -> ShowS
showsPrec :: Int -> UpdateVector -> ShowS
$cshow :: UpdateVector -> String
show :: UpdateVector -> String
$cshowList :: [UpdateVector] -> ShowS
showList :: [UpdateVector] -> ShowS
Show)
deriving anyclass (Maybe UpdateVector
Value -> Parser [UpdateVector]
Value -> Parser UpdateVector
(Value -> Parser UpdateVector)
-> (Value -> Parser [UpdateVector])
-> Maybe UpdateVector
-> FromJSON UpdateVector
forall a.
(Value -> Parser a)
-> (Value -> Parser [a]) -> Maybe a -> FromJSON a
$cparseJSON :: Value -> Parser UpdateVector
parseJSON :: Value -> Parser UpdateVector
$cparseJSONList :: Value -> Parser [UpdateVector]
parseJSONList :: Value -> Parser [UpdateVector]
$comittedField :: Maybe UpdateVector
omittedField :: Maybe UpdateVector
FromJSON, [UpdateVector] -> Value
[UpdateVector] -> Encoding
UpdateVector -> Bool
UpdateVector -> Value
UpdateVector -> Encoding
(UpdateVector -> Value)
-> (UpdateVector -> Encoding)
-> ([UpdateVector] -> Value)
-> ([UpdateVector] -> Encoding)
-> (UpdateVector -> Bool)
-> ToJSON UpdateVector
forall a.
(a -> Value)
-> (a -> Encoding)
-> ([a] -> Value)
-> ([a] -> Encoding)
-> (a -> Bool)
-> ToJSON a
$ctoJSON :: UpdateVector -> Value
toJSON :: UpdateVector -> Value
$ctoEncoding :: UpdateVector -> Encoding
toEncoding :: UpdateVector -> Encoding
$ctoJSONList :: [UpdateVector] -> Value
toJSONList :: [UpdateVector] -> Value
$ctoEncodingList :: [UpdateVector] -> Encoding
toEncodingList :: [UpdateVector] -> Encoding
$comitField :: UpdateVector -> Bool
omitField :: UpdateVector -> Bool
ToJSON)
_UpdateVector :: UpdateVector
_UpdateVector :: UpdateVector
_UpdateVector = UpdateVector
{ $sel:values:UpdateVector :: Maybe (Vector Double)
values = Maybe (Vector Double)
forall a. Maybe a
Nothing
, $sel:sparseValues:UpdateVector :: Maybe SparseValues
sparseValues = Maybe SparseValues
forall a. Maybe a
Nothing
, $sel:setMetadata:UpdateVector :: Maybe (Map Text Scalar)
setMetadata = Maybe (Map Text Scalar)
forall a. Maybe a
Nothing
, $sel:namespace:UpdateVector :: Maybe Namespace
namespace = Maybe Namespace
forall a. Maybe a
Nothing
}
data DeleteVectors = DeleteVectors
{ DeleteVectors -> Maybe (Vector Text)
ids :: Maybe (Vector Text)
, DeleteVectors -> Maybe Bool
deleteAll :: Maybe Bool
, DeleteVectors -> Maybe Namespace
namespace :: Maybe Namespace
, DeleteVectors -> Maybe Filter
filter :: Maybe Filter
} deriving stock (DeleteVectors -> DeleteVectors -> Bool
(DeleteVectors -> DeleteVectors -> Bool)
-> (DeleteVectors -> DeleteVectors -> Bool) -> Eq DeleteVectors
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: DeleteVectors -> DeleteVectors -> Bool
== :: DeleteVectors -> DeleteVectors -> Bool
$c/= :: DeleteVectors -> DeleteVectors -> Bool
/= :: DeleteVectors -> DeleteVectors -> Bool
Eq, (forall x. DeleteVectors -> Rep DeleteVectors x)
-> (forall x. Rep DeleteVectors x -> DeleteVectors)
-> Generic DeleteVectors
forall x. Rep DeleteVectors x -> DeleteVectors
forall x. DeleteVectors -> Rep DeleteVectors x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cfrom :: forall x. DeleteVectors -> Rep DeleteVectors x
from :: forall x. DeleteVectors -> Rep DeleteVectors x
$cto :: forall x. Rep DeleteVectors x -> DeleteVectors
to :: forall x. Rep DeleteVectors x -> DeleteVectors
Generic, Int -> DeleteVectors -> ShowS
[DeleteVectors] -> ShowS
DeleteVectors -> String
(Int -> DeleteVectors -> ShowS)
-> (DeleteVectors -> String)
-> ([DeleteVectors] -> ShowS)
-> Show DeleteVectors
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> DeleteVectors -> ShowS
showsPrec :: Int -> DeleteVectors -> ShowS
$cshow :: DeleteVectors -> String
show :: DeleteVectors -> String
$cshowList :: [DeleteVectors] -> ShowS
showList :: [DeleteVectors] -> ShowS
Show)
deriving anyclass (Maybe DeleteVectors
Value -> Parser [DeleteVectors]
Value -> Parser DeleteVectors
(Value -> Parser DeleteVectors)
-> (Value -> Parser [DeleteVectors])
-> Maybe DeleteVectors
-> FromJSON DeleteVectors
forall a.
(Value -> Parser a)
-> (Value -> Parser [a]) -> Maybe a -> FromJSON a
$cparseJSON :: Value -> Parser DeleteVectors
parseJSON :: Value -> Parser DeleteVectors
$cparseJSONList :: Value -> Parser [DeleteVectors]
parseJSONList :: Value -> Parser [DeleteVectors]
$comittedField :: Maybe DeleteVectors
omittedField :: Maybe DeleteVectors
FromJSON, [DeleteVectors] -> Value
[DeleteVectors] -> Encoding
DeleteVectors -> Bool
DeleteVectors -> Value
DeleteVectors -> Encoding
(DeleteVectors -> Value)
-> (DeleteVectors -> Encoding)
-> ([DeleteVectors] -> Value)
-> ([DeleteVectors] -> Encoding)
-> (DeleteVectors -> Bool)
-> ToJSON DeleteVectors
forall a.
(a -> Value)
-> (a -> Encoding)
-> ([a] -> Value)
-> ([a] -> Encoding)
-> (a -> Bool)
-> ToJSON a
$ctoJSON :: DeleteVectors -> Value
toJSON :: DeleteVectors -> Value
$ctoEncoding :: DeleteVectors -> Encoding
toEncoding :: DeleteVectors -> Encoding
$ctoJSONList :: [DeleteVectors] -> Value
toJSONList :: [DeleteVectors] -> Value
$ctoEncodingList :: [DeleteVectors] -> Encoding
toEncodingList :: [DeleteVectors] -> Encoding
$comitField :: DeleteVectors -> Bool
omitField :: DeleteVectors -> Bool
ToJSON)
_DeleteVectors :: DeleteVectors
_DeleteVectors :: DeleteVectors
_DeleteVectors = DeleteVectors
{ $sel:deleteAll:DeleteVectors :: Maybe Bool
deleteAll = Maybe Bool
forall a. Maybe a
Nothing
, $sel:namespace:DeleteVectors :: Maybe Namespace
namespace = Maybe Namespace
forall a. Maybe a
Nothing
, $sel:filter:DeleteVectors :: Maybe Filter
filter = Maybe Filter
forall a. Maybe a
Nothing
}
data VectorIDs = VectorIDs
{ VectorIDs -> Vector Text
vectors :: Vector Text
, :: Maybe Pagination
, VectorIDs -> Namespace
namespace :: Namespace
, VectorIDs -> Usage
usage :: Usage
} deriving stock (VectorIDs -> VectorIDs -> Bool
(VectorIDs -> VectorIDs -> Bool)
-> (VectorIDs -> VectorIDs -> Bool) -> Eq VectorIDs
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: VectorIDs -> VectorIDs -> Bool
== :: VectorIDs -> VectorIDs -> Bool
$c/= :: VectorIDs -> VectorIDs -> Bool
/= :: VectorIDs -> VectorIDs -> Bool
Eq, (forall x. VectorIDs -> Rep VectorIDs x)
-> (forall x. Rep VectorIDs x -> VectorIDs) -> Generic VectorIDs
forall x. Rep VectorIDs x -> VectorIDs
forall x. VectorIDs -> Rep VectorIDs x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cfrom :: forall x. VectorIDs -> Rep VectorIDs x
from :: forall x. VectorIDs -> Rep VectorIDs x
$cto :: forall x. Rep VectorIDs x -> VectorIDs
to :: forall x. Rep VectorIDs x -> VectorIDs
Generic, Int -> VectorIDs -> ShowS
[VectorIDs] -> ShowS
VectorIDs -> String
(Int -> VectorIDs -> ShowS)
-> (VectorIDs -> String)
-> ([VectorIDs] -> ShowS)
-> Show VectorIDs
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> VectorIDs -> ShowS
showsPrec :: Int -> VectorIDs -> ShowS
$cshow :: VectorIDs -> String
show :: VectorIDs -> String
$cshowList :: [VectorIDs] -> ShowS
showList :: [VectorIDs] -> ShowS
Show)
instance FromJSON VectorIDs where
parseJSON :: Value -> Parser VectorIDs
parseJSON Value
value = do
VectorIDs_{Maybe Pagination
Vector VectorID
Usage
Namespace
vectors :: Vector VectorID
pagination :: Maybe Pagination
namespace :: Namespace
usage :: Usage
$sel:vectors:VectorIDs_ :: VectorIDs_ -> Vector VectorID
$sel:pagination:VectorIDs_ :: VectorIDs_ -> Maybe Pagination
$sel:namespace:VectorIDs_ :: VectorIDs_ -> Namespace
$sel:usage:VectorIDs_ :: VectorIDs_ -> Usage
..} <- Value -> Parser VectorIDs_
forall a. FromJSON a => Value -> Parser a
parseJSON Value
value
VectorIDs -> Parser VectorIDs
forall a. a -> Parser a
forall (m :: * -> *) a. Monad m => a -> m a
return VectorIDs{ $sel:vectors:VectorIDs :: Vector Text
vectors = do VectorID{ Text
id :: Text
$sel:id:VectorID :: VectorID -> Text
id } <- Vector VectorID
vectors; Text -> Vector Text
forall a. a -> Vector a
forall (m :: * -> *) a. Monad m => a -> m a
return Text
id, Maybe Pagination
Usage
Namespace
$sel:pagination:VectorIDs :: Maybe Pagination
$sel:namespace:VectorIDs :: Namespace
$sel:usage:VectorIDs :: Usage
pagination :: Maybe Pagination
namespace :: Namespace
usage :: Usage
..}
data VectorIDs_ = VectorIDs_
{ VectorIDs_ -> Vector VectorID
vectors :: Vector VectorID
, :: Maybe Pagination
, VectorIDs_ -> Namespace
namespace :: Namespace
, VectorIDs_ -> Usage
usage :: Usage
} deriving stock (VectorIDs_ -> VectorIDs_ -> Bool
(VectorIDs_ -> VectorIDs_ -> Bool)
-> (VectorIDs_ -> VectorIDs_ -> Bool) -> Eq VectorIDs_
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: VectorIDs_ -> VectorIDs_ -> Bool
== :: VectorIDs_ -> VectorIDs_ -> Bool
$c/= :: VectorIDs_ -> VectorIDs_ -> Bool
/= :: VectorIDs_ -> VectorIDs_ -> Bool
Eq, (forall x. VectorIDs_ -> Rep VectorIDs_ x)
-> (forall x. Rep VectorIDs_ x -> VectorIDs_) -> Generic VectorIDs_
forall x. Rep VectorIDs_ x -> VectorIDs_
forall x. VectorIDs_ -> Rep VectorIDs_ x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cfrom :: forall x. VectorIDs_ -> Rep VectorIDs_ x
from :: forall x. VectorIDs_ -> Rep VectorIDs_ x
$cto :: forall x. Rep VectorIDs_ x -> VectorIDs_
to :: forall x. Rep VectorIDs_ x -> VectorIDs_
Generic, Int -> VectorIDs_ -> ShowS
[VectorIDs_] -> ShowS
VectorIDs_ -> String
(Int -> VectorIDs_ -> ShowS)
-> (VectorIDs_ -> String)
-> ([VectorIDs_] -> ShowS)
-> Show VectorIDs_
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> VectorIDs_ -> ShowS
showsPrec :: Int -> VectorIDs_ -> ShowS
$cshow :: VectorIDs_ -> String
show :: VectorIDs_ -> String
$cshowList :: [VectorIDs_] -> ShowS
showList :: [VectorIDs_] -> ShowS
Show)
deriving anyclass (Maybe VectorIDs_
Value -> Parser [VectorIDs_]
Value -> Parser VectorIDs_
(Value -> Parser VectorIDs_)
-> (Value -> Parser [VectorIDs_])
-> Maybe VectorIDs_
-> FromJSON VectorIDs_
forall a.
(Value -> Parser a)
-> (Value -> Parser [a]) -> Maybe a -> FromJSON a
$cparseJSON :: Value -> Parser VectorIDs_
parseJSON :: Value -> Parser VectorIDs_
$cparseJSONList :: Value -> Parser [VectorIDs_]
parseJSONList :: Value -> Parser [VectorIDs_]
$comittedField :: Maybe VectorIDs_
omittedField :: Maybe VectorIDs_
FromJSON, [VectorIDs_] -> Value
[VectorIDs_] -> Encoding
VectorIDs_ -> Bool
VectorIDs_ -> Value
VectorIDs_ -> Encoding
(VectorIDs_ -> Value)
-> (VectorIDs_ -> Encoding)
-> ([VectorIDs_] -> Value)
-> ([VectorIDs_] -> Encoding)
-> (VectorIDs_ -> Bool)
-> ToJSON VectorIDs_
forall a.
(a -> Value)
-> (a -> Encoding)
-> ([a] -> Value)
-> ([a] -> Encoding)
-> (a -> Bool)
-> ToJSON a
$ctoJSON :: VectorIDs_ -> Value
toJSON :: VectorIDs_ -> Value
$ctoEncoding :: VectorIDs_ -> Encoding
toEncoding :: VectorIDs_ -> Encoding
$ctoJSONList :: [VectorIDs_] -> Value
toJSONList :: [VectorIDs_] -> Value
$ctoEncodingList :: [VectorIDs_] -> Encoding
toEncodingList :: [VectorIDs_] -> Encoding
$comitField :: VectorIDs_ -> Bool
omitField :: VectorIDs_ -> Bool
ToJSON)
data Record = Record
{ Record -> Text
id :: Text
, Record -> Text
text :: Text
, Record -> Maybe (Map Text Scalar)
metadata :: Maybe (Map Text Scalar)
} deriving stock (Record -> Record -> Bool
(Record -> Record -> Bool)
-> (Record -> Record -> Bool) -> Eq Record
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: Record -> Record -> Bool
== :: Record -> Record -> Bool
$c/= :: Record -> Record -> Bool
/= :: Record -> Record -> Bool
Eq, (forall x. Record -> Rep Record x)
-> (forall x. Rep Record x -> Record) -> Generic Record
forall x. Rep Record x -> Record
forall x. Record -> Rep Record x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cfrom :: forall x. Record -> Rep Record x
from :: forall x. Record -> Rep Record x
$cto :: forall x. Rep Record x -> Record
to :: forall x. Rep Record x -> Record
Generic, Int -> Record -> ShowS
[Record] -> ShowS
Record -> String
(Int -> Record -> ShowS)
-> (Record -> String) -> ([Record] -> ShowS) -> Show Record
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> Record -> ShowS
showsPrec :: Int -> Record -> ShowS
$cshow :: Record -> String
show :: Record -> String
$cshowList :: [Record] -> ShowS
showList :: [Record] -> ShowS
Show)
instance FromJSON Record where
parseJSON :: Value -> Parser Record
parseJSON Value
value = do
Map Text Value
m <- Value -> Parser (Map Text Value)
forall a. FromJSON a => Value -> Parser a
parseJSON Value
value
Text
text <- case Text -> Map Text Value -> Maybe Value
forall k a. Ord k => k -> Map k a -> Maybe a
Map.lookup Text
"text" Map Text Value
m of
Maybe Value
Nothing -> do
String -> Parser Text
forall a. String -> Parser a
forall (m :: * -> *) a. MonadFail m => String -> m a
fail String
"Missing text field"
Just Value
v -> do
Value -> Parser Text
forall a. FromJSON a => Value -> Parser a
parseJSON Value
v
Text
id <- case Text -> Map Text Value -> Maybe Value
forall k a. Ord k => k -> Map k a -> Maybe a
Map.lookup Text
"_id" Map Text Value
m of
Maybe Value
Nothing -> do
String -> Parser Text
forall a. String -> Parser a
forall (m :: * -> *) a. MonadFail m => String -> m a
fail String
"Missing id field"
Just Value
v -> do
Value -> Parser Text
forall a. FromJSON a => Value -> Parser a
parseJSON Value
v
Maybe (Map Text Scalar)
metadata <- (Map Text Scalar -> Maybe (Map Text Scalar))
-> Parser (Map Text Scalar) -> Parser (Maybe (Map Text Scalar))
forall a b. (a -> b) -> Parser a -> Parser b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap Map Text Scalar -> Maybe (Map Text Scalar)
forall a. a -> Maybe a
Just ((Value -> Parser Scalar)
-> Map Text Value -> Parser (Map Text Scalar)
forall (t :: * -> *) (f :: * -> *) a b.
(Traversable t, Applicative f) =>
(a -> f b) -> t a -> f (t b)
forall (f :: * -> *) a b.
Applicative f =>
(a -> f b) -> Map Text a -> f (Map Text b)
traverse Value -> Parser Scalar
forall a. FromJSON a => Value -> Parser a
parseJSON (Text -> Map Text Value -> Map Text Value
forall k a. Ord k => k -> Map k a -> Map k a
Map.delete Text
"_id" (Text -> Map Text Value -> Map Text Value
forall k a. Ord k => k -> Map k a -> Map k a
Map.delete Text
"text" Map Text Value
m)))
Record -> Parser Record
forall a. a -> Parser a
forall (m :: * -> *) a. Monad m => a -> m a
return Record{Maybe (Map Text Scalar)
Text
$sel:id:Record :: Text
$sel:text:Record :: Text
$sel:metadata:Record :: Maybe (Map Text Scalar)
text :: Text
id :: Text
metadata :: Maybe (Map Text Scalar)
..}
instance ToJSON Record where
toJSON :: Record -> Value
toJSON Record{Maybe (Map Text Scalar)
Text
$sel:id:Record :: Record -> Text
$sel:text:Record :: Record -> Text
$sel:metadata:Record :: Record -> Maybe (Map Text Scalar)
id :: Text
text :: Text
metadata :: Maybe (Map Text Scalar)
..} = Map Text Value -> Value
forall a. ToJSON a => a -> Value
toJSON (Map Text Value -> Map Text Value -> Map Text Value
forall k a. Ord k => Map k a -> Map k a -> Map k a
Map.union Map Text Value
reserved Map Text Value
nonReserved)
where
reserved :: Map Text Value
reserved =
[ (Text
"_id", Text -> Value
forall a. ToJSON a => a -> Value
toJSON Text
id)
, (Text
"text", Text -> Value
forall a. ToJSON a => a -> Value
toJSON Text
text)
]
nonReserved :: Map Text Value
nonReserved = case Maybe (Map Text Scalar)
metadata of
Maybe (Map Text Scalar)
Nothing -> Map Text Value
forall k a. Map k a
Map.empty
Just Map Text Scalar
m -> (Scalar -> Value) -> Map Text Scalar -> Map Text Value
forall a b k. (a -> b) -> Map k a -> Map k b
Map.map Scalar -> Value
forall a. ToJSON a => a -> Value
toJSON Map Text Scalar
m
_Record :: Record
_Record :: Record
_Record = Record
{ $sel:metadata:Record :: Maybe (Map Text Scalar)
metadata = Maybe (Map Text Scalar)
forall a. Maybe a
Nothing
}
data VectorObject = VectorObject
{ VectorObject -> Text
id :: Text
, VectorObject -> Maybe (Vector Double)
values :: Maybe (Vector Double)
, VectorObject -> Maybe SparseValues
sparseValues :: Maybe SparseValues
, VectorObject -> Maybe (Map Text Scalar)
metadata :: Maybe (Map Text Scalar)
} deriving stock (VectorObject -> VectorObject -> Bool
(VectorObject -> VectorObject -> Bool)
-> (VectorObject -> VectorObject -> Bool) -> Eq VectorObject
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: VectorObject -> VectorObject -> Bool
== :: VectorObject -> VectorObject -> Bool
$c/= :: VectorObject -> VectorObject -> Bool
/= :: VectorObject -> VectorObject -> Bool
Eq, (forall x. VectorObject -> Rep VectorObject x)
-> (forall x. Rep VectorObject x -> VectorObject)
-> Generic VectorObject
forall x. Rep VectorObject x -> VectorObject
forall x. VectorObject -> Rep VectorObject x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cfrom :: forall x. VectorObject -> Rep VectorObject x
from :: forall x. VectorObject -> Rep VectorObject x
$cto :: forall x. Rep VectorObject x -> VectorObject
to :: forall x. Rep VectorObject x -> VectorObject
Generic, Int -> VectorObject -> ShowS
[VectorObject] -> ShowS
VectorObject -> String
(Int -> VectorObject -> ShowS)
-> (VectorObject -> String)
-> ([VectorObject] -> ShowS)
-> Show VectorObject
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> VectorObject -> ShowS
showsPrec :: Int -> VectorObject -> ShowS
$cshow :: VectorObject -> String
show :: VectorObject -> String
$cshowList :: [VectorObject] -> ShowS
showList :: [VectorObject] -> ShowS
Show)
deriving anyclass (Maybe VectorObject
Value -> Parser [VectorObject]
Value -> Parser VectorObject
(Value -> Parser VectorObject)
-> (Value -> Parser [VectorObject])
-> Maybe VectorObject
-> FromJSON VectorObject
forall a.
(Value -> Parser a)
-> (Value -> Parser [a]) -> Maybe a -> FromJSON a
$cparseJSON :: Value -> Parser VectorObject
parseJSON :: Value -> Parser VectorObject
$cparseJSONList :: Value -> Parser [VectorObject]
parseJSONList :: Value -> Parser [VectorObject]
$comittedField :: Maybe VectorObject
omittedField :: Maybe VectorObject
FromJSON, [VectorObject] -> Value
[VectorObject] -> Encoding
VectorObject -> Bool
VectorObject -> Value
VectorObject -> Encoding
(VectorObject -> Value)
-> (VectorObject -> Encoding)
-> ([VectorObject] -> Value)
-> ([VectorObject] -> Encoding)
-> (VectorObject -> Bool)
-> ToJSON VectorObject
forall a.
(a -> Value)
-> (a -> Encoding)
-> ([a] -> Value)
-> ([a] -> Encoding)
-> (a -> Bool)
-> ToJSON a
$ctoJSON :: VectorObject -> Value
toJSON :: VectorObject -> Value
$ctoEncoding :: VectorObject -> Encoding
toEncoding :: VectorObject -> Encoding
$ctoJSONList :: [VectorObject] -> Value
toJSONList :: [VectorObject] -> Value
$ctoEncodingList :: [VectorObject] -> Encoding
toEncodingList :: [VectorObject] -> Encoding
$comitField :: VectorObject -> Bool
omitField :: VectorObject -> Bool
ToJSON)
data SparseValues = SparseValues
{ SparseValues -> Vector Natural
indices :: Vector Natural
, SparseValues -> Vector Double
values :: Vector Double
} deriving stock (SparseValues -> SparseValues -> Bool
(SparseValues -> SparseValues -> Bool)
-> (SparseValues -> SparseValues -> Bool) -> Eq SparseValues
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: SparseValues -> SparseValues -> Bool
== :: SparseValues -> SparseValues -> Bool
$c/= :: SparseValues -> SparseValues -> Bool
/= :: SparseValues -> SparseValues -> Bool
Eq, (forall x. SparseValues -> Rep SparseValues x)
-> (forall x. Rep SparseValues x -> SparseValues)
-> Generic SparseValues
forall x. Rep SparseValues x -> SparseValues
forall x. SparseValues -> Rep SparseValues x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cfrom :: forall x. SparseValues -> Rep SparseValues x
from :: forall x. SparseValues -> Rep SparseValues x
$cto :: forall x. Rep SparseValues x -> SparseValues
to :: forall x. Rep SparseValues x -> SparseValues
Generic, Int -> SparseValues -> ShowS
[SparseValues] -> ShowS
SparseValues -> String
(Int -> SparseValues -> ShowS)
-> (SparseValues -> String)
-> ([SparseValues] -> ShowS)
-> Show SparseValues
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> SparseValues -> ShowS
showsPrec :: Int -> SparseValues -> ShowS
$cshow :: SparseValues -> String
show :: SparseValues -> String
$cshowList :: [SparseValues] -> ShowS
showList :: [SparseValues] -> ShowS
Show)
deriving anyclass (Maybe SparseValues
Value -> Parser [SparseValues]
Value -> Parser SparseValues
(Value -> Parser SparseValues)
-> (Value -> Parser [SparseValues])
-> Maybe SparseValues
-> FromJSON SparseValues
forall a.
(Value -> Parser a)
-> (Value -> Parser [a]) -> Maybe a -> FromJSON a
$cparseJSON :: Value -> Parser SparseValues
parseJSON :: Value -> Parser SparseValues
$cparseJSONList :: Value -> Parser [SparseValues]
parseJSONList :: Value -> Parser [SparseValues]
$comittedField :: Maybe SparseValues
omittedField :: Maybe SparseValues
FromJSON, [SparseValues] -> Value
[SparseValues] -> Encoding
SparseValues -> Bool
SparseValues -> Value
SparseValues -> Encoding
(SparseValues -> Value)
-> (SparseValues -> Encoding)
-> ([SparseValues] -> Value)
-> ([SparseValues] -> Encoding)
-> (SparseValues -> Bool)
-> ToJSON SparseValues
forall a.
(a -> Value)
-> (a -> Encoding)
-> ([a] -> Value)
-> ([a] -> Encoding)
-> (a -> Bool)
-> ToJSON a
$ctoJSON :: SparseValues -> Value
toJSON :: SparseValues -> Value
$ctoEncoding :: SparseValues -> Encoding
toEncoding :: SparseValues -> Encoding
$ctoJSONList :: [SparseValues] -> Value
toJSONList :: [SparseValues] -> Value
$ctoEncodingList :: [SparseValues] -> Encoding
toEncodingList :: [SparseValues] -> Encoding
$comitField :: SparseValues -> Bool
omitField :: SparseValues -> Bool
ToJSON)
data VectorID = VectorID
{ VectorID -> Text
id :: Text
} deriving stock (VectorID -> VectorID -> Bool
(VectorID -> VectorID -> Bool)
-> (VectorID -> VectorID -> Bool) -> Eq VectorID
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: VectorID -> VectorID -> Bool
== :: VectorID -> VectorID -> Bool
$c/= :: VectorID -> VectorID -> Bool
/= :: VectorID -> VectorID -> Bool
Eq, (forall x. VectorID -> Rep VectorID x)
-> (forall x. Rep VectorID x -> VectorID) -> Generic VectorID
forall x. Rep VectorID x -> VectorID
forall x. VectorID -> Rep VectorID x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cfrom :: forall x. VectorID -> Rep VectorID x
from :: forall x. VectorID -> Rep VectorID x
$cto :: forall x. Rep VectorID x -> VectorID
to :: forall x. Rep VectorID x -> VectorID
Generic, Int -> VectorID -> ShowS
[VectorID] -> ShowS
VectorID -> String
(Int -> VectorID -> ShowS)
-> (VectorID -> String) -> ([VectorID] -> ShowS) -> Show VectorID
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> VectorID -> ShowS
showsPrec :: Int -> VectorID -> ShowS
$cshow :: VectorID -> String
show :: VectorID -> String
$cshowList :: [VectorID] -> ShowS
showList :: [VectorID] -> ShowS
Show)
deriving anyclass (Maybe VectorID
Value -> Parser [VectorID]
Value -> Parser VectorID
(Value -> Parser VectorID)
-> (Value -> Parser [VectorID])
-> Maybe VectorID
-> FromJSON VectorID
forall a.
(Value -> Parser a)
-> (Value -> Parser [a]) -> Maybe a -> FromJSON a
$cparseJSON :: Value -> Parser VectorID
parseJSON :: Value -> Parser VectorID
$cparseJSONList :: Value -> Parser [VectorID]
parseJSONList :: Value -> Parser [VectorID]
$comittedField :: Maybe VectorID
omittedField :: Maybe VectorID
FromJSON, [VectorID] -> Value
[VectorID] -> Encoding
VectorID -> Bool
VectorID -> Value
VectorID -> Encoding
(VectorID -> Value)
-> (VectorID -> Encoding)
-> ([VectorID] -> Value)
-> ([VectorID] -> Encoding)
-> (VectorID -> Bool)
-> ToJSON VectorID
forall a.
(a -> Value)
-> (a -> Encoding)
-> ([a] -> Value)
-> ([a] -> Encoding)
-> (a -> Bool)
-> ToJSON a
$ctoJSON :: VectorID -> Value
toJSON :: VectorID -> Value
$ctoEncoding :: VectorID -> Encoding
toEncoding :: VectorID -> Encoding
$ctoJSONList :: [VectorID] -> Value
toJSONList :: [VectorID] -> Value
$ctoEncodingList :: [VectorID] -> Encoding
toEncodingList :: [VectorID] -> Encoding
$comitField :: VectorID -> Bool
omitField :: VectorID -> Bool
ToJSON)
data Usage = Usage
{ Usage -> Natural
readUnits :: Natural
} deriving stock (Usage -> Usage -> Bool
(Usage -> Usage -> Bool) -> (Usage -> Usage -> Bool) -> Eq Usage
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: Usage -> Usage -> Bool
== :: Usage -> Usage -> Bool
$c/= :: Usage -> Usage -> Bool
/= :: Usage -> Usage -> Bool
Eq, (forall x. Usage -> Rep Usage x)
-> (forall x. Rep Usage x -> Usage) -> Generic Usage
forall x. Rep Usage x -> Usage
forall x. Usage -> Rep Usage x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cfrom :: forall x. Usage -> Rep Usage x
from :: forall x. Usage -> Rep Usage x
$cto :: forall x. Rep Usage x -> Usage
to :: forall x. Rep Usage x -> Usage
Generic, Int -> Usage -> ShowS
[Usage] -> ShowS
Usage -> String
(Int -> Usage -> ShowS)
-> (Usage -> String) -> ([Usage] -> ShowS) -> Show Usage
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> Usage -> ShowS
showsPrec :: Int -> Usage -> ShowS
$cshow :: Usage -> String
show :: Usage -> String
$cshowList :: [Usage] -> ShowS
showList :: [Usage] -> ShowS
Show)
deriving anyclass (Maybe Usage
Value -> Parser [Usage]
Value -> Parser Usage
(Value -> Parser Usage)
-> (Value -> Parser [Usage]) -> Maybe Usage -> FromJSON Usage
forall a.
(Value -> Parser a)
-> (Value -> Parser [a]) -> Maybe a -> FromJSON a
$cparseJSON :: Value -> Parser Usage
parseJSON :: Value -> Parser Usage
$cparseJSONList :: Value -> Parser [Usage]
parseJSONList :: Value -> Parser [Usage]
$comittedField :: Maybe Usage
omittedField :: Maybe Usage
FromJSON, [Usage] -> Value
[Usage] -> Encoding
Usage -> Bool
Usage -> Value
Usage -> Encoding
(Usage -> Value)
-> (Usage -> Encoding)
-> ([Usage] -> Value)
-> ([Usage] -> Encoding)
-> (Usage -> Bool)
-> ToJSON Usage
forall a.
(a -> Value)
-> (a -> Encoding)
-> ([a] -> Value)
-> ([a] -> Encoding)
-> (a -> Bool)
-> ToJSON a
$ctoJSON :: Usage -> Value
toJSON :: Usage -> Value
$ctoEncoding :: Usage -> Encoding
toEncoding :: Usage -> Encoding
$ctoJSONList :: [Usage] -> Value
toJSONList :: [Usage] -> Value
$ctoEncodingList :: [Usage] -> Encoding
toEncodingList :: [Usage] -> Encoding
$comitField :: Usage -> Bool
omitField :: Usage -> Bool
ToJSON)
type API =
( "vectors"
:> ( ( "upsert"
:> ReqBody '[JSON] UpsertVectors
:> Post '[JSON] UpsertStats
)
:<|> ( "fetch"
:> QueryParams "ids" Text
:> QueryParam "namespace" Namespace
:> Get '[JSON] Vectors
)
:<|> ( "update"
:> ReqBody '[JSON] UpdateVector
:> Post '[JSON] NoContent
)
:<|> ( "delete"
:> ReqBody '[JSON] DeleteVectors
:> Post '[JSON] NoContent
)
:<|> ( "list"
:> QueryParam "prefix" Text
:> QueryParam "limit" Natural
:> QueryParam "paginationToken" Text
:> QueryParam "namespace" Namespace
:> Get '[JSON] VectorIDs
)
)
)
:<|> ( "records"
:> "namespaces"
:> Capture "namespace" Namespace
:> "upsert"
:> ReqBody '[JSON] Record
:> PostCreated '[JSON] NoContent
)