module OpenAI.V1.Chat.Completions
(
CreateChatCompletion(..)
, _CreateChatCompletion
, ChatCompletionObject(..)
, Choice(..)
, Message(..)
, messageToContent
, Content(..)
, InputAudio(..)
, ImageURL(..)
, AudioData(..)
, Modality(..)
, Prediction(..)
, Voice(..)
, AudioFormat(..)
, AudioParameters(..)
, ResponseFormat(..)
, ServiceTier(..)
, FinishReason(..)
, Token(..)
, LogProbs(..)
, API
) where
import OpenAI.Prelude
import OpenAI.V1.AutoOr
import OpenAI.V1.Models (Model)
import OpenAI.V1.ResponseFormat
import OpenAI.V1.Tool
import OpenAI.V1.ToolCall
import OpenAI.V1.Usage
import Prelude hiding (id)
data InputAudio = InputAudio{ InputAudio -> Text
data_ :: Text, InputAudio -> AudioFormat
format :: AudioFormat }
deriving stock ((forall x. InputAudio -> Rep InputAudio x)
-> (forall x. Rep InputAudio x -> InputAudio) -> Generic InputAudio
forall x. Rep InputAudio x -> InputAudio
forall x. InputAudio -> Rep InputAudio x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cfrom :: forall x. InputAudio -> Rep InputAudio x
from :: forall x. InputAudio -> Rep InputAudio x
$cto :: forall x. Rep InputAudio x -> InputAudio
to :: forall x. Rep InputAudio x -> InputAudio
Generic, Int -> InputAudio -> ShowS
[InputAudio] -> ShowS
InputAudio -> String
(Int -> InputAudio -> ShowS)
-> (InputAudio -> String)
-> ([InputAudio] -> ShowS)
-> Show InputAudio
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> InputAudio -> ShowS
showsPrec :: Int -> InputAudio -> ShowS
$cshow :: InputAudio -> String
show :: InputAudio -> String
$cshowList :: [InputAudio] -> ShowS
showList :: [InputAudio] -> ShowS
Show)
instance ToJSON InputAudio where
toJSON :: InputAudio -> Value
toJSON = Options -> InputAudio -> Value
forall a.
(Generic a, GToJSON' Value Zero (Rep a)) =>
Options -> a -> Value
genericToJSON Options
aesonOptions
data ImageURL = ImageURL{ ImageURL -> Text
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 ([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{ Content -> Text
text :: Text }
| Image_URL{ Content -> ImageURL
image_url :: ImageURL }
| Input_Audio{ Content -> InputAudio
input_audio :: InputAudio }
deriving ((forall x. Content -> Rep Content x)
-> (forall x. Rep Content x -> Content) -> Generic Content
forall x. Rep Content x -> Content
forall x. Content -> Rep Content x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cfrom :: forall x. Content -> Rep Content x
from :: forall x. Content -> Rep Content x
$cto :: forall x. Rep Content x -> Content
to :: forall x. Rep Content x -> Content
Generic, Int -> Content -> ShowS
[Content] -> ShowS
Content -> String
(Int -> Content -> ShowS)
-> (Content -> String) -> ([Content] -> ShowS) -> Show Content
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> Content -> ShowS
showsPrec :: Int -> Content -> ShowS
$cshow :: Content -> String
show :: Content -> String
$cshowList :: [Content] -> ShowS
showList :: [Content] -> ShowS
Show)
instance IsString Content where
fromString :: String -> Content
fromString String
string = Text{ $sel:text:Text :: Text
text = String -> Text
forall a. IsString a => String -> a
fromString String
string }
instance ToJSON Content where
toJSON :: Content -> Value
toJSON = Options -> Content -> Value
forall a.
(Generic a, GToJSON' Value Zero (Rep a)) =>
Options -> a -> Value
genericToJSON Options
aesonOptions
{ sumEncoding =
TaggedObject{ tagFieldName = "type", contentsFieldName = "" }
, tagSingleConstructors = True
}
data AudioData = AudioData{ AudioData -> Text
id :: Text }
deriving stock ((forall x. AudioData -> Rep AudioData x)
-> (forall x. Rep AudioData x -> AudioData) -> Generic AudioData
forall x. Rep AudioData x -> AudioData
forall x. AudioData -> Rep AudioData x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cfrom :: forall x. AudioData -> Rep AudioData x
from :: forall x. AudioData -> Rep AudioData x
$cto :: forall x. Rep AudioData x -> AudioData
to :: forall x. Rep AudioData x -> AudioData
Generic, Int -> AudioData -> ShowS
[AudioData] -> ShowS
AudioData -> String
(Int -> AudioData -> ShowS)
-> (AudioData -> String)
-> ([AudioData] -> ShowS)
-> Show AudioData
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> AudioData -> ShowS
showsPrec :: Int -> AudioData -> ShowS
$cshow :: AudioData -> String
show :: AudioData -> String
$cshowList :: [AudioData] -> ShowS
showList :: [AudioData] -> ShowS
Show)
deriving anyclass (Maybe AudioData
Value -> Parser [AudioData]
Value -> Parser AudioData
(Value -> Parser AudioData)
-> (Value -> Parser [AudioData])
-> Maybe AudioData
-> FromJSON AudioData
forall a.
(Value -> Parser a)
-> (Value -> Parser [a]) -> Maybe a -> FromJSON a
$cparseJSON :: Value -> Parser AudioData
parseJSON :: Value -> Parser AudioData
$cparseJSONList :: Value -> Parser [AudioData]
parseJSONList :: Value -> Parser [AudioData]
$comittedField :: Maybe AudioData
omittedField :: Maybe AudioData
FromJSON, [AudioData] -> Value
[AudioData] -> Encoding
AudioData -> Bool
AudioData -> Value
AudioData -> Encoding
(AudioData -> Value)
-> (AudioData -> Encoding)
-> ([AudioData] -> Value)
-> ([AudioData] -> Encoding)
-> (AudioData -> Bool)
-> ToJSON AudioData
forall a.
(a -> Value)
-> (a -> Encoding)
-> ([a] -> Value)
-> ([a] -> Encoding)
-> (a -> Bool)
-> ToJSON a
$ctoJSON :: AudioData -> Value
toJSON :: AudioData -> Value
$ctoEncoding :: AudioData -> Encoding
toEncoding :: AudioData -> Encoding
$ctoJSONList :: [AudioData] -> Value
toJSONList :: [AudioData] -> Value
$ctoEncodingList :: [AudioData] -> Encoding
toEncodingList :: [AudioData] -> Encoding
$comitField :: AudioData -> Bool
omitField :: AudioData -> Bool
ToJSON)
data Message content
= System
{ forall content. Message content -> content
content :: content
, forall content. Message content -> Maybe Text
name :: Maybe Text
}
| User
{ content :: content
, name :: Maybe Text
}
| Assistant
{ forall content. Message content -> Maybe content
assistant_content :: Maybe content
, forall content. Message content -> Maybe Text
refusal :: Maybe Text
, name :: Maybe Text
, forall content. Message content -> Maybe AudioData
assistant_audio :: Maybe AudioData
, forall content. Message content -> Maybe (Vector ToolCall)
tool_calls :: Maybe (Vector ToolCall)
}
| Tool
{ content :: content
, forall content. Message content -> Text
tool_call_id :: Text
}
deriving stock ((forall x. Message content -> Rep (Message content) x)
-> (forall x. Rep (Message content) x -> Message content)
-> Generic (Message content)
forall x. Rep (Message content) x -> Message content
forall x. Message content -> Rep (Message content) x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
forall content x. Rep (Message content) x -> Message content
forall content x. Message content -> Rep (Message content) x
$cfrom :: forall content x. Message content -> Rep (Message content) x
from :: forall x. Message content -> Rep (Message content) x
$cto :: forall content x. Rep (Message content) x -> Message content
to :: forall x. Rep (Message content) x -> Message content
Generic, Int -> Message content -> ShowS
[Message content] -> ShowS
Message content -> String
(Int -> Message content -> ShowS)
-> (Message content -> String)
-> ([Message content] -> ShowS)
-> Show (Message content)
forall content. Show content => Int -> Message content -> ShowS
forall content. Show content => [Message content] -> ShowS
forall content. Show content => Message content -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: forall content. Show content => Int -> Message content -> ShowS
showsPrec :: Int -> Message content -> ShowS
$cshow :: forall content. Show content => Message content -> String
show :: Message content -> String
$cshowList :: forall content. Show content => [Message content] -> ShowS
showList :: [Message content] -> ShowS
Show)
messageOptions :: Options
messageOptions :: Options
messageOptions = Options
aesonOptions
{ sumEncoding =
TaggedObject{ tagFieldName = "role", contentsFieldName = "" }
, tagSingleConstructors = True
, fieldLabelModifier = stripPrefix "assistant_"
}
instance FromJSON content => FromJSON (Message content) where
parseJSON :: Value -> Parser (Message content)
parseJSON = Options -> Value -> Parser (Message content)
forall a.
(Generic a, GFromJSON Zero (Rep a)) =>
Options -> Value -> Parser a
genericParseJSON Options
messageOptions
instance ToJSON content => ToJSON (Message content) where
toJSON :: Message content -> Value
toJSON = Options -> Message content -> Value
forall a.
(Generic a, GToJSON' Value Zero (Rep a)) =>
Options -> a -> Value
genericToJSON Options
messageOptions
messageToContent :: Monoid content => Message content -> content
messageToContent :: forall content. Monoid content => Message content -> content
messageToContent System{ content
$sel:content:System :: forall content. Message content -> content
content :: content
content } = content
content
messageToContent User{ content
$sel:content:System :: forall content. Message content -> content
content :: content
content } = content
content
messageToContent Assistant{ $sel:assistant_content:System :: forall content. Message content -> Maybe content
assistant_content = Just content
content } = content
content
messageToContent Assistant{ $sel:assistant_content:System :: forall content. Message content -> Maybe content
assistant_content = Maybe content
Nothing } = content
forall a. Monoid a => a
mempty
messageToContent Tool{ content
$sel:content:System :: forall content. Message content -> content
content :: content
content } = content
content
data Modality = Modality_Text | Modality_Audio
deriving stock ((forall x. Modality -> Rep Modality x)
-> (forall x. Rep Modality x -> Modality) -> Generic Modality
forall x. Rep Modality x -> Modality
forall x. Modality -> Rep Modality x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cfrom :: forall x. Modality -> Rep Modality x
from :: forall x. Modality -> Rep Modality x
$cto :: forall x. Rep Modality x -> Modality
to :: forall x. Rep Modality x -> Modality
Generic, Int -> Modality -> ShowS
[Modality] -> ShowS
Modality -> String
(Int -> Modality -> ShowS)
-> (Modality -> String) -> ([Modality] -> ShowS) -> Show Modality
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> Modality -> ShowS
showsPrec :: Int -> Modality -> ShowS
$cshow :: Modality -> String
show :: Modality -> String
$cshowList :: [Modality] -> ShowS
showList :: [Modality] -> ShowS
Show)
instance ToJSON Modality where
toJSON :: Modality -> Value
toJSON = Options -> Modality -> Value
forall a.
(Generic a, GToJSON' Value Zero (Rep a)) =>
Options -> a -> Value
genericToJSON Options
aesonOptions
{ constructorTagModifier = stripPrefix "Modality_" }
data Prediction = Content{ Prediction -> Text
content :: Text }
deriving stock ((forall x. Prediction -> Rep Prediction x)
-> (forall x. Rep Prediction x -> Prediction) -> Generic Prediction
forall x. Rep Prediction x -> Prediction
forall x. Prediction -> Rep Prediction x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cfrom :: forall x. Prediction -> Rep Prediction x
from :: forall x. Prediction -> Rep Prediction x
$cto :: forall x. Rep Prediction x -> Prediction
to :: forall x. Rep Prediction x -> Prediction
Generic, Int -> Prediction -> ShowS
[Prediction] -> ShowS
Prediction -> String
(Int -> Prediction -> ShowS)
-> (Prediction -> String)
-> ([Prediction] -> ShowS)
-> Show Prediction
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> Prediction -> ShowS
showsPrec :: Int -> Prediction -> ShowS
$cshow :: Prediction -> String
show :: Prediction -> String
$cshowList :: [Prediction] -> ShowS
showList :: [Prediction] -> ShowS
Show)
instance ToJSON Prediction where
toJSON :: Prediction -> Value
toJSON = Options -> Prediction -> Value
forall a.
(Generic a, GToJSON' Value Zero (Rep a)) =>
Options -> a -> Value
genericToJSON Options
aesonOptions
{ sumEncoding =
TaggedObject{ tagFieldName = "type", contentsFieldName = "" }
, tagSingleConstructors = True
}
data Voice = Ash | Ballad | Coral | Sage | Verse
deriving stock ((forall x. Voice -> Rep Voice x)
-> (forall x. Rep Voice x -> Voice) -> Generic Voice
forall x. Rep Voice x -> Voice
forall x. Voice -> Rep Voice x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cfrom :: forall x. Voice -> Rep Voice x
from :: forall x. Voice -> Rep Voice x
$cto :: forall x. Rep Voice x -> Voice
to :: forall x. Rep Voice x -> Voice
Generic, Int -> Voice -> ShowS
[Voice] -> ShowS
Voice -> String
(Int -> Voice -> ShowS)
-> (Voice -> String) -> ([Voice] -> ShowS) -> Show Voice
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> Voice -> ShowS
showsPrec :: Int -> Voice -> ShowS
$cshow :: Voice -> String
show :: Voice -> String
$cshowList :: [Voice] -> ShowS
showList :: [Voice] -> ShowS
Show)
instance ToJSON Voice where
toJSON :: Voice -> Value
toJSON = Options -> Voice -> Value
forall a.
(Generic a, GToJSON' Value Zero (Rep a)) =>
Options -> a -> Value
genericToJSON Options
aesonOptions
data AudioFormat = WAV | MP3 | FLAC | Opus | PCM16
deriving stock ((forall x. AudioFormat -> Rep AudioFormat x)
-> (forall x. Rep AudioFormat x -> AudioFormat)
-> Generic AudioFormat
forall x. Rep AudioFormat x -> AudioFormat
forall x. AudioFormat -> Rep AudioFormat x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cfrom :: forall x. AudioFormat -> Rep AudioFormat x
from :: forall x. AudioFormat -> Rep AudioFormat x
$cto :: forall x. Rep AudioFormat x -> AudioFormat
to :: forall x. Rep AudioFormat x -> AudioFormat
Generic, Int -> AudioFormat -> ShowS
[AudioFormat] -> ShowS
AudioFormat -> String
(Int -> AudioFormat -> ShowS)
-> (AudioFormat -> String)
-> ([AudioFormat] -> ShowS)
-> Show AudioFormat
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> AudioFormat -> ShowS
showsPrec :: Int -> AudioFormat -> ShowS
$cshow :: AudioFormat -> String
show :: AudioFormat -> String
$cshowList :: [AudioFormat] -> ShowS
showList :: [AudioFormat] -> ShowS
Show)
instance ToJSON AudioFormat where
toJSON :: AudioFormat -> Value
toJSON = Options -> AudioFormat -> Value
forall a.
(Generic a, GToJSON' Value Zero (Rep a)) =>
Options -> a -> Value
genericToJSON Options
aesonOptions
data AudioParameters = AudioParameters
{ AudioParameters -> Voice
voice :: Voice
, AudioParameters -> AudioFormat
format :: AudioFormat
} deriving stock ((forall x. AudioParameters -> Rep AudioParameters x)
-> (forall x. Rep AudioParameters x -> AudioParameters)
-> Generic AudioParameters
forall x. Rep AudioParameters x -> AudioParameters
forall x. AudioParameters -> Rep AudioParameters x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cfrom :: forall x. AudioParameters -> Rep AudioParameters x
from :: forall x. AudioParameters -> Rep AudioParameters x
$cto :: forall x. Rep AudioParameters x -> AudioParameters
to :: forall x. Rep AudioParameters x -> AudioParameters
Generic, Int -> AudioParameters -> ShowS
[AudioParameters] -> ShowS
AudioParameters -> String
(Int -> AudioParameters -> ShowS)
-> (AudioParameters -> String)
-> ([AudioParameters] -> ShowS)
-> Show AudioParameters
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> AudioParameters -> ShowS
showsPrec :: Int -> AudioParameters -> ShowS
$cshow :: AudioParameters -> String
show :: AudioParameters -> String
$cshowList :: [AudioParameters] -> ShowS
showList :: [AudioParameters] -> ShowS
Show)
deriving anyclass ([AudioParameters] -> Value
[AudioParameters] -> Encoding
AudioParameters -> Bool
AudioParameters -> Value
AudioParameters -> Encoding
(AudioParameters -> Value)
-> (AudioParameters -> Encoding)
-> ([AudioParameters] -> Value)
-> ([AudioParameters] -> Encoding)
-> (AudioParameters -> Bool)
-> ToJSON AudioParameters
forall a.
(a -> Value)
-> (a -> Encoding)
-> ([a] -> Value)
-> ([a] -> Encoding)
-> (a -> Bool)
-> ToJSON a
$ctoJSON :: AudioParameters -> Value
toJSON :: AudioParameters -> Value
$ctoEncoding :: AudioParameters -> Encoding
toEncoding :: AudioParameters -> Encoding
$ctoJSONList :: [AudioParameters] -> Value
toJSONList :: [AudioParameters] -> Value
$ctoEncodingList :: [AudioParameters] -> Encoding
toEncodingList :: [AudioParameters] -> Encoding
$comitField :: AudioParameters -> Bool
omitField :: AudioParameters -> Bool
ToJSON)
data ServiceTier = Default
deriving stock ((forall x. ServiceTier -> Rep ServiceTier x)
-> (forall x. Rep ServiceTier x -> ServiceTier)
-> Generic ServiceTier
forall x. Rep ServiceTier x -> ServiceTier
forall x. ServiceTier -> Rep ServiceTier x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cfrom :: forall x. ServiceTier -> Rep ServiceTier x
from :: forall x. ServiceTier -> Rep ServiceTier x
$cto :: forall x. Rep ServiceTier x -> ServiceTier
to :: forall x. Rep ServiceTier x -> ServiceTier
Generic, Int -> ServiceTier -> ShowS
[ServiceTier] -> ShowS
ServiceTier -> String
(Int -> ServiceTier -> ShowS)
-> (ServiceTier -> String)
-> ([ServiceTier] -> ShowS)
-> Show ServiceTier
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> ServiceTier -> ShowS
showsPrec :: Int -> ServiceTier -> ShowS
$cshow :: ServiceTier -> String
show :: ServiceTier -> String
$cshowList :: [ServiceTier] -> ShowS
showList :: [ServiceTier] -> ShowS
Show)
instance FromJSON ServiceTier where
parseJSON :: Value -> Parser ServiceTier
parseJSON = Options -> Value -> Parser ServiceTier
forall a.
(Generic a, GFromJSON Zero (Rep a)) =>
Options -> Value -> Parser a
genericParseJSON Options
aesonOptions{ tagSingleConstructors = True }
instance ToJSON ServiceTier where
toJSON :: ServiceTier -> Value
toJSON = Options -> ServiceTier -> Value
forall a.
(Generic a, GToJSON' Value Zero (Rep a)) =>
Options -> a -> Value
genericToJSON Options
aesonOptions
data CreateChatCompletion = CreateChatCompletion
{ CreateChatCompletion -> Vector (Message (Vector Content))
messages :: Vector (Message (Vector Content))
, CreateChatCompletion -> Model
model :: Model
, CreateChatCompletion -> Maybe Bool
store :: Maybe Bool
, CreateChatCompletion -> Maybe (Map Text Text)
metadata :: Maybe (Map Text Text)
, CreateChatCompletion -> Maybe Double
frequency_penalty :: Maybe Double
, CreateChatCompletion -> Maybe (Map Word Int)
logit_bias :: Maybe (Map Word Int)
, CreateChatCompletion -> Maybe Bool
logprobs :: Maybe Bool
, CreateChatCompletion -> Maybe Word
top_logprobs :: Maybe Word
, CreateChatCompletion -> Maybe Natural
max_completion_tokens :: Maybe Natural
, CreateChatCompletion -> Maybe Natural
n :: Maybe Natural
, CreateChatCompletion -> Maybe (Vector Modality)
modalities :: Maybe (Vector Modality)
, CreateChatCompletion -> Maybe Prediction
prediction :: Maybe Prediction
, CreateChatCompletion -> Maybe AudioParameters
audio :: Maybe AudioParameters
, CreateChatCompletion -> Maybe Double
presence_penalty :: Maybe Double
, CreateChatCompletion -> Maybe ResponseFormat
response_format :: Maybe ResponseFormat
, CreateChatCompletion -> Maybe Integer
seed :: Maybe Integer
, CreateChatCompletion -> Maybe (AutoOr ServiceTier)
service_tier :: Maybe (AutoOr ServiceTier)
, CreateChatCompletion -> Maybe (Vector Text)
stop :: Maybe (Vector Text)
, CreateChatCompletion -> Maybe Double
temperature :: Maybe Double
, CreateChatCompletion -> Maybe Double
top_p :: Maybe Double
, CreateChatCompletion -> Maybe (Vector Tool)
tools :: Maybe (Vector Tool)
, CreateChatCompletion -> Maybe ToolChoice
tool_choice :: Maybe ToolChoice
, CreateChatCompletion -> Maybe Bool
parallel_tool_calls :: Maybe Bool
, CreateChatCompletion -> Maybe Text
user :: Maybe Text
} deriving stock ((forall x. CreateChatCompletion -> Rep CreateChatCompletion x)
-> (forall x. Rep CreateChatCompletion x -> CreateChatCompletion)
-> Generic CreateChatCompletion
forall x. Rep CreateChatCompletion x -> CreateChatCompletion
forall x. CreateChatCompletion -> Rep CreateChatCompletion x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cfrom :: forall x. CreateChatCompletion -> Rep CreateChatCompletion x
from :: forall x. CreateChatCompletion -> Rep CreateChatCompletion x
$cto :: forall x. Rep CreateChatCompletion x -> CreateChatCompletion
to :: forall x. Rep CreateChatCompletion x -> CreateChatCompletion
Generic, Int -> CreateChatCompletion -> ShowS
[CreateChatCompletion] -> ShowS
CreateChatCompletion -> String
(Int -> CreateChatCompletion -> ShowS)
-> (CreateChatCompletion -> String)
-> ([CreateChatCompletion] -> ShowS)
-> Show CreateChatCompletion
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> CreateChatCompletion -> ShowS
showsPrec :: Int -> CreateChatCompletion -> ShowS
$cshow :: CreateChatCompletion -> String
show :: CreateChatCompletion -> String
$cshowList :: [CreateChatCompletion] -> ShowS
showList :: [CreateChatCompletion] -> ShowS
Show)
instance ToJSON CreateChatCompletion where
toJSON :: CreateChatCompletion -> Value
toJSON = Options -> CreateChatCompletion -> Value
forall a.
(Generic a, GToJSON' Value Zero (Rep a)) =>
Options -> a -> Value
genericToJSON Options
aesonOptions
_CreateChatCompletion :: CreateChatCompletion
_CreateChatCompletion :: CreateChatCompletion
_CreateChatCompletion = CreateChatCompletion
{ $sel:store:CreateChatCompletion :: Maybe Bool
store = Maybe Bool
forall a. Maybe a
Nothing
, $sel:metadata:CreateChatCompletion :: Maybe (Map Text Text)
metadata = Maybe (Map Text Text)
forall a. Maybe a
Nothing
, $sel:frequency_penalty:CreateChatCompletion :: Maybe Double
frequency_penalty = Maybe Double
forall a. Maybe a
Nothing
, $sel:logit_bias:CreateChatCompletion :: Maybe (Map Word Int)
logit_bias = Maybe (Map Word Int)
forall a. Maybe a
Nothing
, $sel:logprobs:CreateChatCompletion :: Maybe Bool
logprobs = Maybe Bool
forall a. Maybe a
Nothing
, $sel:top_logprobs:CreateChatCompletion :: Maybe Word
top_logprobs = Maybe Word
forall a. Maybe a
Nothing
, $sel:max_completion_tokens:CreateChatCompletion :: Maybe Natural
max_completion_tokens = Maybe Natural
forall a. Maybe a
Nothing
, $sel:n:CreateChatCompletion :: Maybe Natural
n = Maybe Natural
forall a. Maybe a
Nothing
, $sel:modalities:CreateChatCompletion :: Maybe (Vector Modality)
modalities = Maybe (Vector Modality)
forall a. Maybe a
Nothing
, $sel:prediction:CreateChatCompletion :: Maybe Prediction
prediction = Maybe Prediction
forall a. Maybe a
Nothing
, $sel:audio:CreateChatCompletion :: Maybe AudioParameters
audio = Maybe AudioParameters
forall a. Maybe a
Nothing
, $sel:presence_penalty:CreateChatCompletion :: Maybe Double
presence_penalty = Maybe Double
forall a. Maybe a
Nothing
, $sel:response_format:CreateChatCompletion :: Maybe ResponseFormat
response_format = Maybe ResponseFormat
forall a. Maybe a
Nothing
, $sel:seed:CreateChatCompletion :: Maybe Integer
seed = Maybe Integer
forall a. Maybe a
Nothing
, $sel:service_tier:CreateChatCompletion :: Maybe (AutoOr ServiceTier)
service_tier = Maybe (AutoOr ServiceTier)
forall a. Maybe a
Nothing
, $sel:stop:CreateChatCompletion :: Maybe (Vector Text)
stop = Maybe (Vector Text)
forall a. Maybe a
Nothing
, $sel:temperature:CreateChatCompletion :: Maybe Double
temperature = Maybe Double
forall a. Maybe a
Nothing
, $sel:top_p:CreateChatCompletion :: Maybe Double
top_p = Maybe Double
forall a. Maybe a
Nothing
, $sel:tools:CreateChatCompletion :: Maybe (Vector Tool)
tools = Maybe (Vector Tool)
forall a. Maybe a
Nothing
, $sel:tool_choice:CreateChatCompletion :: Maybe ToolChoice
tool_choice = Maybe ToolChoice
forall a. Maybe a
Nothing
, $sel:parallel_tool_calls:CreateChatCompletion :: Maybe Bool
parallel_tool_calls = Maybe Bool
forall a. Maybe a
Nothing
, $sel:user:CreateChatCompletion :: Maybe Text
user = Maybe Text
forall a. Maybe a
Nothing
}
data FinishReason
= Stop
| Length
| Content_Filter
| Tool_Calls
deriving stock ((forall x. FinishReason -> Rep FinishReason x)
-> (forall x. Rep FinishReason x -> FinishReason)
-> Generic FinishReason
forall x. Rep FinishReason x -> FinishReason
forall x. FinishReason -> Rep FinishReason x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cfrom :: forall x. FinishReason -> Rep FinishReason x
from :: forall x. FinishReason -> Rep FinishReason x
$cto :: forall x. Rep FinishReason x -> FinishReason
to :: forall x. Rep FinishReason x -> FinishReason
Generic, Int -> FinishReason -> ShowS
[FinishReason] -> ShowS
FinishReason -> String
(Int -> FinishReason -> ShowS)
-> (FinishReason -> String)
-> ([FinishReason] -> ShowS)
-> Show FinishReason
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> FinishReason -> ShowS
showsPrec :: Int -> FinishReason -> ShowS
$cshow :: FinishReason -> String
show :: FinishReason -> String
$cshowList :: [FinishReason] -> ShowS
showList :: [FinishReason] -> ShowS
Show)
instance FromJSON FinishReason where
parseJSON :: Value -> Parser FinishReason
parseJSON = Options -> Value -> Parser FinishReason
forall a.
(Generic a, GFromJSON Zero (Rep a)) =>
Options -> Value -> Parser a
genericParseJSON Options
messageOptions
data Token = Token
{ Token -> Text
token :: Text
, Token -> Double
logprob :: Double
, Token -> Maybe (Vector Word8)
bytes :: Maybe (Vector Word8)
, Token -> Maybe (Vector Token)
top_logprobs :: Maybe (Vector Token)
} deriving stock ((forall x. Token -> Rep Token x)
-> (forall x. Rep Token x -> Token) -> Generic Token
forall x. Rep Token x -> Token
forall x. Token -> Rep Token x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cfrom :: forall x. Token -> Rep Token x
from :: forall x. Token -> Rep Token x
$cto :: forall x. Rep Token x -> Token
to :: forall x. Rep Token x -> Token
Generic, Int -> Token -> ShowS
[Token] -> ShowS
Token -> String
(Int -> Token -> ShowS)
-> (Token -> String) -> ([Token] -> ShowS) -> Show Token
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> Token -> ShowS
showsPrec :: Int -> Token -> ShowS
$cshow :: Token -> String
show :: Token -> String
$cshowList :: [Token] -> ShowS
showList :: [Token] -> ShowS
Show)
deriving anyclass (Maybe Token
Value -> Parser [Token]
Value -> Parser Token
(Value -> Parser Token)
-> (Value -> Parser [Token]) -> Maybe Token -> FromJSON Token
forall a.
(Value -> Parser a)
-> (Value -> Parser [a]) -> Maybe a -> FromJSON a
$cparseJSON :: Value -> Parser Token
parseJSON :: Value -> Parser Token
$cparseJSONList :: Value -> Parser [Token]
parseJSONList :: Value -> Parser [Token]
$comittedField :: Maybe Token
omittedField :: Maybe Token
FromJSON)
data LogProbs = LogProbs
{ LogProbs -> Maybe (Vector Token)
content :: Maybe (Vector Token)
, LogProbs -> Maybe (Vector Token)
refusal :: Maybe (Vector Token)
} deriving stock ((forall x. LogProbs -> Rep LogProbs x)
-> (forall x. Rep LogProbs x -> LogProbs) -> Generic LogProbs
forall x. Rep LogProbs x -> LogProbs
forall x. LogProbs -> Rep LogProbs x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cfrom :: forall x. LogProbs -> Rep LogProbs x
from :: forall x. LogProbs -> Rep LogProbs x
$cto :: forall x. Rep LogProbs x -> LogProbs
to :: forall x. Rep LogProbs x -> LogProbs
Generic, Int -> LogProbs -> ShowS
[LogProbs] -> ShowS
LogProbs -> String
(Int -> LogProbs -> ShowS)
-> (LogProbs -> String) -> ([LogProbs] -> ShowS) -> Show LogProbs
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> LogProbs -> ShowS
showsPrec :: Int -> LogProbs -> ShowS
$cshow :: LogProbs -> String
show :: LogProbs -> String
$cshowList :: [LogProbs] -> ShowS
showList :: [LogProbs] -> ShowS
Show)
deriving anyclass (Maybe LogProbs
Value -> Parser [LogProbs]
Value -> Parser LogProbs
(Value -> Parser LogProbs)
-> (Value -> Parser [LogProbs])
-> Maybe LogProbs
-> FromJSON LogProbs
forall a.
(Value -> Parser a)
-> (Value -> Parser [a]) -> Maybe a -> FromJSON a
$cparseJSON :: Value -> Parser LogProbs
parseJSON :: Value -> Parser LogProbs
$cparseJSONList :: Value -> Parser [LogProbs]
parseJSONList :: Value -> Parser [LogProbs]
$comittedField :: Maybe LogProbs
omittedField :: Maybe LogProbs
FromJSON)
data Choice = Choice
{ Choice -> Text
finish_reason :: Text
, Choice -> Natural
index :: Natural
, Choice -> Message Text
message :: Message Text
, Choice -> Maybe LogProbs
logprobs :: Maybe LogProbs
} deriving stock ((forall x. Choice -> Rep Choice x)
-> (forall x. Rep Choice x -> Choice) -> Generic Choice
forall x. Rep Choice x -> Choice
forall x. Choice -> Rep Choice x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cfrom :: forall x. Choice -> Rep Choice x
from :: forall x. Choice -> Rep Choice x
$cto :: forall x. Rep Choice x -> Choice
to :: forall x. Rep Choice x -> Choice
Generic, Int -> Choice -> ShowS
[Choice] -> ShowS
Choice -> String
(Int -> Choice -> ShowS)
-> (Choice -> String) -> ([Choice] -> ShowS) -> Show Choice
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> Choice -> ShowS
showsPrec :: Int -> Choice -> ShowS
$cshow :: Choice -> String
show :: Choice -> String
$cshowList :: [Choice] -> ShowS
showList :: [Choice] -> ShowS
Show)
deriving anyclass (Maybe Choice
Value -> Parser [Choice]
Value -> Parser Choice
(Value -> Parser Choice)
-> (Value -> Parser [Choice]) -> Maybe Choice -> FromJSON Choice
forall a.
(Value -> Parser a)
-> (Value -> Parser [a]) -> Maybe a -> FromJSON a
$cparseJSON :: Value -> Parser Choice
parseJSON :: Value -> Parser Choice
$cparseJSONList :: Value -> Parser [Choice]
parseJSONList :: Value -> Parser [Choice]
$comittedField :: Maybe Choice
omittedField :: Maybe Choice
FromJSON)
data ChatCompletionObject = ChatCompletionObject
{ ChatCompletionObject -> Text
id :: Text
, ChatCompletionObject -> Vector Choice
choices :: Vector Choice
, ChatCompletionObject -> POSIXTime
created :: POSIXTime
, ChatCompletionObject -> Model
model :: Model
, ChatCompletionObject -> Maybe ServiceTier
service_tier :: Maybe ServiceTier
, ChatCompletionObject -> Text
system_fingerprint :: Text
, ChatCompletionObject -> Text
object :: Text
, ChatCompletionObject
-> Usage CompletionTokensDetails PromptTokensDetails
usage :: Usage CompletionTokensDetails PromptTokensDetails
} deriving stock ((forall x. ChatCompletionObject -> Rep ChatCompletionObject x)
-> (forall x. Rep ChatCompletionObject x -> ChatCompletionObject)
-> Generic ChatCompletionObject
forall x. Rep ChatCompletionObject x -> ChatCompletionObject
forall x. ChatCompletionObject -> Rep ChatCompletionObject x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cfrom :: forall x. ChatCompletionObject -> Rep ChatCompletionObject x
from :: forall x. ChatCompletionObject -> Rep ChatCompletionObject x
$cto :: forall x. Rep ChatCompletionObject x -> ChatCompletionObject
to :: forall x. Rep ChatCompletionObject x -> ChatCompletionObject
Generic, Int -> ChatCompletionObject -> ShowS
[ChatCompletionObject] -> ShowS
ChatCompletionObject -> String
(Int -> ChatCompletionObject -> ShowS)
-> (ChatCompletionObject -> String)
-> ([ChatCompletionObject] -> ShowS)
-> Show ChatCompletionObject
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> ChatCompletionObject -> ShowS
showsPrec :: Int -> ChatCompletionObject -> ShowS
$cshow :: ChatCompletionObject -> String
show :: ChatCompletionObject -> String
$cshowList :: [ChatCompletionObject] -> ShowS
showList :: [ChatCompletionObject] -> ShowS
Show)
deriving anyclass (Maybe ChatCompletionObject
Value -> Parser [ChatCompletionObject]
Value -> Parser ChatCompletionObject
(Value -> Parser ChatCompletionObject)
-> (Value -> Parser [ChatCompletionObject])
-> Maybe ChatCompletionObject
-> FromJSON ChatCompletionObject
forall a.
(Value -> Parser a)
-> (Value -> Parser [a]) -> Maybe a -> FromJSON a
$cparseJSON :: Value -> Parser ChatCompletionObject
parseJSON :: Value -> Parser ChatCompletionObject
$cparseJSONList :: Value -> Parser [ChatCompletionObject]
parseJSONList :: Value -> Parser [ChatCompletionObject]
$comittedField :: Maybe ChatCompletionObject
omittedField :: Maybe ChatCompletionObject
FromJSON)
type API =
"chat"
:> "completions"
:> ReqBody '[JSON] CreateChatCompletion
:> Post '[JSON] ChatCompletionObject