module OpenAI.V1.ResponseFormat
(
ResponseFormat(..)
, JSONSchema(..)
) where
import OpenAI.Prelude
data ResponseFormat
= ResponseFormat_Text
| JSON_Object
| JSON_Schema{ ResponseFormat -> JSONSchema
json_schema :: JSONSchema }
deriving stock ((forall x. ResponseFormat -> Rep ResponseFormat x)
-> (forall x. Rep ResponseFormat x -> ResponseFormat)
-> Generic ResponseFormat
forall x. Rep ResponseFormat x -> ResponseFormat
forall x. ResponseFormat -> Rep ResponseFormat x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cfrom :: forall x. ResponseFormat -> Rep ResponseFormat x
from :: forall x. ResponseFormat -> Rep ResponseFormat x
$cto :: forall x. Rep ResponseFormat x -> ResponseFormat
to :: forall x. Rep ResponseFormat x -> ResponseFormat
Generic, Int -> ResponseFormat -> ShowS
[ResponseFormat] -> ShowS
ResponseFormat -> String
(Int -> ResponseFormat -> ShowS)
-> (ResponseFormat -> String)
-> ([ResponseFormat] -> ShowS)
-> Show ResponseFormat
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> ResponseFormat -> ShowS
showsPrec :: Int -> ResponseFormat -> ShowS
$cshow :: ResponseFormat -> String
show :: ResponseFormat -> String
$cshowList :: [ResponseFormat] -> ShowS
showList :: [ResponseFormat] -> ShowS
Show)
responseFormatOptions :: Options
responseFormatOptions :: Options
responseFormatOptions = Options
aesonOptions
{ sumEncoding =
TaggedObject{ tagFieldName = "type", contentsFieldName = "" }
, tagSingleConstructors = True
, constructorTagModifier = stripPrefix "ResponseFormat_"
}
instance FromJSON ResponseFormat where
parseJSON :: Value -> Parser ResponseFormat
parseJSON = Options -> Value -> Parser ResponseFormat
forall a.
(Generic a, GFromJSON Zero (Rep a)) =>
Options -> Value -> Parser a
genericParseJSON Options
responseFormatOptions
instance ToJSON ResponseFormat where
toJSON :: ResponseFormat -> Value
toJSON = Options -> ResponseFormat -> Value
forall a.
(Generic a, GToJSON' Value Zero (Rep a)) =>
Options -> a -> Value
genericToJSON Options
responseFormatOptions
data JSONSchema = JSONSchema
{ JSONSchema -> Maybe Text
description :: Maybe Text
, JSONSchema -> Text
name :: Text
, JSONSchema -> Maybe Value
schema :: Maybe Value
, JSONSchema -> Maybe Bool
strict :: Maybe Bool
} deriving stock ((forall x. JSONSchema -> Rep JSONSchema x)
-> (forall x. Rep JSONSchema x -> JSONSchema) -> Generic JSONSchema
forall x. Rep JSONSchema x -> JSONSchema
forall x. JSONSchema -> Rep JSONSchema x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cfrom :: forall x. JSONSchema -> Rep JSONSchema x
from :: forall x. JSONSchema -> Rep JSONSchema x
$cto :: forall x. Rep JSONSchema x -> JSONSchema
to :: forall x. Rep JSONSchema x -> JSONSchema
Generic, Int -> JSONSchema -> ShowS
[JSONSchema] -> ShowS
JSONSchema -> String
(Int -> JSONSchema -> ShowS)
-> (JSONSchema -> String)
-> ([JSONSchema] -> ShowS)
-> Show JSONSchema
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> JSONSchema -> ShowS
showsPrec :: Int -> JSONSchema -> ShowS
$cshow :: JSONSchema -> String
show :: JSONSchema -> String
$cshowList :: [JSONSchema] -> ShowS
showList :: [JSONSchema] -> ShowS
Show)
deriving anyclass (Maybe JSONSchema
Value -> Parser [JSONSchema]
Value -> Parser JSONSchema
(Value -> Parser JSONSchema)
-> (Value -> Parser [JSONSchema])
-> Maybe JSONSchema
-> FromJSON JSONSchema
forall a.
(Value -> Parser a)
-> (Value -> Parser [a]) -> Maybe a -> FromJSON a
$cparseJSON :: Value -> Parser JSONSchema
parseJSON :: Value -> Parser JSONSchema
$cparseJSONList :: Value -> Parser [JSONSchema]
parseJSONList :: Value -> Parser [JSONSchema]
$comittedField :: Maybe JSONSchema
omittedField :: Maybe JSONSchema
FromJSON, [JSONSchema] -> Value
[JSONSchema] -> Encoding
JSONSchema -> Bool
JSONSchema -> Value
JSONSchema -> Encoding
(JSONSchema -> Value)
-> (JSONSchema -> Encoding)
-> ([JSONSchema] -> Value)
-> ([JSONSchema] -> Encoding)
-> (JSONSchema -> Bool)
-> ToJSON JSONSchema
forall a.
(a -> Value)
-> (a -> Encoding)
-> ([a] -> Value)
-> ([a] -> Encoding)
-> (a -> Bool)
-> ToJSON a
$ctoJSON :: JSONSchema -> Value
toJSON :: JSONSchema -> Value
$ctoEncoding :: JSONSchema -> Encoding
toEncoding :: JSONSchema -> Encoding
$ctoJSONList :: [JSONSchema] -> Value
toJSONList :: [JSONSchema] -> Value
$ctoEncodingList :: [JSONSchema] -> Encoding
toEncodingList :: [JSONSchema] -> Encoding
$comitField :: JSONSchema -> Bool
omitField :: JSONSchema -> Bool
ToJSON)