module OpenAI.V1.ChunkingStrategy
(
ChunkingStrategy(..)
, Static(..)
) where
import OpenAI.Prelude
data Static = Static
{ Static -> Natural
max_chunk_size_tokens :: Natural
, Static -> Natural
chunk_overlap_tokens :: Natural
} deriving stock ((forall x. Static -> Rep Static x)
-> (forall x. Rep Static x -> Static) -> Generic Static
forall x. Rep Static x -> Static
forall x. Static -> Rep Static x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cfrom :: forall x. Static -> Rep Static x
from :: forall x. Static -> Rep Static x
$cto :: forall x. Rep Static x -> Static
to :: forall x. Rep Static x -> Static
Generic, Int -> Static -> ShowS
[Static] -> ShowS
Static -> String
(Int -> Static -> ShowS)
-> (Static -> String) -> ([Static] -> ShowS) -> Show Static
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> Static -> ShowS
showsPrec :: Int -> Static -> ShowS
$cshow :: Static -> String
show :: Static -> String
$cshowList :: [Static] -> ShowS
showList :: [Static] -> ShowS
Show)
deriving anyclass (Maybe Static
Value -> Parser [Static]
Value -> Parser Static
(Value -> Parser Static)
-> (Value -> Parser [Static]) -> Maybe Static -> FromJSON Static
forall a.
(Value -> Parser a)
-> (Value -> Parser [a]) -> Maybe a -> FromJSON a
$cparseJSON :: Value -> Parser Static
parseJSON :: Value -> Parser Static
$cparseJSONList :: Value -> Parser [Static]
parseJSONList :: Value -> Parser [Static]
$comittedField :: Maybe Static
omittedField :: Maybe Static
FromJSON, [Static] -> Value
[Static] -> Encoding
Static -> Bool
Static -> Value
Static -> Encoding
(Static -> Value)
-> (Static -> Encoding)
-> ([Static] -> Value)
-> ([Static] -> Encoding)
-> (Static -> Bool)
-> ToJSON Static
forall a.
(a -> Value)
-> (a -> Encoding)
-> ([a] -> Value)
-> ([a] -> Encoding)
-> (a -> Bool)
-> ToJSON a
$ctoJSON :: Static -> Value
toJSON :: Static -> Value
$ctoEncoding :: Static -> Encoding
toEncoding :: Static -> Encoding
$ctoJSONList :: [Static] -> Value
toJSONList :: [Static] -> Value
$ctoEncodingList :: [Static] -> Encoding
toEncodingList :: [Static] -> Encoding
$comitField :: Static -> Bool
omitField :: Static -> Bool
ToJSON)
data ChunkingStrategy = ChunkingStrategy_Static{ ChunkingStrategy -> Static
static :: Static }
deriving stock ((forall x. ChunkingStrategy -> Rep ChunkingStrategy x)
-> (forall x. Rep ChunkingStrategy x -> ChunkingStrategy)
-> Generic ChunkingStrategy
forall x. Rep ChunkingStrategy x -> ChunkingStrategy
forall x. ChunkingStrategy -> Rep ChunkingStrategy x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cfrom :: forall x. ChunkingStrategy -> Rep ChunkingStrategy x
from :: forall x. ChunkingStrategy -> Rep ChunkingStrategy x
$cto :: forall x. Rep ChunkingStrategy x -> ChunkingStrategy
to :: forall x. Rep ChunkingStrategy x -> ChunkingStrategy
Generic, Int -> ChunkingStrategy -> ShowS
[ChunkingStrategy] -> ShowS
ChunkingStrategy -> String
(Int -> ChunkingStrategy -> ShowS)
-> (ChunkingStrategy -> String)
-> ([ChunkingStrategy] -> ShowS)
-> Show ChunkingStrategy
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> ChunkingStrategy -> ShowS
showsPrec :: Int -> ChunkingStrategy -> ShowS
$cshow :: ChunkingStrategy -> String
show :: ChunkingStrategy -> String
$cshowList :: [ChunkingStrategy] -> ShowS
showList :: [ChunkingStrategy] -> ShowS
Show)
chunkingStrategyOptions :: Options
chunkingStrategyOptions :: Options
chunkingStrategyOptions = Options
aesonOptions
{ sumEncoding =
TaggedObject{ tagFieldName = "type", contentsFieldName = "" }
, tagSingleConstructors = True
, constructorTagModifier = stripPrefix "ChunkingStrategy_"
}
instance ToJSON ChunkingStrategy where
toJSON :: ChunkingStrategy -> Value
toJSON = Options -> ChunkingStrategy -> Value
forall a.
(Generic a, GToJSON' Value Zero (Rep a)) =>
Options -> a -> Value
genericToJSON Options
chunkingStrategyOptions
instance FromJSON ChunkingStrategy where
parseJSON :: Value -> Parser ChunkingStrategy
parseJSON = Options -> Value -> Parser ChunkingStrategy
forall a.
(Generic a, GFromJSON Zero (Rep a)) =>
Options -> Value -> Parser a
genericParseJSON Options
chunkingStrategyOptions