module OpenAI.V1.Message
(
Message(..)
, ImageFile(..)
, ImageURL(..)
, Content(..)
, Attachment(..)
) where
import OpenAI.Prelude
import OpenAI.V1.AutoOr
import OpenAI.V1.Files (FileID)
import OpenAI.V1.Tool
data ImageFile = ImageFile{ ImageFile -> FileID
file_id :: FileID, ImageFile -> Maybe (AutoOr Text)
detail :: Maybe (AutoOr Text) }
deriving stock ((forall x. ImageFile -> Rep ImageFile x)
-> (forall x. Rep ImageFile x -> ImageFile) -> Generic ImageFile
forall x. Rep ImageFile x -> ImageFile
forall x. ImageFile -> Rep ImageFile x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cfrom :: forall x. ImageFile -> Rep ImageFile x
from :: forall x. ImageFile -> Rep ImageFile x
$cto :: forall x. Rep ImageFile x -> ImageFile
to :: forall x. Rep ImageFile x -> ImageFile
Generic, Int -> ImageFile -> ShowS
[ImageFile] -> ShowS
ImageFile -> String
(Int -> ImageFile -> ShowS)
-> (ImageFile -> String)
-> ([ImageFile] -> ShowS)
-> Show ImageFile
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> ImageFile -> ShowS
showsPrec :: Int -> ImageFile -> ShowS
$cshow :: ImageFile -> String
show :: ImageFile -> String
$cshowList :: [ImageFile] -> ShowS
showList :: [ImageFile] -> ShowS
Show)
deriving anyclass (Maybe ImageFile
Value -> Parser [ImageFile]
Value -> Parser ImageFile
(Value -> Parser ImageFile)
-> (Value -> Parser [ImageFile])
-> Maybe ImageFile
-> FromJSON ImageFile
forall a.
(Value -> Parser a)
-> (Value -> Parser [a]) -> Maybe a -> FromJSON a
$cparseJSON :: Value -> Parser ImageFile
parseJSON :: Value -> Parser ImageFile
$cparseJSONList :: Value -> Parser [ImageFile]
parseJSONList :: Value -> Parser [ImageFile]
$comittedField :: Maybe ImageFile
omittedField :: Maybe ImageFile
FromJSON, [ImageFile] -> Value
[ImageFile] -> Encoding
ImageFile -> Bool
ImageFile -> Value
ImageFile -> Encoding
(ImageFile -> Value)
-> (ImageFile -> Encoding)
-> ([ImageFile] -> Value)
-> ([ImageFile] -> Encoding)
-> (ImageFile -> Bool)
-> ToJSON ImageFile
forall a.
(a -> Value)
-> (a -> Encoding)
-> ([a] -> Value)
-> ([a] -> Encoding)
-> (a -> Bool)
-> ToJSON a
$ctoJSON :: ImageFile -> Value
toJSON :: ImageFile -> Value
$ctoEncoding :: ImageFile -> Encoding
toEncoding :: ImageFile -> Encoding
$ctoJSONList :: [ImageFile] -> Value
toJSONList :: [ImageFile] -> Value
$ctoEncodingList :: [ImageFile] -> Encoding
toEncodingList :: [ImageFile] -> Encoding
$comitField :: ImageFile -> Bool
omitField :: ImageFile -> Bool
ToJSON)
data ImageURL = ImageURL
{ ImageURL -> Text
image_url :: Text
, ImageURL -> Maybe (AutoOr Text)
detail :: Maybe (AutoOr Text)
} deriving stock ((forall x. ImageURL -> Rep ImageURL x)
-> (forall x. Rep ImageURL x -> ImageURL) -> Generic ImageURL
forall x. Rep ImageURL x -> ImageURL
forall x. ImageURL -> Rep ImageURL x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cfrom :: forall x. ImageURL -> Rep ImageURL x
from :: forall x. ImageURL -> Rep ImageURL x
$cto :: forall x. Rep ImageURL x -> ImageURL
to :: forall x. Rep ImageURL x -> ImageURL
Generic, Int -> ImageURL -> ShowS
[ImageURL] -> ShowS
ImageURL -> String
(Int -> ImageURL -> ShowS)
-> (ImageURL -> String) -> ([ImageURL] -> ShowS) -> Show ImageURL
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> ImageURL -> ShowS
showsPrec :: Int -> ImageURL -> ShowS
$cshow :: ImageURL -> String
show :: ImageURL -> String
$cshowList :: [ImageURL] -> ShowS
showList :: [ImageURL] -> ShowS
Show)
deriving anyclass (Maybe ImageURL
Value -> Parser [ImageURL]
Value -> Parser ImageURL
(Value -> Parser ImageURL)
-> (Value -> Parser [ImageURL])
-> Maybe ImageURL
-> FromJSON ImageURL
forall a.
(Value -> Parser a)
-> (Value -> Parser [a]) -> Maybe a -> FromJSON a
$cparseJSON :: Value -> Parser ImageURL
parseJSON :: Value -> Parser ImageURL
$cparseJSONList :: Value -> Parser [ImageURL]
parseJSONList :: Value -> Parser [ImageURL]
$comittedField :: Maybe ImageURL
omittedField :: Maybe ImageURL
FromJSON, [ImageURL] -> Value
[ImageURL] -> Encoding
ImageURL -> Bool
ImageURL -> Value
ImageURL -> Encoding
(ImageURL -> Value)
-> (ImageURL -> Encoding)
-> ([ImageURL] -> Value)
-> ([ImageURL] -> Encoding)
-> (ImageURL -> Bool)
-> ToJSON ImageURL
forall a.
(a -> Value)
-> (a -> Encoding)
-> ([a] -> Value)
-> ([a] -> Encoding)
-> (a -> Bool)
-> ToJSON a
$ctoJSON :: ImageURL -> Value
toJSON :: ImageURL -> Value
$ctoEncoding :: ImageURL -> Encoding
toEncoding :: ImageURL -> Encoding
$ctoJSONList :: [ImageURL] -> Value
toJSONList :: [ImageURL] -> Value
$ctoEncodingList :: [ImageURL] -> Encoding
toEncodingList :: [ImageURL] -> Encoding
$comitField :: ImageURL -> Bool
omitField :: ImageURL -> Bool
ToJSON)
data Content text
= Image_File{ forall text. Content text -> ImageFile
image_file :: ImageFile }
| Image_URL{ forall text. Content text -> ImageURL
image_url :: ImageURL }
| Text{ forall text. Content text -> text
text :: text }
deriving stock ((forall x. Content text -> Rep (Content text) x)
-> (forall x. Rep (Content text) x -> Content text)
-> Generic (Content text)
forall x. Rep (Content text) x -> Content text
forall x. Content text -> Rep (Content text) x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
forall text x. Rep (Content text) x -> Content text
forall text x. Content text -> Rep (Content text) x
$cfrom :: forall text x. Content text -> Rep (Content text) x
from :: forall x. Content text -> Rep (Content text) x
$cto :: forall text x. Rep (Content text) x -> Content text
to :: forall x. Rep (Content text) x -> Content text
Generic, Int -> Content text -> ShowS
[Content text] -> ShowS
Content text -> String
(Int -> Content text -> ShowS)
-> (Content text -> String)
-> ([Content text] -> ShowS)
-> Show (Content text)
forall text. Show text => Int -> Content text -> ShowS
forall text. Show text => [Content text] -> ShowS
forall text. Show text => Content text -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: forall text. Show text => Int -> Content text -> ShowS
showsPrec :: Int -> Content text -> ShowS
$cshow :: forall text. Show text => Content text -> String
show :: Content text -> String
$cshowList :: forall text. Show text => [Content text] -> ShowS
showList :: [Content text] -> ShowS
Show)
contentOptions :: Options
contentOptions :: Options
contentOptions = Options
aesonOptions
{ sumEncoding =
TaggedObject{ tagFieldName = "type", contentsFieldName = "" }
, tagSingleConstructors = True
}
instance FromJSON text => FromJSON (Content text) where
parseJSON :: Value -> Parser (Content text)
parseJSON = Options -> Value -> Parser (Content text)
forall a.
(Generic a, GFromJSON Zero (Rep a)) =>
Options -> Value -> Parser a
genericParseJSON Options
contentOptions
instance ToJSON text => ToJSON (Content text) where
toJSON :: Content text -> Value
toJSON = Options -> Content text -> Value
forall a.
(Generic a, GToJSON' Value Zero (Rep a)) =>
Options -> a -> Value
genericToJSON Options
contentOptions
instance IsString text => IsString (Content text) where
fromString :: String -> Content text
fromString String
string = Text{ $sel:text:Image_File :: text
text = String -> text
forall a. IsString a => String -> a
fromString String
string }
data Attachment = Attachment{ Attachment -> FileID
file_id :: FileID, Attachment -> Maybe (Vector Tool)
tools :: Maybe (Vector Tool) }
deriving stock ((forall x. Attachment -> Rep Attachment x)
-> (forall x. Rep Attachment x -> Attachment) -> Generic Attachment
forall x. Rep Attachment x -> Attachment
forall x. Attachment -> Rep Attachment x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cfrom :: forall x. Attachment -> Rep Attachment x
from :: forall x. Attachment -> Rep Attachment x
$cto :: forall x. Rep Attachment x -> Attachment
to :: forall x. Rep Attachment x -> Attachment
Generic, Int -> Attachment -> ShowS
[Attachment] -> ShowS
Attachment -> String
(Int -> Attachment -> ShowS)
-> (Attachment -> String)
-> ([Attachment] -> ShowS)
-> Show Attachment
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> Attachment -> ShowS
showsPrec :: Int -> Attachment -> ShowS
$cshow :: Attachment -> String
show :: Attachment -> String
$cshowList :: [Attachment] -> ShowS
showList :: [Attachment] -> ShowS
Show)
deriving anyclass (Maybe Attachment
Value -> Parser [Attachment]
Value -> Parser Attachment
(Value -> Parser Attachment)
-> (Value -> Parser [Attachment])
-> Maybe Attachment
-> FromJSON Attachment
forall a.
(Value -> Parser a)
-> (Value -> Parser [a]) -> Maybe a -> FromJSON a
$cparseJSON :: Value -> Parser Attachment
parseJSON :: Value -> Parser Attachment
$cparseJSONList :: Value -> Parser [Attachment]
parseJSONList :: Value -> Parser [Attachment]
$comittedField :: Maybe Attachment
omittedField :: Maybe Attachment
FromJSON, [Attachment] -> Value
[Attachment] -> Encoding
Attachment -> Bool
Attachment -> Value
Attachment -> Encoding
(Attachment -> Value)
-> (Attachment -> Encoding)
-> ([Attachment] -> Value)
-> ([Attachment] -> Encoding)
-> (Attachment -> Bool)
-> ToJSON Attachment
forall a.
(a -> Value)
-> (a -> Encoding)
-> ([a] -> Value)
-> ([a] -> Encoding)
-> (a -> Bool)
-> ToJSON a
$ctoJSON :: Attachment -> Value
toJSON :: Attachment -> Value
$ctoEncoding :: Attachment -> Encoding
toEncoding :: Attachment -> Encoding
$ctoJSONList :: [Attachment] -> Value
toJSONList :: [Attachment] -> Value
$ctoEncodingList :: [Attachment] -> Encoding
toEncodingList :: [Attachment] -> Encoding
$comitField :: Attachment -> Bool
omitField :: Attachment -> Bool
ToJSON)
data Message
= User
{ Message -> Vector (Content Text)
content :: Vector (Content Text)
, Message -> Maybe (Vector Attachment)
attachments :: Maybe (Vector Attachment)
, Message -> Maybe (Map Text Text)
metadata :: Maybe (Map Text Text)
}
| Assistant
{ content :: Vector (Content Text)
, attachments :: Maybe (Vector Attachment)
, metadata :: Maybe (Map Text Text)
}
deriving stock ((forall x. Message -> Rep Message x)
-> (forall x. Rep Message x -> Message) -> Generic Message
forall x. Rep Message x -> Message
forall x. Message -> Rep Message x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cfrom :: forall x. Message -> Rep Message x
from :: forall x. Message -> Rep Message x
$cto :: forall x. Rep Message x -> Message
to :: forall x. Rep Message x -> Message
Generic, Int -> Message -> ShowS
[Message] -> ShowS
Message -> String
(Int -> Message -> ShowS)
-> (Message -> String) -> ([Message] -> ShowS) -> Show Message
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> Message -> ShowS
showsPrec :: Int -> Message -> ShowS
$cshow :: Message -> String
show :: Message -> String
$cshowList :: [Message] -> ShowS
showList :: [Message] -> ShowS
Show)
instance ToJSON Message where
toJSON :: Message -> Value
toJSON = Options -> Message -> Value
forall a.
(Generic a, GToJSON' Value Zero (Rep a)) =>
Options -> a -> Value
genericToJSON Options
aesonOptions
{ sumEncoding =
TaggedObject{ tagFieldName = "role", contentsFieldName = "" }
, tagSingleConstructors = True
}