module Pinecone.Backups
(
Collection(..)
, Collections(..)
, CreateCollection(..)
, _CreateCollection
, CollectionModel(..)
, Status(..)
, API
) where
import Pinecone.Indexes (Index)
import Pinecone.Prelude
newtype Collection = Collection{ Collection -> Text
text :: Text }
deriving newtype (Collection -> Collection -> Bool
(Collection -> Collection -> Bool)
-> (Collection -> Collection -> Bool) -> Eq Collection
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: Collection -> Collection -> Bool
== :: Collection -> Collection -> Bool
$c/= :: Collection -> Collection -> Bool
/= :: Collection -> Collection -> Bool
Eq, Maybe Collection
Value -> Parser [Collection]
Value -> Parser Collection
(Value -> Parser Collection)
-> (Value -> Parser [Collection])
-> Maybe Collection
-> FromJSON Collection
forall a.
(Value -> Parser a)
-> (Value -> Parser [a]) -> Maybe a -> FromJSON a
$cparseJSON :: Value -> Parser Collection
parseJSON :: Value -> Parser Collection
$cparseJSONList :: Value -> Parser [Collection]
parseJSONList :: Value -> Parser [Collection]
$comittedField :: Maybe Collection
omittedField :: Maybe Collection
FromJSON, String -> Collection
(String -> Collection) -> IsString Collection
forall a. (String -> a) -> IsString a
$cfromString :: String -> Collection
fromString :: String -> Collection
IsString, Int -> Collection -> ShowS
[Collection] -> ShowS
Collection -> String
(Int -> Collection -> ShowS)
-> (Collection -> String)
-> ([Collection] -> ShowS)
-> Show Collection
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> Collection -> ShowS
showsPrec :: Int -> Collection -> ShowS
$cshow :: Collection -> String
show :: Collection -> String
$cshowList :: [Collection] -> ShowS
showList :: [Collection] -> ShowS
Show, Collection -> Text
Collection -> ByteString
Collection -> Builder
(Collection -> Text)
-> (Collection -> Builder)
-> (Collection -> ByteString)
-> (Collection -> Text)
-> (Collection -> Builder)
-> ToHttpApiData Collection
forall a.
(a -> Text)
-> (a -> Builder)
-> (a -> ByteString)
-> (a -> Text)
-> (a -> Builder)
-> ToHttpApiData a
$ctoUrlPiece :: Collection -> Text
toUrlPiece :: Collection -> Text
$ctoEncodedUrlPiece :: Collection -> Builder
toEncodedUrlPiece :: Collection -> Builder
$ctoHeader :: Collection -> ByteString
toHeader :: Collection -> ByteString
$ctoQueryParam :: Collection -> Text
toQueryParam :: Collection -> Text
$ctoEncodedQueryParam :: Collection -> Builder
toEncodedQueryParam :: Collection -> Builder
ToHttpApiData, [Collection] -> Value
[Collection] -> Encoding
Collection -> Bool
Collection -> Value
Collection -> Encoding
(Collection -> Value)
-> (Collection -> Encoding)
-> ([Collection] -> Value)
-> ([Collection] -> Encoding)
-> (Collection -> Bool)
-> ToJSON Collection
forall a.
(a -> Value)
-> (a -> Encoding)
-> ([a] -> Value)
-> ([a] -> Encoding)
-> (a -> Bool)
-> ToJSON a
$ctoJSON :: Collection -> Value
toJSON :: Collection -> Value
$ctoEncoding :: Collection -> Encoding
toEncoding :: Collection -> Encoding
$ctoJSONList :: [Collection] -> Value
toJSONList :: [Collection] -> Value
$ctoEncodingList :: [Collection] -> Encoding
toEncodingList :: [Collection] -> Encoding
$comitField :: Collection -> Bool
omitField :: Collection -> Bool
ToJSON)
data Collections = Collections
{ Collections -> Vector CollectionModel
collections :: Vector CollectionModel
} deriving stock (Collections -> Collections -> Bool
(Collections -> Collections -> Bool)
-> (Collections -> Collections -> Bool) -> Eq Collections
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: Collections -> Collections -> Bool
== :: Collections -> Collections -> Bool
$c/= :: Collections -> Collections -> Bool
/= :: Collections -> Collections -> Bool
Eq, (forall x. Collections -> Rep Collections x)
-> (forall x. Rep Collections x -> Collections)
-> Generic Collections
forall x. Rep Collections x -> Collections
forall x. Collections -> Rep Collections x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cfrom :: forall x. Collections -> Rep Collections x
from :: forall x. Collections -> Rep Collections x
$cto :: forall x. Rep Collections x -> Collections
to :: forall x. Rep Collections x -> Collections
Generic, Int -> Collections -> ShowS
[Collections] -> ShowS
Collections -> String
(Int -> Collections -> ShowS)
-> (Collections -> String)
-> ([Collections] -> ShowS)
-> Show Collections
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> Collections -> ShowS
showsPrec :: Int -> Collections -> ShowS
$cshow :: Collections -> String
show :: Collections -> String
$cshowList :: [Collections] -> ShowS
showList :: [Collections] -> ShowS
Show)
deriving anyclass (Maybe Collections
Value -> Parser [Collections]
Value -> Parser Collections
(Value -> Parser Collections)
-> (Value -> Parser [Collections])
-> Maybe Collections
-> FromJSON Collections
forall a.
(Value -> Parser a)
-> (Value -> Parser [a]) -> Maybe a -> FromJSON a
$cparseJSON :: Value -> Parser Collections
parseJSON :: Value -> Parser Collections
$cparseJSONList :: Value -> Parser [Collections]
parseJSONList :: Value -> Parser [Collections]
$comittedField :: Maybe Collections
omittedField :: Maybe Collections
FromJSON, [Collections] -> Value
[Collections] -> Encoding
Collections -> Bool
Collections -> Value
Collections -> Encoding
(Collections -> Value)
-> (Collections -> Encoding)
-> ([Collections] -> Value)
-> ([Collections] -> Encoding)
-> (Collections -> Bool)
-> ToJSON Collections
forall a.
(a -> Value)
-> (a -> Encoding)
-> ([a] -> Value)
-> ([a] -> Encoding)
-> (a -> Bool)
-> ToJSON a
$ctoJSON :: Collections -> Value
toJSON :: Collections -> Value
$ctoEncoding :: Collections -> Encoding
toEncoding :: Collections -> Encoding
$ctoJSONList :: [Collections] -> Value
toJSONList :: [Collections] -> Value
$ctoEncodingList :: [Collections] -> Encoding
toEncodingList :: [Collections] -> Encoding
$comitField :: Collections -> Bool
omitField :: Collections -> Bool
ToJSON)
data CreateCollection = CreateCollection
{ CreateCollection -> Text
name :: Text
, CreateCollection -> Index
source :: Index
} deriving stock (CreateCollection -> CreateCollection -> Bool
(CreateCollection -> CreateCollection -> Bool)
-> (CreateCollection -> CreateCollection -> Bool)
-> Eq CreateCollection
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: CreateCollection -> CreateCollection -> Bool
== :: CreateCollection -> CreateCollection -> Bool
$c/= :: CreateCollection -> CreateCollection -> Bool
/= :: CreateCollection -> CreateCollection -> Bool
Eq, (forall x. CreateCollection -> Rep CreateCollection x)
-> (forall x. Rep CreateCollection x -> CreateCollection)
-> Generic CreateCollection
forall x. Rep CreateCollection x -> CreateCollection
forall x. CreateCollection -> Rep CreateCollection x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cfrom :: forall x. CreateCollection -> Rep CreateCollection x
from :: forall x. CreateCollection -> Rep CreateCollection x
$cto :: forall x. Rep CreateCollection x -> CreateCollection
to :: forall x. Rep CreateCollection x -> CreateCollection
Generic, Int -> CreateCollection -> ShowS
[CreateCollection] -> ShowS
CreateCollection -> String
(Int -> CreateCollection -> ShowS)
-> (CreateCollection -> String)
-> ([CreateCollection] -> ShowS)
-> Show CreateCollection
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> CreateCollection -> ShowS
showsPrec :: Int -> CreateCollection -> ShowS
$cshow :: CreateCollection -> String
show :: CreateCollection -> String
$cshowList :: [CreateCollection] -> ShowS
showList :: [CreateCollection] -> ShowS
Show)
deriving anyclass (Maybe CreateCollection
Value -> Parser [CreateCollection]
Value -> Parser CreateCollection
(Value -> Parser CreateCollection)
-> (Value -> Parser [CreateCollection])
-> Maybe CreateCollection
-> FromJSON CreateCollection
forall a.
(Value -> Parser a)
-> (Value -> Parser [a]) -> Maybe a -> FromJSON a
$cparseJSON :: Value -> Parser CreateCollection
parseJSON :: Value -> Parser CreateCollection
$cparseJSONList :: Value -> Parser [CreateCollection]
parseJSONList :: Value -> Parser [CreateCollection]
$comittedField :: Maybe CreateCollection
omittedField :: Maybe CreateCollection
FromJSON, [CreateCollection] -> Value
[CreateCollection] -> Encoding
CreateCollection -> Bool
CreateCollection -> Value
CreateCollection -> Encoding
(CreateCollection -> Value)
-> (CreateCollection -> Encoding)
-> ([CreateCollection] -> Value)
-> ([CreateCollection] -> Encoding)
-> (CreateCollection -> Bool)
-> ToJSON CreateCollection
forall a.
(a -> Value)
-> (a -> Encoding)
-> ([a] -> Value)
-> ([a] -> Encoding)
-> (a -> Bool)
-> ToJSON a
$ctoJSON :: CreateCollection -> Value
toJSON :: CreateCollection -> Value
$ctoEncoding :: CreateCollection -> Encoding
toEncoding :: CreateCollection -> Encoding
$ctoJSONList :: [CreateCollection] -> Value
toJSONList :: [CreateCollection] -> Value
$ctoEncodingList :: [CreateCollection] -> Encoding
toEncodingList :: [CreateCollection] -> Encoding
$comitField :: CreateCollection -> Bool
omitField :: CreateCollection -> Bool
ToJSON)
_CreateCollection :: CreateCollection
_CreateCollection :: CreateCollection
_CreateCollection = CreateCollection{ }
data CollectionModel = CollectionModel
{ CollectionModel -> Collection
name :: Collection
, CollectionModel -> Status
status :: Status
, CollectionModel -> Text
environment :: Text
, CollectionModel -> Maybe Natural
size :: Maybe Natural
, CollectionModel -> Maybe Natural
dimension :: Maybe Natural
, CollectionModel -> Maybe Natural
vector_count :: Maybe Natural
} deriving stock (CollectionModel -> CollectionModel -> Bool
(CollectionModel -> CollectionModel -> Bool)
-> (CollectionModel -> CollectionModel -> Bool)
-> Eq CollectionModel
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: CollectionModel -> CollectionModel -> Bool
== :: CollectionModel -> CollectionModel -> Bool
$c/= :: CollectionModel -> CollectionModel -> Bool
/= :: CollectionModel -> CollectionModel -> Bool
Eq, (forall x. CollectionModel -> Rep CollectionModel x)
-> (forall x. Rep CollectionModel x -> CollectionModel)
-> Generic CollectionModel
forall x. Rep CollectionModel x -> CollectionModel
forall x. CollectionModel -> Rep CollectionModel x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cfrom :: forall x. CollectionModel -> Rep CollectionModel x
from :: forall x. CollectionModel -> Rep CollectionModel x
$cto :: forall x. Rep CollectionModel x -> CollectionModel
to :: forall x. Rep CollectionModel x -> CollectionModel
Generic, Int -> CollectionModel -> ShowS
[CollectionModel] -> ShowS
CollectionModel -> String
(Int -> CollectionModel -> ShowS)
-> (CollectionModel -> String)
-> ([CollectionModel] -> ShowS)
-> Show CollectionModel
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> CollectionModel -> ShowS
showsPrec :: Int -> CollectionModel -> ShowS
$cshow :: CollectionModel -> String
show :: CollectionModel -> String
$cshowList :: [CollectionModel] -> ShowS
showList :: [CollectionModel] -> ShowS
Show)
deriving anyclass (Maybe CollectionModel
Value -> Parser [CollectionModel]
Value -> Parser CollectionModel
(Value -> Parser CollectionModel)
-> (Value -> Parser [CollectionModel])
-> Maybe CollectionModel
-> FromJSON CollectionModel
forall a.
(Value -> Parser a)
-> (Value -> Parser [a]) -> Maybe a -> FromJSON a
$cparseJSON :: Value -> Parser CollectionModel
parseJSON :: Value -> Parser CollectionModel
$cparseJSONList :: Value -> Parser [CollectionModel]
parseJSONList :: Value -> Parser [CollectionModel]
$comittedField :: Maybe CollectionModel
omittedField :: Maybe CollectionModel
FromJSON, [CollectionModel] -> Value
[CollectionModel] -> Encoding
CollectionModel -> Bool
CollectionModel -> Value
CollectionModel -> Encoding
(CollectionModel -> Value)
-> (CollectionModel -> Encoding)
-> ([CollectionModel] -> Value)
-> ([CollectionModel] -> Encoding)
-> (CollectionModel -> Bool)
-> ToJSON CollectionModel
forall a.
(a -> Value)
-> (a -> Encoding)
-> ([a] -> Value)
-> ([a] -> Encoding)
-> (a -> Bool)
-> ToJSON a
$ctoJSON :: CollectionModel -> Value
toJSON :: CollectionModel -> Value
$ctoEncoding :: CollectionModel -> Encoding
toEncoding :: CollectionModel -> Encoding
$ctoJSONList :: [CollectionModel] -> Value
toJSONList :: [CollectionModel] -> Value
$ctoEncodingList :: [CollectionModel] -> Encoding
toEncodingList :: [CollectionModel] -> Encoding
$comitField :: CollectionModel -> Bool
omitField :: CollectionModel -> Bool
ToJSON)
data Status
= Initializing
| Ready
| Terminating
deriving stock (Status -> Status -> Bool
(Status -> Status -> Bool)
-> (Status -> Status -> Bool) -> Eq Status
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: Status -> Status -> Bool
== :: Status -> Status -> Bool
$c/= :: Status -> Status -> Bool
/= :: Status -> Status -> Bool
Eq, (forall x. Status -> Rep Status x)
-> (forall x. Rep Status x -> Status) -> Generic Status
forall x. Rep Status x -> Status
forall x. Status -> Rep Status x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cfrom :: forall x. Status -> Rep Status x
from :: forall x. Status -> Rep Status x
$cto :: forall x. Rep Status x -> Status
to :: forall x. Rep Status x -> Status
Generic, Int -> Status -> ShowS
[Status] -> ShowS
Status -> String
(Int -> Status -> ShowS)
-> (Status -> String) -> ([Status] -> ShowS) -> Show Status
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> Status -> ShowS
showsPrec :: Int -> Status -> ShowS
$cshow :: Status -> String
show :: Status -> String
$cshowList :: [Status] -> ShowS
showList :: [Status] -> ShowS
Show)
instance FromJSON Status where
parseJSON :: Value -> Parser Status
parseJSON = Options -> Value -> Parser Status
forall a.
(Generic a, GFromJSON Zero (Rep a)) =>
Options -> Value -> Parser a
genericParseJSON Options
aesonOptions{ constructorTagModifier = id }
instance ToJSON Status where
toJSON :: Status -> Value
toJSON = Options -> Status -> Value
forall a.
(Generic a, GToJSON' Value Zero (Rep a)) =>
Options -> a -> Value
genericToJSON Options
aesonOptions{ constructorTagModifier = id }
type API =
"collections"
:> ( Get '[JSON] Collections
:<|> ReqBody '[JSON] CreateCollection
:> Post '[JSON] CollectionModel
:<|> Capture "collection_name" Collection
:> Get '[JSON] CollectionModel
:<|> Capture "collection_name" Collection
:> DeleteAccepted '[JSON] NoContent
)