module OpenAI.V1.Images.Image
(
ImageObject(..)
) where
import OpenAI.Prelude
data ImageObject = ImageObject
{ ImageObject -> Maybe Text
b64_json :: Maybe Text
, ImageObject -> Maybe Text
url :: Maybe Text
, ImageObject -> Maybe Text
revised_prompt :: Maybe Text
} deriving stock ((forall x. ImageObject -> Rep ImageObject x)
-> (forall x. Rep ImageObject x -> ImageObject)
-> Generic ImageObject
forall x. Rep ImageObject x -> ImageObject
forall x. ImageObject -> Rep ImageObject x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cfrom :: forall x. ImageObject -> Rep ImageObject x
from :: forall x. ImageObject -> Rep ImageObject x
$cto :: forall x. Rep ImageObject x -> ImageObject
to :: forall x. Rep ImageObject x -> ImageObject
Generic, Int -> ImageObject -> ShowS
[ImageObject] -> ShowS
ImageObject -> String
(Int -> ImageObject -> ShowS)
-> (ImageObject -> String)
-> ([ImageObject] -> ShowS)
-> Show ImageObject
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> ImageObject -> ShowS
showsPrec :: Int -> ImageObject -> ShowS
$cshow :: ImageObject -> String
show :: ImageObject -> String
$cshowList :: [ImageObject] -> ShowS
showList :: [ImageObject] -> ShowS
Show)
deriving anyclass (Maybe ImageObject
Value -> Parser [ImageObject]
Value -> Parser ImageObject
(Value -> Parser ImageObject)
-> (Value -> Parser [ImageObject])
-> Maybe ImageObject
-> FromJSON ImageObject
forall a.
(Value -> Parser a)
-> (Value -> Parser [a]) -> Maybe a -> FromJSON a
$cparseJSON :: Value -> Parser ImageObject
parseJSON :: Value -> Parser ImageObject
$cparseJSONList :: Value -> Parser [ImageObject]
parseJSONList :: Value -> Parser [ImageObject]
$comittedField :: Maybe ImageObject
omittedField :: Maybe ImageObject
FromJSON)