module Pinecone.Indexes
(
Index(..)
, Host(..)
, IndexModels(..)
, IndexModel(..)
, CreateIndex(..)
, _CreateIndex
, CreateIndexWithEmbedding(..)
, _CreateIndexWithEmbedding
, ConfigureIndex(..)
, _ConfigureIndex
, GetIndexStats(..)
, _GetIndexStats
, IndexStats(..)
, Metric(..)
, Spec(..)
, Pod(..)
, PodType(..)
, Prefix(..)
, Suffix(..)
, MetadataConfig(..)
, Serverless(..)
, Cloud(..)
, Status(..)
, State(..)
, DeletionProtection(..)
, EmbedRequest(..)
, EmbedResponse(..)
, Contents(..)
, ControlAPI
, DataAPI
) where
import Pinecone.Embed (VectorType)
import Pinecone.Metadata (Filter)
import Pinecone.Prelude
import qualified Data.Text as Text
newtype Index = Index{ Index -> Text
text :: Text }
deriving newtype (Index -> Index -> Bool
(Index -> Index -> Bool) -> (Index -> Index -> Bool) -> Eq Index
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: Index -> Index -> Bool
== :: Index -> Index -> Bool
$c/= :: Index -> Index -> Bool
/= :: Index -> Index -> Bool
Eq, Maybe Index
Value -> Parser [Index]
Value -> Parser Index
(Value -> Parser Index)
-> (Value -> Parser [Index]) -> Maybe Index -> FromJSON Index
forall a.
(Value -> Parser a)
-> (Value -> Parser [a]) -> Maybe a -> FromJSON a
$cparseJSON :: Value -> Parser Index
parseJSON :: Value -> Parser Index
$cparseJSONList :: Value -> Parser [Index]
parseJSONList :: Value -> Parser [Index]
$comittedField :: Maybe Index
omittedField :: Maybe Index
FromJSON, String -> Index
(String -> Index) -> IsString Index
forall a. (String -> a) -> IsString a
$cfromString :: String -> Index
fromString :: String -> Index
IsString, Int -> Index -> ShowS
[Index] -> ShowS
Index -> String
(Int -> Index -> ShowS)
-> (Index -> String) -> ([Index] -> ShowS) -> Show Index
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> Index -> ShowS
showsPrec :: Int -> Index -> ShowS
$cshow :: Index -> String
show :: Index -> String
$cshowList :: [Index] -> ShowS
showList :: [Index] -> ShowS
Show, Index -> Text
Index -> ByteString
Index -> Builder
(Index -> Text)
-> (Index -> Builder)
-> (Index -> ByteString)
-> (Index -> Text)
-> (Index -> Builder)
-> ToHttpApiData Index
forall a.
(a -> Text)
-> (a -> Builder)
-> (a -> ByteString)
-> (a -> Text)
-> (a -> Builder)
-> ToHttpApiData a
$ctoUrlPiece :: Index -> Text
toUrlPiece :: Index -> Text
$ctoEncodedUrlPiece :: Index -> Builder
toEncodedUrlPiece :: Index -> Builder
$ctoHeader :: Index -> ByteString
toHeader :: Index -> ByteString
$ctoQueryParam :: Index -> Text
toQueryParam :: Index -> Text
$ctoEncodedQueryParam :: Index -> Builder
toEncodedQueryParam :: Index -> Builder
ToHttpApiData, [Index] -> Value
[Index] -> Encoding
Index -> Bool
Index -> Value
Index -> Encoding
(Index -> Value)
-> (Index -> Encoding)
-> ([Index] -> Value)
-> ([Index] -> Encoding)
-> (Index -> Bool)
-> ToJSON Index
forall a.
(a -> Value)
-> (a -> Encoding)
-> ([a] -> Value)
-> ([a] -> Encoding)
-> (a -> Bool)
-> ToJSON a
$ctoJSON :: Index -> Value
toJSON :: Index -> Value
$ctoEncoding :: Index -> Encoding
toEncoding :: Index -> Encoding
$ctoJSONList :: [Index] -> Value
toJSONList :: [Index] -> Value
$ctoEncodingList :: [Index] -> Encoding
toEncodingList :: [Index] -> Encoding
$comitField :: Index -> Bool
omitField :: Index -> Bool
ToJSON)
newtype Host = Host{ Host -> Text
text :: Text }
deriving newtype (Host -> Host -> Bool
(Host -> Host -> Bool) -> (Host -> Host -> Bool) -> Eq Host
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: Host -> Host -> Bool
== :: Host -> Host -> Bool
$c/= :: Host -> Host -> Bool
/= :: Host -> Host -> Bool
Eq, Maybe Host
Value -> Parser [Host]
Value -> Parser Host
(Value -> Parser Host)
-> (Value -> Parser [Host]) -> Maybe Host -> FromJSON Host
forall a.
(Value -> Parser a)
-> (Value -> Parser [a]) -> Maybe a -> FromJSON a
$cparseJSON :: Value -> Parser Host
parseJSON :: Value -> Parser Host
$cparseJSONList :: Value -> Parser [Host]
parseJSONList :: Value -> Parser [Host]
$comittedField :: Maybe Host
omittedField :: Maybe Host
FromJSON, String -> Host
(String -> Host) -> IsString Host
forall a. (String -> a) -> IsString a
$cfromString :: String -> Host
fromString :: String -> Host
IsString, Int -> Host -> ShowS
[Host] -> ShowS
Host -> String
(Int -> Host -> ShowS)
-> (Host -> String) -> ([Host] -> ShowS) -> Show Host
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> Host -> ShowS
showsPrec :: Int -> Host -> ShowS
$cshow :: Host -> String
show :: Host -> String
$cshowList :: [Host] -> ShowS
showList :: [Host] -> ShowS
Show, Host -> Text
Host -> ByteString
Host -> Builder
(Host -> Text)
-> (Host -> Builder)
-> (Host -> ByteString)
-> (Host -> Text)
-> (Host -> Builder)
-> ToHttpApiData Host
forall a.
(a -> Text)
-> (a -> Builder)
-> (a -> ByteString)
-> (a -> Text)
-> (a -> Builder)
-> ToHttpApiData a
$ctoUrlPiece :: Host -> Text
toUrlPiece :: Host -> Text
$ctoEncodedUrlPiece :: Host -> Builder
toEncodedUrlPiece :: Host -> Builder
$ctoHeader :: Host -> ByteString
toHeader :: Host -> ByteString
$ctoQueryParam :: Host -> Text
toQueryParam :: Host -> Text
$ctoEncodedQueryParam :: Host -> Builder
toEncodedQueryParam :: Host -> Builder
ToHttpApiData, [Host] -> Value
[Host] -> Encoding
Host -> Bool
Host -> Value
Host -> Encoding
(Host -> Value)
-> (Host -> Encoding)
-> ([Host] -> Value)
-> ([Host] -> Encoding)
-> (Host -> Bool)
-> ToJSON Host
forall a.
(a -> Value)
-> (a -> Encoding)
-> ([a] -> Value)
-> ([a] -> Encoding)
-> (a -> Bool)
-> ToJSON a
$ctoJSON :: Host -> Value
toJSON :: Host -> Value
$ctoEncoding :: Host -> Encoding
toEncoding :: Host -> Encoding
$ctoJSONList :: [Host] -> Value
toJSONList :: [Host] -> Value
$ctoEncodingList :: [Host] -> Encoding
toEncodingList :: [Host] -> Encoding
$comitField :: Host -> Bool
omitField :: Host -> Bool
ToJSON)
data IndexModels = IndexModels
{ IndexModels -> Vector IndexModel
indexes :: Vector IndexModel
} deriving stock (IndexModels -> IndexModels -> Bool
(IndexModels -> IndexModels -> Bool)
-> (IndexModels -> IndexModels -> Bool) -> Eq IndexModels
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: IndexModels -> IndexModels -> Bool
== :: IndexModels -> IndexModels -> Bool
$c/= :: IndexModels -> IndexModels -> Bool
/= :: IndexModels -> IndexModels -> Bool
Eq, (forall x. IndexModels -> Rep IndexModels x)
-> (forall x. Rep IndexModels x -> IndexModels)
-> Generic IndexModels
forall x. Rep IndexModels x -> IndexModels
forall x. IndexModels -> Rep IndexModels x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cfrom :: forall x. IndexModels -> Rep IndexModels x
from :: forall x. IndexModels -> Rep IndexModels x
$cto :: forall x. Rep IndexModels x -> IndexModels
to :: forall x. Rep IndexModels x -> IndexModels
Generic, Int -> IndexModels -> ShowS
[IndexModels] -> ShowS
IndexModels -> String
(Int -> IndexModels -> ShowS)
-> (IndexModels -> String)
-> ([IndexModels] -> ShowS)
-> Show IndexModels
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> IndexModels -> ShowS
showsPrec :: Int -> IndexModels -> ShowS
$cshow :: IndexModels -> String
show :: IndexModels -> String
$cshowList :: [IndexModels] -> ShowS
showList :: [IndexModels] -> ShowS
Show)
deriving anyclass (Maybe IndexModels
Value -> Parser [IndexModels]
Value -> Parser IndexModels
(Value -> Parser IndexModels)
-> (Value -> Parser [IndexModels])
-> Maybe IndexModels
-> FromJSON IndexModels
forall a.
(Value -> Parser a)
-> (Value -> Parser [a]) -> Maybe a -> FromJSON a
$cparseJSON :: Value -> Parser IndexModels
parseJSON :: Value -> Parser IndexModels
$cparseJSONList :: Value -> Parser [IndexModels]
parseJSONList :: Value -> Parser [IndexModels]
$comittedField :: Maybe IndexModels
omittedField :: Maybe IndexModels
FromJSON, [IndexModels] -> Value
[IndexModels] -> Encoding
IndexModels -> Bool
IndexModels -> Value
IndexModels -> Encoding
(IndexModels -> Value)
-> (IndexModels -> Encoding)
-> ([IndexModels] -> Value)
-> ([IndexModels] -> Encoding)
-> (IndexModels -> Bool)
-> ToJSON IndexModels
forall a.
(a -> Value)
-> (a -> Encoding)
-> ([a] -> Value)
-> ([a] -> Encoding)
-> (a -> Bool)
-> ToJSON a
$ctoJSON :: IndexModels -> Value
toJSON :: IndexModels -> Value
$ctoEncoding :: IndexModels -> Encoding
toEncoding :: IndexModels -> Encoding
$ctoJSONList :: [IndexModels] -> Value
toJSONList :: [IndexModels] -> Value
$ctoEncodingList :: [IndexModels] -> Encoding
toEncodingList :: [IndexModels] -> Encoding
$comitField :: IndexModels -> Bool
omitField :: IndexModels -> Bool
ToJSON)
data IndexModel = IndexModel
{ IndexModel -> Index
name :: Index
, IndexModel -> Metric
metric :: Metric
, IndexModel -> Host
host :: Host
, IndexModel -> Spec
spec :: Spec
, IndexModel -> Status
status :: Status
, IndexModel -> VectorType
vector_type :: VectorType
, IndexModel -> Maybe Natural
dimension :: Maybe Natural
, IndexModel -> Maybe DeletionProtection
deletion_protection :: Maybe DeletionProtection
, IndexModel -> Maybe (Map Text Text)
tags :: Maybe (Map Text Text)
, IndexModel -> Maybe EmbedResponse
embed :: Maybe EmbedResponse
} deriving stock (IndexModel -> IndexModel -> Bool
(IndexModel -> IndexModel -> Bool)
-> (IndexModel -> IndexModel -> Bool) -> Eq IndexModel
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: IndexModel -> IndexModel -> Bool
== :: IndexModel -> IndexModel -> Bool
$c/= :: IndexModel -> IndexModel -> Bool
/= :: IndexModel -> IndexModel -> Bool
Eq, (forall x. IndexModel -> Rep IndexModel x)
-> (forall x. Rep IndexModel x -> IndexModel) -> Generic IndexModel
forall x. Rep IndexModel x -> IndexModel
forall x. IndexModel -> Rep IndexModel x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cfrom :: forall x. IndexModel -> Rep IndexModel x
from :: forall x. IndexModel -> Rep IndexModel x
$cto :: forall x. Rep IndexModel x -> IndexModel
to :: forall x. Rep IndexModel x -> IndexModel
Generic, Int -> IndexModel -> ShowS
[IndexModel] -> ShowS
IndexModel -> String
(Int -> IndexModel -> ShowS)
-> (IndexModel -> String)
-> ([IndexModel] -> ShowS)
-> Show IndexModel
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> IndexModel -> ShowS
showsPrec :: Int -> IndexModel -> ShowS
$cshow :: IndexModel -> String
show :: IndexModel -> String
$cshowList :: [IndexModel] -> ShowS
showList :: [IndexModel] -> ShowS
Show)
deriving anyclass (Maybe IndexModel
Value -> Parser [IndexModel]
Value -> Parser IndexModel
(Value -> Parser IndexModel)
-> (Value -> Parser [IndexModel])
-> Maybe IndexModel
-> FromJSON IndexModel
forall a.
(Value -> Parser a)
-> (Value -> Parser [a]) -> Maybe a -> FromJSON a
$cparseJSON :: Value -> Parser IndexModel
parseJSON :: Value -> Parser IndexModel
$cparseJSONList :: Value -> Parser [IndexModel]
parseJSONList :: Value -> Parser [IndexModel]
$comittedField :: Maybe IndexModel
omittedField :: Maybe IndexModel
FromJSON, [IndexModel] -> Value
[IndexModel] -> Encoding
IndexModel -> Bool
IndexModel -> Value
IndexModel -> Encoding
(IndexModel -> Value)
-> (IndexModel -> Encoding)
-> ([IndexModel] -> Value)
-> ([IndexModel] -> Encoding)
-> (IndexModel -> Bool)
-> ToJSON IndexModel
forall a.
(a -> Value)
-> (a -> Encoding)
-> ([a] -> Value)
-> ([a] -> Encoding)
-> (a -> Bool)
-> ToJSON a
$ctoJSON :: IndexModel -> Value
toJSON :: IndexModel -> Value
$ctoEncoding :: IndexModel -> Encoding
toEncoding :: IndexModel -> Encoding
$ctoJSONList :: [IndexModel] -> Value
toJSONList :: [IndexModel] -> Value
$ctoEncodingList :: [IndexModel] -> Encoding
toEncodingList :: [IndexModel] -> Encoding
$comitField :: IndexModel -> Bool
omitField :: IndexModel -> Bool
ToJSON)
data CreateIndex = CreateIndex
{ CreateIndex -> Index
name :: Index
, CreateIndex -> Spec
spec :: Spec
, CreateIndex -> Maybe Natural
dimension :: Maybe Natural
, CreateIndex -> Maybe Metric
metric :: Maybe Metric
, CreateIndex -> Maybe DeletionProtection
deletion_protection :: Maybe DeletionProtection
, CreateIndex -> Maybe (Map Text Text)
tags :: Maybe (Map Text Text)
, CreateIndex -> Maybe VectorType
vector_type :: Maybe VectorType
} deriving stock (CreateIndex -> CreateIndex -> Bool
(CreateIndex -> CreateIndex -> Bool)
-> (CreateIndex -> CreateIndex -> Bool) -> Eq CreateIndex
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: CreateIndex -> CreateIndex -> Bool
== :: CreateIndex -> CreateIndex -> Bool
$c/= :: CreateIndex -> CreateIndex -> Bool
/= :: CreateIndex -> CreateIndex -> Bool
Eq, (forall x. CreateIndex -> Rep CreateIndex x)
-> (forall x. Rep CreateIndex x -> CreateIndex)
-> Generic CreateIndex
forall x. Rep CreateIndex x -> CreateIndex
forall x. CreateIndex -> Rep CreateIndex x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cfrom :: forall x. CreateIndex -> Rep CreateIndex x
from :: forall x. CreateIndex -> Rep CreateIndex x
$cto :: forall x. Rep CreateIndex x -> CreateIndex
to :: forall x. Rep CreateIndex x -> CreateIndex
Generic, Int -> CreateIndex -> ShowS
[CreateIndex] -> ShowS
CreateIndex -> String
(Int -> CreateIndex -> ShowS)
-> (CreateIndex -> String)
-> ([CreateIndex] -> ShowS)
-> Show CreateIndex
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> CreateIndex -> ShowS
showsPrec :: Int -> CreateIndex -> ShowS
$cshow :: CreateIndex -> String
show :: CreateIndex -> String
$cshowList :: [CreateIndex] -> ShowS
showList :: [CreateIndex] -> ShowS
Show)
deriving anyclass (Maybe CreateIndex
Value -> Parser [CreateIndex]
Value -> Parser CreateIndex
(Value -> Parser CreateIndex)
-> (Value -> Parser [CreateIndex])
-> Maybe CreateIndex
-> FromJSON CreateIndex
forall a.
(Value -> Parser a)
-> (Value -> Parser [a]) -> Maybe a -> FromJSON a
$cparseJSON :: Value -> Parser CreateIndex
parseJSON :: Value -> Parser CreateIndex
$cparseJSONList :: Value -> Parser [CreateIndex]
parseJSONList :: Value -> Parser [CreateIndex]
$comittedField :: Maybe CreateIndex
omittedField :: Maybe CreateIndex
FromJSON, [CreateIndex] -> Value
[CreateIndex] -> Encoding
CreateIndex -> Bool
CreateIndex -> Value
CreateIndex -> Encoding
(CreateIndex -> Value)
-> (CreateIndex -> Encoding)
-> ([CreateIndex] -> Value)
-> ([CreateIndex] -> Encoding)
-> (CreateIndex -> Bool)
-> ToJSON CreateIndex
forall a.
(a -> Value)
-> (a -> Encoding)
-> ([a] -> Value)
-> ([a] -> Encoding)
-> (a -> Bool)
-> ToJSON a
$ctoJSON :: CreateIndex -> Value
toJSON :: CreateIndex -> Value
$ctoEncoding :: CreateIndex -> Encoding
toEncoding :: CreateIndex -> Encoding
$ctoJSONList :: [CreateIndex] -> Value
toJSONList :: [CreateIndex] -> Value
$ctoEncodingList :: [CreateIndex] -> Encoding
toEncodingList :: [CreateIndex] -> Encoding
$comitField :: CreateIndex -> Bool
omitField :: CreateIndex -> Bool
ToJSON)
_CreateIndex :: CreateIndex
_CreateIndex :: CreateIndex
_CreateIndex = CreateIndex
{ $sel:dimension:CreateIndex :: Maybe Natural
dimension = Maybe Natural
forall a. Maybe a
Nothing
, $sel:metric:CreateIndex :: Maybe Metric
metric = Maybe Metric
forall a. Maybe a
Nothing
, $sel:deletion_protection:CreateIndex :: Maybe DeletionProtection
deletion_protection = Maybe DeletionProtection
forall a. Maybe a
Nothing
, $sel:tags:CreateIndex :: Maybe (Map Text Text)
tags = Maybe (Map Text Text)
forall a. Maybe a
Nothing
, $sel:vector_type:CreateIndex :: Maybe VectorType
vector_type = Maybe VectorType
forall a. Maybe a
Nothing
}
data CreateIndexWithEmbedding = CreateIndexWithEmbedding
{ CreateIndexWithEmbedding -> Index
name :: Index
, CreateIndexWithEmbedding -> Cloud
cloud :: Cloud
, CreateIndexWithEmbedding -> Text
region :: Text
, CreateIndexWithEmbedding -> EmbedRequest
embed :: EmbedRequest
, CreateIndexWithEmbedding -> Maybe DeletionProtection
deletion_protection :: Maybe DeletionProtection
, CreateIndexWithEmbedding -> Maybe (Map Text Text)
tags :: Maybe (Map Text Text)
} deriving stock (CreateIndexWithEmbedding -> CreateIndexWithEmbedding -> Bool
(CreateIndexWithEmbedding -> CreateIndexWithEmbedding -> Bool)
-> (CreateIndexWithEmbedding -> CreateIndexWithEmbedding -> Bool)
-> Eq CreateIndexWithEmbedding
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: CreateIndexWithEmbedding -> CreateIndexWithEmbedding -> Bool
== :: CreateIndexWithEmbedding -> CreateIndexWithEmbedding -> Bool
$c/= :: CreateIndexWithEmbedding -> CreateIndexWithEmbedding -> Bool
/= :: CreateIndexWithEmbedding -> CreateIndexWithEmbedding -> Bool
Eq, (forall x.
CreateIndexWithEmbedding -> Rep CreateIndexWithEmbedding x)
-> (forall x.
Rep CreateIndexWithEmbedding x -> CreateIndexWithEmbedding)
-> Generic CreateIndexWithEmbedding
forall x.
Rep CreateIndexWithEmbedding x -> CreateIndexWithEmbedding
forall x.
CreateIndexWithEmbedding -> Rep CreateIndexWithEmbedding x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cfrom :: forall x.
CreateIndexWithEmbedding -> Rep CreateIndexWithEmbedding x
from :: forall x.
CreateIndexWithEmbedding -> Rep CreateIndexWithEmbedding x
$cto :: forall x.
Rep CreateIndexWithEmbedding x -> CreateIndexWithEmbedding
to :: forall x.
Rep CreateIndexWithEmbedding x -> CreateIndexWithEmbedding
Generic, Int -> CreateIndexWithEmbedding -> ShowS
[CreateIndexWithEmbedding] -> ShowS
CreateIndexWithEmbedding -> String
(Int -> CreateIndexWithEmbedding -> ShowS)
-> (CreateIndexWithEmbedding -> String)
-> ([CreateIndexWithEmbedding] -> ShowS)
-> Show CreateIndexWithEmbedding
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> CreateIndexWithEmbedding -> ShowS
showsPrec :: Int -> CreateIndexWithEmbedding -> ShowS
$cshow :: CreateIndexWithEmbedding -> String
show :: CreateIndexWithEmbedding -> String
$cshowList :: [CreateIndexWithEmbedding] -> ShowS
showList :: [CreateIndexWithEmbedding] -> ShowS
Show)
deriving anyclass (Maybe CreateIndexWithEmbedding
Value -> Parser [CreateIndexWithEmbedding]
Value -> Parser CreateIndexWithEmbedding
(Value -> Parser CreateIndexWithEmbedding)
-> (Value -> Parser [CreateIndexWithEmbedding])
-> Maybe CreateIndexWithEmbedding
-> FromJSON CreateIndexWithEmbedding
forall a.
(Value -> Parser a)
-> (Value -> Parser [a]) -> Maybe a -> FromJSON a
$cparseJSON :: Value -> Parser CreateIndexWithEmbedding
parseJSON :: Value -> Parser CreateIndexWithEmbedding
$cparseJSONList :: Value -> Parser [CreateIndexWithEmbedding]
parseJSONList :: Value -> Parser [CreateIndexWithEmbedding]
$comittedField :: Maybe CreateIndexWithEmbedding
omittedField :: Maybe CreateIndexWithEmbedding
FromJSON, [CreateIndexWithEmbedding] -> Value
[CreateIndexWithEmbedding] -> Encoding
CreateIndexWithEmbedding -> Bool
CreateIndexWithEmbedding -> Value
CreateIndexWithEmbedding -> Encoding
(CreateIndexWithEmbedding -> Value)
-> (CreateIndexWithEmbedding -> Encoding)
-> ([CreateIndexWithEmbedding] -> Value)
-> ([CreateIndexWithEmbedding] -> Encoding)
-> (CreateIndexWithEmbedding -> Bool)
-> ToJSON CreateIndexWithEmbedding
forall a.
(a -> Value)
-> (a -> Encoding)
-> ([a] -> Value)
-> ([a] -> Encoding)
-> (a -> Bool)
-> ToJSON a
$ctoJSON :: CreateIndexWithEmbedding -> Value
toJSON :: CreateIndexWithEmbedding -> Value
$ctoEncoding :: CreateIndexWithEmbedding -> Encoding
toEncoding :: CreateIndexWithEmbedding -> Encoding
$ctoJSONList :: [CreateIndexWithEmbedding] -> Value
toJSONList :: [CreateIndexWithEmbedding] -> Value
$ctoEncodingList :: [CreateIndexWithEmbedding] -> Encoding
toEncodingList :: [CreateIndexWithEmbedding] -> Encoding
$comitField :: CreateIndexWithEmbedding -> Bool
omitField :: CreateIndexWithEmbedding -> Bool
ToJSON)
_CreateIndexWithEmbedding :: CreateIndexWithEmbedding
_CreateIndexWithEmbedding :: CreateIndexWithEmbedding
_CreateIndexWithEmbedding = CreateIndexWithEmbedding
{ $sel:deletion_protection:CreateIndexWithEmbedding :: Maybe DeletionProtection
deletion_protection = Maybe DeletionProtection
forall a. Maybe a
Nothing
, $sel:tags:CreateIndexWithEmbedding :: Maybe (Map Text Text)
tags = Maybe (Map Text Text)
forall a. Maybe a
Nothing
}
data ConfigureIndex = ConfigureIndex
{ ConfigureIndex -> Maybe Spec
spec :: Maybe Spec
, ConfigureIndex -> Maybe DeletionProtection
deletion_protection :: Maybe DeletionProtection
, ConfigureIndex -> Maybe (Map Text Text)
tags :: Maybe (Map Text Text)
, ConfigureIndex -> Maybe EmbedRequest
embed :: Maybe EmbedRequest
} deriving stock (ConfigureIndex -> ConfigureIndex -> Bool
(ConfigureIndex -> ConfigureIndex -> Bool)
-> (ConfigureIndex -> ConfigureIndex -> Bool) -> Eq ConfigureIndex
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: ConfigureIndex -> ConfigureIndex -> Bool
== :: ConfigureIndex -> ConfigureIndex -> Bool
$c/= :: ConfigureIndex -> ConfigureIndex -> Bool
/= :: ConfigureIndex -> ConfigureIndex -> Bool
Eq, (forall x. ConfigureIndex -> Rep ConfigureIndex x)
-> (forall x. Rep ConfigureIndex x -> ConfigureIndex)
-> Generic ConfigureIndex
forall x. Rep ConfigureIndex x -> ConfigureIndex
forall x. ConfigureIndex -> Rep ConfigureIndex x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cfrom :: forall x. ConfigureIndex -> Rep ConfigureIndex x
from :: forall x. ConfigureIndex -> Rep ConfigureIndex x
$cto :: forall x. Rep ConfigureIndex x -> ConfigureIndex
to :: forall x. Rep ConfigureIndex x -> ConfigureIndex
Generic, Int -> ConfigureIndex -> ShowS
[ConfigureIndex] -> ShowS
ConfigureIndex -> String
(Int -> ConfigureIndex -> ShowS)
-> (ConfigureIndex -> String)
-> ([ConfigureIndex] -> ShowS)
-> Show ConfigureIndex
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> ConfigureIndex -> ShowS
showsPrec :: Int -> ConfigureIndex -> ShowS
$cshow :: ConfigureIndex -> String
show :: ConfigureIndex -> String
$cshowList :: [ConfigureIndex] -> ShowS
showList :: [ConfigureIndex] -> ShowS
Show)
deriving anyclass (Maybe ConfigureIndex
Value -> Parser [ConfigureIndex]
Value -> Parser ConfigureIndex
(Value -> Parser ConfigureIndex)
-> (Value -> Parser [ConfigureIndex])
-> Maybe ConfigureIndex
-> FromJSON ConfigureIndex
forall a.
(Value -> Parser a)
-> (Value -> Parser [a]) -> Maybe a -> FromJSON a
$cparseJSON :: Value -> Parser ConfigureIndex
parseJSON :: Value -> Parser ConfigureIndex
$cparseJSONList :: Value -> Parser [ConfigureIndex]
parseJSONList :: Value -> Parser [ConfigureIndex]
$comittedField :: Maybe ConfigureIndex
omittedField :: Maybe ConfigureIndex
FromJSON, [ConfigureIndex] -> Value
[ConfigureIndex] -> Encoding
ConfigureIndex -> Bool
ConfigureIndex -> Value
ConfigureIndex -> Encoding
(ConfigureIndex -> Value)
-> (ConfigureIndex -> Encoding)
-> ([ConfigureIndex] -> Value)
-> ([ConfigureIndex] -> Encoding)
-> (ConfigureIndex -> Bool)
-> ToJSON ConfigureIndex
forall a.
(a -> Value)
-> (a -> Encoding)
-> ([a] -> Value)
-> ([a] -> Encoding)
-> (a -> Bool)
-> ToJSON a
$ctoJSON :: ConfigureIndex -> Value
toJSON :: ConfigureIndex -> Value
$ctoEncoding :: ConfigureIndex -> Encoding
toEncoding :: ConfigureIndex -> Encoding
$ctoJSONList :: [ConfigureIndex] -> Value
toJSONList :: [ConfigureIndex] -> Value
$ctoEncodingList :: [ConfigureIndex] -> Encoding
toEncodingList :: [ConfigureIndex] -> Encoding
$comitField :: ConfigureIndex -> Bool
omitField :: ConfigureIndex -> Bool
ToJSON)
_ConfigureIndex :: ConfigureIndex
_ConfigureIndex :: ConfigureIndex
_ConfigureIndex = ConfigureIndex
{ $sel:spec:ConfigureIndex :: Maybe Spec
spec = Maybe Spec
forall a. Maybe a
Nothing
, $sel:deletion_protection:ConfigureIndex :: Maybe DeletionProtection
deletion_protection = Maybe DeletionProtection
forall a. Maybe a
Nothing
, $sel:tags:ConfigureIndex :: Maybe (Map Text Text)
tags = Maybe (Map Text Text)
forall a. Maybe a
Nothing
, $sel:embed:ConfigureIndex :: Maybe EmbedRequest
embed = Maybe EmbedRequest
forall a. Maybe a
Nothing
}
data GetIndexStats = GetIndexStats
{ GetIndexStats -> Maybe Filter
filter :: Maybe Filter
} deriving stock (GetIndexStats -> GetIndexStats -> Bool
(GetIndexStats -> GetIndexStats -> Bool)
-> (GetIndexStats -> GetIndexStats -> Bool) -> Eq GetIndexStats
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: GetIndexStats -> GetIndexStats -> Bool
== :: GetIndexStats -> GetIndexStats -> Bool
$c/= :: GetIndexStats -> GetIndexStats -> Bool
/= :: GetIndexStats -> GetIndexStats -> Bool
Eq, (forall x. GetIndexStats -> Rep GetIndexStats x)
-> (forall x. Rep GetIndexStats x -> GetIndexStats)
-> Generic GetIndexStats
forall x. Rep GetIndexStats x -> GetIndexStats
forall x. GetIndexStats -> Rep GetIndexStats x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cfrom :: forall x. GetIndexStats -> Rep GetIndexStats x
from :: forall x. GetIndexStats -> Rep GetIndexStats x
$cto :: forall x. Rep GetIndexStats x -> GetIndexStats
to :: forall x. Rep GetIndexStats x -> GetIndexStats
Generic, Int -> GetIndexStats -> ShowS
[GetIndexStats] -> ShowS
GetIndexStats -> String
(Int -> GetIndexStats -> ShowS)
-> (GetIndexStats -> String)
-> ([GetIndexStats] -> ShowS)
-> Show GetIndexStats
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> GetIndexStats -> ShowS
showsPrec :: Int -> GetIndexStats -> ShowS
$cshow :: GetIndexStats -> String
show :: GetIndexStats -> String
$cshowList :: [GetIndexStats] -> ShowS
showList :: [GetIndexStats] -> ShowS
Show)
deriving anyclass (Maybe GetIndexStats
Value -> Parser [GetIndexStats]
Value -> Parser GetIndexStats
(Value -> Parser GetIndexStats)
-> (Value -> Parser [GetIndexStats])
-> Maybe GetIndexStats
-> FromJSON GetIndexStats
forall a.
(Value -> Parser a)
-> (Value -> Parser [a]) -> Maybe a -> FromJSON a
$cparseJSON :: Value -> Parser GetIndexStats
parseJSON :: Value -> Parser GetIndexStats
$cparseJSONList :: Value -> Parser [GetIndexStats]
parseJSONList :: Value -> Parser [GetIndexStats]
$comittedField :: Maybe GetIndexStats
omittedField :: Maybe GetIndexStats
FromJSON, [GetIndexStats] -> Value
[GetIndexStats] -> Encoding
GetIndexStats -> Bool
GetIndexStats -> Value
GetIndexStats -> Encoding
(GetIndexStats -> Value)
-> (GetIndexStats -> Encoding)
-> ([GetIndexStats] -> Value)
-> ([GetIndexStats] -> Encoding)
-> (GetIndexStats -> Bool)
-> ToJSON GetIndexStats
forall a.
(a -> Value)
-> (a -> Encoding)
-> ([a] -> Value)
-> ([a] -> Encoding)
-> (a -> Bool)
-> ToJSON a
$ctoJSON :: GetIndexStats -> Value
toJSON :: GetIndexStats -> Value
$ctoEncoding :: GetIndexStats -> Encoding
toEncoding :: GetIndexStats -> Encoding
$ctoJSONList :: [GetIndexStats] -> Value
toJSONList :: [GetIndexStats] -> Value
$ctoEncodingList :: [GetIndexStats] -> Encoding
toEncodingList :: [GetIndexStats] -> Encoding
$comitField :: GetIndexStats -> Bool
omitField :: GetIndexStats -> Bool
ToJSON)
_GetIndexStats :: GetIndexStats
_GetIndexStats :: GetIndexStats
_GetIndexStats = GetIndexStats
{ $sel:filter:GetIndexStats :: Maybe Filter
filter = Maybe Filter
forall a. Maybe a
Nothing
}
data IndexStats = IndexStats
{ IndexStats -> Map Text Contents
namespaces :: Map Text Contents
, IndexStats -> Natural
dimension :: Natural
, IndexStats -> Double
indexFullness :: Double
, IndexStats -> Natural
totalVectorCount :: Natural
, IndexStats -> Metric
metric :: Metric
, IndexStats -> VectorType
vectorType :: VectorType
} deriving stock (IndexStats -> IndexStats -> Bool
(IndexStats -> IndexStats -> Bool)
-> (IndexStats -> IndexStats -> Bool) -> Eq IndexStats
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: IndexStats -> IndexStats -> Bool
== :: IndexStats -> IndexStats -> Bool
$c/= :: IndexStats -> IndexStats -> Bool
/= :: IndexStats -> IndexStats -> Bool
Eq, (forall x. IndexStats -> Rep IndexStats x)
-> (forall x. Rep IndexStats x -> IndexStats) -> Generic IndexStats
forall x. Rep IndexStats x -> IndexStats
forall x. IndexStats -> Rep IndexStats x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cfrom :: forall x. IndexStats -> Rep IndexStats x
from :: forall x. IndexStats -> Rep IndexStats x
$cto :: forall x. Rep IndexStats x -> IndexStats
to :: forall x. Rep IndexStats x -> IndexStats
Generic, Int -> IndexStats -> ShowS
[IndexStats] -> ShowS
IndexStats -> String
(Int -> IndexStats -> ShowS)
-> (IndexStats -> String)
-> ([IndexStats] -> ShowS)
-> Show IndexStats
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> IndexStats -> ShowS
showsPrec :: Int -> IndexStats -> ShowS
$cshow :: IndexStats -> String
show :: IndexStats -> String
$cshowList :: [IndexStats] -> ShowS
showList :: [IndexStats] -> ShowS
Show)
deriving anyclass (Maybe IndexStats
Value -> Parser [IndexStats]
Value -> Parser IndexStats
(Value -> Parser IndexStats)
-> (Value -> Parser [IndexStats])
-> Maybe IndexStats
-> FromJSON IndexStats
forall a.
(Value -> Parser a)
-> (Value -> Parser [a]) -> Maybe a -> FromJSON a
$cparseJSON :: Value -> Parser IndexStats
parseJSON :: Value -> Parser IndexStats
$cparseJSONList :: Value -> Parser [IndexStats]
parseJSONList :: Value -> Parser [IndexStats]
$comittedField :: Maybe IndexStats
omittedField :: Maybe IndexStats
FromJSON, [IndexStats] -> Value
[IndexStats] -> Encoding
IndexStats -> Bool
IndexStats -> Value
IndexStats -> Encoding
(IndexStats -> Value)
-> (IndexStats -> Encoding)
-> ([IndexStats] -> Value)
-> ([IndexStats] -> Encoding)
-> (IndexStats -> Bool)
-> ToJSON IndexStats
forall a.
(a -> Value)
-> (a -> Encoding)
-> ([a] -> Value)
-> ([a] -> Encoding)
-> (a -> Bool)
-> ToJSON a
$ctoJSON :: IndexStats -> Value
toJSON :: IndexStats -> Value
$ctoEncoding :: IndexStats -> Encoding
toEncoding :: IndexStats -> Encoding
$ctoJSONList :: [IndexStats] -> Value
toJSONList :: [IndexStats] -> Value
$ctoEncodingList :: [IndexStats] -> Encoding
toEncodingList :: [IndexStats] -> Encoding
$comitField :: IndexStats -> Bool
omitField :: IndexStats -> Bool
ToJSON)
data Metric = Cosine | Euclidean | DotProduct
deriving stock (Metric -> Metric -> Bool
(Metric -> Metric -> Bool)
-> (Metric -> Metric -> Bool) -> Eq Metric
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: Metric -> Metric -> Bool
== :: Metric -> Metric -> Bool
$c/= :: Metric -> Metric -> Bool
/= :: Metric -> Metric -> Bool
Eq, (forall x. Metric -> Rep Metric x)
-> (forall x. Rep Metric x -> Metric) -> Generic Metric
forall x. Rep Metric x -> Metric
forall x. Metric -> Rep Metric x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cfrom :: forall x. Metric -> Rep Metric x
from :: forall x. Metric -> Rep Metric x
$cto :: forall x. Rep Metric x -> Metric
to :: forall x. Rep Metric x -> Metric
Generic, Int -> Metric -> ShowS
[Metric] -> ShowS
Metric -> String
(Int -> Metric -> ShowS)
-> (Metric -> String) -> ([Metric] -> ShowS) -> Show Metric
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> Metric -> ShowS
showsPrec :: Int -> Metric -> ShowS
$cshow :: Metric -> String
show :: Metric -> String
$cshowList :: [Metric] -> ShowS
showList :: [Metric] -> ShowS
Show)
instance FromJSON Metric where
parseJSON :: Value -> Parser Metric
parseJSON = Options -> Value -> Parser Metric
forall a.
(Generic a, GFromJSON Zero (Rep a)) =>
Options -> Value -> Parser a
genericParseJSON Options
aesonOptions
instance ToJSON Metric where
toJSON :: Metric -> Value
toJSON = Options -> Metric -> Value
forall a.
(Generic a, GToJSON' Value Zero (Rep a)) =>
Options -> a -> Value
genericToJSON Options
aesonOptions
data Spec = Spec
{ Spec -> Maybe Pod
pod :: Maybe Pod
, Spec -> Maybe Serverless
serverless :: Maybe Serverless
} deriving stock (Spec -> Spec -> Bool
(Spec -> Spec -> Bool) -> (Spec -> Spec -> Bool) -> Eq Spec
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: Spec -> Spec -> Bool
== :: Spec -> Spec -> Bool
$c/= :: Spec -> Spec -> Bool
/= :: Spec -> Spec -> Bool
Eq, (forall x. Spec -> Rep Spec x)
-> (forall x. Rep Spec x -> Spec) -> Generic Spec
forall x. Rep Spec x -> Spec
forall x. Spec -> Rep Spec x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cfrom :: forall x. Spec -> Rep Spec x
from :: forall x. Spec -> Rep Spec x
$cto :: forall x. Rep Spec x -> Spec
to :: forall x. Rep Spec x -> Spec
Generic, Int -> Spec -> ShowS
[Spec] -> ShowS
Spec -> String
(Int -> Spec -> ShowS)
-> (Spec -> String) -> ([Spec] -> ShowS) -> Show Spec
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> Spec -> ShowS
showsPrec :: Int -> Spec -> ShowS
$cshow :: Spec -> String
show :: Spec -> String
$cshowList :: [Spec] -> ShowS
showList :: [Spec] -> ShowS
Show)
deriving anyclass (Maybe Spec
Value -> Parser [Spec]
Value -> Parser Spec
(Value -> Parser Spec)
-> (Value -> Parser [Spec]) -> Maybe Spec -> FromJSON Spec
forall a.
(Value -> Parser a)
-> (Value -> Parser [a]) -> Maybe a -> FromJSON a
$cparseJSON :: Value -> Parser Spec
parseJSON :: Value -> Parser Spec
$cparseJSONList :: Value -> Parser [Spec]
parseJSONList :: Value -> Parser [Spec]
$comittedField :: Maybe Spec
omittedField :: Maybe Spec
FromJSON, [Spec] -> Value
[Spec] -> Encoding
Spec -> Bool
Spec -> Value
Spec -> Encoding
(Spec -> Value)
-> (Spec -> Encoding)
-> ([Spec] -> Value)
-> ([Spec] -> Encoding)
-> (Spec -> Bool)
-> ToJSON Spec
forall a.
(a -> Value)
-> (a -> Encoding)
-> ([a] -> Value)
-> ([a] -> Encoding)
-> (a -> Bool)
-> ToJSON a
$ctoJSON :: Spec -> Value
toJSON :: Spec -> Value
$ctoEncoding :: Spec -> Encoding
toEncoding :: Spec -> Encoding
$ctoJSONList :: [Spec] -> Value
toJSONList :: [Spec] -> Value
$ctoEncodingList :: [Spec] -> Encoding
toEncodingList :: [Spec] -> Encoding
$comitField :: Spec -> Bool
omitField :: Spec -> Bool
ToJSON)
data Pod = Pod
{ Pod -> Text
environment :: Text
, Pod -> PodType
pod_type :: PodType
, Pod -> Maybe Natural
replicas :: Maybe Natural
, Pod -> Maybe Natural
shards :: Maybe Natural
, Pod -> Maybe Natural
pods :: Maybe Natural
, Pod -> Maybe MetadataConfig
metadata_config :: Maybe MetadataConfig
, Pod -> Maybe Text
source_collection :: Maybe Text
} deriving stock (Pod -> Pod -> Bool
(Pod -> Pod -> Bool) -> (Pod -> Pod -> Bool) -> Eq Pod
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: Pod -> Pod -> Bool
== :: Pod -> Pod -> Bool
$c/= :: Pod -> Pod -> Bool
/= :: Pod -> Pod -> Bool
Eq, (forall x. Pod -> Rep Pod x)
-> (forall x. Rep Pod x -> Pod) -> Generic Pod
forall x. Rep Pod x -> Pod
forall x. Pod -> Rep Pod x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cfrom :: forall x. Pod -> Rep Pod x
from :: forall x. Pod -> Rep Pod x
$cto :: forall x. Rep Pod x -> Pod
to :: forall x. Rep Pod x -> Pod
Generic, Int -> Pod -> ShowS
[Pod] -> ShowS
Pod -> String
(Int -> Pod -> ShowS)
-> (Pod -> String) -> ([Pod] -> ShowS) -> Show Pod
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> Pod -> ShowS
showsPrec :: Int -> Pod -> ShowS
$cshow :: Pod -> String
show :: Pod -> String
$cshowList :: [Pod] -> ShowS
showList :: [Pod] -> ShowS
Show)
deriving anyclass (Maybe Pod
Value -> Parser [Pod]
Value -> Parser Pod
(Value -> Parser Pod)
-> (Value -> Parser [Pod]) -> Maybe Pod -> FromJSON Pod
forall a.
(Value -> Parser a)
-> (Value -> Parser [a]) -> Maybe a -> FromJSON a
$cparseJSON :: Value -> Parser Pod
parseJSON :: Value -> Parser Pod
$cparseJSONList :: Value -> Parser [Pod]
parseJSONList :: Value -> Parser [Pod]
$comittedField :: Maybe Pod
omittedField :: Maybe Pod
FromJSON, [Pod] -> Value
[Pod] -> Encoding
Pod -> Bool
Pod -> Value
Pod -> Encoding
(Pod -> Value)
-> (Pod -> Encoding)
-> ([Pod] -> Value)
-> ([Pod] -> Encoding)
-> (Pod -> Bool)
-> ToJSON Pod
forall a.
(a -> Value)
-> (a -> Encoding)
-> ([a] -> Value)
-> ([a] -> Encoding)
-> (a -> Bool)
-> ToJSON a
$ctoJSON :: Pod -> Value
toJSON :: Pod -> Value
$ctoEncoding :: Pod -> Encoding
toEncoding :: Pod -> Encoding
$ctoJSONList :: [Pod] -> Value
toJSONList :: [Pod] -> Value
$ctoEncodingList :: [Pod] -> Encoding
toEncodingList :: [Pod] -> Encoding
$comitField :: Pod -> Bool
omitField :: Pod -> Bool
ToJSON)
data PodType = PodType
{ PodType -> Prefix
prefix :: Prefix
, PodType -> Suffix
suffix :: Suffix
} deriving stock (PodType -> PodType -> Bool
(PodType -> PodType -> Bool)
-> (PodType -> PodType -> Bool) -> Eq PodType
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: PodType -> PodType -> Bool
== :: PodType -> PodType -> Bool
$c/= :: PodType -> PodType -> Bool
/= :: PodType -> PodType -> Bool
Eq, (forall x. PodType -> Rep PodType x)
-> (forall x. Rep PodType x -> PodType) -> Generic PodType
forall x. Rep PodType x -> PodType
forall x. PodType -> Rep PodType x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cfrom :: forall x. PodType -> Rep PodType x
from :: forall x. PodType -> Rep PodType x
$cto :: forall x. Rep PodType x -> PodType
to :: forall x. Rep PodType x -> PodType
Generic, Int -> PodType -> ShowS
[PodType] -> ShowS
PodType -> String
(Int -> PodType -> ShowS)
-> (PodType -> String) -> ([PodType] -> ShowS) -> Show PodType
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> PodType -> ShowS
showsPrec :: Int -> PodType -> ShowS
$cshow :: PodType -> String
show :: PodType -> String
$cshowList :: [PodType] -> ShowS
showList :: [PodType] -> ShowS
Show)
instance ToJSON PodType where
toJSON :: PodType -> Value
toJSON PodType{Suffix
Prefix
$sel:prefix:PodType :: PodType -> Prefix
$sel:suffix:PodType :: PodType -> Suffix
prefix :: Prefix
suffix :: Suffix
..} = do
Text -> Value
forall a. ToJSON a => a -> Value
toJSON ([Text] -> Text
Text.concat [ Text
Item [Text]
prefixText, Text
Item [Text]
".", Text
Item [Text]
suffixText ])
where
prefixText :: Text
prefixText = case Prefix -> Value
forall a. ToJSON a => a -> Value
toJSON Prefix
prefix of
String Text
text -> Text
text
Value
_ -> Text
""
suffixText :: Text
suffixText = case Suffix -> Value
forall a. ToJSON a => a -> Value
toJSON Suffix
suffix of
String Text
text -> Text
text
Value
_ -> Text
""
instance FromJSON PodType where
parseJSON :: Value -> Parser PodType
parseJSON Value
value = do
Text
text <- Value -> Parser Text
forall a. FromJSON a => Value -> Parser a
parseJSON Value
value
case HasCallStack => Text -> Text -> [Text]
Text -> Text -> [Text]
Text.splitOn Text
"." Text
text of
[ Item [Text]
prefixText, Item [Text]
suffixText ] -> do
Prefix
prefix <- Value -> Parser Prefix
forall a. FromJSON a => Value -> Parser a
parseJSON (Text -> Value
String Text
Item [Text]
prefixText)
Suffix
suffix <- Value -> Parser Suffix
forall a. FromJSON a => Value -> Parser a
parseJSON (Text -> Value
String Text
Item [Text]
suffixText)
PodType -> Parser PodType
forall a. a -> Parser a
forall (m :: * -> *) a. Monad m => a -> m a
return PodType{Suffix
Prefix
$sel:prefix:PodType :: Prefix
$sel:suffix:PodType :: Suffix
prefix :: Prefix
suffix :: Suffix
..}
[Text]
_ -> do
String -> Parser PodType
forall a. String -> Parser a
forall (m :: * -> *) a. MonadFail m => String -> m a
fail String
"Pod type must be of the form PREFIX.SUFFIX"
data Prefix = S1 | P1 | P2
deriving stock (Prefix -> Prefix -> Bool
(Prefix -> Prefix -> Bool)
-> (Prefix -> Prefix -> Bool) -> Eq Prefix
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: Prefix -> Prefix -> Bool
== :: Prefix -> Prefix -> Bool
$c/= :: Prefix -> Prefix -> Bool
/= :: Prefix -> Prefix -> Bool
Eq, (forall x. Prefix -> Rep Prefix x)
-> (forall x. Rep Prefix x -> Prefix) -> Generic Prefix
forall x. Rep Prefix x -> Prefix
forall x. Prefix -> Rep Prefix x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cfrom :: forall x. Prefix -> Rep Prefix x
from :: forall x. Prefix -> Rep Prefix x
$cto :: forall x. Rep Prefix x -> Prefix
to :: forall x. Rep Prefix x -> Prefix
Generic, Int -> Prefix -> ShowS
[Prefix] -> ShowS
Prefix -> String
(Int -> Prefix -> ShowS)
-> (Prefix -> String) -> ([Prefix] -> ShowS) -> Show Prefix
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> Prefix -> ShowS
showsPrec :: Int -> Prefix -> ShowS
$cshow :: Prefix -> String
show :: Prefix -> String
$cshowList :: [Prefix] -> ShowS
showList :: [Prefix] -> ShowS
Show)
instance FromJSON Prefix where
parseJSON :: Value -> Parser Prefix
parseJSON = Options -> Value -> Parser Prefix
forall a.
(Generic a, GFromJSON Zero (Rep a)) =>
Options -> Value -> Parser a
genericParseJSON Options
aesonOptions
instance ToJSON Prefix where
toJSON :: Prefix -> Value
toJSON = Options -> Prefix -> Value
forall a.
(Generic a, GToJSON' Value Zero (Rep a)) =>
Options -> a -> Value
genericToJSON Options
aesonOptions
data Suffix = X1 | X2 | X4 | X8
deriving stock (Suffix -> Suffix -> Bool
(Suffix -> Suffix -> Bool)
-> (Suffix -> Suffix -> Bool) -> Eq Suffix
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: Suffix -> Suffix -> Bool
== :: Suffix -> Suffix -> Bool
$c/= :: Suffix -> Suffix -> Bool
/= :: Suffix -> Suffix -> Bool
Eq, (forall x. Suffix -> Rep Suffix x)
-> (forall x. Rep Suffix x -> Suffix) -> Generic Suffix
forall x. Rep Suffix x -> Suffix
forall x. Suffix -> Rep Suffix x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cfrom :: forall x. Suffix -> Rep Suffix x
from :: forall x. Suffix -> Rep Suffix x
$cto :: forall x. Rep Suffix x -> Suffix
to :: forall x. Rep Suffix x -> Suffix
Generic, Int -> Suffix -> ShowS
[Suffix] -> ShowS
Suffix -> String
(Int -> Suffix -> ShowS)
-> (Suffix -> String) -> ([Suffix] -> ShowS) -> Show Suffix
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> Suffix -> ShowS
showsPrec :: Int -> Suffix -> ShowS
$cshow :: Suffix -> String
show :: Suffix -> String
$cshowList :: [Suffix] -> ShowS
showList :: [Suffix] -> ShowS
Show)
instance FromJSON Suffix where
parseJSON :: Value -> Parser Suffix
parseJSON = Options -> Value -> Parser Suffix
forall a.
(Generic a, GFromJSON Zero (Rep a)) =>
Options -> Value -> Parser a
genericParseJSON Options
aesonOptions
instance ToJSON Suffix where
toJSON :: Suffix -> Value
toJSON = Options -> Suffix -> Value
forall a.
(Generic a, GToJSON' Value Zero (Rep a)) =>
Options -> a -> Value
genericToJSON Options
aesonOptions
data MetadataConfig = MetadataConfig
{ MetadataConfig -> Maybe (Vector Text)
indexed :: Maybe (Vector Text)
} deriving stock (MetadataConfig -> MetadataConfig -> Bool
(MetadataConfig -> MetadataConfig -> Bool)
-> (MetadataConfig -> MetadataConfig -> Bool) -> Eq MetadataConfig
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: MetadataConfig -> MetadataConfig -> Bool
== :: MetadataConfig -> MetadataConfig -> Bool
$c/= :: MetadataConfig -> MetadataConfig -> Bool
/= :: MetadataConfig -> MetadataConfig -> Bool
Eq, (forall x. MetadataConfig -> Rep MetadataConfig x)
-> (forall x. Rep MetadataConfig x -> MetadataConfig)
-> Generic MetadataConfig
forall x. Rep MetadataConfig x -> MetadataConfig
forall x. MetadataConfig -> Rep MetadataConfig x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cfrom :: forall x. MetadataConfig -> Rep MetadataConfig x
from :: forall x. MetadataConfig -> Rep MetadataConfig x
$cto :: forall x. Rep MetadataConfig x -> MetadataConfig
to :: forall x. Rep MetadataConfig x -> MetadataConfig
Generic, Int -> MetadataConfig -> ShowS
[MetadataConfig] -> ShowS
MetadataConfig -> String
(Int -> MetadataConfig -> ShowS)
-> (MetadataConfig -> String)
-> ([MetadataConfig] -> ShowS)
-> Show MetadataConfig
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> MetadataConfig -> ShowS
showsPrec :: Int -> MetadataConfig -> ShowS
$cshow :: MetadataConfig -> String
show :: MetadataConfig -> String
$cshowList :: [MetadataConfig] -> ShowS
showList :: [MetadataConfig] -> ShowS
Show)
deriving anyclass (Maybe MetadataConfig
Value -> Parser [MetadataConfig]
Value -> Parser MetadataConfig
(Value -> Parser MetadataConfig)
-> (Value -> Parser [MetadataConfig])
-> Maybe MetadataConfig
-> FromJSON MetadataConfig
forall a.
(Value -> Parser a)
-> (Value -> Parser [a]) -> Maybe a -> FromJSON a
$cparseJSON :: Value -> Parser MetadataConfig
parseJSON :: Value -> Parser MetadataConfig
$cparseJSONList :: Value -> Parser [MetadataConfig]
parseJSONList :: Value -> Parser [MetadataConfig]
$comittedField :: Maybe MetadataConfig
omittedField :: Maybe MetadataConfig
FromJSON, [MetadataConfig] -> Value
[MetadataConfig] -> Encoding
MetadataConfig -> Bool
MetadataConfig -> Value
MetadataConfig -> Encoding
(MetadataConfig -> Value)
-> (MetadataConfig -> Encoding)
-> ([MetadataConfig] -> Value)
-> ([MetadataConfig] -> Encoding)
-> (MetadataConfig -> Bool)
-> ToJSON MetadataConfig
forall a.
(a -> Value)
-> (a -> Encoding)
-> ([a] -> Value)
-> ([a] -> Encoding)
-> (a -> Bool)
-> ToJSON a
$ctoJSON :: MetadataConfig -> Value
toJSON :: MetadataConfig -> Value
$ctoEncoding :: MetadataConfig -> Encoding
toEncoding :: MetadataConfig -> Encoding
$ctoJSONList :: [MetadataConfig] -> Value
toJSONList :: [MetadataConfig] -> Value
$ctoEncodingList :: [MetadataConfig] -> Encoding
toEncodingList :: [MetadataConfig] -> Encoding
$comitField :: MetadataConfig -> Bool
omitField :: MetadataConfig -> Bool
ToJSON)
data Serverless = Serverless
{ Serverless -> Cloud
cloud :: Cloud
, Serverless -> Text
region :: Text
} deriving stock (Serverless -> Serverless -> Bool
(Serverless -> Serverless -> Bool)
-> (Serverless -> Serverless -> Bool) -> Eq Serverless
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: Serverless -> Serverless -> Bool
== :: Serverless -> Serverless -> Bool
$c/= :: Serverless -> Serverless -> Bool
/= :: Serverless -> Serverless -> Bool
Eq, (forall x. Serverless -> Rep Serverless x)
-> (forall x. Rep Serverless x -> Serverless) -> Generic Serverless
forall x. Rep Serverless x -> Serverless
forall x. Serverless -> Rep Serverless x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cfrom :: forall x. Serverless -> Rep Serverless x
from :: forall x. Serverless -> Rep Serverless x
$cto :: forall x. Rep Serverless x -> Serverless
to :: forall x. Rep Serverless x -> Serverless
Generic, Int -> Serverless -> ShowS
[Serverless] -> ShowS
Serverless -> String
(Int -> Serverless -> ShowS)
-> (Serverless -> String)
-> ([Serverless] -> ShowS)
-> Show Serverless
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> Serverless -> ShowS
showsPrec :: Int -> Serverless -> ShowS
$cshow :: Serverless -> String
show :: Serverless -> String
$cshowList :: [Serverless] -> ShowS
showList :: [Serverless] -> ShowS
Show)
deriving anyclass (Maybe Serverless
Value -> Parser [Serverless]
Value -> Parser Serverless
(Value -> Parser Serverless)
-> (Value -> Parser [Serverless])
-> Maybe Serverless
-> FromJSON Serverless
forall a.
(Value -> Parser a)
-> (Value -> Parser [a]) -> Maybe a -> FromJSON a
$cparseJSON :: Value -> Parser Serverless
parseJSON :: Value -> Parser Serverless
$cparseJSONList :: Value -> Parser [Serverless]
parseJSONList :: Value -> Parser [Serverless]
$comittedField :: Maybe Serverless
omittedField :: Maybe Serverless
FromJSON, [Serverless] -> Value
[Serverless] -> Encoding
Serverless -> Bool
Serverless -> Value
Serverless -> Encoding
(Serverless -> Value)
-> (Serverless -> Encoding)
-> ([Serverless] -> Value)
-> ([Serverless] -> Encoding)
-> (Serverless -> Bool)
-> ToJSON Serverless
forall a.
(a -> Value)
-> (a -> Encoding)
-> ([a] -> Value)
-> ([a] -> Encoding)
-> (a -> Bool)
-> ToJSON a
$ctoJSON :: Serverless -> Value
toJSON :: Serverless -> Value
$ctoEncoding :: Serverless -> Encoding
toEncoding :: Serverless -> Encoding
$ctoJSONList :: [Serverless] -> Value
toJSONList :: [Serverless] -> Value
$ctoEncodingList :: [Serverless] -> Encoding
toEncodingList :: [Serverless] -> Encoding
$comitField :: Serverless -> Bool
omitField :: Serverless -> Bool
ToJSON)
data Cloud = GCP | AWS | Azure
deriving stock (Cloud -> Cloud -> Bool
(Cloud -> Cloud -> Bool) -> (Cloud -> Cloud -> Bool) -> Eq Cloud
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: Cloud -> Cloud -> Bool
== :: Cloud -> Cloud -> Bool
$c/= :: Cloud -> Cloud -> Bool
/= :: Cloud -> Cloud -> Bool
Eq, (forall x. Cloud -> Rep Cloud x)
-> (forall x. Rep Cloud x -> Cloud) -> Generic Cloud
forall x. Rep Cloud x -> Cloud
forall x. Cloud -> Rep Cloud x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cfrom :: forall x. Cloud -> Rep Cloud x
from :: forall x. Cloud -> Rep Cloud x
$cto :: forall x. Rep Cloud x -> Cloud
to :: forall x. Rep Cloud x -> Cloud
Generic, Int -> Cloud -> ShowS
[Cloud] -> ShowS
Cloud -> String
(Int -> Cloud -> ShowS)
-> (Cloud -> String) -> ([Cloud] -> ShowS) -> Show Cloud
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> Cloud -> ShowS
showsPrec :: Int -> Cloud -> ShowS
$cshow :: Cloud -> String
show :: Cloud -> String
$cshowList :: [Cloud] -> ShowS
showList :: [Cloud] -> ShowS
Show)
instance FromJSON Cloud where
parseJSON :: Value -> Parser Cloud
parseJSON = Options -> Value -> Parser Cloud
forall a.
(Generic a, GFromJSON Zero (Rep a)) =>
Options -> Value -> Parser a
genericParseJSON Options
aesonOptions
instance ToJSON Cloud where
toJSON :: Cloud -> Value
toJSON = Options -> Cloud -> Value
forall a.
(Generic a, GToJSON' Value Zero (Rep a)) =>
Options -> a -> Value
genericToJSON Options
aesonOptions
data Status = Status
{ Status -> Bool
ready :: Bool
, Status -> State
state :: State
} 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)
deriving anyclass (Maybe Status
Value -> Parser [Status]
Value -> Parser Status
(Value -> Parser Status)
-> (Value -> Parser [Status]) -> Maybe Status -> FromJSON Status
forall a.
(Value -> Parser a)
-> (Value -> Parser [a]) -> Maybe a -> FromJSON a
$cparseJSON :: Value -> Parser Status
parseJSON :: Value -> Parser Status
$cparseJSONList :: Value -> Parser [Status]
parseJSONList :: Value -> Parser [Status]
$comittedField :: Maybe Status
omittedField :: Maybe Status
FromJSON, [Status] -> Value
[Status] -> Encoding
Status -> Bool
Status -> Value
Status -> Encoding
(Status -> Value)
-> (Status -> Encoding)
-> ([Status] -> Value)
-> ([Status] -> Encoding)
-> (Status -> Bool)
-> ToJSON Status
forall a.
(a -> Value)
-> (a -> Encoding)
-> ([a] -> Value)
-> ([a] -> Encoding)
-> (a -> Bool)
-> ToJSON a
$ctoJSON :: Status -> Value
toJSON :: Status -> Value
$ctoEncoding :: Status -> Encoding
toEncoding :: Status -> Encoding
$ctoJSONList :: [Status] -> Value
toJSONList :: [Status] -> Value
$ctoEncodingList :: [Status] -> Encoding
toEncodingList :: [Status] -> Encoding
$comitField :: Status -> Bool
omitField :: Status -> Bool
ToJSON)
data State
= Initializing
| InitializationFailed
| ScalingUp
| ScalingDown
| ScalingUpPodSize
| ScalingDownPodSize
| Terminating
| Ready
deriving stock (State -> State -> Bool
(State -> State -> Bool) -> (State -> State -> Bool) -> Eq State
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: State -> State -> Bool
== :: State -> State -> Bool
$c/= :: State -> State -> Bool
/= :: State -> State -> Bool
Eq, (forall x. State -> Rep State x)
-> (forall x. Rep State x -> State) -> Generic State
forall x. Rep State x -> State
forall x. State -> Rep State x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cfrom :: forall x. State -> Rep State x
from :: forall x. State -> Rep State x
$cto :: forall x. Rep State x -> State
to :: forall x. Rep State x -> State
Generic, Int -> State -> ShowS
[State] -> ShowS
State -> String
(Int -> State -> ShowS)
-> (State -> String) -> ([State] -> ShowS) -> Show State
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> State -> ShowS
showsPrec :: Int -> State -> ShowS
$cshow :: State -> String
show :: State -> String
$cshowList :: [State] -> ShowS
showList :: [State] -> ShowS
Show)
instance FromJSON State where
parseJSON :: Value -> Parser State
parseJSON = Options -> Value -> Parser State
forall a.
(Generic a, GFromJSON Zero (Rep a)) =>
Options -> Value -> Parser a
genericParseJSON Options
aesonOptions{ constructorTagModifier = id }
instance ToJSON State where
toJSON :: State -> Value
toJSON = Options -> State -> Value
forall a.
(Generic a, GToJSON' Value Zero (Rep a)) =>
Options -> a -> Value
genericToJSON Options
aesonOptions{ constructorTagModifier = id }
data DeletionProtection = Disabled | Enabled
deriving stock (DeletionProtection -> DeletionProtection -> Bool
(DeletionProtection -> DeletionProtection -> Bool)
-> (DeletionProtection -> DeletionProtection -> Bool)
-> Eq DeletionProtection
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: DeletionProtection -> DeletionProtection -> Bool
== :: DeletionProtection -> DeletionProtection -> Bool
$c/= :: DeletionProtection -> DeletionProtection -> Bool
/= :: DeletionProtection -> DeletionProtection -> Bool
Eq, (forall x. DeletionProtection -> Rep DeletionProtection x)
-> (forall x. Rep DeletionProtection x -> DeletionProtection)
-> Generic DeletionProtection
forall x. Rep DeletionProtection x -> DeletionProtection
forall x. DeletionProtection -> Rep DeletionProtection x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cfrom :: forall x. DeletionProtection -> Rep DeletionProtection x
from :: forall x. DeletionProtection -> Rep DeletionProtection x
$cto :: forall x. Rep DeletionProtection x -> DeletionProtection
to :: forall x. Rep DeletionProtection x -> DeletionProtection
Generic, Int -> DeletionProtection -> ShowS
[DeletionProtection] -> ShowS
DeletionProtection -> String
(Int -> DeletionProtection -> ShowS)
-> (DeletionProtection -> String)
-> ([DeletionProtection] -> ShowS)
-> Show DeletionProtection
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> DeletionProtection -> ShowS
showsPrec :: Int -> DeletionProtection -> ShowS
$cshow :: DeletionProtection -> String
show :: DeletionProtection -> String
$cshowList :: [DeletionProtection] -> ShowS
showList :: [DeletionProtection] -> ShowS
Show)
instance FromJSON DeletionProtection where
parseJSON :: Value -> Parser DeletionProtection
parseJSON = Options -> Value -> Parser DeletionProtection
forall a.
(Generic a, GFromJSON Zero (Rep a)) =>
Options -> Value -> Parser a
genericParseJSON Options
aesonOptions
instance ToJSON DeletionProtection where
toJSON :: DeletionProtection -> Value
toJSON = Options -> DeletionProtection -> Value
forall a.
(Generic a, GToJSON' Value Zero (Rep a)) =>
Options -> a -> Value
genericToJSON Options
aesonOptions
data EmbedRequest = EmbedRequest
{ EmbedRequest -> Text
model :: Text
, EmbedRequest -> Maybe Metric
metric :: Maybe Metric
, EmbedRequest -> Maybe (Map Text Value)
read_parameters :: Maybe (Map Text Value)
, EmbedRequest -> Maybe (Map Text Value)
write_parameters :: Maybe (Map Text Value)
} deriving stock (EmbedRequest -> EmbedRequest -> Bool
(EmbedRequest -> EmbedRequest -> Bool)
-> (EmbedRequest -> EmbedRequest -> Bool) -> Eq EmbedRequest
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: EmbedRequest -> EmbedRequest -> Bool
== :: EmbedRequest -> EmbedRequest -> Bool
$c/= :: EmbedRequest -> EmbedRequest -> Bool
/= :: EmbedRequest -> EmbedRequest -> Bool
Eq, (forall x. EmbedRequest -> Rep EmbedRequest x)
-> (forall x. Rep EmbedRequest x -> EmbedRequest)
-> Generic EmbedRequest
forall x. Rep EmbedRequest x -> EmbedRequest
forall x. EmbedRequest -> Rep EmbedRequest x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cfrom :: forall x. EmbedRequest -> Rep EmbedRequest x
from :: forall x. EmbedRequest -> Rep EmbedRequest x
$cto :: forall x. Rep EmbedRequest x -> EmbedRequest
to :: forall x. Rep EmbedRequest x -> EmbedRequest
Generic, Int -> EmbedRequest -> ShowS
[EmbedRequest] -> ShowS
EmbedRequest -> String
(Int -> EmbedRequest -> ShowS)
-> (EmbedRequest -> String)
-> ([EmbedRequest] -> ShowS)
-> Show EmbedRequest
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> EmbedRequest -> ShowS
showsPrec :: Int -> EmbedRequest -> ShowS
$cshow :: EmbedRequest -> String
show :: EmbedRequest -> String
$cshowList :: [EmbedRequest] -> ShowS
showList :: [EmbedRequest] -> ShowS
Show)
deriving anyclass (Maybe EmbedRequest
Value -> Parser [EmbedRequest]
Value -> Parser EmbedRequest
(Value -> Parser EmbedRequest)
-> (Value -> Parser [EmbedRequest])
-> Maybe EmbedRequest
-> FromJSON EmbedRequest
forall a.
(Value -> Parser a)
-> (Value -> Parser [a]) -> Maybe a -> FromJSON a
$cparseJSON :: Value -> Parser EmbedRequest
parseJSON :: Value -> Parser EmbedRequest
$cparseJSONList :: Value -> Parser [EmbedRequest]
parseJSONList :: Value -> Parser [EmbedRequest]
$comittedField :: Maybe EmbedRequest
omittedField :: Maybe EmbedRequest
FromJSON)
data EmbedRequest_ = EmbedRequest_
{ EmbedRequest_ -> Text
model :: Text
, EmbedRequest_ -> Map Text Text
field_map :: Map Text Text
, EmbedRequest_ -> Maybe Metric
metric :: Maybe Metric
, EmbedRequest_ -> Maybe (Map Text Value)
read_parameters :: Maybe (Map Text Value)
, EmbedRequest_ -> Maybe (Map Text Value)
write_parameters :: Maybe (Map Text Value)
} deriving stock (EmbedRequest_ -> EmbedRequest_ -> Bool
(EmbedRequest_ -> EmbedRequest_ -> Bool)
-> (EmbedRequest_ -> EmbedRequest_ -> Bool) -> Eq EmbedRequest_
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: EmbedRequest_ -> EmbedRequest_ -> Bool
== :: EmbedRequest_ -> EmbedRequest_ -> Bool
$c/= :: EmbedRequest_ -> EmbedRequest_ -> Bool
/= :: EmbedRequest_ -> EmbedRequest_ -> Bool
Eq, (forall x. EmbedRequest_ -> Rep EmbedRequest_ x)
-> (forall x. Rep EmbedRequest_ x -> EmbedRequest_)
-> Generic EmbedRequest_
forall x. Rep EmbedRequest_ x -> EmbedRequest_
forall x. EmbedRequest_ -> Rep EmbedRequest_ x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cfrom :: forall x. EmbedRequest_ -> Rep EmbedRequest_ x
from :: forall x. EmbedRequest_ -> Rep EmbedRequest_ x
$cto :: forall x. Rep EmbedRequest_ x -> EmbedRequest_
to :: forall x. Rep EmbedRequest_ x -> EmbedRequest_
Generic, Int -> EmbedRequest_ -> ShowS
[EmbedRequest_] -> ShowS
EmbedRequest_ -> String
(Int -> EmbedRequest_ -> ShowS)
-> (EmbedRequest_ -> String)
-> ([EmbedRequest_] -> ShowS)
-> Show EmbedRequest_
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> EmbedRequest_ -> ShowS
showsPrec :: Int -> EmbedRequest_ -> ShowS
$cshow :: EmbedRequest_ -> String
show :: EmbedRequest_ -> String
$cshowList :: [EmbedRequest_] -> ShowS
showList :: [EmbedRequest_] -> ShowS
Show)
deriving anyclass (Maybe EmbedRequest_
Value -> Parser [EmbedRequest_]
Value -> Parser EmbedRequest_
(Value -> Parser EmbedRequest_)
-> (Value -> Parser [EmbedRequest_])
-> Maybe EmbedRequest_
-> FromJSON EmbedRequest_
forall a.
(Value -> Parser a)
-> (Value -> Parser [a]) -> Maybe a -> FromJSON a
$cparseJSON :: Value -> Parser EmbedRequest_
parseJSON :: Value -> Parser EmbedRequest_
$cparseJSONList :: Value -> Parser [EmbedRequest_]
parseJSONList :: Value -> Parser [EmbedRequest_]
$comittedField :: Maybe EmbedRequest_
omittedField :: Maybe EmbedRequest_
FromJSON, [EmbedRequest_] -> Value
[EmbedRequest_] -> Encoding
EmbedRequest_ -> Bool
EmbedRequest_ -> Value
EmbedRequest_ -> Encoding
(EmbedRequest_ -> Value)
-> (EmbedRequest_ -> Encoding)
-> ([EmbedRequest_] -> Value)
-> ([EmbedRequest_] -> Encoding)
-> (EmbedRequest_ -> Bool)
-> ToJSON EmbedRequest_
forall a.
(a -> Value)
-> (a -> Encoding)
-> ([a] -> Value)
-> ([a] -> Encoding)
-> (a -> Bool)
-> ToJSON a
$ctoJSON :: EmbedRequest_ -> Value
toJSON :: EmbedRequest_ -> Value
$ctoEncoding :: EmbedRequest_ -> Encoding
toEncoding :: EmbedRequest_ -> Encoding
$ctoJSONList :: [EmbedRequest_] -> Value
toJSONList :: [EmbedRequest_] -> Value
$ctoEncodingList :: [EmbedRequest_] -> Encoding
toEncodingList :: [EmbedRequest_] -> Encoding
$comitField :: EmbedRequest_ -> Bool
omitField :: EmbedRequest_ -> Bool
ToJSON)
instance ToJSON EmbedRequest where
toJSON :: EmbedRequest -> Value
toJSON EmbedRequest{Maybe (Map Text Value)
Maybe Metric
Text
$sel:model:EmbedRequest :: EmbedRequest -> Text
$sel:metric:EmbedRequest :: EmbedRequest -> Maybe Metric
$sel:read_parameters:EmbedRequest :: EmbedRequest -> Maybe (Map Text Value)
$sel:write_parameters:EmbedRequest :: EmbedRequest -> Maybe (Map Text Value)
model :: Text
metric :: Maybe Metric
read_parameters :: Maybe (Map Text Value)
write_parameters :: Maybe (Map Text Value)
..} = EmbedRequest_ -> Value
forall a. ToJSON a => a -> Value
toJSON EmbedRequest_{Maybe (Map Text Value)
Maybe Metric
Map Text Text
Text
$sel:model:EmbedRequest_ :: Text
$sel:field_map:EmbedRequest_ :: Map Text Text
$sel:metric:EmbedRequest_ :: Maybe Metric
$sel:read_parameters:EmbedRequest_ :: Maybe (Map Text Value)
$sel:write_parameters:EmbedRequest_ :: Maybe (Map Text Value)
model :: Text
metric :: Maybe Metric
read_parameters :: Maybe (Map Text Value)
write_parameters :: Maybe (Map Text Value)
field_map :: Map Text Text
..}
where
field_map :: Map Text Text
field_map = [ (Text
"text", Text
"text") ]
data EmbedResponse = EmbedResponse
{ EmbedResponse -> Text
model :: Text
, EmbedResponse -> Maybe Metric
metric :: Maybe Metric
, EmbedResponse -> Maybe Natural
dimension :: Maybe Natural
, EmbedResponse -> Maybe VectorType
vector_type :: Maybe VectorType
, EmbedResponse -> Maybe (Map Text Text)
field_map :: Maybe (Map Text Text)
, EmbedResponse -> Maybe (Map Text Value)
read_parameters :: Maybe (Map Text Value)
, EmbedResponse -> Maybe (Map Text Value)
write_parameters :: Maybe (Map Text Value)
} deriving stock (EmbedResponse -> EmbedResponse -> Bool
(EmbedResponse -> EmbedResponse -> Bool)
-> (EmbedResponse -> EmbedResponse -> Bool) -> Eq EmbedResponse
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: EmbedResponse -> EmbedResponse -> Bool
== :: EmbedResponse -> EmbedResponse -> Bool
$c/= :: EmbedResponse -> EmbedResponse -> Bool
/= :: EmbedResponse -> EmbedResponse -> Bool
Eq, (forall x. EmbedResponse -> Rep EmbedResponse x)
-> (forall x. Rep EmbedResponse x -> EmbedResponse)
-> Generic EmbedResponse
forall x. Rep EmbedResponse x -> EmbedResponse
forall x. EmbedResponse -> Rep EmbedResponse x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cfrom :: forall x. EmbedResponse -> Rep EmbedResponse x
from :: forall x. EmbedResponse -> Rep EmbedResponse x
$cto :: forall x. Rep EmbedResponse x -> EmbedResponse
to :: forall x. Rep EmbedResponse x -> EmbedResponse
Generic, Int -> EmbedResponse -> ShowS
[EmbedResponse] -> ShowS
EmbedResponse -> String
(Int -> EmbedResponse -> ShowS)
-> (EmbedResponse -> String)
-> ([EmbedResponse] -> ShowS)
-> Show EmbedResponse
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> EmbedResponse -> ShowS
showsPrec :: Int -> EmbedResponse -> ShowS
$cshow :: EmbedResponse -> String
show :: EmbedResponse -> String
$cshowList :: [EmbedResponse] -> ShowS
showList :: [EmbedResponse] -> ShowS
Show)
deriving anyclass (Maybe EmbedResponse
Value -> Parser [EmbedResponse]
Value -> Parser EmbedResponse
(Value -> Parser EmbedResponse)
-> (Value -> Parser [EmbedResponse])
-> Maybe EmbedResponse
-> FromJSON EmbedResponse
forall a.
(Value -> Parser a)
-> (Value -> Parser [a]) -> Maybe a -> FromJSON a
$cparseJSON :: Value -> Parser EmbedResponse
parseJSON :: Value -> Parser EmbedResponse
$cparseJSONList :: Value -> Parser [EmbedResponse]
parseJSONList :: Value -> Parser [EmbedResponse]
$comittedField :: Maybe EmbedResponse
omittedField :: Maybe EmbedResponse
FromJSON, [EmbedResponse] -> Value
[EmbedResponse] -> Encoding
EmbedResponse -> Bool
EmbedResponse -> Value
EmbedResponse -> Encoding
(EmbedResponse -> Value)
-> (EmbedResponse -> Encoding)
-> ([EmbedResponse] -> Value)
-> ([EmbedResponse] -> Encoding)
-> (EmbedResponse -> Bool)
-> ToJSON EmbedResponse
forall a.
(a -> Value)
-> (a -> Encoding)
-> ([a] -> Value)
-> ([a] -> Encoding)
-> (a -> Bool)
-> ToJSON a
$ctoJSON :: EmbedResponse -> Value
toJSON :: EmbedResponse -> Value
$ctoEncoding :: EmbedResponse -> Encoding
toEncoding :: EmbedResponse -> Encoding
$ctoJSONList :: [EmbedResponse] -> Value
toJSONList :: [EmbedResponse] -> Value
$ctoEncodingList :: [EmbedResponse] -> Encoding
toEncodingList :: [EmbedResponse] -> Encoding
$comitField :: EmbedResponse -> Bool
omitField :: EmbedResponse -> Bool
ToJSON)
data Contents = Contents
{ Contents -> Natural
vectorCount :: Natural
} deriving stock (Contents -> Contents -> Bool
(Contents -> Contents -> Bool)
-> (Contents -> Contents -> Bool) -> Eq Contents
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: Contents -> Contents -> Bool
== :: Contents -> Contents -> Bool
$c/= :: Contents -> Contents -> Bool
/= :: Contents -> Contents -> Bool
Eq, (forall x. Contents -> Rep Contents x)
-> (forall x. Rep Contents x -> Contents) -> Generic Contents
forall x. Rep Contents x -> Contents
forall x. Contents -> Rep Contents x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cfrom :: forall x. Contents -> Rep Contents x
from :: forall x. Contents -> Rep Contents x
$cto :: forall x. Rep Contents x -> Contents
to :: forall x. Rep Contents x -> Contents
Generic, Int -> Contents -> ShowS
[Contents] -> ShowS
Contents -> String
(Int -> Contents -> ShowS)
-> (Contents -> String) -> ([Contents] -> ShowS) -> Show Contents
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> Contents -> ShowS
showsPrec :: Int -> Contents -> ShowS
$cshow :: Contents -> String
show :: Contents -> String
$cshowList :: [Contents] -> ShowS
showList :: [Contents] -> ShowS
Show)
deriving anyclass (Maybe Contents
Value -> Parser [Contents]
Value -> Parser Contents
(Value -> Parser Contents)
-> (Value -> Parser [Contents])
-> Maybe Contents
-> FromJSON Contents
forall a.
(Value -> Parser a)
-> (Value -> Parser [a]) -> Maybe a -> FromJSON a
$cparseJSON :: Value -> Parser Contents
parseJSON :: Value -> Parser Contents
$cparseJSONList :: Value -> Parser [Contents]
parseJSONList :: Value -> Parser [Contents]
$comittedField :: Maybe Contents
omittedField :: Maybe Contents
FromJSON, [Contents] -> Value
[Contents] -> Encoding
Contents -> Bool
Contents -> Value
Contents -> Encoding
(Contents -> Value)
-> (Contents -> Encoding)
-> ([Contents] -> Value)
-> ([Contents] -> Encoding)
-> (Contents -> Bool)
-> ToJSON Contents
forall a.
(a -> Value)
-> (a -> Encoding)
-> ([a] -> Value)
-> ([a] -> Encoding)
-> (a -> Bool)
-> ToJSON a
$ctoJSON :: Contents -> Value
toJSON :: Contents -> Value
$ctoEncoding :: Contents -> Encoding
toEncoding :: Contents -> Encoding
$ctoJSONList :: [Contents] -> Value
toJSONList :: [Contents] -> Value
$ctoEncodingList :: [Contents] -> Encoding
toEncodingList :: [Contents] -> Encoding
$comitField :: Contents -> Bool
omitField :: Contents -> Bool
ToJSON)
type ControlAPI =
"indexes"
:> ( Get '[JSON] IndexModels
:<|> ( ReqBody '[JSON] CreateIndex
:> Post '[JSON] IndexModel
)
:<|> ( "create-for-model"
:> ReqBody '[JSON] CreateIndexWithEmbedding
:> PostCreated '[JSON] IndexModel
)
:<|> ( Capture "index_name" Index
:> Get '[JSON] IndexModel
)
:<|> ( Capture "index_name" Index
:> DeleteAccepted '[JSON] NoContent
)
:<|> ( Capture "index_name" Index
:> ReqBody '[JSON] ConfigureIndex
:> Patch '[JSON] IndexModel
)
)
type DataAPI =
"describe_index_stats"
:> ReqBody '[JSON] GetIndexStats
:> Post '[JSON] IndexStats