{-# LANGUAGE DeriveGeneric #-}
{-# LANGUAGE DuplicateRecordFields #-}
{-# LANGUAGE NamedFieldPuns #-}
{-# LANGUAGE OverloadedStrings #-}
{-# LANGUAGE RecordWildCards #-}
module Langchain.LLM.OpenAI
( OpenAI (..)
, ChatCompletionRequest (..)
, ChatCompletionResponse (..)
, Message (..)
, Role (..)
, MessageContent (..)
, TextContent (..)
, Tool_ (..)
, Function_ (..)
, ToolCall (..)
, FunctionCall_ (..)
, Usage (..)
, Choice (..)
, FinishReason (..)
, LogProbs (..)
, LogProbContent (..)
, TopLogProb (..)
, AudioConfig (..)
, AudioResponse (..)
, Modality (..)
, ToolChoice (..)
, SpecificToolChoice (..)
, ReasoningEffort (..)
, PredictionOutput (..)
, PredictionContent (..)
, ResponseFormat (..)
, StreamOptions (..)
, WebSearchOptions (..)
, UserLocation (..)
, ApproximateLocation (..)
, CompletionTokensDetails (..)
, PromptTokensDetails (..)
, createChatCompletion
, defaultChatCompletionRequest
, defaultMessage
) where
import Data.Aeson
import qualified Data.List.NonEmpty as NE
import Data.Map (Map)
import Data.Maybe (listToMaybe)
import Data.Text (Text)
import Data.Text.Encoding (encodeUtf8)
import GHC.Generics
import Langchain.Callback (Callback)
import qualified Langchain.LLM.Core as LLM
import Network.HTTP.Simple
import Network.HTTP.Types.Status (statusCode)
data Role
= User
| Assistant
| System
| Developer
| Tool
| Function
deriving (Int -> Role -> ShowS
[Role] -> ShowS
Role -> String
(Int -> Role -> ShowS)
-> (Role -> String) -> ([Role] -> ShowS) -> Show Role
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> Role -> ShowS
showsPrec :: Int -> Role -> ShowS
$cshow :: Role -> String
show :: Role -> String
$cshowList :: [Role] -> ShowS
showList :: [Role] -> ShowS
Show, Role -> Role -> Bool
(Role -> Role -> Bool) -> (Role -> Role -> Bool) -> Eq Role
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: Role -> Role -> Bool
== :: Role -> Role -> Bool
$c/= :: Role -> Role -> Bool
/= :: Role -> Role -> Bool
Eq, (forall x. Role -> Rep Role x)
-> (forall x. Rep Role x -> Role) -> Generic Role
forall x. Rep Role x -> Role
forall x. Role -> Rep Role x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cfrom :: forall x. Role -> Rep Role x
from :: forall x. Role -> Rep Role x
$cto :: forall x. Rep Role x -> Role
to :: forall x. Rep Role x -> Role
Generic)
instance ToJSON Role where
toJSON :: Role -> Value
toJSON Role
User = Text -> Value
String Text
"user"
toJSON Role
Assistant = Text -> Value
String Text
"assistant"
toJSON Role
System = Text -> Value
String Text
"system"
toJSON Role
Developer = Text -> Value
String Text
"developer"
toJSON Role
Tool = Text -> Value
String Text
"tool"
toJSON Role
Function = Text -> Value
String Text
"function"
instance FromJSON Role where
parseJSON :: Value -> Parser Role
parseJSON (String Text
"user") = Role -> Parser Role
forall a. a -> Parser a
forall (m :: * -> *) a. Monad m => a -> m a
return Role
User
parseJSON (String Text
"assistant") = Role -> Parser Role
forall a. a -> Parser a
forall (m :: * -> *) a. Monad m => a -> m a
return Role
Assistant
parseJSON (String Text
"system") = Role -> Parser Role
forall a. a -> Parser a
forall (m :: * -> *) a. Monad m => a -> m a
return Role
System
parseJSON (String Text
"developer") = Role -> Parser Role
forall a. a -> Parser a
forall (m :: * -> *) a. Monad m => a -> m a
return Role
Developer
parseJSON (String Text
"tool") = Role -> Parser Role
forall a. a -> Parser a
forall (m :: * -> *) a. Monad m => a -> m a
return Role
Tool
parseJSON (String Text
"function") = Role -> Parser Role
forall a. a -> Parser a
forall (m :: * -> *) a. Monad m => a -> m a
return Role
Function
parseJSON Value
invalid = String -> Parser Role
forall a. String -> Parser a
forall (m :: * -> *) a. MonadFail m => String -> m a
fail (String -> Parser Role) -> String -> Parser Role
forall a b. (a -> b) -> a -> b
$ String
"Invalid role: " String -> ShowS
forall a. [a] -> [a] -> [a]
++ Value -> String
forall a. Show a => a -> String
show Value
invalid
data TextContent = TextContent
{ TextContent -> Text
text_ :: Text
, TextContent -> Text
contentType :: Text
}
deriving (Int -> TextContent -> ShowS
[TextContent] -> ShowS
TextContent -> String
(Int -> TextContent -> ShowS)
-> (TextContent -> String)
-> ([TextContent] -> ShowS)
-> Show TextContent
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> TextContent -> ShowS
showsPrec :: Int -> TextContent -> ShowS
$cshow :: TextContent -> String
show :: TextContent -> String
$cshowList :: [TextContent] -> ShowS
showList :: [TextContent] -> ShowS
Show, TextContent -> TextContent -> Bool
(TextContent -> TextContent -> Bool)
-> (TextContent -> TextContent -> Bool) -> Eq TextContent
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: TextContent -> TextContent -> Bool
== :: TextContent -> TextContent -> Bool
$c/= :: TextContent -> TextContent -> Bool
/= :: TextContent -> TextContent -> Bool
Eq, (forall x. TextContent -> Rep TextContent x)
-> (forall x. Rep TextContent x -> TextContent)
-> Generic TextContent
forall x. Rep TextContent x -> TextContent
forall x. TextContent -> Rep TextContent x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cfrom :: forall x. TextContent -> Rep TextContent x
from :: forall x. TextContent -> Rep TextContent x
$cto :: forall x. Rep TextContent x -> TextContent
to :: forall x. Rep TextContent x -> TextContent
Generic)
instance ToJSON TextContent where
toJSON :: TextContent -> Value
toJSON TextContent {Text
$sel:text_:TextContent :: TextContent -> Text
$sel:contentType:TextContent :: TextContent -> Text
text_ :: Text
contentType :: Text
..} =
[Pair] -> Value
object
[ Key
"text" Key -> Text -> Pair
forall v. ToJSON v => Key -> v -> Pair
forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
.= Text
text_
, Key
"type" Key -> Text -> Pair
forall v. ToJSON v => Key -> v -> Pair
forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
.= Text
contentType
]
instance FromJSON TextContent where
parseJSON :: Value -> Parser TextContent
parseJSON = String
-> (Object -> Parser TextContent) -> Value -> Parser TextContent
forall a. String -> (Object -> Parser a) -> Value -> Parser a
withObject String
"TextContent" ((Object -> Parser TextContent) -> Value -> Parser TextContent)
-> (Object -> Parser TextContent) -> Value -> Parser TextContent
forall a b. (a -> b) -> a -> b
$ \Object
v ->
Text -> Text -> TextContent
TextContent
(Text -> Text -> TextContent)
-> Parser Text -> Parser (Text -> TextContent)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Object
v Object -> Key -> Parser Text
forall a. FromJSON a => Object -> Key -> Parser a
.: Key
"text"
Parser (Text -> TextContent) -> Parser Text -> Parser TextContent
forall a b. Parser (a -> b) -> Parser a -> Parser b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Object
v Object -> Key -> Parser Text
forall a. FromJSON a => Object -> Key -> Parser a
.: Key
"type"
data MessageContent
= StringContent Text
| ContentParts [TextContent]
deriving (Int -> MessageContent -> ShowS
[MessageContent] -> ShowS
MessageContent -> String
(Int -> MessageContent -> ShowS)
-> (MessageContent -> String)
-> ([MessageContent] -> ShowS)
-> Show MessageContent
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> MessageContent -> ShowS
showsPrec :: Int -> MessageContent -> ShowS
$cshow :: MessageContent -> String
show :: MessageContent -> String
$cshowList :: [MessageContent] -> ShowS
showList :: [MessageContent] -> ShowS
Show, MessageContent -> MessageContent -> Bool
(MessageContent -> MessageContent -> Bool)
-> (MessageContent -> MessageContent -> Bool) -> Eq MessageContent
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: MessageContent -> MessageContent -> Bool
== :: MessageContent -> MessageContent -> Bool
$c/= :: MessageContent -> MessageContent -> Bool
/= :: MessageContent -> MessageContent -> Bool
Eq, (forall x. MessageContent -> Rep MessageContent x)
-> (forall x. Rep MessageContent x -> MessageContent)
-> Generic MessageContent
forall x. Rep MessageContent x -> MessageContent
forall x. MessageContent -> Rep MessageContent x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cfrom :: forall x. MessageContent -> Rep MessageContent x
from :: forall x. MessageContent -> Rep MessageContent x
$cto :: forall x. Rep MessageContent x -> MessageContent
to :: forall x. Rep MessageContent x -> MessageContent
Generic)
instance ToJSON MessageContent where
toJSON :: MessageContent -> Value
toJSON (StringContent Text
text) = Text -> Value
String Text
text
toJSON (ContentParts [TextContent]
parts) = [TextContent] -> Value
forall a. ToJSON a => a -> Value
toJSON [TextContent]
parts
instance FromJSON MessageContent where
parseJSON :: Value -> Parser MessageContent
parseJSON (String Text
s) = MessageContent -> Parser MessageContent
forall a. a -> Parser a
forall (m :: * -> *) a. Monad m => a -> m a
return (MessageContent -> Parser MessageContent)
-> MessageContent -> Parser MessageContent
forall a b. (a -> b) -> a -> b
$ Text -> MessageContent
StringContent Text
s
parseJSON (Array Array
arr) = [TextContent] -> MessageContent
ContentParts ([TextContent] -> MessageContent)
-> Parser [TextContent] -> Parser MessageContent
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Value -> Parser [TextContent]
forall a. FromJSON a => Value -> Parser a
parseJSON (Array -> Value
Array Array
arr)
parseJSON Value
invalid = String -> Parser MessageContent
forall a. String -> Parser a
forall (m :: * -> *) a. MonadFail m => String -> m a
fail (String -> Parser MessageContent)
-> String -> Parser MessageContent
forall a b. (a -> b) -> a -> b
$ String
"Invalid message content: " String -> ShowS
forall a. [a] -> [a] -> [a]
++ Value -> String
forall a. Show a => a -> String
show Value
invalid
data Function_ = Function_
{ Function_ -> Text
name :: Text
, Function_ -> Maybe Text
description :: Maybe Text
, Function_ -> Maybe Value
parameters :: Maybe Value
, Function_ -> Maybe Bool
strict :: Maybe Bool
}
deriving (Int -> Function_ -> ShowS
[Function_] -> ShowS
Function_ -> String
(Int -> Function_ -> ShowS)
-> (Function_ -> String)
-> ([Function_] -> ShowS)
-> Show Function_
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> Function_ -> ShowS
showsPrec :: Int -> Function_ -> ShowS
$cshow :: Function_ -> String
show :: Function_ -> String
$cshowList :: [Function_] -> ShowS
showList :: [Function_] -> ShowS
Show, Function_ -> Function_ -> Bool
(Function_ -> Function_ -> Bool)
-> (Function_ -> Function_ -> Bool) -> Eq Function_
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: Function_ -> Function_ -> Bool
== :: Function_ -> Function_ -> Bool
$c/= :: Function_ -> Function_ -> Bool
/= :: Function_ -> Function_ -> Bool
Eq, (forall x. Function_ -> Rep Function_ x)
-> (forall x. Rep Function_ x -> Function_) -> Generic Function_
forall x. Rep Function_ x -> Function_
forall x. Function_ -> Rep Function_ x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cfrom :: forall x. Function_ -> Rep Function_ x
from :: forall x. Function_ -> Rep Function_ x
$cto :: forall x. Rep Function_ x -> Function_
to :: forall x. Rep Function_ x -> Function_
Generic)
instance ToJSON Function_ where
toJSON :: Function_ -> Value
toJSON Function_ {Maybe Bool
Maybe Value
Maybe Text
Text
$sel:name:Function_ :: Function_ -> Text
$sel:description:Function_ :: Function_ -> Maybe Text
$sel:parameters:Function_ :: Function_ -> Maybe Value
$sel:strict:Function_ :: Function_ -> Maybe Bool
name :: Text
description :: Maybe Text
parameters :: Maybe Value
strict :: Maybe Bool
..} =
[Pair] -> Value
object ([Pair] -> Value) -> [Pair] -> Value
forall a b. (a -> b) -> a -> b
$
[ Key
"name" Key -> Text -> Pair
forall v. ToJSON v => Key -> v -> Pair
forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
.= Text
name
]
[Pair] -> [Pair] -> [Pair]
forall a. [a] -> [a] -> [a]
++ [Pair] -> (Text -> [Pair]) -> Maybe Text -> [Pair]
forall b a. b -> (a -> b) -> Maybe a -> b
maybe [] (\Text
d -> [Key
"description" Key -> Text -> Pair
forall v. ToJSON v => Key -> v -> Pair
forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
.= Text
d]) Maybe Text
description
[Pair] -> [Pair] -> [Pair]
forall a. [a] -> [a] -> [a]
++ [Pair] -> (Value -> [Pair]) -> Maybe Value -> [Pair]
forall b a. b -> (a -> b) -> Maybe a -> b
maybe [] (\Value
p -> [Key
"parameters" Key -> Value -> Pair
forall v. ToJSON v => Key -> v -> Pair
forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
.= Value
p]) Maybe Value
parameters
[Pair] -> [Pair] -> [Pair]
forall a. [a] -> [a] -> [a]
++ [Pair] -> (Bool -> [Pair]) -> Maybe Bool -> [Pair]
forall b a. b -> (a -> b) -> Maybe a -> b
maybe [] (\Bool
s -> [Key
"strict" Key -> Bool -> Pair
forall v. ToJSON v => Key -> v -> Pair
forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
.= Bool
s]) Maybe Bool
strict
instance FromJSON Function_ where
parseJSON :: Value -> Parser Function_
parseJSON = String -> (Object -> Parser Function_) -> Value -> Parser Function_
forall a. String -> (Object -> Parser a) -> Value -> Parser a
withObject String
"Function" ((Object -> Parser Function_) -> Value -> Parser Function_)
-> (Object -> Parser Function_) -> Value -> Parser Function_
forall a b. (a -> b) -> a -> b
$ \Object
v ->
Text -> Maybe Text -> Maybe Value -> Maybe Bool -> Function_
Function_
(Text -> Maybe Text -> Maybe Value -> Maybe Bool -> Function_)
-> Parser Text
-> Parser (Maybe Text -> Maybe Value -> Maybe Bool -> Function_)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Object
v Object -> Key -> Parser Text
forall a. FromJSON a => Object -> Key -> Parser a
.: Key
"name"
Parser (Maybe Text -> Maybe Value -> Maybe Bool -> Function_)
-> Parser (Maybe Text)
-> Parser (Maybe Value -> Maybe Bool -> Function_)
forall a b. Parser (a -> b) -> Parser a -> Parser b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Object
v Object -> Key -> Parser (Maybe Text)
forall a. FromJSON a => Object -> Key -> Parser (Maybe a)
.:? Key
"description"
Parser (Maybe Value -> Maybe Bool -> Function_)
-> Parser (Maybe Value) -> Parser (Maybe Bool -> Function_)
forall a b. Parser (a -> b) -> Parser a -> Parser b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Object
v Object -> Key -> Parser (Maybe Value)
forall a. FromJSON a => Object -> Key -> Parser (Maybe a)
.:? Key
"parameters"
Parser (Maybe Bool -> Function_)
-> Parser (Maybe Bool) -> Parser Function_
forall a b. Parser (a -> b) -> Parser a -> Parser b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Object
v Object -> Key -> Parser (Maybe Bool)
forall a. FromJSON a => Object -> Key -> Parser (Maybe a)
.:? Key
"strict"
data Tool_ = Tool_
{ Tool_ -> Text
toolType :: Text
, Tool_ -> Function_
function :: Function_
}
deriving (Int -> Tool_ -> ShowS
[Tool_] -> ShowS
Tool_ -> String
(Int -> Tool_ -> ShowS)
-> (Tool_ -> String) -> ([Tool_] -> ShowS) -> Show Tool_
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> Tool_ -> ShowS
showsPrec :: Int -> Tool_ -> ShowS
$cshow :: Tool_ -> String
show :: Tool_ -> String
$cshowList :: [Tool_] -> ShowS
showList :: [Tool_] -> ShowS
Show, Tool_ -> Tool_ -> Bool
(Tool_ -> Tool_ -> Bool) -> (Tool_ -> Tool_ -> Bool) -> Eq Tool_
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: Tool_ -> Tool_ -> Bool
== :: Tool_ -> Tool_ -> Bool
$c/= :: Tool_ -> Tool_ -> Bool
/= :: Tool_ -> Tool_ -> Bool
Eq, (forall x. Tool_ -> Rep Tool_ x)
-> (forall x. Rep Tool_ x -> Tool_) -> Generic Tool_
forall x. Rep Tool_ x -> Tool_
forall x. Tool_ -> Rep Tool_ x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cfrom :: forall x. Tool_ -> Rep Tool_ x
from :: forall x. Tool_ -> Rep Tool_ x
$cto :: forall x. Rep Tool_ x -> Tool_
to :: forall x. Rep Tool_ x -> Tool_
Generic)
instance ToJSON Tool_ where
toJSON :: Tool_ -> Value
toJSON Tool_ {Text
Function_
$sel:toolType:Tool_ :: Tool_ -> Text
$sel:function:Tool_ :: Tool_ -> Function_
toolType :: Text
function :: Function_
..} =
[Pair] -> Value
object
[ Key
"type" Key -> Text -> Pair
forall v. ToJSON v => Key -> v -> Pair
forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
.= Text
toolType
, Key
"function" Key -> Function_ -> Pair
forall v. ToJSON v => Key -> v -> Pair
forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
.= Function_
function
]
instance FromJSON Tool_ where
parseJSON :: Value -> Parser Tool_
parseJSON = String -> (Object -> Parser Tool_) -> Value -> Parser Tool_
forall a. String -> (Object -> Parser a) -> Value -> Parser a
withObject String
"Tool" ((Object -> Parser Tool_) -> Value -> Parser Tool_)
-> (Object -> Parser Tool_) -> Value -> Parser Tool_
forall a b. (a -> b) -> a -> b
$ \Object
v ->
Text -> Function_ -> Tool_
Tool_
(Text -> Function_ -> Tool_)
-> Parser Text -> Parser (Function_ -> Tool_)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Object
v Object -> Key -> Parser Text
forall a. FromJSON a => Object -> Key -> Parser a
.: Key
"type"
Parser (Function_ -> Tool_) -> Parser Function_ -> Parser Tool_
forall a b. Parser (a -> b) -> Parser a -> Parser b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Object
v Object -> Key -> Parser Function_
forall a. FromJSON a => Object -> Key -> Parser a
.: Key
"function"
data FunctionCall_ = FunctionCall_
{ FunctionCall_ -> Text
name :: Text
, FunctionCall_ -> Text
arguments :: Text
}
deriving (Int -> FunctionCall_ -> ShowS
[FunctionCall_] -> ShowS
FunctionCall_ -> String
(Int -> FunctionCall_ -> ShowS)
-> (FunctionCall_ -> String)
-> ([FunctionCall_] -> ShowS)
-> Show FunctionCall_
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> FunctionCall_ -> ShowS
showsPrec :: Int -> FunctionCall_ -> ShowS
$cshow :: FunctionCall_ -> String
show :: FunctionCall_ -> String
$cshowList :: [FunctionCall_] -> ShowS
showList :: [FunctionCall_] -> ShowS
Show, FunctionCall_ -> FunctionCall_ -> Bool
(FunctionCall_ -> FunctionCall_ -> Bool)
-> (FunctionCall_ -> FunctionCall_ -> Bool) -> Eq FunctionCall_
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: FunctionCall_ -> FunctionCall_ -> Bool
== :: FunctionCall_ -> FunctionCall_ -> Bool
$c/= :: FunctionCall_ -> FunctionCall_ -> Bool
/= :: FunctionCall_ -> FunctionCall_ -> Bool
Eq, (forall x. FunctionCall_ -> Rep FunctionCall_ x)
-> (forall x. Rep FunctionCall_ x -> FunctionCall_)
-> Generic FunctionCall_
forall x. Rep FunctionCall_ x -> FunctionCall_
forall x. FunctionCall_ -> Rep FunctionCall_ x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cfrom :: forall x. FunctionCall_ -> Rep FunctionCall_ x
from :: forall x. FunctionCall_ -> Rep FunctionCall_ x
$cto :: forall x. Rep FunctionCall_ x -> FunctionCall_
to :: forall x. Rep FunctionCall_ x -> FunctionCall_
Generic)
instance ToJSON FunctionCall_ where
toJSON :: FunctionCall_ -> Value
toJSON FunctionCall_ {Text
$sel:name:FunctionCall_ :: FunctionCall_ -> Text
$sel:arguments:FunctionCall_ :: FunctionCall_ -> Text
name :: Text
arguments :: Text
..} =
[Pair] -> Value
object
[ Key
"name" Key -> Text -> Pair
forall v. ToJSON v => Key -> v -> Pair
forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
.= Text
name
, Key
"arguments" Key -> Text -> Pair
forall v. ToJSON v => Key -> v -> Pair
forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
.= Text
arguments
]
instance FromJSON FunctionCall_ where
parseJSON :: Value -> Parser FunctionCall_
parseJSON = String
-> (Object -> Parser FunctionCall_)
-> Value
-> Parser FunctionCall_
forall a. String -> (Object -> Parser a) -> Value -> Parser a
withObject String
"FunctionCall" ((Object -> Parser FunctionCall_) -> Value -> Parser FunctionCall_)
-> (Object -> Parser FunctionCall_)
-> Value
-> Parser FunctionCall_
forall a b. (a -> b) -> a -> b
$ \Object
v ->
Text -> Text -> FunctionCall_
FunctionCall_
(Text -> Text -> FunctionCall_)
-> Parser Text -> Parser (Text -> FunctionCall_)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Object
v Object -> Key -> Parser Text
forall a. FromJSON a => Object -> Key -> Parser a
.: Key
"name"
Parser (Text -> FunctionCall_)
-> Parser Text -> Parser FunctionCall_
forall a b. Parser (a -> b) -> Parser a -> Parser b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Object
v Object -> Key -> Parser Text
forall a. FromJSON a => Object -> Key -> Parser a
.: Key
"arguments"
data ToolCall = ToolCall
{ ToolCall -> Text
id_ :: Text
, ToolCall -> Text
toolType :: Text
, ToolCall -> FunctionCall_
function :: FunctionCall_
}
deriving (Int -> ToolCall -> ShowS
[ToolCall] -> ShowS
ToolCall -> String
(Int -> ToolCall -> ShowS)
-> (ToolCall -> String) -> ([ToolCall] -> ShowS) -> Show ToolCall
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> ToolCall -> ShowS
showsPrec :: Int -> ToolCall -> ShowS
$cshow :: ToolCall -> String
show :: ToolCall -> String
$cshowList :: [ToolCall] -> ShowS
showList :: [ToolCall] -> ShowS
Show, ToolCall -> ToolCall -> Bool
(ToolCall -> ToolCall -> Bool)
-> (ToolCall -> ToolCall -> Bool) -> Eq ToolCall
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: ToolCall -> ToolCall -> Bool
== :: ToolCall -> ToolCall -> Bool
$c/= :: ToolCall -> ToolCall -> Bool
/= :: ToolCall -> ToolCall -> Bool
Eq, (forall x. ToolCall -> Rep ToolCall x)
-> (forall x. Rep ToolCall x -> ToolCall) -> Generic ToolCall
forall x. Rep ToolCall x -> ToolCall
forall x. ToolCall -> Rep ToolCall x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cfrom :: forall x. ToolCall -> Rep ToolCall x
from :: forall x. ToolCall -> Rep ToolCall x
$cto :: forall x. Rep ToolCall x -> ToolCall
to :: forall x. Rep ToolCall x -> ToolCall
Generic)
instance ToJSON ToolCall where
toJSON :: ToolCall -> Value
toJSON ToolCall {Text
FunctionCall_
$sel:id_:ToolCall :: ToolCall -> Text
$sel:toolType:ToolCall :: ToolCall -> Text
$sel:function:ToolCall :: ToolCall -> FunctionCall_
id_ :: Text
toolType :: Text
function :: FunctionCall_
..} =
[Pair] -> Value
object
[ Key
"id" Key -> Text -> Pair
forall v. ToJSON v => Key -> v -> Pair
forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
.= Text
id_
, Key
"type" Key -> Text -> Pair
forall v. ToJSON v => Key -> v -> Pair
forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
.= Text
toolType
, Key
"function" Key -> FunctionCall_ -> Pair
forall v. ToJSON v => Key -> v -> Pair
forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
.= FunctionCall_
function
]
instance FromJSON ToolCall where
parseJSON :: Value -> Parser ToolCall
parseJSON = String -> (Object -> Parser ToolCall) -> Value -> Parser ToolCall
forall a. String -> (Object -> Parser a) -> Value -> Parser a
withObject String
"ToolCall" ((Object -> Parser ToolCall) -> Value -> Parser ToolCall)
-> (Object -> Parser ToolCall) -> Value -> Parser ToolCall
forall a b. (a -> b) -> a -> b
$ \Object
v ->
Text -> Text -> FunctionCall_ -> ToolCall
ToolCall
(Text -> Text -> FunctionCall_ -> ToolCall)
-> Parser Text -> Parser (Text -> FunctionCall_ -> ToolCall)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Object
v Object -> Key -> Parser Text
forall a. FromJSON a => Object -> Key -> Parser a
.: Key
"id"
Parser (Text -> FunctionCall_ -> ToolCall)
-> Parser Text -> Parser (FunctionCall_ -> ToolCall)
forall a b. Parser (a -> b) -> Parser a -> Parser b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Object
v Object -> Key -> Parser Text
forall a. FromJSON a => Object -> Key -> Parser a
.: Key
"type"
Parser (FunctionCall_ -> ToolCall)
-> Parser FunctionCall_ -> Parser ToolCall
forall a b. Parser (a -> b) -> Parser a -> Parser b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Object
v Object -> Key -> Parser FunctionCall_
forall a. FromJSON a => Object -> Key -> Parser a
.: Key
"function"
data AudioConfig = AudioConfig
{ AudioConfig -> Text
format :: Text
, AudioConfig -> Text
voice :: Text
}
deriving (Int -> AudioConfig -> ShowS
[AudioConfig] -> ShowS
AudioConfig -> String
(Int -> AudioConfig -> ShowS)
-> (AudioConfig -> String)
-> ([AudioConfig] -> ShowS)
-> Show AudioConfig
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> AudioConfig -> ShowS
showsPrec :: Int -> AudioConfig -> ShowS
$cshow :: AudioConfig -> String
show :: AudioConfig -> String
$cshowList :: [AudioConfig] -> ShowS
showList :: [AudioConfig] -> ShowS
Show, AudioConfig -> AudioConfig -> Bool
(AudioConfig -> AudioConfig -> Bool)
-> (AudioConfig -> AudioConfig -> Bool) -> Eq AudioConfig
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: AudioConfig -> AudioConfig -> Bool
== :: AudioConfig -> AudioConfig -> Bool
$c/= :: AudioConfig -> AudioConfig -> Bool
/= :: AudioConfig -> AudioConfig -> Bool
Eq, (forall x. AudioConfig -> Rep AudioConfig x)
-> (forall x. Rep AudioConfig x -> AudioConfig)
-> Generic AudioConfig
forall x. Rep AudioConfig x -> AudioConfig
forall x. AudioConfig -> Rep AudioConfig x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cfrom :: forall x. AudioConfig -> Rep AudioConfig x
from :: forall x. AudioConfig -> Rep AudioConfig x
$cto :: forall x. Rep AudioConfig x -> AudioConfig
to :: forall x. Rep AudioConfig x -> AudioConfig
Generic)
instance ToJSON AudioConfig where
toJSON :: AudioConfig -> Value
toJSON AudioConfig {Text
$sel:format:AudioConfig :: AudioConfig -> Text
$sel:voice:AudioConfig :: AudioConfig -> Text
format :: Text
voice :: Text
..} =
[Pair] -> Value
object
[ Key
"format" Key -> Text -> Pair
forall v. ToJSON v => Key -> v -> Pair
forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
.= Text
format
, Key
"voice" Key -> Text -> Pair
forall v. ToJSON v => Key -> v -> Pair
forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
.= Text
voice
]
instance FromJSON AudioConfig where
parseJSON :: Value -> Parser AudioConfig
parseJSON = String
-> (Object -> Parser AudioConfig) -> Value -> Parser AudioConfig
forall a. String -> (Object -> Parser a) -> Value -> Parser a
withObject String
"AudioConfig" ((Object -> Parser AudioConfig) -> Value -> Parser AudioConfig)
-> (Object -> Parser AudioConfig) -> Value -> Parser AudioConfig
forall a b. (a -> b) -> a -> b
$ \Object
v ->
Text -> Text -> AudioConfig
AudioConfig
(Text -> Text -> AudioConfig)
-> Parser Text -> Parser (Text -> AudioConfig)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Object
v Object -> Key -> Parser Text
forall a. FromJSON a => Object -> Key -> Parser a
.: Key
"format"
Parser (Text -> AudioConfig) -> Parser Text -> Parser AudioConfig
forall a b. Parser (a -> b) -> Parser a -> Parser b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Object
v Object -> Key -> Parser Text
forall a. FromJSON a => Object -> Key -> Parser a
.: Key
"voice"
data AudioResponse = AudioResponse
{ AudioResponse -> Text
data_ :: Text
, AudioResponse -> Integer
expiresAt :: Integer
, AudioResponse -> Text
id_ :: Text
, AudioResponse -> Text
transcript :: Text
}
deriving (Int -> AudioResponse -> ShowS
[AudioResponse] -> ShowS
AudioResponse -> String
(Int -> AudioResponse -> ShowS)
-> (AudioResponse -> String)
-> ([AudioResponse] -> ShowS)
-> Show AudioResponse
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> AudioResponse -> ShowS
showsPrec :: Int -> AudioResponse -> ShowS
$cshow :: AudioResponse -> String
show :: AudioResponse -> String
$cshowList :: [AudioResponse] -> ShowS
showList :: [AudioResponse] -> ShowS
Show, AudioResponse -> AudioResponse -> Bool
(AudioResponse -> AudioResponse -> Bool)
-> (AudioResponse -> AudioResponse -> Bool) -> Eq AudioResponse
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: AudioResponse -> AudioResponse -> Bool
== :: AudioResponse -> AudioResponse -> Bool
$c/= :: AudioResponse -> AudioResponse -> Bool
/= :: AudioResponse -> AudioResponse -> Bool
Eq, (forall x. AudioResponse -> Rep AudioResponse x)
-> (forall x. Rep AudioResponse x -> AudioResponse)
-> Generic AudioResponse
forall x. Rep AudioResponse x -> AudioResponse
forall x. AudioResponse -> Rep AudioResponse x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cfrom :: forall x. AudioResponse -> Rep AudioResponse x
from :: forall x. AudioResponse -> Rep AudioResponse x
$cto :: forall x. Rep AudioResponse x -> AudioResponse
to :: forall x. Rep AudioResponse x -> AudioResponse
Generic)
instance ToJSON AudioResponse where
toJSON :: AudioResponse -> Value
toJSON AudioResponse {Integer
Text
$sel:data_:AudioResponse :: AudioResponse -> Text
$sel:expiresAt:AudioResponse :: AudioResponse -> Integer
$sel:id_:AudioResponse :: AudioResponse -> Text
$sel:transcript:AudioResponse :: AudioResponse -> Text
data_ :: Text
expiresAt :: Integer
id_ :: Text
transcript :: Text
..} =
[Pair] -> Value
object
[ Key
"data" Key -> Text -> Pair
forall v. ToJSON v => Key -> v -> Pair
forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
.= Text
data_
, Key
"expires_at" Key -> Integer -> Pair
forall v. ToJSON v => Key -> v -> Pair
forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
.= Integer
expiresAt
, Key
"id" Key -> Text -> Pair
forall v. ToJSON v => Key -> v -> Pair
forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
.= Text
id_
, Key
"transcript" Key -> Text -> Pair
forall v. ToJSON v => Key -> v -> Pair
forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
.= Text
transcript
]
instance FromJSON AudioResponse where
parseJSON :: Value -> Parser AudioResponse
parseJSON = String
-> (Object -> Parser AudioResponse)
-> Value
-> Parser AudioResponse
forall a. String -> (Object -> Parser a) -> Value -> Parser a
withObject String
"AudioResponse" ((Object -> Parser AudioResponse) -> Value -> Parser AudioResponse)
-> (Object -> Parser AudioResponse)
-> Value
-> Parser AudioResponse
forall a b. (a -> b) -> a -> b
$ \Object
v ->
Text -> Integer -> Text -> Text -> AudioResponse
AudioResponse
(Text -> Integer -> Text -> Text -> AudioResponse)
-> Parser Text -> Parser (Integer -> Text -> Text -> AudioResponse)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Object
v Object -> Key -> Parser Text
forall a. FromJSON a => Object -> Key -> Parser a
.: Key
"data"
Parser (Integer -> Text -> Text -> AudioResponse)
-> Parser Integer -> Parser (Text -> Text -> AudioResponse)
forall a b. Parser (a -> b) -> Parser a -> Parser b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Object
v Object -> Key -> Parser Integer
forall a. FromJSON a => Object -> Key -> Parser a
.: Key
"expires_at"
Parser (Text -> Text -> AudioResponse)
-> Parser Text -> Parser (Text -> AudioResponse)
forall a b. Parser (a -> b) -> Parser a -> Parser b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Object
v Object -> Key -> Parser Text
forall a. FromJSON a => Object -> Key -> Parser a
.: Key
"id"
Parser (Text -> AudioResponse)
-> Parser Text -> Parser AudioResponse
forall a b. Parser (a -> b) -> Parser a -> Parser b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Object
v Object -> Key -> Parser Text
forall a. FromJSON a => Object -> Key -> Parser a
.: Key
"transcript"
data Message = Message
{ Message -> Role
role :: Role
, Message -> Maybe MessageContent
content :: Maybe MessageContent
, Message -> Maybe Text
name :: Maybe Text
, Message -> Maybe FunctionCall_
functionCall :: Maybe FunctionCall_
, Message -> Maybe [ToolCall]
toolCalls :: Maybe [ToolCall]
, Message -> Maybe Text
toolCallId :: Maybe Text
, Message -> Maybe AudioResponse
audio :: Maybe AudioResponse
, Message -> Maybe Text
refusal :: Maybe Text
}
deriving (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, Message -> Message -> Bool
(Message -> Message -> Bool)
-> (Message -> Message -> Bool) -> Eq Message
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: Message -> Message -> Bool
== :: Message -> Message -> Bool
$c/= :: Message -> Message -> Bool
/= :: Message -> Message -> Bool
Eq, (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)
defaultMessage :: Message
defaultMessage :: Message
defaultMessage =
Message
{ $sel:role:Message :: Role
role = Role
User
, $sel:content:Message :: Maybe MessageContent
content = Maybe MessageContent
forall a. Maybe a
Nothing
, $sel:name:Message :: Maybe Text
name = Maybe Text
forall a. Maybe a
Nothing
, $sel:functionCall:Message :: Maybe FunctionCall_
functionCall = Maybe FunctionCall_
forall a. Maybe a
Nothing
, $sel:toolCalls:Message :: Maybe [ToolCall]
toolCalls = Maybe [ToolCall]
forall a. Maybe a
Nothing
, $sel:toolCallId:Message :: Maybe Text
toolCallId = Maybe Text
forall a. Maybe a
Nothing
, $sel:audio:Message :: Maybe AudioResponse
audio = Maybe AudioResponse
forall a. Maybe a
Nothing
, $sel:refusal:Message :: Maybe Text
refusal = Maybe Text
forall a. Maybe a
Nothing
}
instance ToJSON Message where
toJSON :: Message -> Value
toJSON Message {Maybe [ToolCall]
Maybe Text
Maybe AudioResponse
Maybe FunctionCall_
Maybe MessageContent
Role
$sel:role:Message :: Message -> Role
$sel:content:Message :: Message -> Maybe MessageContent
$sel:name:Message :: Message -> Maybe Text
$sel:functionCall:Message :: Message -> Maybe FunctionCall_
$sel:toolCalls:Message :: Message -> Maybe [ToolCall]
$sel:toolCallId:Message :: Message -> Maybe Text
$sel:audio:Message :: Message -> Maybe AudioResponse
$sel:refusal:Message :: Message -> Maybe Text
role :: Role
content :: Maybe MessageContent
name :: Maybe Text
functionCall :: Maybe FunctionCall_
toolCalls :: Maybe [ToolCall]
toolCallId :: Maybe Text
audio :: Maybe AudioResponse
refusal :: Maybe Text
..} =
[Pair] -> Value
object ([Pair] -> Value) -> [Pair] -> Value
forall a b. (a -> b) -> a -> b
$
[Key
"role" Key -> Role -> Pair
forall v. ToJSON v => Key -> v -> Pair
forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
.= Role
role]
[Pair] -> [Pair] -> [Pair]
forall a. [a] -> [a] -> [a]
++ [Pair]
-> (MessageContent -> [Pair]) -> Maybe MessageContent -> [Pair]
forall b a. b -> (a -> b) -> Maybe a -> b
maybe [] (\MessageContent
c -> [Key
"content" Key -> MessageContent -> Pair
forall v. ToJSON v => Key -> v -> Pair
forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
.= MessageContent
c]) Maybe MessageContent
content
[Pair] -> [Pair] -> [Pair]
forall a. [a] -> [a] -> [a]
++ [Pair] -> (Text -> [Pair]) -> Maybe Text -> [Pair]
forall b a. b -> (a -> b) -> Maybe a -> b
maybe [] (\Text
n -> [Key
"name" Key -> Text -> Pair
forall v. ToJSON v => Key -> v -> Pair
forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
.= Text
n]) Maybe Text
name
[Pair] -> [Pair] -> [Pair]
forall a. [a] -> [a] -> [a]
++ [Pair]
-> (FunctionCall_ -> [Pair]) -> Maybe FunctionCall_ -> [Pair]
forall b a. b -> (a -> b) -> Maybe a -> b
maybe [] (\FunctionCall_
fc -> [Key
"function_call" Key -> FunctionCall_ -> Pair
forall v. ToJSON v => Key -> v -> Pair
forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
.= FunctionCall_
fc]) Maybe FunctionCall_
functionCall
[Pair] -> [Pair] -> [Pair]
forall a. [a] -> [a] -> [a]
++ [Pair] -> ([ToolCall] -> [Pair]) -> Maybe [ToolCall] -> [Pair]
forall b a. b -> (a -> b) -> Maybe a -> b
maybe [] (\[ToolCall]
tc -> [Key
"tool_calls" Key -> [ToolCall] -> Pair
forall v. ToJSON v => Key -> v -> Pair
forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
.= [ToolCall]
tc]) Maybe [ToolCall]
toolCalls
[Pair] -> [Pair] -> [Pair]
forall a. [a] -> [a] -> [a]
++ [Pair] -> (Text -> [Pair]) -> Maybe Text -> [Pair]
forall b a. b -> (a -> b) -> Maybe a -> b
maybe [] (\Text
tcid -> [Key
"tool_call_id" Key -> Text -> Pair
forall v. ToJSON v => Key -> v -> Pair
forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
.= Text
tcid]) Maybe Text
toolCallId
[Pair] -> [Pair] -> [Pair]
forall a. [a] -> [a] -> [a]
++ [Pair]
-> (AudioResponse -> [Pair]) -> Maybe AudioResponse -> [Pair]
forall b a. b -> (a -> b) -> Maybe a -> b
maybe [] (\AudioResponse
a -> [Key
"audio" Key -> AudioResponse -> Pair
forall v. ToJSON v => Key -> v -> Pair
forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
.= AudioResponse
a]) Maybe AudioResponse
audio
[Pair] -> [Pair] -> [Pair]
forall a. [a] -> [a] -> [a]
++ [Pair] -> (Text -> [Pair]) -> Maybe Text -> [Pair]
forall b a. b -> (a -> b) -> Maybe a -> b
maybe [] (\Text
r -> [Key
"refusal" Key -> Text -> Pair
forall v. ToJSON v => Key -> v -> Pair
forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
.= Text
r]) Maybe Text
refusal
instance FromJSON Message where
parseJSON :: Value -> Parser Message
parseJSON = String -> (Object -> Parser Message) -> Value -> Parser Message
forall a. String -> (Object -> Parser a) -> Value -> Parser a
withObject String
"Message" ((Object -> Parser Message) -> Value -> Parser Message)
-> (Object -> Parser Message) -> Value -> Parser Message
forall a b. (a -> b) -> a -> b
$ \Object
v ->
Role
-> Maybe MessageContent
-> Maybe Text
-> Maybe FunctionCall_
-> Maybe [ToolCall]
-> Maybe Text
-> Maybe AudioResponse
-> Maybe Text
-> Message
Message
(Role
-> Maybe MessageContent
-> Maybe Text
-> Maybe FunctionCall_
-> Maybe [ToolCall]
-> Maybe Text
-> Maybe AudioResponse
-> Maybe Text
-> Message)
-> Parser Role
-> Parser
(Maybe MessageContent
-> Maybe Text
-> Maybe FunctionCall_
-> Maybe [ToolCall]
-> Maybe Text
-> Maybe AudioResponse
-> Maybe Text
-> Message)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Object
v Object -> Key -> Parser Role
forall a. FromJSON a => Object -> Key -> Parser a
.: Key
"role"
Parser
(Maybe MessageContent
-> Maybe Text
-> Maybe FunctionCall_
-> Maybe [ToolCall]
-> Maybe Text
-> Maybe AudioResponse
-> Maybe Text
-> Message)
-> Parser (Maybe MessageContent)
-> Parser
(Maybe Text
-> Maybe FunctionCall_
-> Maybe [ToolCall]
-> Maybe Text
-> Maybe AudioResponse
-> Maybe Text
-> Message)
forall a b. Parser (a -> b) -> Parser a -> Parser b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Object
v Object -> Key -> Parser (Maybe MessageContent)
forall a. FromJSON a => Object -> Key -> Parser (Maybe a)
.:? Key
"content"
Parser
(Maybe Text
-> Maybe FunctionCall_
-> Maybe [ToolCall]
-> Maybe Text
-> Maybe AudioResponse
-> Maybe Text
-> Message)
-> Parser (Maybe Text)
-> Parser
(Maybe FunctionCall_
-> Maybe [ToolCall]
-> Maybe Text
-> Maybe AudioResponse
-> Maybe Text
-> Message)
forall a b. Parser (a -> b) -> Parser a -> Parser b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Object
v Object -> Key -> Parser (Maybe Text)
forall a. FromJSON a => Object -> Key -> Parser (Maybe a)
.:? Key
"name"
Parser
(Maybe FunctionCall_
-> Maybe [ToolCall]
-> Maybe Text
-> Maybe AudioResponse
-> Maybe Text
-> Message)
-> Parser (Maybe FunctionCall_)
-> Parser
(Maybe [ToolCall]
-> Maybe Text -> Maybe AudioResponse -> Maybe Text -> Message)
forall a b. Parser (a -> b) -> Parser a -> Parser b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Object
v Object -> Key -> Parser (Maybe FunctionCall_)
forall a. FromJSON a => Object -> Key -> Parser (Maybe a)
.:? Key
"function_call"
Parser
(Maybe [ToolCall]
-> Maybe Text -> Maybe AudioResponse -> Maybe Text -> Message)
-> Parser (Maybe [ToolCall])
-> Parser
(Maybe Text -> Maybe AudioResponse -> Maybe Text -> Message)
forall a b. Parser (a -> b) -> Parser a -> Parser b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Object
v Object -> Key -> Parser (Maybe [ToolCall])
forall a. FromJSON a => Object -> Key -> Parser (Maybe a)
.:? Key
"tool_calls"
Parser (Maybe Text -> Maybe AudioResponse -> Maybe Text -> Message)
-> Parser (Maybe Text)
-> Parser (Maybe AudioResponse -> Maybe Text -> Message)
forall a b. Parser (a -> b) -> Parser a -> Parser b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Object
v Object -> Key -> Parser (Maybe Text)
forall a. FromJSON a => Object -> Key -> Parser (Maybe a)
.:? Key
"tool_call_id"
Parser (Maybe AudioResponse -> Maybe Text -> Message)
-> Parser (Maybe AudioResponse) -> Parser (Maybe Text -> Message)
forall a b. Parser (a -> b) -> Parser a -> Parser b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Object
v Object -> Key -> Parser (Maybe AudioResponse)
forall a. FromJSON a => Object -> Key -> Parser (Maybe a)
.:? Key
"audio"
Parser (Maybe Text -> Message)
-> Parser (Maybe Text) -> Parser Message
forall a b. Parser (a -> b) -> Parser a -> Parser b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Object
v Object -> Key -> Parser (Maybe Text)
forall a. FromJSON a => Object -> Key -> Parser (Maybe a)
.:? Key
"refusal"
data Modality = TextModality | AudioModality
deriving (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, Modality -> Modality -> Bool
(Modality -> Modality -> Bool)
-> (Modality -> Modality -> Bool) -> Eq Modality
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: Modality -> Modality -> Bool
== :: Modality -> Modality -> Bool
$c/= :: Modality -> Modality -> Bool
/= :: Modality -> Modality -> Bool
Eq, (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)
instance ToJSON Modality where
toJSON :: Modality -> Value
toJSON Modality
TextModality = Text -> Value
String Text
"text"
toJSON Modality
AudioModality = Text -> Value
String Text
"audio"
instance FromJSON Modality where
parseJSON :: Value -> Parser Modality
parseJSON (String Text
"text") = Modality -> Parser Modality
forall a. a -> Parser a
forall (m :: * -> *) a. Monad m => a -> m a
return Modality
TextModality
parseJSON (String Text
"audio") = Modality -> Parser Modality
forall a. a -> Parser a
forall (m :: * -> *) a. Monad m => a -> m a
return Modality
AudioModality
parseJSON Value
invalid = String -> Parser Modality
forall a. String -> Parser a
forall (m :: * -> *) a. MonadFail m => String -> m a
fail (String -> Parser Modality) -> String -> Parser Modality
forall a b. (a -> b) -> a -> b
$ String
"Invalid modality: " String -> ShowS
forall a. [a] -> [a] -> [a]
++ Value -> String
forall a. Show a => a -> String
show Value
invalid
data ToolChoice = None | Auto | Required | SpecificTool SpecificToolChoice
deriving (Int -> ToolChoice -> ShowS
[ToolChoice] -> ShowS
ToolChoice -> String
(Int -> ToolChoice -> ShowS)
-> (ToolChoice -> String)
-> ([ToolChoice] -> ShowS)
-> Show ToolChoice
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> ToolChoice -> ShowS
showsPrec :: Int -> ToolChoice -> ShowS
$cshow :: ToolChoice -> String
show :: ToolChoice -> String
$cshowList :: [ToolChoice] -> ShowS
showList :: [ToolChoice] -> ShowS
Show, ToolChoice -> ToolChoice -> Bool
(ToolChoice -> ToolChoice -> Bool)
-> (ToolChoice -> ToolChoice -> Bool) -> Eq ToolChoice
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: ToolChoice -> ToolChoice -> Bool
== :: ToolChoice -> ToolChoice -> Bool
$c/= :: ToolChoice -> ToolChoice -> Bool
/= :: ToolChoice -> ToolChoice -> Bool
Eq, (forall x. ToolChoice -> Rep ToolChoice x)
-> (forall x. Rep ToolChoice x -> ToolChoice) -> Generic ToolChoice
forall x. Rep ToolChoice x -> ToolChoice
forall x. ToolChoice -> Rep ToolChoice x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cfrom :: forall x. ToolChoice -> Rep ToolChoice x
from :: forall x. ToolChoice -> Rep ToolChoice x
$cto :: forall x. Rep ToolChoice x -> ToolChoice
to :: forall x. Rep ToolChoice x -> ToolChoice
Generic)
instance ToJSON ToolChoice where
toJSON :: ToolChoice -> Value
toJSON ToolChoice
None = Text -> Value
String Text
"none"
toJSON ToolChoice
Auto = Text -> Value
String Text
"auto"
toJSON ToolChoice
Required = Text -> Value
String Text
"required"
toJSON (SpecificTool SpecificToolChoice
choice) = SpecificToolChoice -> Value
forall a. ToJSON a => a -> Value
toJSON SpecificToolChoice
choice
instance FromJSON ToolChoice where
parseJSON :: Value -> Parser ToolChoice
parseJSON (String Text
"none") = ToolChoice -> Parser ToolChoice
forall a. a -> Parser a
forall (m :: * -> *) a. Monad m => a -> m a
return ToolChoice
None
parseJSON (String Text
"auto") = ToolChoice -> Parser ToolChoice
forall a. a -> Parser a
forall (m :: * -> *) a. Monad m => a -> m a
return ToolChoice
Auto
parseJSON (String Text
"required") = ToolChoice -> Parser ToolChoice
forall a. a -> Parser a
forall (m :: * -> *) a. Monad m => a -> m a
return ToolChoice
Required
parseJSON o :: Value
o@(Object Object
_) = SpecificToolChoice -> ToolChoice
SpecificTool (SpecificToolChoice -> ToolChoice)
-> Parser SpecificToolChoice -> Parser ToolChoice
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Value -> Parser SpecificToolChoice
forall a. FromJSON a => Value -> Parser a
parseJSON Value
o
parseJSON Value
invalid = String -> Parser ToolChoice
forall a. String -> Parser a
forall (m :: * -> *) a. MonadFail m => String -> m a
fail (String -> Parser ToolChoice) -> String -> Parser ToolChoice
forall a b. (a -> b) -> a -> b
$ String
"Invalid tool choice: " String -> ShowS
forall a. [a] -> [a] -> [a]
++ Value -> String
forall a. Show a => a -> String
show Value
invalid
data SpecificToolChoice = SpecificToolChoice
{ SpecificToolChoice -> Text
toolType :: Text
, SpecificToolChoice -> Value
function :: Value
}
deriving (Int -> SpecificToolChoice -> ShowS
[SpecificToolChoice] -> ShowS
SpecificToolChoice -> String
(Int -> SpecificToolChoice -> ShowS)
-> (SpecificToolChoice -> String)
-> ([SpecificToolChoice] -> ShowS)
-> Show SpecificToolChoice
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> SpecificToolChoice -> ShowS
showsPrec :: Int -> SpecificToolChoice -> ShowS
$cshow :: SpecificToolChoice -> String
show :: SpecificToolChoice -> String
$cshowList :: [SpecificToolChoice] -> ShowS
showList :: [SpecificToolChoice] -> ShowS
Show, SpecificToolChoice -> SpecificToolChoice -> Bool
(SpecificToolChoice -> SpecificToolChoice -> Bool)
-> (SpecificToolChoice -> SpecificToolChoice -> Bool)
-> Eq SpecificToolChoice
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: SpecificToolChoice -> SpecificToolChoice -> Bool
== :: SpecificToolChoice -> SpecificToolChoice -> Bool
$c/= :: SpecificToolChoice -> SpecificToolChoice -> Bool
/= :: SpecificToolChoice -> SpecificToolChoice -> Bool
Eq, (forall x. SpecificToolChoice -> Rep SpecificToolChoice x)
-> (forall x. Rep SpecificToolChoice x -> SpecificToolChoice)
-> Generic SpecificToolChoice
forall x. Rep SpecificToolChoice x -> SpecificToolChoice
forall x. SpecificToolChoice -> Rep SpecificToolChoice x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cfrom :: forall x. SpecificToolChoice -> Rep SpecificToolChoice x
from :: forall x. SpecificToolChoice -> Rep SpecificToolChoice x
$cto :: forall x. Rep SpecificToolChoice x -> SpecificToolChoice
to :: forall x. Rep SpecificToolChoice x -> SpecificToolChoice
Generic)
instance ToJSON SpecificToolChoice where
toJSON :: SpecificToolChoice -> Value
toJSON SpecificToolChoice {Value
Text
$sel:toolType:SpecificToolChoice :: SpecificToolChoice -> Text
$sel:function:SpecificToolChoice :: SpecificToolChoice -> Value
toolType :: Text
function :: Value
..} =
[Pair] -> Value
object
[ Key
"type" Key -> Text -> Pair
forall v. ToJSON v => Key -> v -> Pair
forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
.= Text
toolType
, Key
"function" Key -> Value -> Pair
forall v. ToJSON v => Key -> v -> Pair
forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
.= Value
function
]
instance FromJSON SpecificToolChoice where
parseJSON :: Value -> Parser SpecificToolChoice
parseJSON = String
-> (Object -> Parser SpecificToolChoice)
-> Value
-> Parser SpecificToolChoice
forall a. String -> (Object -> Parser a) -> Value -> Parser a
withObject String
"SpecificToolChoice" ((Object -> Parser SpecificToolChoice)
-> Value -> Parser SpecificToolChoice)
-> (Object -> Parser SpecificToolChoice)
-> Value
-> Parser SpecificToolChoice
forall a b. (a -> b) -> a -> b
$ \Object
v ->
Text -> Value -> SpecificToolChoice
SpecificToolChoice
(Text -> Value -> SpecificToolChoice)
-> Parser Text -> Parser (Value -> SpecificToolChoice)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Object
v Object -> Key -> Parser Text
forall a. FromJSON a => Object -> Key -> Parser a
.: Key
"type"
Parser (Value -> SpecificToolChoice)
-> Parser Value -> Parser SpecificToolChoice
forall a b. Parser (a -> b) -> Parser a -> Parser b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Object
v Object -> Key -> Parser Value
forall a. FromJSON a => Object -> Key -> Parser a
.: Key
"function"
data ReasoningEffort = Low | Medium | High
deriving (Int -> ReasoningEffort -> ShowS
[ReasoningEffort] -> ShowS
ReasoningEffort -> String
(Int -> ReasoningEffort -> ShowS)
-> (ReasoningEffort -> String)
-> ([ReasoningEffort] -> ShowS)
-> Show ReasoningEffort
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> ReasoningEffort -> ShowS
showsPrec :: Int -> ReasoningEffort -> ShowS
$cshow :: ReasoningEffort -> String
show :: ReasoningEffort -> String
$cshowList :: [ReasoningEffort] -> ShowS
showList :: [ReasoningEffort] -> ShowS
Show, ReasoningEffort -> ReasoningEffort -> Bool
(ReasoningEffort -> ReasoningEffort -> Bool)
-> (ReasoningEffort -> ReasoningEffort -> Bool)
-> Eq ReasoningEffort
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: ReasoningEffort -> ReasoningEffort -> Bool
== :: ReasoningEffort -> ReasoningEffort -> Bool
$c/= :: ReasoningEffort -> ReasoningEffort -> Bool
/= :: ReasoningEffort -> ReasoningEffort -> Bool
Eq, (forall x. ReasoningEffort -> Rep ReasoningEffort x)
-> (forall x. Rep ReasoningEffort x -> ReasoningEffort)
-> Generic ReasoningEffort
forall x. Rep ReasoningEffort x -> ReasoningEffort
forall x. ReasoningEffort -> Rep ReasoningEffort x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cfrom :: forall x. ReasoningEffort -> Rep ReasoningEffort x
from :: forall x. ReasoningEffort -> Rep ReasoningEffort x
$cto :: forall x. Rep ReasoningEffort x -> ReasoningEffort
to :: forall x. Rep ReasoningEffort x -> ReasoningEffort
Generic)
instance ToJSON ReasoningEffort where
toJSON :: ReasoningEffort -> Value
toJSON ReasoningEffort
Low = Text -> Value
String Text
"low"
toJSON ReasoningEffort
Medium = Text -> Value
String Text
"medium"
toJSON ReasoningEffort
High = Text -> Value
String Text
"high"
instance FromJSON ReasoningEffort where
parseJSON :: Value -> Parser ReasoningEffort
parseJSON (String Text
"low") = ReasoningEffort -> Parser ReasoningEffort
forall a. a -> Parser a
forall (m :: * -> *) a. Monad m => a -> m a
return ReasoningEffort
Low
parseJSON (String Text
"medium") = ReasoningEffort -> Parser ReasoningEffort
forall a. a -> Parser a
forall (m :: * -> *) a. Monad m => a -> m a
return ReasoningEffort
Medium
parseJSON (String Text
"high") = ReasoningEffort -> Parser ReasoningEffort
forall a. a -> Parser a
forall (m :: * -> *) a. Monad m => a -> m a
return ReasoningEffort
High
parseJSON Value
invalid = String -> Parser ReasoningEffort
forall a. String -> Parser a
forall (m :: * -> *) a. MonadFail m => String -> m a
fail (String -> Parser ReasoningEffort)
-> String -> Parser ReasoningEffort
forall a b. (a -> b) -> a -> b
$ String
"Invalid reasoning effort: " String -> ShowS
forall a. [a] -> [a] -> [a]
++ Value -> String
forall a. Show a => a -> String
show Value
invalid
data PredictionContent = PredictionContent
{ PredictionContent -> MessageContent
content :: MessageContent
, PredictionContent -> Text
contentType :: Text
}
deriving (Int -> PredictionContent -> ShowS
[PredictionContent] -> ShowS
PredictionContent -> String
(Int -> PredictionContent -> ShowS)
-> (PredictionContent -> String)
-> ([PredictionContent] -> ShowS)
-> Show PredictionContent
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> PredictionContent -> ShowS
showsPrec :: Int -> PredictionContent -> ShowS
$cshow :: PredictionContent -> String
show :: PredictionContent -> String
$cshowList :: [PredictionContent] -> ShowS
showList :: [PredictionContent] -> ShowS
Show, PredictionContent -> PredictionContent -> Bool
(PredictionContent -> PredictionContent -> Bool)
-> (PredictionContent -> PredictionContent -> Bool)
-> Eq PredictionContent
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: PredictionContent -> PredictionContent -> Bool
== :: PredictionContent -> PredictionContent -> Bool
$c/= :: PredictionContent -> PredictionContent -> Bool
/= :: PredictionContent -> PredictionContent -> Bool
Eq, (forall x. PredictionContent -> Rep PredictionContent x)
-> (forall x. Rep PredictionContent x -> PredictionContent)
-> Generic PredictionContent
forall x. Rep PredictionContent x -> PredictionContent
forall x. PredictionContent -> Rep PredictionContent x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cfrom :: forall x. PredictionContent -> Rep PredictionContent x
from :: forall x. PredictionContent -> Rep PredictionContent x
$cto :: forall x. Rep PredictionContent x -> PredictionContent
to :: forall x. Rep PredictionContent x -> PredictionContent
Generic)
instance ToJSON PredictionContent where
toJSON :: PredictionContent -> Value
toJSON PredictionContent {Text
MessageContent
$sel:content:PredictionContent :: PredictionContent -> MessageContent
$sel:contentType:PredictionContent :: PredictionContent -> Text
content :: MessageContent
contentType :: Text
..} =
[Pair] -> Value
object
[ Key
"content" Key -> MessageContent -> Pair
forall v. ToJSON v => Key -> v -> Pair
forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
.= MessageContent
content
, Key
"type" Key -> Text -> Pair
forall v. ToJSON v => Key -> v -> Pair
forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
.= Text
contentType
]
instance FromJSON PredictionContent where
parseJSON :: Value -> Parser PredictionContent
parseJSON = String
-> (Object -> Parser PredictionContent)
-> Value
-> Parser PredictionContent
forall a. String -> (Object -> Parser a) -> Value -> Parser a
withObject String
"PredictionContent" ((Object -> Parser PredictionContent)
-> Value -> Parser PredictionContent)
-> (Object -> Parser PredictionContent)
-> Value
-> Parser PredictionContent
forall a b. (a -> b) -> a -> b
$ \Object
v ->
MessageContent -> Text -> PredictionContent
PredictionContent
(MessageContent -> Text -> PredictionContent)
-> Parser MessageContent -> Parser (Text -> PredictionContent)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Object
v Object -> Key -> Parser MessageContent
forall a. FromJSON a => Object -> Key -> Parser a
.: Key
"content"
Parser (Text -> PredictionContent)
-> Parser Text -> Parser PredictionContent
forall a b. Parser (a -> b) -> Parser a -> Parser b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Object
v Object -> Key -> Parser Text
forall a. FromJSON a => Object -> Key -> Parser a
.: Key
"type"
data PredictionOutput = PredictionOutput
{ PredictionOutput -> Text
predictionType :: Text
, PredictionOutput -> MessageContent
content :: MessageContent
}
deriving (Int -> PredictionOutput -> ShowS
[PredictionOutput] -> ShowS
PredictionOutput -> String
(Int -> PredictionOutput -> ShowS)
-> (PredictionOutput -> String)
-> ([PredictionOutput] -> ShowS)
-> Show PredictionOutput
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> PredictionOutput -> ShowS
showsPrec :: Int -> PredictionOutput -> ShowS
$cshow :: PredictionOutput -> String
show :: PredictionOutput -> String
$cshowList :: [PredictionOutput] -> ShowS
showList :: [PredictionOutput] -> ShowS
Show, PredictionOutput -> PredictionOutput -> Bool
(PredictionOutput -> PredictionOutput -> Bool)
-> (PredictionOutput -> PredictionOutput -> Bool)
-> Eq PredictionOutput
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: PredictionOutput -> PredictionOutput -> Bool
== :: PredictionOutput -> PredictionOutput -> Bool
$c/= :: PredictionOutput -> PredictionOutput -> Bool
/= :: PredictionOutput -> PredictionOutput -> Bool
Eq, (forall x. PredictionOutput -> Rep PredictionOutput x)
-> (forall x. Rep PredictionOutput x -> PredictionOutput)
-> Generic PredictionOutput
forall x. Rep PredictionOutput x -> PredictionOutput
forall x. PredictionOutput -> Rep PredictionOutput x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cfrom :: forall x. PredictionOutput -> Rep PredictionOutput x
from :: forall x. PredictionOutput -> Rep PredictionOutput x
$cto :: forall x. Rep PredictionOutput x -> PredictionOutput
to :: forall x. Rep PredictionOutput x -> PredictionOutput
Generic)
instance ToJSON PredictionOutput where
toJSON :: PredictionOutput -> Value
toJSON PredictionOutput {Text
MessageContent
$sel:predictionType:PredictionOutput :: PredictionOutput -> Text
$sel:content:PredictionOutput :: PredictionOutput -> MessageContent
predictionType :: Text
content :: MessageContent
..} =
[Pair] -> Value
object
[ Key
"type" Key -> Text -> Pair
forall v. ToJSON v => Key -> v -> Pair
forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
.= Text
predictionType
, Key
"content" Key -> MessageContent -> Pair
forall v. ToJSON v => Key -> v -> Pair
forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
.= MessageContent
content
]
instance FromJSON PredictionOutput where
parseJSON :: Value -> Parser PredictionOutput
parseJSON = String
-> (Object -> Parser PredictionOutput)
-> Value
-> Parser PredictionOutput
forall a. String -> (Object -> Parser a) -> Value -> Parser a
withObject String
"PredictionOutput" ((Object -> Parser PredictionOutput)
-> Value -> Parser PredictionOutput)
-> (Object -> Parser PredictionOutput)
-> Value
-> Parser PredictionOutput
forall a b. (a -> b) -> a -> b
$ \Object
v ->
Text -> MessageContent -> PredictionOutput
PredictionOutput
(Text -> MessageContent -> PredictionOutput)
-> Parser Text -> Parser (MessageContent -> PredictionOutput)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Object
v Object -> Key -> Parser Text
forall a. FromJSON a => Object -> Key -> Parser a
.: Key
"type"
Parser (MessageContent -> PredictionOutput)
-> Parser MessageContent -> Parser PredictionOutput
forall a b. Parser (a -> b) -> Parser a -> Parser b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Object
v Object -> Key -> Parser MessageContent
forall a. FromJSON a => Object -> Key -> Parser a
.: Key
"content"
data ResponseFormat = JsonObjectFormat | JsonSchemaFormat Value
deriving (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, ResponseFormat -> ResponseFormat -> Bool
(ResponseFormat -> ResponseFormat -> Bool)
-> (ResponseFormat -> ResponseFormat -> Bool) -> Eq ResponseFormat
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: ResponseFormat -> ResponseFormat -> Bool
== :: ResponseFormat -> ResponseFormat -> Bool
$c/= :: ResponseFormat -> ResponseFormat -> Bool
/= :: ResponseFormat -> ResponseFormat -> Bool
Eq, (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)
instance ToJSON ResponseFormat where
toJSON :: ResponseFormat -> Value
toJSON ResponseFormat
JsonObjectFormat = [Pair] -> Value
object [Key
"type" Key -> Text -> Pair
forall v. ToJSON v => Key -> v -> Pair
forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
.= (Text
"json_object" :: Text)]
toJSON (JsonSchemaFormat Value
schema) =
[Pair] -> Value
object
[ Key
"type" Key -> Text -> Pair
forall v. ToJSON v => Key -> v -> Pair
forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
.= (Text
"json_schema" :: Text)
, Key
"json_schema" Key -> Value -> Pair
forall v. ToJSON v => Key -> v -> Pair
forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
.= Value
schema
]
instance FromJSON ResponseFormat where
parseJSON :: Value -> Parser ResponseFormat
parseJSON = String
-> (Object -> Parser ResponseFormat)
-> Value
-> Parser ResponseFormat
forall a. String -> (Object -> Parser a) -> Value -> Parser a
withObject String
"ResponseFormat" ((Object -> Parser ResponseFormat)
-> Value -> Parser ResponseFormat)
-> (Object -> Parser ResponseFormat)
-> Value
-> Parser ResponseFormat
forall a b. (a -> b) -> a -> b
$ \Object
v -> do
Value
formatType <- Object
v Object -> Key -> Parser Value
forall a. FromJSON a => Object -> Key -> Parser a
.: Key
"type"
case Value
formatType of
String Text
"json_object" -> ResponseFormat -> Parser ResponseFormat
forall a. a -> Parser a
forall (m :: * -> *) a. Monad m => a -> m a
return ResponseFormat
JsonObjectFormat
String Text
"json_schema" -> Value -> ResponseFormat
JsonSchemaFormat (Value -> ResponseFormat) -> Parser Value -> Parser ResponseFormat
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Object
v Object -> Key -> Parser Value
forall a. FromJSON a => Object -> Key -> Parser a
.: Key
"json_schema"
Value
_ -> String -> Parser ResponseFormat
forall a. String -> Parser a
forall (m :: * -> *) a. MonadFail m => String -> m a
fail (String -> Parser ResponseFormat)
-> String -> Parser ResponseFormat
forall a b. (a -> b) -> a -> b
$ String
"Invalid response format type: " String -> ShowS
forall a. [a] -> [a] -> [a]
++ Value -> String
forall a. Show a => a -> String
show Value
formatType
data StreamOptions = StreamOptions
{ StreamOptions -> Bool
includeUsage :: Bool
}
deriving (Int -> StreamOptions -> ShowS
[StreamOptions] -> ShowS
StreamOptions -> String
(Int -> StreamOptions -> ShowS)
-> (StreamOptions -> String)
-> ([StreamOptions] -> ShowS)
-> Show StreamOptions
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> StreamOptions -> ShowS
showsPrec :: Int -> StreamOptions -> ShowS
$cshow :: StreamOptions -> String
show :: StreamOptions -> String
$cshowList :: [StreamOptions] -> ShowS
showList :: [StreamOptions] -> ShowS
Show, StreamOptions -> StreamOptions -> Bool
(StreamOptions -> StreamOptions -> Bool)
-> (StreamOptions -> StreamOptions -> Bool) -> Eq StreamOptions
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: StreamOptions -> StreamOptions -> Bool
== :: StreamOptions -> StreamOptions -> Bool
$c/= :: StreamOptions -> StreamOptions -> Bool
/= :: StreamOptions -> StreamOptions -> Bool
Eq, (forall x. StreamOptions -> Rep StreamOptions x)
-> (forall x. Rep StreamOptions x -> StreamOptions)
-> Generic StreamOptions
forall x. Rep StreamOptions x -> StreamOptions
forall x. StreamOptions -> Rep StreamOptions x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cfrom :: forall x. StreamOptions -> Rep StreamOptions x
from :: forall x. StreamOptions -> Rep StreamOptions x
$cto :: forall x. Rep StreamOptions x -> StreamOptions
to :: forall x. Rep StreamOptions x -> StreamOptions
Generic)
instance ToJSON StreamOptions where
toJSON :: StreamOptions -> Value
toJSON StreamOptions {Bool
$sel:includeUsage:StreamOptions :: StreamOptions -> Bool
includeUsage :: Bool
..} =
[Pair] -> Value
object
[ Key
"include_usage" Key -> Bool -> Pair
forall v. ToJSON v => Key -> v -> Pair
forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
.= Bool
includeUsage
]
instance FromJSON StreamOptions where
parseJSON :: Value -> Parser StreamOptions
parseJSON = String
-> (Object -> Parser StreamOptions)
-> Value
-> Parser StreamOptions
forall a. String -> (Object -> Parser a) -> Value -> Parser a
withObject String
"StreamOptions" ((Object -> Parser StreamOptions) -> Value -> Parser StreamOptions)
-> (Object -> Parser StreamOptions)
-> Value
-> Parser StreamOptions
forall a b. (a -> b) -> a -> b
$ \Object
v ->
Bool -> StreamOptions
StreamOptions (Bool -> StreamOptions) -> Parser Bool -> Parser StreamOptions
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Object
v Object -> Key -> Parser Bool
forall a. FromJSON a => Object -> Key -> Parser a
.: Key
"include_usage"
data ApproximateLocation = ApproximateLocation
{ ApproximateLocation -> Text
locationType :: Text
}
deriving (Int -> ApproximateLocation -> ShowS
[ApproximateLocation] -> ShowS
ApproximateLocation -> String
(Int -> ApproximateLocation -> ShowS)
-> (ApproximateLocation -> String)
-> ([ApproximateLocation] -> ShowS)
-> Show ApproximateLocation
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> ApproximateLocation -> ShowS
showsPrec :: Int -> ApproximateLocation -> ShowS
$cshow :: ApproximateLocation -> String
show :: ApproximateLocation -> String
$cshowList :: [ApproximateLocation] -> ShowS
showList :: [ApproximateLocation] -> ShowS
Show, ApproximateLocation -> ApproximateLocation -> Bool
(ApproximateLocation -> ApproximateLocation -> Bool)
-> (ApproximateLocation -> ApproximateLocation -> Bool)
-> Eq ApproximateLocation
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: ApproximateLocation -> ApproximateLocation -> Bool
== :: ApproximateLocation -> ApproximateLocation -> Bool
$c/= :: ApproximateLocation -> ApproximateLocation -> Bool
/= :: ApproximateLocation -> ApproximateLocation -> Bool
Eq, (forall x. ApproximateLocation -> Rep ApproximateLocation x)
-> (forall x. Rep ApproximateLocation x -> ApproximateLocation)
-> Generic ApproximateLocation
forall x. Rep ApproximateLocation x -> ApproximateLocation
forall x. ApproximateLocation -> Rep ApproximateLocation x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cfrom :: forall x. ApproximateLocation -> Rep ApproximateLocation x
from :: forall x. ApproximateLocation -> Rep ApproximateLocation x
$cto :: forall x. Rep ApproximateLocation x -> ApproximateLocation
to :: forall x. Rep ApproximateLocation x -> ApproximateLocation
Generic)
instance ToJSON ApproximateLocation where
toJSON :: ApproximateLocation -> Value
toJSON ApproximateLocation {Text
$sel:locationType:ApproximateLocation :: ApproximateLocation -> Text
locationType :: Text
..} =
[Pair] -> Value
object
[ Key
"type" Key -> Text -> Pair
forall v. ToJSON v => Key -> v -> Pair
forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
.= Text
locationType
]
instance FromJSON ApproximateLocation where
parseJSON :: Value -> Parser ApproximateLocation
parseJSON = String
-> (Object -> Parser ApproximateLocation)
-> Value
-> Parser ApproximateLocation
forall a. String -> (Object -> Parser a) -> Value -> Parser a
withObject String
"ApproximateLocation" ((Object -> Parser ApproximateLocation)
-> Value -> Parser ApproximateLocation)
-> (Object -> Parser ApproximateLocation)
-> Value
-> Parser ApproximateLocation
forall a b. (a -> b) -> a -> b
$ \Object
v ->
Text -> ApproximateLocation
ApproximateLocation (Text -> ApproximateLocation)
-> Parser Text -> Parser ApproximateLocation
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Object
v Object -> Key -> Parser Text
forall a. FromJSON a => Object -> Key -> Parser a
.: Key
"type"
data UserLocation = UserLocation
{ UserLocation -> ApproximateLocation
approximate :: ApproximateLocation
}
deriving (Int -> UserLocation -> ShowS
[UserLocation] -> ShowS
UserLocation -> String
(Int -> UserLocation -> ShowS)
-> (UserLocation -> String)
-> ([UserLocation] -> ShowS)
-> Show UserLocation
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> UserLocation -> ShowS
showsPrec :: Int -> UserLocation -> ShowS
$cshow :: UserLocation -> String
show :: UserLocation -> String
$cshowList :: [UserLocation] -> ShowS
showList :: [UserLocation] -> ShowS
Show, UserLocation -> UserLocation -> Bool
(UserLocation -> UserLocation -> Bool)
-> (UserLocation -> UserLocation -> Bool) -> Eq UserLocation
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: UserLocation -> UserLocation -> Bool
== :: UserLocation -> UserLocation -> Bool
$c/= :: UserLocation -> UserLocation -> Bool
/= :: UserLocation -> UserLocation -> Bool
Eq, (forall x. UserLocation -> Rep UserLocation x)
-> (forall x. Rep UserLocation x -> UserLocation)
-> Generic UserLocation
forall x. Rep UserLocation x -> UserLocation
forall x. UserLocation -> Rep UserLocation x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cfrom :: forall x. UserLocation -> Rep UserLocation x
from :: forall x. UserLocation -> Rep UserLocation x
$cto :: forall x. Rep UserLocation x -> UserLocation
to :: forall x. Rep UserLocation x -> UserLocation
Generic)
instance ToJSON UserLocation where
toJSON :: UserLocation -> Value
toJSON UserLocation {ApproximateLocation
$sel:approximate:UserLocation :: UserLocation -> ApproximateLocation
approximate :: ApproximateLocation
..} =
[Pair] -> Value
object
[ Key
"approximate" Key -> ApproximateLocation -> Pair
forall v. ToJSON v => Key -> v -> Pair
forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
.= ApproximateLocation
approximate
]
instance FromJSON UserLocation where
parseJSON :: Value -> Parser UserLocation
parseJSON = String
-> (Object -> Parser UserLocation) -> Value -> Parser UserLocation
forall a. String -> (Object -> Parser a) -> Value -> Parser a
withObject String
"UserLocation" ((Object -> Parser UserLocation) -> Value -> Parser UserLocation)
-> (Object -> Parser UserLocation) -> Value -> Parser UserLocation
forall a b. (a -> b) -> a -> b
$ \Object
v ->
ApproximateLocation -> UserLocation
UserLocation (ApproximateLocation -> UserLocation)
-> Parser ApproximateLocation -> Parser UserLocation
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Object
v Object -> Key -> Parser ApproximateLocation
forall a. FromJSON a => Object -> Key -> Parser a
.: Key
"approximate"
data WebSearchOptions = WebSearchOptions
{ WebSearchOptions -> Maybe Text
searchContextSize :: Maybe Text
, WebSearchOptions -> Maybe UserLocation
userLocation :: Maybe UserLocation
}
deriving (Int -> WebSearchOptions -> ShowS
[WebSearchOptions] -> ShowS
WebSearchOptions -> String
(Int -> WebSearchOptions -> ShowS)
-> (WebSearchOptions -> String)
-> ([WebSearchOptions] -> ShowS)
-> Show WebSearchOptions
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> WebSearchOptions -> ShowS
showsPrec :: Int -> WebSearchOptions -> ShowS
$cshow :: WebSearchOptions -> String
show :: WebSearchOptions -> String
$cshowList :: [WebSearchOptions] -> ShowS
showList :: [WebSearchOptions] -> ShowS
Show, WebSearchOptions -> WebSearchOptions -> Bool
(WebSearchOptions -> WebSearchOptions -> Bool)
-> (WebSearchOptions -> WebSearchOptions -> Bool)
-> Eq WebSearchOptions
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: WebSearchOptions -> WebSearchOptions -> Bool
== :: WebSearchOptions -> WebSearchOptions -> Bool
$c/= :: WebSearchOptions -> WebSearchOptions -> Bool
/= :: WebSearchOptions -> WebSearchOptions -> Bool
Eq, (forall x. WebSearchOptions -> Rep WebSearchOptions x)
-> (forall x. Rep WebSearchOptions x -> WebSearchOptions)
-> Generic WebSearchOptions
forall x. Rep WebSearchOptions x -> WebSearchOptions
forall x. WebSearchOptions -> Rep WebSearchOptions x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cfrom :: forall x. WebSearchOptions -> Rep WebSearchOptions x
from :: forall x. WebSearchOptions -> Rep WebSearchOptions x
$cto :: forall x. Rep WebSearchOptions x -> WebSearchOptions
to :: forall x. Rep WebSearchOptions x -> WebSearchOptions
Generic)
instance ToJSON WebSearchOptions where
toJSON :: WebSearchOptions -> Value
toJSON WebSearchOptions {Maybe Text
Maybe UserLocation
$sel:searchContextSize:WebSearchOptions :: WebSearchOptions -> Maybe Text
$sel:userLocation:WebSearchOptions :: WebSearchOptions -> Maybe UserLocation
searchContextSize :: Maybe Text
userLocation :: Maybe UserLocation
..} =
[Pair] -> Value
object ([Pair] -> Value) -> [Pair] -> Value
forall a b. (a -> b) -> a -> b
$
[Pair] -> (Text -> [Pair]) -> Maybe Text -> [Pair]
forall b a. b -> (a -> b) -> Maybe a -> b
maybe [] (\Text
s -> [Key
"search_context_size" Key -> Text -> Pair
forall v. ToJSON v => Key -> v -> Pair
forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
.= Text
s]) Maybe Text
searchContextSize
[Pair] -> [Pair] -> [Pair]
forall a. [a] -> [a] -> [a]
++ [Pair] -> (UserLocation -> [Pair]) -> Maybe UserLocation -> [Pair]
forall b a. b -> (a -> b) -> Maybe a -> b
maybe [] (\UserLocation
l -> [Key
"user_location" Key -> UserLocation -> Pair
forall v. ToJSON v => Key -> v -> Pair
forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
.= UserLocation
l]) Maybe UserLocation
userLocation
instance FromJSON WebSearchOptions where
parseJSON :: Value -> Parser WebSearchOptions
parseJSON = String
-> (Object -> Parser WebSearchOptions)
-> Value
-> Parser WebSearchOptions
forall a. String -> (Object -> Parser a) -> Value -> Parser a
withObject String
"WebSearchOptions" ((Object -> Parser WebSearchOptions)
-> Value -> Parser WebSearchOptions)
-> (Object -> Parser WebSearchOptions)
-> Value
-> Parser WebSearchOptions
forall a b. (a -> b) -> a -> b
$ \Object
v ->
Maybe Text -> Maybe UserLocation -> WebSearchOptions
WebSearchOptions
(Maybe Text -> Maybe UserLocation -> WebSearchOptions)
-> Parser (Maybe Text)
-> Parser (Maybe UserLocation -> WebSearchOptions)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Object
v Object -> Key -> Parser (Maybe Text)
forall a. FromJSON a => Object -> Key -> Parser (Maybe a)
.:? Key
"search_context_size"
Parser (Maybe UserLocation -> WebSearchOptions)
-> Parser (Maybe UserLocation) -> Parser WebSearchOptions
forall a b. Parser (a -> b) -> Parser a -> Parser b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Object
v Object -> Key -> Parser (Maybe UserLocation)
forall a. FromJSON a => Object -> Key -> Parser (Maybe a)
.:? Key
"user_location"
data ChatCompletionRequest = ChatCompletionRequest
{ ChatCompletionRequest -> [Message]
messages :: [Message]
, ChatCompletionRequest -> Text
model :: Text
, ChatCompletionRequest -> Maybe Double
frequencyPenalty :: Maybe Double
, ChatCompletionRequest -> Maybe (Map Text Double)
logitBias :: Maybe (Map Text Double)
, ChatCompletionRequest -> Maybe Bool
logprobs :: Maybe Bool
, ChatCompletionRequest -> Maybe Int
maxCompletionTokens :: Maybe Int
, ChatCompletionRequest -> Maybe Int
maxTokens :: Maybe Int
, ChatCompletionRequest -> Maybe (Map Text Text)
metadata :: Maybe (Map Text Text)
, ChatCompletionRequest -> Maybe [Modality]
modalities :: Maybe [Modality]
, ChatCompletionRequest -> Maybe Int
n :: Maybe Int
, ChatCompletionRequest -> Maybe Bool
parallelToolCalls :: Maybe Bool
, ChatCompletionRequest -> Maybe PredictionOutput
prediction :: Maybe PredictionOutput
, ChatCompletionRequest -> Maybe Double
presencePenalty :: Maybe Double
, ChatCompletionRequest -> Maybe ReasoningEffort
reasoningEffort :: Maybe ReasoningEffort
, ChatCompletionRequest -> Maybe ResponseFormat
responseFormat :: Maybe ResponseFormat
, ChatCompletionRequest -> Maybe Int
seed :: Maybe Int
, ChatCompletionRequest -> Maybe Text
serviceTier :: Maybe Text
, ChatCompletionRequest -> Maybe (Either Text [Text])
stop :: Maybe (Either Text [Text])
, ChatCompletionRequest -> Maybe Bool
store :: Maybe Bool
, ChatCompletionRequest -> Maybe Bool
stream :: Maybe Bool
, ChatCompletionRequest -> Maybe StreamOptions
streamOptions :: Maybe StreamOptions
, ChatCompletionRequest -> Maybe Double
temperature :: Maybe Double
, ChatCompletionRequest -> Maybe ToolChoice
toolChoice :: Maybe ToolChoice
, ChatCompletionRequest -> Maybe [Tool_]
tools :: Maybe [Tool_]
, ChatCompletionRequest -> Maybe Int
topLogprobs :: Maybe Int
, ChatCompletionRequest -> Maybe Double
topP :: Maybe Double
, ChatCompletionRequest -> Maybe Text
user :: Maybe Text
, ChatCompletionRequest -> Maybe WebSearchOptions
webSearchOptions :: Maybe WebSearchOptions
, ChatCompletionRequest -> Maybe AudioConfig
audio :: Maybe AudioConfig
}
deriving (Int -> ChatCompletionRequest -> ShowS
[ChatCompletionRequest] -> ShowS
ChatCompletionRequest -> String
(Int -> ChatCompletionRequest -> ShowS)
-> (ChatCompletionRequest -> String)
-> ([ChatCompletionRequest] -> ShowS)
-> Show ChatCompletionRequest
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> ChatCompletionRequest -> ShowS
showsPrec :: Int -> ChatCompletionRequest -> ShowS
$cshow :: ChatCompletionRequest -> String
show :: ChatCompletionRequest -> String
$cshowList :: [ChatCompletionRequest] -> ShowS
showList :: [ChatCompletionRequest] -> ShowS
Show, ChatCompletionRequest -> ChatCompletionRequest -> Bool
(ChatCompletionRequest -> ChatCompletionRequest -> Bool)
-> (ChatCompletionRequest -> ChatCompletionRequest -> Bool)
-> Eq ChatCompletionRequest
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: ChatCompletionRequest -> ChatCompletionRequest -> Bool
== :: ChatCompletionRequest -> ChatCompletionRequest -> Bool
$c/= :: ChatCompletionRequest -> ChatCompletionRequest -> Bool
/= :: ChatCompletionRequest -> ChatCompletionRequest -> Bool
Eq, (forall x. ChatCompletionRequest -> Rep ChatCompletionRequest x)
-> (forall x. Rep ChatCompletionRequest x -> ChatCompletionRequest)
-> Generic ChatCompletionRequest
forall x. Rep ChatCompletionRequest x -> ChatCompletionRequest
forall x. ChatCompletionRequest -> Rep ChatCompletionRequest x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cfrom :: forall x. ChatCompletionRequest -> Rep ChatCompletionRequest x
from :: forall x. ChatCompletionRequest -> Rep ChatCompletionRequest x
$cto :: forall x. Rep ChatCompletionRequest x -> ChatCompletionRequest
to :: forall x. Rep ChatCompletionRequest x -> ChatCompletionRequest
Generic)
instance ToJSON ChatCompletionRequest where
toJSON :: ChatCompletionRequest -> Value
toJSON ChatCompletionRequest {[Message]
Maybe Bool
Maybe Double
Maybe Int
Maybe [Modality]
Maybe [Tool_]
Maybe (Either Text [Text])
Maybe (Map Text Double)
Maybe (Map Text Text)
Maybe Text
Maybe WebSearchOptions
Maybe StreamOptions
Maybe ResponseFormat
Maybe PredictionOutput
Maybe ReasoningEffort
Maybe ToolChoice
Maybe AudioConfig
Text
$sel:messages:ChatCompletionRequest :: ChatCompletionRequest -> [Message]
$sel:model:ChatCompletionRequest :: ChatCompletionRequest -> Text
$sel:frequencyPenalty:ChatCompletionRequest :: ChatCompletionRequest -> Maybe Double
$sel:logitBias:ChatCompletionRequest :: ChatCompletionRequest -> Maybe (Map Text Double)
$sel:logprobs:ChatCompletionRequest :: ChatCompletionRequest -> Maybe Bool
$sel:maxCompletionTokens:ChatCompletionRequest :: ChatCompletionRequest -> Maybe Int
$sel:maxTokens:ChatCompletionRequest :: ChatCompletionRequest -> Maybe Int
$sel:metadata:ChatCompletionRequest :: ChatCompletionRequest -> Maybe (Map Text Text)
$sel:modalities:ChatCompletionRequest :: ChatCompletionRequest -> Maybe [Modality]
$sel:n:ChatCompletionRequest :: ChatCompletionRequest -> Maybe Int
$sel:parallelToolCalls:ChatCompletionRequest :: ChatCompletionRequest -> Maybe Bool
$sel:prediction:ChatCompletionRequest :: ChatCompletionRequest -> Maybe PredictionOutput
$sel:presencePenalty:ChatCompletionRequest :: ChatCompletionRequest -> Maybe Double
$sel:reasoningEffort:ChatCompletionRequest :: ChatCompletionRequest -> Maybe ReasoningEffort
$sel:responseFormat:ChatCompletionRequest :: ChatCompletionRequest -> Maybe ResponseFormat
$sel:seed:ChatCompletionRequest :: ChatCompletionRequest -> Maybe Int
$sel:serviceTier:ChatCompletionRequest :: ChatCompletionRequest -> Maybe Text
$sel:stop:ChatCompletionRequest :: ChatCompletionRequest -> Maybe (Either Text [Text])
$sel:store:ChatCompletionRequest :: ChatCompletionRequest -> Maybe Bool
$sel:stream:ChatCompletionRequest :: ChatCompletionRequest -> Maybe Bool
$sel:streamOptions:ChatCompletionRequest :: ChatCompletionRequest -> Maybe StreamOptions
$sel:temperature:ChatCompletionRequest :: ChatCompletionRequest -> Maybe Double
$sel:toolChoice:ChatCompletionRequest :: ChatCompletionRequest -> Maybe ToolChoice
$sel:tools:ChatCompletionRequest :: ChatCompletionRequest -> Maybe [Tool_]
$sel:topLogprobs:ChatCompletionRequest :: ChatCompletionRequest -> Maybe Int
$sel:topP:ChatCompletionRequest :: ChatCompletionRequest -> Maybe Double
$sel:user:ChatCompletionRequest :: ChatCompletionRequest -> Maybe Text
$sel:webSearchOptions:ChatCompletionRequest :: ChatCompletionRequest -> Maybe WebSearchOptions
$sel:audio:ChatCompletionRequest :: ChatCompletionRequest -> Maybe AudioConfig
messages :: [Message]
model :: Text
frequencyPenalty :: Maybe Double
logitBias :: Maybe (Map Text Double)
logprobs :: Maybe Bool
maxCompletionTokens :: Maybe Int
maxTokens :: Maybe Int
metadata :: Maybe (Map Text Text)
modalities :: Maybe [Modality]
n :: Maybe Int
parallelToolCalls :: Maybe Bool
prediction :: Maybe PredictionOutput
presencePenalty :: Maybe Double
reasoningEffort :: Maybe ReasoningEffort
responseFormat :: Maybe ResponseFormat
seed :: Maybe Int
serviceTier :: Maybe Text
stop :: Maybe (Either Text [Text])
store :: Maybe Bool
stream :: Maybe Bool
streamOptions :: Maybe StreamOptions
temperature :: Maybe Double
toolChoice :: Maybe ToolChoice
tools :: Maybe [Tool_]
topLogprobs :: Maybe Int
topP :: Maybe Double
user :: Maybe Text
webSearchOptions :: Maybe WebSearchOptions
audio :: Maybe AudioConfig
..} =
[Pair] -> Value
object ([Pair] -> Value) -> [Pair] -> Value
forall a b. (a -> b) -> a -> b
$
[ Key
"messages" Key -> [Message] -> Pair
forall v. ToJSON v => Key -> v -> Pair
forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
.= [Message]
messages
, Key
"model" Key -> Text -> Pair
forall v. ToJSON v => Key -> v -> Pair
forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
.= Text
model
]
[Pair] -> [Pair] -> [Pair]
forall a. [a] -> [a] -> [a]
++ [Pair] -> (Double -> [Pair]) -> Maybe Double -> [Pair]
forall b a. b -> (a -> b) -> Maybe a -> b
maybe [] (\Double
fp -> [Key
"frequency_penalty" Key -> Double -> Pair
forall v. ToJSON v => Key -> v -> Pair
forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
.= Double
fp]) Maybe Double
frequencyPenalty
[Pair] -> [Pair] -> [Pair]
forall a. [a] -> [a] -> [a]
++ [Pair]
-> (Map Text Double -> [Pair]) -> Maybe (Map Text Double) -> [Pair]
forall b a. b -> (a -> b) -> Maybe a -> b
maybe [] (\Map Text Double
lb -> [Key
"logit_bias" Key -> Map Text Double -> Pair
forall v. ToJSON v => Key -> v -> Pair
forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
.= Map Text Double
lb]) Maybe (Map Text Double)
logitBias
[Pair] -> [Pair] -> [Pair]
forall a. [a] -> [a] -> [a]
++ [Pair] -> (Bool -> [Pair]) -> Maybe Bool -> [Pair]
forall b a. b -> (a -> b) -> Maybe a -> b
maybe [] (\Bool
lp -> [Key
"logprobs" Key -> Bool -> Pair
forall v. ToJSON v => Key -> v -> Pair
forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
.= Bool
lp]) Maybe Bool
logprobs
[Pair] -> [Pair] -> [Pair]
forall a. [a] -> [a] -> [a]
++ [Pair] -> (Int -> [Pair]) -> Maybe Int -> [Pair]
forall b a. b -> (a -> b) -> Maybe a -> b
maybe [] (\Int
mt -> [Key
"max_completion_tokens" Key -> Int -> Pair
forall v. ToJSON v => Key -> v -> Pair
forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
.= Int
mt]) Maybe Int
maxCompletionTokens
[Pair] -> [Pair] -> [Pair]
forall a. [a] -> [a] -> [a]
++ [Pair] -> (Int -> [Pair]) -> Maybe Int -> [Pair]
forall b a. b -> (a -> b) -> Maybe a -> b
maybe [] (\Int
mt -> [Key
"max_tokens" Key -> Int -> Pair
forall v. ToJSON v => Key -> v -> Pair
forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
.= Int
mt]) Maybe Int
maxTokens
[Pair] -> [Pair] -> [Pair]
forall a. [a] -> [a] -> [a]
++ [Pair]
-> (Map Text Text -> [Pair]) -> Maybe (Map Text Text) -> [Pair]
forall b a. b -> (a -> b) -> Maybe a -> b
maybe [] (\Map Text Text
md -> [Key
"metadata" Key -> Map Text Text -> Pair
forall v. ToJSON v => Key -> v -> Pair
forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
.= Map Text Text
md]) Maybe (Map Text Text)
metadata
[Pair] -> [Pair] -> [Pair]
forall a. [a] -> [a] -> [a]
++ [Pair] -> ([Modality] -> [Pair]) -> Maybe [Modality] -> [Pair]
forall b a. b -> (a -> b) -> Maybe a -> b
maybe [] (\[Modality]
m -> [Key
"modalities" Key -> [Modality] -> Pair
forall v. ToJSON v => Key -> v -> Pair
forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
.= [Modality]
m]) Maybe [Modality]
modalities
[Pair] -> [Pair] -> [Pair]
forall a. [a] -> [a] -> [a]
++ [Pair] -> (Int -> [Pair]) -> Maybe Int -> [Pair]
forall b a. b -> (a -> b) -> Maybe a -> b
maybe [] (\Int
n' -> [Key
"n" Key -> Int -> Pair
forall v. ToJSON v => Key -> v -> Pair
forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
.= Int
n']) Maybe Int
n
[Pair] -> [Pair] -> [Pair]
forall a. [a] -> [a] -> [a]
++ [Pair] -> (Bool -> [Pair]) -> Maybe Bool -> [Pair]
forall b a. b -> (a -> b) -> Maybe a -> b
maybe [] (\Bool
ptc -> [Key
"parallel_tool_calls" Key -> Bool -> Pair
forall v. ToJSON v => Key -> v -> Pair
forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
.= Bool
ptc]) Maybe Bool
parallelToolCalls
[Pair] -> [Pair] -> [Pair]
forall a. [a] -> [a] -> [a]
++ [Pair]
-> (PredictionOutput -> [Pair]) -> Maybe PredictionOutput -> [Pair]
forall b a. b -> (a -> b) -> Maybe a -> b
maybe [] (\PredictionOutput
p -> [Key
"prediction" Key -> PredictionOutput -> Pair
forall v. ToJSON v => Key -> v -> Pair
forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
.= PredictionOutput
p]) Maybe PredictionOutput
prediction
[Pair] -> [Pair] -> [Pair]
forall a. [a] -> [a] -> [a]
++ [Pair] -> (Double -> [Pair]) -> Maybe Double -> [Pair]
forall b a. b -> (a -> b) -> Maybe a -> b
maybe [] (\Double
pp -> [Key
"presence_penalty" Key -> Double -> Pair
forall v. ToJSON v => Key -> v -> Pair
forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
.= Double
pp]) Maybe Double
presencePenalty
[Pair] -> [Pair] -> [Pair]
forall a. [a] -> [a] -> [a]
++ [Pair]
-> (ReasoningEffort -> [Pair]) -> Maybe ReasoningEffort -> [Pair]
forall b a. b -> (a -> b) -> Maybe a -> b
maybe [] (\ReasoningEffort
re -> [Key
"reasoning_effort" Key -> ReasoningEffort -> Pair
forall v. ToJSON v => Key -> v -> Pair
forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
.= ReasoningEffort
re]) Maybe ReasoningEffort
reasoningEffort
[Pair] -> [Pair] -> [Pair]
forall a. [a] -> [a] -> [a]
++ [Pair]
-> (ResponseFormat -> [Pair]) -> Maybe ResponseFormat -> [Pair]
forall b a. b -> (a -> b) -> Maybe a -> b
maybe [] (\ResponseFormat
rf -> [Key
"response_format" Key -> ResponseFormat -> Pair
forall v. ToJSON v => Key -> v -> Pair
forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
.= ResponseFormat
rf]) Maybe ResponseFormat
responseFormat
[Pair] -> [Pair] -> [Pair]
forall a. [a] -> [a] -> [a]
++ [Pair] -> (Int -> [Pair]) -> Maybe Int -> [Pair]
forall b a. b -> (a -> b) -> Maybe a -> b
maybe [] (\Int
s -> [Key
"seed" Key -> Int -> Pair
forall v. ToJSON v => Key -> v -> Pair
forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
.= Int
s]) Maybe Int
seed
[Pair] -> [Pair] -> [Pair]
forall a. [a] -> [a] -> [a]
++ [Pair] -> (Text -> [Pair]) -> Maybe Text -> [Pair]
forall b a. b -> (a -> b) -> Maybe a -> b
maybe [] (\Text
st -> [Key
"service_tier" Key -> Text -> Pair
forall v. ToJSON v => Key -> v -> Pair
forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
.= Text
st]) Maybe Text
serviceTier
[Pair] -> [Pair] -> [Pair]
forall a. [a] -> [a] -> [a]
++ [Pair]
-> (Either Text [Text] -> [Pair])
-> Maybe (Either Text [Text])
-> [Pair]
forall b a. b -> (a -> b) -> Maybe a -> b
maybe [] (\Either Text [Text]
s -> [Key
"stop" Key -> Either Text [Text] -> Pair
forall v. ToJSON v => Key -> v -> Pair
forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
.= Either Text [Text]
s]) Maybe (Either Text [Text])
stop
[Pair] -> [Pair] -> [Pair]
forall a. [a] -> [a] -> [a]
++ [Pair] -> (Bool -> [Pair]) -> Maybe Bool -> [Pair]
forall b a. b -> (a -> b) -> Maybe a -> b
maybe [] (\Bool
s -> [Key
"store" Key -> Bool -> Pair
forall v. ToJSON v => Key -> v -> Pair
forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
.= Bool
s]) Maybe Bool
store
[Pair] -> [Pair] -> [Pair]
forall a. [a] -> [a] -> [a]
++ [Pair] -> (Bool -> [Pair]) -> Maybe Bool -> [Pair]
forall b a. b -> (a -> b) -> Maybe a -> b
maybe [] (\Bool
s -> [Key
"stream" Key -> Bool -> Pair
forall v. ToJSON v => Key -> v -> Pair
forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
.= Bool
s]) Maybe Bool
stream
[Pair] -> [Pair] -> [Pair]
forall a. [a] -> [a] -> [a]
++ [Pair]
-> (StreamOptions -> [Pair]) -> Maybe StreamOptions -> [Pair]
forall b a. b -> (a -> b) -> Maybe a -> b
maybe [] (\StreamOptions
so -> [Key
"stream_options" Key -> StreamOptions -> Pair
forall v. ToJSON v => Key -> v -> Pair
forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
.= StreamOptions
so]) Maybe StreamOptions
streamOptions
[Pair] -> [Pair] -> [Pair]
forall a. [a] -> [a] -> [a]
++ [Pair] -> (Double -> [Pair]) -> Maybe Double -> [Pair]
forall b a. b -> (a -> b) -> Maybe a -> b
maybe [] (\Double
t -> [Key
"temperature" Key -> Double -> Pair
forall v. ToJSON v => Key -> v -> Pair
forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
.= Double
t]) Maybe Double
temperature
[Pair] -> [Pair] -> [Pair]
forall a. [a] -> [a] -> [a]
++ [Pair] -> (ToolChoice -> [Pair]) -> Maybe ToolChoice -> [Pair]
forall b a. b -> (a -> b) -> Maybe a -> b
maybe [] (\ToolChoice
tc -> [Key
"tool_choice" Key -> ToolChoice -> Pair
forall v. ToJSON v => Key -> v -> Pair
forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
.= ToolChoice
tc]) Maybe ToolChoice
toolChoice
[Pair] -> [Pair] -> [Pair]
forall a. [a] -> [a] -> [a]
++ [Pair] -> ([Tool_] -> [Pair]) -> Maybe [Tool_] -> [Pair]
forall b a. b -> (a -> b) -> Maybe a -> b
maybe [] (\[Tool_]
t -> [Key
"tools" Key -> [Tool_] -> Pair
forall v. ToJSON v => Key -> v -> Pair
forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
.= [Tool_]
t]) Maybe [Tool_]
tools
[Pair] -> [Pair] -> [Pair]
forall a. [a] -> [a] -> [a]
++ [Pair] -> (Int -> [Pair]) -> Maybe Int -> [Pair]
forall b a. b -> (a -> b) -> Maybe a -> b
maybe [] (\Int
tlp -> [Key
"top_logprobs" Key -> Int -> Pair
forall v. ToJSON v => Key -> v -> Pair
forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
.= Int
tlp]) Maybe Int
topLogprobs
[Pair] -> [Pair] -> [Pair]
forall a. [a] -> [a] -> [a]
++ [Pair] -> (Double -> [Pair]) -> Maybe Double -> [Pair]
forall b a. b -> (a -> b) -> Maybe a -> b
maybe [] (\Double
tp -> [Key
"top_p" Key -> Double -> Pair
forall v. ToJSON v => Key -> v -> Pair
forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
.= Double
tp]) Maybe Double
topP
[Pair] -> [Pair] -> [Pair]
forall a. [a] -> [a] -> [a]
++ [Pair] -> (Text -> [Pair]) -> Maybe Text -> [Pair]
forall b a. b -> (a -> b) -> Maybe a -> b
maybe [] (\Text
u -> [Key
"user" Key -> Text -> Pair
forall v. ToJSON v => Key -> v -> Pair
forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
.= Text
u]) Maybe Text
user
[Pair] -> [Pair] -> [Pair]
forall a. [a] -> [a] -> [a]
++ [Pair]
-> (WebSearchOptions -> [Pair]) -> Maybe WebSearchOptions -> [Pair]
forall b a. b -> (a -> b) -> Maybe a -> b
maybe [] (\WebSearchOptions
wso -> [Key
"web_search_options" Key -> WebSearchOptions -> Pair
forall v. ToJSON v => Key -> v -> Pair
forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
.= WebSearchOptions
wso]) Maybe WebSearchOptions
webSearchOptions
[Pair] -> [Pair] -> [Pair]
forall a. [a] -> [a] -> [a]
++ [Pair] -> (AudioConfig -> [Pair]) -> Maybe AudioConfig -> [Pair]
forall b a. b -> (a -> b) -> Maybe a -> b
maybe [] (\AudioConfig
a -> [Key
"audio" Key -> AudioConfig -> Pair
forall v. ToJSON v => Key -> v -> Pair
forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
.= AudioConfig
a]) Maybe AudioConfig
audio
data FinishReason = Stop | Length | ContentFilter | ToolCalls | FunctionCall
deriving (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, FinishReason -> FinishReason -> Bool
(FinishReason -> FinishReason -> Bool)
-> (FinishReason -> FinishReason -> Bool) -> Eq FinishReason
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: FinishReason -> FinishReason -> Bool
== :: FinishReason -> FinishReason -> Bool
$c/= :: FinishReason -> FinishReason -> Bool
/= :: FinishReason -> FinishReason -> Bool
Eq, (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)
instance FromJSON FinishReason where
parseJSON :: Value -> Parser FinishReason
parseJSON (String Text
"stop") = FinishReason -> Parser FinishReason
forall a. a -> Parser a
forall (m :: * -> *) a. Monad m => a -> m a
return FinishReason
Stop
parseJSON (String Text
"length") = FinishReason -> Parser FinishReason
forall a. a -> Parser a
forall (m :: * -> *) a. Monad m => a -> m a
return FinishReason
Length
parseJSON (String Text
"content_filter") = FinishReason -> Parser FinishReason
forall a. a -> Parser a
forall (m :: * -> *) a. Monad m => a -> m a
return FinishReason
ContentFilter
parseJSON (String Text
"tool_calls") = FinishReason -> Parser FinishReason
forall a. a -> Parser a
forall (m :: * -> *) a. Monad m => a -> m a
return FinishReason
ToolCalls
parseJSON (String Text
"function_call") = FinishReason -> Parser FinishReason
forall a. a -> Parser a
forall (m :: * -> *) a. Monad m => a -> m a
return FinishReason
FunctionCall
parseJSON Value
invalid = String -> Parser FinishReason
forall a. String -> Parser a
forall (m :: * -> *) a. MonadFail m => String -> m a
fail (String -> Parser FinishReason) -> String -> Parser FinishReason
forall a b. (a -> b) -> a -> b
$ String
"Invalid finish reason: " String -> ShowS
forall a. [a] -> [a] -> [a]
++ Value -> String
forall a. Show a => a -> String
show Value
invalid
data TopLogProb = TopLogProb
{ TopLogProb -> Maybe [Int]
bytes :: Maybe [Int]
, TopLogProb -> Double
logprob :: Double
, TopLogProb -> Text
token :: Text
}
deriving (Int -> TopLogProb -> ShowS
[TopLogProb] -> ShowS
TopLogProb -> String
(Int -> TopLogProb -> ShowS)
-> (TopLogProb -> String)
-> ([TopLogProb] -> ShowS)
-> Show TopLogProb
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> TopLogProb -> ShowS
showsPrec :: Int -> TopLogProb -> ShowS
$cshow :: TopLogProb -> String
show :: TopLogProb -> String
$cshowList :: [TopLogProb] -> ShowS
showList :: [TopLogProb] -> ShowS
Show, TopLogProb -> TopLogProb -> Bool
(TopLogProb -> TopLogProb -> Bool)
-> (TopLogProb -> TopLogProb -> Bool) -> Eq TopLogProb
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: TopLogProb -> TopLogProb -> Bool
== :: TopLogProb -> TopLogProb -> Bool
$c/= :: TopLogProb -> TopLogProb -> Bool
/= :: TopLogProb -> TopLogProb -> Bool
Eq, (forall x. TopLogProb -> Rep TopLogProb x)
-> (forall x. Rep TopLogProb x -> TopLogProb) -> Generic TopLogProb
forall x. Rep TopLogProb x -> TopLogProb
forall x. TopLogProb -> Rep TopLogProb x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cfrom :: forall x. TopLogProb -> Rep TopLogProb x
from :: forall x. TopLogProb -> Rep TopLogProb x
$cto :: forall x. Rep TopLogProb x -> TopLogProb
to :: forall x. Rep TopLogProb x -> TopLogProb
Generic)
instance FromJSON TopLogProb where
parseJSON :: Value -> Parser TopLogProb
parseJSON = String
-> (Object -> Parser TopLogProb) -> Value -> Parser TopLogProb
forall a. String -> (Object -> Parser a) -> Value -> Parser a
withObject String
"TopLogProb" ((Object -> Parser TopLogProb) -> Value -> Parser TopLogProb)
-> (Object -> Parser TopLogProb) -> Value -> Parser TopLogProb
forall a b. (a -> b) -> a -> b
$ \Object
v ->
Maybe [Int] -> Double -> Text -> TopLogProb
TopLogProb
(Maybe [Int] -> Double -> Text -> TopLogProb)
-> Parser (Maybe [Int]) -> Parser (Double -> Text -> TopLogProb)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Object
v Object -> Key -> Parser (Maybe [Int])
forall a. FromJSON a => Object -> Key -> Parser (Maybe a)
.:? Key
"bytes"
Parser (Double -> Text -> TopLogProb)
-> Parser Double -> Parser (Text -> TopLogProb)
forall a b. Parser (a -> b) -> Parser a -> Parser b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Object
v Object -> Key -> Parser Double
forall a. FromJSON a => Object -> Key -> Parser a
.: Key
"logprob"
Parser (Text -> TopLogProb) -> Parser Text -> Parser TopLogProb
forall a b. Parser (a -> b) -> Parser a -> Parser b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Object
v Object -> Key -> Parser Text
forall a. FromJSON a => Object -> Key -> Parser a
.: Key
"token"
data LogProbContent = LogProbContent
{ LogProbContent -> Maybe [Int]
bytes :: Maybe [Int]
, LogProbContent -> Double
logprob :: Double
, LogProbContent -> Text
token :: Text
, LogProbContent -> [TopLogProb]
topLogprobs :: [TopLogProb]
}
deriving (Int -> LogProbContent -> ShowS
[LogProbContent] -> ShowS
LogProbContent -> String
(Int -> LogProbContent -> ShowS)
-> (LogProbContent -> String)
-> ([LogProbContent] -> ShowS)
-> Show LogProbContent
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> LogProbContent -> ShowS
showsPrec :: Int -> LogProbContent -> ShowS
$cshow :: LogProbContent -> String
show :: LogProbContent -> String
$cshowList :: [LogProbContent] -> ShowS
showList :: [LogProbContent] -> ShowS
Show, LogProbContent -> LogProbContent -> Bool
(LogProbContent -> LogProbContent -> Bool)
-> (LogProbContent -> LogProbContent -> Bool) -> Eq LogProbContent
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: LogProbContent -> LogProbContent -> Bool
== :: LogProbContent -> LogProbContent -> Bool
$c/= :: LogProbContent -> LogProbContent -> Bool
/= :: LogProbContent -> LogProbContent -> Bool
Eq, (forall x. LogProbContent -> Rep LogProbContent x)
-> (forall x. Rep LogProbContent x -> LogProbContent)
-> Generic LogProbContent
forall x. Rep LogProbContent x -> LogProbContent
forall x. LogProbContent -> Rep LogProbContent x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cfrom :: forall x. LogProbContent -> Rep LogProbContent x
from :: forall x. LogProbContent -> Rep LogProbContent x
$cto :: forall x. Rep LogProbContent x -> LogProbContent
to :: forall x. Rep LogProbContent x -> LogProbContent
Generic)
instance FromJSON LogProbContent where
parseJSON :: Value -> Parser LogProbContent
parseJSON = String
-> (Object -> Parser LogProbContent)
-> Value
-> Parser LogProbContent
forall a. String -> (Object -> Parser a) -> Value -> Parser a
withObject String
"LogProbContent" ((Object -> Parser LogProbContent)
-> Value -> Parser LogProbContent)
-> (Object -> Parser LogProbContent)
-> Value
-> Parser LogProbContent
forall a b. (a -> b) -> a -> b
$ \Object
v ->
Maybe [Int] -> Double -> Text -> [TopLogProb] -> LogProbContent
LogProbContent
(Maybe [Int] -> Double -> Text -> [TopLogProb] -> LogProbContent)
-> Parser (Maybe [Int])
-> Parser (Double -> Text -> [TopLogProb] -> LogProbContent)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Object
v Object -> Key -> Parser (Maybe [Int])
forall a. FromJSON a => Object -> Key -> Parser (Maybe a)
.:? Key
"bytes"
Parser (Double -> Text -> [TopLogProb] -> LogProbContent)
-> Parser Double -> Parser (Text -> [TopLogProb] -> LogProbContent)
forall a b. Parser (a -> b) -> Parser a -> Parser b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Object
v Object -> Key -> Parser Double
forall a. FromJSON a => Object -> Key -> Parser a
.: Key
"logprob"
Parser (Text -> [TopLogProb] -> LogProbContent)
-> Parser Text -> Parser ([TopLogProb] -> LogProbContent)
forall a b. Parser (a -> b) -> Parser a -> Parser b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Object
v Object -> Key -> Parser Text
forall a. FromJSON a => Object -> Key -> Parser a
.: Key
"token"
Parser ([TopLogProb] -> LogProbContent)
-> Parser [TopLogProb] -> Parser LogProbContent
forall a b. Parser (a -> b) -> Parser a -> Parser b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Object
v Object -> Key -> Parser [TopLogProb]
forall a. FromJSON a => Object -> Key -> Parser a
.: Key
"top_logprobs"
data LogProbs = LogProbs
{ LogProbs -> Maybe [LogProbContent]
content :: Maybe [LogProbContent]
, LogProbs -> Maybe [LogProbContent]
refusal :: Maybe [LogProbContent]
}
deriving (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, LogProbs -> LogProbs -> Bool
(LogProbs -> LogProbs -> Bool)
-> (LogProbs -> LogProbs -> Bool) -> Eq LogProbs
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: LogProbs -> LogProbs -> Bool
== :: LogProbs -> LogProbs -> Bool
$c/= :: LogProbs -> LogProbs -> Bool
/= :: LogProbs -> LogProbs -> Bool
Eq, (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)
instance FromJSON LogProbs where
parseJSON :: Value -> Parser LogProbs
parseJSON = String -> (Object -> Parser LogProbs) -> Value -> Parser LogProbs
forall a. String -> (Object -> Parser a) -> Value -> Parser a
withObject String
"LogProbs" ((Object -> Parser LogProbs) -> Value -> Parser LogProbs)
-> (Object -> Parser LogProbs) -> Value -> Parser LogProbs
forall a b. (a -> b) -> a -> b
$ \Object
v ->
Maybe [LogProbContent] -> Maybe [LogProbContent] -> LogProbs
LogProbs
(Maybe [LogProbContent] -> Maybe [LogProbContent] -> LogProbs)
-> Parser (Maybe [LogProbContent])
-> Parser (Maybe [LogProbContent] -> LogProbs)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Object
v Object -> Key -> Parser (Maybe [LogProbContent])
forall a. FromJSON a => Object -> Key -> Parser (Maybe a)
.:? Key
"content"
Parser (Maybe [LogProbContent] -> LogProbs)
-> Parser (Maybe [LogProbContent]) -> Parser LogProbs
forall a b. Parser (a -> b) -> Parser a -> Parser b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Object
v Object -> Key -> Parser (Maybe [LogProbContent])
forall a. FromJSON a => Object -> Key -> Parser (Maybe a)
.:? Key
"refusal"
data CompletionTokensDetails = CompletionTokensDetails
{ CompletionTokensDetails -> Int
acceptedPredictionTokens :: Int
, CompletionTokensDetails -> Int
audioTokens :: Int
, CompletionTokensDetails -> Int
reasoningTokens :: Int
, CompletionTokensDetails -> Int
rejectedPredictionTokens :: Int
}
deriving (Int -> CompletionTokensDetails -> ShowS
[CompletionTokensDetails] -> ShowS
CompletionTokensDetails -> String
(Int -> CompletionTokensDetails -> ShowS)
-> (CompletionTokensDetails -> String)
-> ([CompletionTokensDetails] -> ShowS)
-> Show CompletionTokensDetails
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> CompletionTokensDetails -> ShowS
showsPrec :: Int -> CompletionTokensDetails -> ShowS
$cshow :: CompletionTokensDetails -> String
show :: CompletionTokensDetails -> String
$cshowList :: [CompletionTokensDetails] -> ShowS
showList :: [CompletionTokensDetails] -> ShowS
Show, CompletionTokensDetails -> CompletionTokensDetails -> Bool
(CompletionTokensDetails -> CompletionTokensDetails -> Bool)
-> (CompletionTokensDetails -> CompletionTokensDetails -> Bool)
-> Eq CompletionTokensDetails
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: CompletionTokensDetails -> CompletionTokensDetails -> Bool
== :: CompletionTokensDetails -> CompletionTokensDetails -> Bool
$c/= :: CompletionTokensDetails -> CompletionTokensDetails -> Bool
/= :: CompletionTokensDetails -> CompletionTokensDetails -> Bool
Eq, (forall x.
CompletionTokensDetails -> Rep CompletionTokensDetails x)
-> (forall x.
Rep CompletionTokensDetails x -> CompletionTokensDetails)
-> Generic CompletionTokensDetails
forall x. Rep CompletionTokensDetails x -> CompletionTokensDetails
forall x. CompletionTokensDetails -> Rep CompletionTokensDetails x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cfrom :: forall x. CompletionTokensDetails -> Rep CompletionTokensDetails x
from :: forall x. CompletionTokensDetails -> Rep CompletionTokensDetails x
$cto :: forall x. Rep CompletionTokensDetails x -> CompletionTokensDetails
to :: forall x. Rep CompletionTokensDetails x -> CompletionTokensDetails
Generic)
instance FromJSON CompletionTokensDetails where
parseJSON :: Value -> Parser CompletionTokensDetails
parseJSON = String
-> (Object -> Parser CompletionTokensDetails)
-> Value
-> Parser CompletionTokensDetails
forall a. String -> (Object -> Parser a) -> Value -> Parser a
withObject String
"CompletionTokensDetails" ((Object -> Parser CompletionTokensDetails)
-> Value -> Parser CompletionTokensDetails)
-> (Object -> Parser CompletionTokensDetails)
-> Value
-> Parser CompletionTokensDetails
forall a b. (a -> b) -> a -> b
$ \Object
v ->
Int -> Int -> Int -> Int -> CompletionTokensDetails
CompletionTokensDetails
(Int -> Int -> Int -> Int -> CompletionTokensDetails)
-> Parser Int
-> Parser (Int -> Int -> Int -> CompletionTokensDetails)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Object
v Object -> Key -> Parser Int
forall a. FromJSON a => Object -> Key -> Parser a
.: Key
"accepted_prediction_tokens"
Parser (Int -> Int -> Int -> CompletionTokensDetails)
-> Parser Int -> Parser (Int -> Int -> CompletionTokensDetails)
forall a b. Parser (a -> b) -> Parser a -> Parser b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Object
v Object -> Key -> Parser Int
forall a. FromJSON a => Object -> Key -> Parser a
.: Key
"audio_tokens"
Parser (Int -> Int -> CompletionTokensDetails)
-> Parser Int -> Parser (Int -> CompletionTokensDetails)
forall a b. Parser (a -> b) -> Parser a -> Parser b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Object
v Object -> Key -> Parser Int
forall a. FromJSON a => Object -> Key -> Parser a
.: Key
"reasoning_tokens"
Parser (Int -> CompletionTokensDetails)
-> Parser Int -> Parser CompletionTokensDetails
forall a b. Parser (a -> b) -> Parser a -> Parser b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Object
v Object -> Key -> Parser Int
forall a. FromJSON a => Object -> Key -> Parser a
.: Key
"rejected_prediction_tokens"
data PromptTokensDetails = PromptTokensDetails
{ PromptTokensDetails -> Int
audioTokens :: Int
, PromptTokensDetails -> Int
cachedTokens :: Int
}
deriving (Int -> PromptTokensDetails -> ShowS
[PromptTokensDetails] -> ShowS
PromptTokensDetails -> String
(Int -> PromptTokensDetails -> ShowS)
-> (PromptTokensDetails -> String)
-> ([PromptTokensDetails] -> ShowS)
-> Show PromptTokensDetails
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> PromptTokensDetails -> ShowS
showsPrec :: Int -> PromptTokensDetails -> ShowS
$cshow :: PromptTokensDetails -> String
show :: PromptTokensDetails -> String
$cshowList :: [PromptTokensDetails] -> ShowS
showList :: [PromptTokensDetails] -> ShowS
Show, PromptTokensDetails -> PromptTokensDetails -> Bool
(PromptTokensDetails -> PromptTokensDetails -> Bool)
-> (PromptTokensDetails -> PromptTokensDetails -> Bool)
-> Eq PromptTokensDetails
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: PromptTokensDetails -> PromptTokensDetails -> Bool
== :: PromptTokensDetails -> PromptTokensDetails -> Bool
$c/= :: PromptTokensDetails -> PromptTokensDetails -> Bool
/= :: PromptTokensDetails -> PromptTokensDetails -> Bool
Eq, (forall x. PromptTokensDetails -> Rep PromptTokensDetails x)
-> (forall x. Rep PromptTokensDetails x -> PromptTokensDetails)
-> Generic PromptTokensDetails
forall x. Rep PromptTokensDetails x -> PromptTokensDetails
forall x. PromptTokensDetails -> Rep PromptTokensDetails x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cfrom :: forall x. PromptTokensDetails -> Rep PromptTokensDetails x
from :: forall x. PromptTokensDetails -> Rep PromptTokensDetails x
$cto :: forall x. Rep PromptTokensDetails x -> PromptTokensDetails
to :: forall x. Rep PromptTokensDetails x -> PromptTokensDetails
Generic)
instance FromJSON PromptTokensDetails where
parseJSON :: Value -> Parser PromptTokensDetails
parseJSON = String
-> (Object -> Parser PromptTokensDetails)
-> Value
-> Parser PromptTokensDetails
forall a. String -> (Object -> Parser a) -> Value -> Parser a
withObject String
"PromptTokensDetails" ((Object -> Parser PromptTokensDetails)
-> Value -> Parser PromptTokensDetails)
-> (Object -> Parser PromptTokensDetails)
-> Value
-> Parser PromptTokensDetails
forall a b. (a -> b) -> a -> b
$ \Object
v ->
Int -> Int -> PromptTokensDetails
PromptTokensDetails
(Int -> Int -> PromptTokensDetails)
-> Parser Int -> Parser (Int -> PromptTokensDetails)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Object
v Object -> Key -> Parser Int
forall a. FromJSON a => Object -> Key -> Parser a
.: Key
"audio_tokens"
Parser (Int -> PromptTokensDetails)
-> Parser Int -> Parser PromptTokensDetails
forall a b. Parser (a -> b) -> Parser a -> Parser b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Object
v Object -> Key -> Parser Int
forall a. FromJSON a => Object -> Key -> Parser a
.: Key
"cached_tokens"
data Usage = Usage
{ Usage -> Int
completionTokens :: Int
, Usage -> Int
promptTokens :: Int
, Usage -> Int
totalTokens :: Int
, Usage -> Maybe CompletionTokensDetails
completionTokensDetails :: Maybe CompletionTokensDetails
, Usage -> Maybe PromptTokensDetails
promptTokensDetails :: Maybe PromptTokensDetails
}
deriving (Int -> Usage -> ShowS
[Usage] -> ShowS
Usage -> String
(Int -> Usage -> ShowS)
-> (Usage -> String) -> ([Usage] -> ShowS) -> Show Usage
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> Usage -> ShowS
showsPrec :: Int -> Usage -> ShowS
$cshow :: Usage -> String
show :: Usage -> String
$cshowList :: [Usage] -> ShowS
showList :: [Usage] -> ShowS
Show, Usage -> Usage -> Bool
(Usage -> Usage -> Bool) -> (Usage -> Usage -> Bool) -> Eq Usage
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: Usage -> Usage -> Bool
== :: Usage -> Usage -> Bool
$c/= :: Usage -> Usage -> Bool
/= :: Usage -> Usage -> Bool
Eq, (forall x. Usage -> Rep Usage x)
-> (forall x. Rep Usage x -> Usage) -> Generic Usage
forall x. Rep Usage x -> Usage
forall x. Usage -> Rep Usage x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cfrom :: forall x. Usage -> Rep Usage x
from :: forall x. Usage -> Rep Usage x
$cto :: forall x. Rep Usage x -> Usage
to :: forall x. Rep Usage x -> Usage
Generic)
instance FromJSON Usage where
parseJSON :: Value -> Parser Usage
parseJSON = String -> (Object -> Parser Usage) -> Value -> Parser Usage
forall a. String -> (Object -> Parser a) -> Value -> Parser a
withObject String
"Usage" ((Object -> Parser Usage) -> Value -> Parser Usage)
-> (Object -> Parser Usage) -> Value -> Parser Usage
forall a b. (a -> b) -> a -> b
$ \Object
v ->
Int
-> Int
-> Int
-> Maybe CompletionTokensDetails
-> Maybe PromptTokensDetails
-> Usage
Usage
(Int
-> Int
-> Int
-> Maybe CompletionTokensDetails
-> Maybe PromptTokensDetails
-> Usage)
-> Parser Int
-> Parser
(Int
-> Int
-> Maybe CompletionTokensDetails
-> Maybe PromptTokensDetails
-> Usage)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Object
v Object -> Key -> Parser Int
forall a. FromJSON a => Object -> Key -> Parser a
.: Key
"completion_tokens"
Parser
(Int
-> Int
-> Maybe CompletionTokensDetails
-> Maybe PromptTokensDetails
-> Usage)
-> Parser Int
-> Parser
(Int
-> Maybe CompletionTokensDetails
-> Maybe PromptTokensDetails
-> Usage)
forall a b. Parser (a -> b) -> Parser a -> Parser b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Object
v Object -> Key -> Parser Int
forall a. FromJSON a => Object -> Key -> Parser a
.: Key
"prompt_tokens"
Parser
(Int
-> Maybe CompletionTokensDetails
-> Maybe PromptTokensDetails
-> Usage)
-> Parser Int
-> Parser
(Maybe CompletionTokensDetails
-> Maybe PromptTokensDetails -> Usage)
forall a b. Parser (a -> b) -> Parser a -> Parser b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Object
v Object -> Key -> Parser Int
forall a. FromJSON a => Object -> Key -> Parser a
.: Key
"total_tokens"
Parser
(Maybe CompletionTokensDetails
-> Maybe PromptTokensDetails -> Usage)
-> Parser (Maybe CompletionTokensDetails)
-> Parser (Maybe PromptTokensDetails -> Usage)
forall a b. Parser (a -> b) -> Parser a -> Parser b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Object
v Object -> Key -> Parser (Maybe CompletionTokensDetails)
forall a. FromJSON a => Object -> Key -> Parser (Maybe a)
.:? Key
"completion_tokens_details"
Parser (Maybe PromptTokensDetails -> Usage)
-> Parser (Maybe PromptTokensDetails) -> Parser Usage
forall a b. Parser (a -> b) -> Parser a -> Parser b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Object
v Object -> Key -> Parser (Maybe PromptTokensDetails)
forall a. FromJSON a => Object -> Key -> Parser (Maybe a)
.:? Key
"prompt_tokens_details"
data Choice = Choice
{ Choice -> FinishReason
finishReason :: FinishReason
, Choice -> Int
index :: Int
, Choice -> Maybe LogProbs
logprobs :: Maybe LogProbs
, Choice -> Message
message :: Message
}
deriving (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, Choice -> Choice -> Bool
(Choice -> Choice -> Bool)
-> (Choice -> Choice -> Bool) -> Eq Choice
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: Choice -> Choice -> Bool
== :: Choice -> Choice -> Bool
$c/= :: Choice -> Choice -> Bool
/= :: Choice -> Choice -> Bool
Eq, (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)
instance FromJSON Choice where
parseJSON :: Value -> Parser Choice
parseJSON = String -> (Object -> Parser Choice) -> Value -> Parser Choice
forall a. String -> (Object -> Parser a) -> Value -> Parser a
withObject String
"Choice" ((Object -> Parser Choice) -> Value -> Parser Choice)
-> (Object -> Parser Choice) -> Value -> Parser Choice
forall a b. (a -> b) -> a -> b
$ \Object
v ->
FinishReason -> Int -> Maybe LogProbs -> Message -> Choice
Choice
(FinishReason -> Int -> Maybe LogProbs -> Message -> Choice)
-> Parser FinishReason
-> Parser (Int -> Maybe LogProbs -> Message -> Choice)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Object
v Object -> Key -> Parser FinishReason
forall a. FromJSON a => Object -> Key -> Parser a
.: Key
"finish_reason"
Parser (Int -> Maybe LogProbs -> Message -> Choice)
-> Parser Int -> Parser (Maybe LogProbs -> Message -> Choice)
forall a b. Parser (a -> b) -> Parser a -> Parser b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Object
v Object -> Key -> Parser Int
forall a. FromJSON a => Object -> Key -> Parser a
.: Key
"index"
Parser (Maybe LogProbs -> Message -> Choice)
-> Parser (Maybe LogProbs) -> Parser (Message -> Choice)
forall a b. Parser (a -> b) -> Parser a -> Parser b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Object
v Object -> Key -> Parser (Maybe LogProbs)
forall a. FromJSON a => Object -> Key -> Parser (Maybe a)
.:? Key
"logprobs"
Parser (Message -> Choice) -> Parser Message -> Parser Choice
forall a b. Parser (a -> b) -> Parser a -> Parser b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Object
v Object -> Key -> Parser Message
forall a. FromJSON a => Object -> Key -> Parser a
.: Key
"message"
data ChatCompletionResponse = ChatCompletionResponse
{ ChatCompletionResponse -> [Choice]
choices :: [Choice]
, ChatCompletionResponse -> Integer
created :: Integer
, ChatCompletionResponse -> Text
id_ :: Text
, ChatCompletionResponse -> Text
responseModel :: Text
, ChatCompletionResponse -> Text
object_ :: Text
, ChatCompletionResponse -> Maybe Text
serviceTier :: Maybe Text
, ChatCompletionResponse -> Text
systemFingerprint :: Text
, ChatCompletionResponse -> Usage
usage :: Usage
}
deriving (Int -> ChatCompletionResponse -> ShowS
[ChatCompletionResponse] -> ShowS
ChatCompletionResponse -> String
(Int -> ChatCompletionResponse -> ShowS)
-> (ChatCompletionResponse -> String)
-> ([ChatCompletionResponse] -> ShowS)
-> Show ChatCompletionResponse
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> ChatCompletionResponse -> ShowS
showsPrec :: Int -> ChatCompletionResponse -> ShowS
$cshow :: ChatCompletionResponse -> String
show :: ChatCompletionResponse -> String
$cshowList :: [ChatCompletionResponse] -> ShowS
showList :: [ChatCompletionResponse] -> ShowS
Show, ChatCompletionResponse -> ChatCompletionResponse -> Bool
(ChatCompletionResponse -> ChatCompletionResponse -> Bool)
-> (ChatCompletionResponse -> ChatCompletionResponse -> Bool)
-> Eq ChatCompletionResponse
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: ChatCompletionResponse -> ChatCompletionResponse -> Bool
== :: ChatCompletionResponse -> ChatCompletionResponse -> Bool
$c/= :: ChatCompletionResponse -> ChatCompletionResponse -> Bool
/= :: ChatCompletionResponse -> ChatCompletionResponse -> Bool
Eq, (forall x. ChatCompletionResponse -> Rep ChatCompletionResponse x)
-> (forall x.
Rep ChatCompletionResponse x -> ChatCompletionResponse)
-> Generic ChatCompletionResponse
forall x. Rep ChatCompletionResponse x -> ChatCompletionResponse
forall x. ChatCompletionResponse -> Rep ChatCompletionResponse x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cfrom :: forall x. ChatCompletionResponse -> Rep ChatCompletionResponse x
from :: forall x. ChatCompletionResponse -> Rep ChatCompletionResponse x
$cto :: forall x. Rep ChatCompletionResponse x -> ChatCompletionResponse
to :: forall x. Rep ChatCompletionResponse x -> ChatCompletionResponse
Generic)
instance FromJSON ChatCompletionResponse where
parseJSON :: Value -> Parser ChatCompletionResponse
parseJSON = String
-> (Object -> Parser ChatCompletionResponse)
-> Value
-> Parser ChatCompletionResponse
forall a. String -> (Object -> Parser a) -> Value -> Parser a
withObject String
"ChatCompletionResponse" ((Object -> Parser ChatCompletionResponse)
-> Value -> Parser ChatCompletionResponse)
-> (Object -> Parser ChatCompletionResponse)
-> Value
-> Parser ChatCompletionResponse
forall a b. (a -> b) -> a -> b
$ \Object
v ->
[Choice]
-> Integer
-> Text
-> Text
-> Text
-> Maybe Text
-> Text
-> Usage
-> ChatCompletionResponse
ChatCompletionResponse
([Choice]
-> Integer
-> Text
-> Text
-> Text
-> Maybe Text
-> Text
-> Usage
-> ChatCompletionResponse)
-> Parser [Choice]
-> Parser
(Integer
-> Text
-> Text
-> Text
-> Maybe Text
-> Text
-> Usage
-> ChatCompletionResponse)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Object
v Object -> Key -> Parser [Choice]
forall a. FromJSON a => Object -> Key -> Parser a
.: Key
"choices"
Parser
(Integer
-> Text
-> Text
-> Text
-> Maybe Text
-> Text
-> Usage
-> ChatCompletionResponse)
-> Parser Integer
-> Parser
(Text
-> Text
-> Text
-> Maybe Text
-> Text
-> Usage
-> ChatCompletionResponse)
forall a b. Parser (a -> b) -> Parser a -> Parser b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Object
v Object -> Key -> Parser Integer
forall a. FromJSON a => Object -> Key -> Parser a
.: Key
"created"
Parser
(Text
-> Text
-> Text
-> Maybe Text
-> Text
-> Usage
-> ChatCompletionResponse)
-> Parser Text
-> Parser
(Text
-> Text -> Maybe Text -> Text -> Usage -> ChatCompletionResponse)
forall a b. Parser (a -> b) -> Parser a -> Parser b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Object
v Object -> Key -> Parser Text
forall a. FromJSON a => Object -> Key -> Parser a
.: Key
"id"
Parser
(Text
-> Text -> Maybe Text -> Text -> Usage -> ChatCompletionResponse)
-> Parser Text
-> Parser
(Text -> Maybe Text -> Text -> Usage -> ChatCompletionResponse)
forall a b. Parser (a -> b) -> Parser a -> Parser b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Object
v Object -> Key -> Parser Text
forall a. FromJSON a => Object -> Key -> Parser a
.: Key
"model"
Parser
(Text -> Maybe Text -> Text -> Usage -> ChatCompletionResponse)
-> Parser Text
-> Parser (Maybe Text -> Text -> Usage -> ChatCompletionResponse)
forall a b. Parser (a -> b) -> Parser a -> Parser b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Object
v Object -> Key -> Parser Text
forall a. FromJSON a => Object -> Key -> Parser a
.: Key
"object"
Parser (Maybe Text -> Text -> Usage -> ChatCompletionResponse)
-> Parser (Maybe Text)
-> Parser (Text -> Usage -> ChatCompletionResponse)
forall a b. Parser (a -> b) -> Parser a -> Parser b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Object
v Object -> Key -> Parser (Maybe Text)
forall a. FromJSON a => Object -> Key -> Parser (Maybe a)
.:? Key
"service_tier"
Parser (Text -> Usage -> ChatCompletionResponse)
-> Parser Text -> Parser (Usage -> ChatCompletionResponse)
forall a b. Parser (a -> b) -> Parser a -> Parser b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Object
v Object -> Key -> Parser Text
forall a. FromJSON a => Object -> Key -> Parser a
.: Key
"system_fingerprint"
Parser (Usage -> ChatCompletionResponse)
-> Parser Usage -> Parser ChatCompletionResponse
forall a b. Parser (a -> b) -> Parser a -> Parser b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Object
v Object -> Key -> Parser Usage
forall a. FromJSON a => Object -> Key -> Parser a
.: Key
"usage"
defaultChatCompletionRequest :: ChatCompletionRequest
defaultChatCompletionRequest :: ChatCompletionRequest
defaultChatCompletionRequest =
ChatCompletionRequest
{ $sel:messages:ChatCompletionRequest :: [Message]
messages = []
, $sel:model:ChatCompletionRequest :: Text
model = Text
"gpt-4o-mini-2024-07-18"
, $sel:frequencyPenalty:ChatCompletionRequest :: Maybe Double
frequencyPenalty = Maybe Double
forall a. Maybe a
Nothing
, $sel:logitBias:ChatCompletionRequest :: Maybe (Map Text Double)
logitBias = Maybe (Map Text Double)
forall a. Maybe a
Nothing
, $sel:logprobs:ChatCompletionRequest :: Maybe Bool
logprobs = Maybe Bool
forall a. Maybe a
Nothing
, $sel:maxCompletionTokens:ChatCompletionRequest :: Maybe Int
maxCompletionTokens = Maybe Int
forall a. Maybe a
Nothing
, $sel:maxTokens:ChatCompletionRequest :: Maybe Int
maxTokens = Maybe Int
forall a. Maybe a
Nothing
, $sel:metadata:ChatCompletionRequest :: Maybe (Map Text Text)
metadata = Maybe (Map Text Text)
forall a. Maybe a
Nothing
, $sel:modalities:ChatCompletionRequest :: Maybe [Modality]
modalities = Maybe [Modality]
forall a. Maybe a
Nothing
, $sel:n:ChatCompletionRequest :: Maybe Int
n = Maybe Int
forall a. Maybe a
Nothing
, $sel:parallelToolCalls:ChatCompletionRequest :: Maybe Bool
parallelToolCalls = Maybe Bool
forall a. Maybe a
Nothing
, $sel:prediction:ChatCompletionRequest :: Maybe PredictionOutput
prediction = Maybe PredictionOutput
forall a. Maybe a
Nothing
, $sel:presencePenalty:ChatCompletionRequest :: Maybe Double
presencePenalty = Maybe Double
forall a. Maybe a
Nothing
, $sel:reasoningEffort:ChatCompletionRequest :: Maybe ReasoningEffort
reasoningEffort = Maybe ReasoningEffort
forall a. Maybe a
Nothing
, $sel:responseFormat:ChatCompletionRequest :: Maybe ResponseFormat
responseFormat = Maybe ResponseFormat
forall a. Maybe a
Nothing
, $sel:seed:ChatCompletionRequest :: Maybe Int
seed = Maybe Int
forall a. Maybe a
Nothing
, $sel:serviceTier:ChatCompletionRequest :: Maybe Text
serviceTier = Maybe Text
forall a. Maybe a
Nothing
, $sel:stop:ChatCompletionRequest :: Maybe (Either Text [Text])
stop = Maybe (Either Text [Text])
forall a. Maybe a
Nothing
, $sel:store:ChatCompletionRequest :: Maybe Bool
store = Maybe Bool
forall a. Maybe a
Nothing
, $sel:stream:ChatCompletionRequest :: Maybe Bool
stream = Maybe Bool
forall a. Maybe a
Nothing
, $sel:streamOptions:ChatCompletionRequest :: Maybe StreamOptions
streamOptions = Maybe StreamOptions
forall a. Maybe a
Nothing
, $sel:temperature:ChatCompletionRequest :: Maybe Double
temperature = Maybe Double
forall a. Maybe a
Nothing
, $sel:toolChoice:ChatCompletionRequest :: Maybe ToolChoice
toolChoice = Maybe ToolChoice
forall a. Maybe a
Nothing
, $sel:tools:ChatCompletionRequest :: Maybe [Tool_]
tools = Maybe [Tool_]
forall a. Maybe a
Nothing
, $sel:topLogprobs:ChatCompletionRequest :: Maybe Int
topLogprobs = Maybe Int
forall a. Maybe a
Nothing
, $sel:topP:ChatCompletionRequest :: Maybe Double
topP = Maybe Double
forall a. Maybe a
Nothing
, $sel:user:ChatCompletionRequest :: Maybe Text
user = Maybe Text
forall a. Maybe a
Nothing
, $sel:webSearchOptions:ChatCompletionRequest :: Maybe WebSearchOptions
webSearchOptions = Maybe WebSearchOptions
forall a. Maybe a
Nothing
, $sel:audio:ChatCompletionRequest :: Maybe AudioConfig
audio = Maybe AudioConfig
forall a. Maybe a
Nothing
}
createChatCompletion :: Text -> ChatCompletionRequest -> IO (Either String ChatCompletionResponse)
createChatCompletion :: Text
-> ChatCompletionRequest
-> IO (Either String ChatCompletionResponse)
createChatCompletion Text
apiKey ChatCompletionRequest
r = do
Request
request_ <- String -> IO Request
forall (m :: * -> *). MonadThrow m => String -> m Request
parseRequest String
"https://api.openai.com/v1/chat/completions"
let req :: Request
req =
ByteString -> Request -> Request
setRequestMethod ByteString
"POST" (Request -> Request) -> Request -> Request
forall a b. (a -> b) -> a -> b
$
Bool -> Request -> Request
setRequestSecure Bool
True (Request -> Request) -> Request -> Request
forall a b. (a -> b) -> a -> b
$
ByteString -> Request -> Request
setRequestHost ByteString
"api.openai.com" (Request -> Request) -> Request -> Request
forall a b. (a -> b) -> a -> b
$
ByteString -> Request -> Request
setRequestPath ByteString
"/v1/chat/completions" (Request -> Request) -> Request -> Request
forall a b. (a -> b) -> a -> b
$
HeaderName -> [ByteString] -> Request -> Request
setRequestHeader HeaderName
"Content-Type" [ByteString
"application/json"] (Request -> Request) -> Request -> Request
forall a b. (a -> b) -> a -> b
$
HeaderName -> [ByteString] -> Request -> Request
setRequestHeader HeaderName
"Authorization" [ByteString
"Bearer " ByteString -> ByteString -> ByteString
forall a. Semigroup a => a -> a -> a
<> Text -> ByteString
encodeUtf8 Text
apiKey] (Request -> Request) -> Request -> Request
forall a b. (a -> b) -> a -> b
$
ChatCompletionRequest -> Request -> Request
forall a. ToJSON a => a -> Request -> Request
setRequestBodyJSON ChatCompletionRequest
r (Request -> Request) -> Request -> Request
forall a b. (a -> b) -> a -> b
$
Request
request_
Response ByteString
response <- Request -> IO (Response ByteString)
forall (m :: * -> *).
MonadIO m =>
Request -> m (Response ByteString)
httpLBS Request
req
let status :: Int
status = Status -> Int
statusCode (Status -> Int) -> Status -> Int
forall a b. (a -> b) -> a -> b
$ Response ByteString -> Status
forall a. Response a -> Status
getResponseStatus Response ByteString
response
if Int
status Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
>= Int
200 Bool -> Bool -> Bool
&& Int
status Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
< Int
300
then case ByteString -> Either String ChatCompletionResponse
forall a. FromJSON a => ByteString -> Either String a
eitherDecode (Response ByteString -> ByteString
forall a. Response a -> a
getResponseBody Response ByteString
response) of
Left String
err -> Either String ChatCompletionResponse
-> IO (Either String ChatCompletionResponse)
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return (Either String ChatCompletionResponse
-> IO (Either String ChatCompletionResponse))
-> Either String ChatCompletionResponse
-> IO (Either String ChatCompletionResponse)
forall a b. (a -> b) -> a -> b
$ String -> Either String ChatCompletionResponse
forall a b. a -> Either a b
Left (String -> Either String ChatCompletionResponse)
-> String -> Either String ChatCompletionResponse
forall a b. (a -> b) -> a -> b
$ String
"JSON parse error: " String -> ShowS
forall a. Semigroup a => a -> a -> a
<> String
err
Right ChatCompletionResponse
completionResponse -> Either String ChatCompletionResponse
-> IO (Either String ChatCompletionResponse)
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return (Either String ChatCompletionResponse
-> IO (Either String ChatCompletionResponse))
-> Either String ChatCompletionResponse
-> IO (Either String ChatCompletionResponse)
forall a b. (a -> b) -> a -> b
$ ChatCompletionResponse -> Either String ChatCompletionResponse
forall a b. b -> Either a b
Right ChatCompletionResponse
completionResponse
else Either String ChatCompletionResponse
-> IO (Either String ChatCompletionResponse)
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return (Either String ChatCompletionResponse
-> IO (Either String ChatCompletionResponse))
-> Either String ChatCompletionResponse
-> IO (Either String ChatCompletionResponse)
forall a b. (a -> b) -> a -> b
$ String -> Either String ChatCompletionResponse
forall a b. a -> Either a b
Left (String -> Either String ChatCompletionResponse)
-> String -> Either String ChatCompletionResponse
forall a b. (a -> b) -> a -> b
$ String
"API error: " String -> ShowS
forall a. Semigroup a => a -> a -> a
<> Int -> String
forall a. Show a => a -> String
show Int
status String -> ShowS
forall a. Semigroup a => a -> a -> a
<> String
" " String -> ShowS
forall a. Semigroup a => a -> a -> a
<> ByteString -> String
forall a. Show a => a -> String
show (Response ByteString -> ByteString
forall a. Response a -> a
getResponseBody Response ByteString
response)
data OpenAI = OpenAI
{ OpenAI -> Text
apiKey :: Text
, OpenAI -> Text
openAIModelName :: Text
, OpenAI -> [Callback]
callbacks :: [Callback]
}
instance Show OpenAI where
show :: OpenAI -> String
show OpenAI {[Callback]
Text
$sel:apiKey:OpenAI :: OpenAI -> Text
$sel:openAIModelName:OpenAI :: OpenAI -> Text
$sel:callbacks:OpenAI :: OpenAI -> [Callback]
apiKey :: Text
openAIModelName :: Text
callbacks :: [Callback]
..} = String
"OpenAI " String -> ShowS
forall a. [a] -> [a] -> [a]
++ Text -> String
forall a. Show a => a -> String
show Text
openAIModelName
instance LLM.LLM OpenAI where
generate :: OpenAI -> Text -> Maybe Params -> IO (Either String Text)
generate OpenAI {[Callback]
Text
$sel:apiKey:OpenAI :: OpenAI -> Text
$sel:openAIModelName:OpenAI :: OpenAI -> Text
$sel:callbacks:OpenAI :: OpenAI -> [Callback]
apiKey :: Text
openAIModelName :: Text
callbacks :: [Callback]
..} Text
prompt Maybe Params
_ = do
Either String ChatCompletionResponse
eRes <-
Text
-> ChatCompletionRequest
-> IO (Either String ChatCompletionResponse)
createChatCompletion
Text
apiKey
( ChatCompletionRequest
defaultChatCompletionRequest
{ model = openAIModelName
, messages =
[ Message
{ role = User
, content = Just (StringContent prompt)
, name = Nothing
, functionCall = Nothing
, toolCalls = Nothing
, toolCallId = Nothing
, audio = Nothing
, refusal = Nothing
}
]
}
)
case Either String ChatCompletionResponse
eRes of
Left String
err -> Either String Text -> IO (Either String Text)
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return (Either String Text -> IO (Either String Text))
-> Either String Text -> IO (Either String Text)
forall a b. (a -> b) -> a -> b
$ String -> Either String Text
forall a b. a -> Either a b
Left String
err
Right ChatCompletionResponse
r -> do
case [Choice] -> Maybe Choice
forall a. [a] -> Maybe a
listToMaybe (ChatCompletionResponse -> [Choice]
choices ChatCompletionResponse
r) of
Maybe Choice
Nothing -> Either String Text -> IO (Either String Text)
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return (Either String Text -> IO (Either String Text))
-> Either String Text -> IO (Either String Text)
forall a b. (a -> b) -> a -> b
$ String -> Either String Text
forall a b. a -> Either a b
Left String
"Did not received any response"
Just Choice
resp ->
let Message {Maybe [ToolCall]
Maybe Text
Maybe AudioResponse
Maybe FunctionCall_
Maybe MessageContent
Role
$sel:role:Message :: Message -> Role
$sel:content:Message :: Message -> Maybe MessageContent
$sel:name:Message :: Message -> Maybe Text
$sel:functionCall:Message :: Message -> Maybe FunctionCall_
$sel:toolCalls:Message :: Message -> Maybe [ToolCall]
$sel:toolCallId:Message :: Message -> Maybe Text
$sel:audio:Message :: Message -> Maybe AudioResponse
$sel:refusal:Message :: Message -> Maybe Text
role :: Role
content :: Maybe MessageContent
name :: Maybe Text
functionCall :: Maybe FunctionCall_
toolCalls :: Maybe [ToolCall]
toolCallId :: Maybe Text
audio :: Maybe AudioResponse
refusal :: Maybe Text
..} = Choice -> Message
message Choice
resp
in Either String Text -> IO (Either String Text)
forall a. a -> IO a
forall (f :: * -> *) a. Applicative f => a -> f a
pure (Either String Text -> IO (Either String Text))
-> Either String Text -> IO (Either String Text)
forall a b. (a -> b) -> a -> b
$
Text -> Either String Text
forall a b. b -> Either a b
Right (Text -> Either String Text) -> Text -> Either String Text
forall a b. (a -> b) -> a -> b
$
Text -> (MessageContent -> Text) -> Maybe MessageContent -> Text
forall b a. b -> (a -> b) -> Maybe a -> b
maybe
Text
""
( \MessageContent
c -> case MessageContent
c of
StringContent Text
t -> Text
t
ContentParts [TextContent]
_ -> Text
""
)
Maybe MessageContent
content
chat :: OpenAI -> ChatMessage -> Maybe Params -> IO (Either String Text)
chat OpenAI {[Callback]
Text
$sel:apiKey:OpenAI :: OpenAI -> Text
$sel:openAIModelName:OpenAI :: OpenAI -> Text
$sel:callbacks:OpenAI :: OpenAI -> [Callback]
apiKey :: Text
openAIModelName :: Text
callbacks :: [Callback]
..} ChatMessage
msgs Maybe Params
_ = do
Either String ChatCompletionResponse
eRes <-
Text
-> ChatCompletionRequest
-> IO (Either String ChatCompletionResponse)
createChatCompletion
Text
apiKey
( ChatCompletionRequest
defaultChatCompletionRequest
{ model = openAIModelName
, messages = toOpenAIMessages msgs
}
)
case Either String ChatCompletionResponse
eRes of
Left String
err -> Either String Text -> IO (Either String Text)
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return (Either String Text -> IO (Either String Text))
-> Either String Text -> IO (Either String Text)
forall a b. (a -> b) -> a -> b
$ String -> Either String Text
forall a b. a -> Either a b
Left String
err
Right ChatCompletionResponse
r -> do
case [Choice] -> Maybe Choice
forall a. [a] -> Maybe a
listToMaybe (ChatCompletionResponse -> [Choice]
choices ChatCompletionResponse
r) of
Maybe Choice
Nothing -> Either String Text -> IO (Either String Text)
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return (Either String Text -> IO (Either String Text))
-> Either String Text -> IO (Either String Text)
forall a b. (a -> b) -> a -> b
$ String -> Either String Text
forall a b. a -> Either a b
Left String
"Did not received any response"
Just Choice
resp ->
let Message {Maybe [ToolCall]
Maybe Text
Maybe AudioResponse
Maybe FunctionCall_
Maybe MessageContent
Role
$sel:role:Message :: Message -> Role
$sel:content:Message :: Message -> Maybe MessageContent
$sel:name:Message :: Message -> Maybe Text
$sel:functionCall:Message :: Message -> Maybe FunctionCall_
$sel:toolCalls:Message :: Message -> Maybe [ToolCall]
$sel:toolCallId:Message :: Message -> Maybe Text
$sel:audio:Message :: Message -> Maybe AudioResponse
$sel:refusal:Message :: Message -> Maybe Text
role :: Role
content :: Maybe MessageContent
name :: Maybe Text
functionCall :: Maybe FunctionCall_
toolCalls :: Maybe [ToolCall]
toolCallId :: Maybe Text
audio :: Maybe AudioResponse
refusal :: Maybe Text
..} = Choice -> Message
message Choice
resp
in Either String Text -> IO (Either String Text)
forall a. a -> IO a
forall (f :: * -> *) a. Applicative f => a -> f a
pure (Either String Text -> IO (Either String Text))
-> Either String Text -> IO (Either String Text)
forall a b. (a -> b) -> a -> b
$
Text -> Either String Text
forall a b. b -> Either a b
Right (Text -> Either String Text) -> Text -> Either String Text
forall a b. (a -> b) -> a -> b
$
Text -> (MessageContent -> Text) -> Maybe MessageContent -> Text
forall b a. b -> (a -> b) -> Maybe a -> b
maybe
Text
""
( \MessageContent
c -> case MessageContent
c of
StringContent Text
t -> Text
t
ContentParts [TextContent]
_ -> Text
""
)
Maybe MessageContent
content
stream :: OpenAI
-> ChatMessage
-> StreamHandler
-> Maybe Params
-> IO (Either String ())
stream OpenAI
_ ChatMessage
_ StreamHandler
_ Maybe Params
_ = Either String () -> IO (Either String ())
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return (Either String () -> IO (Either String ()))
-> Either String () -> IO (Either String ())
forall a b. (a -> b) -> a -> b
$ String -> Either String ()
forall a b. a -> Either a b
Left String
"stream functionality for OpenAI is not supported yet"
toOpenAIMessages :: LLM.ChatMessage -> [Message]
toOpenAIMessages :: ChatMessage -> [Message]
toOpenAIMessages ChatMessage
msgs = (Message -> Message) -> [Message] -> [Message]
forall a b. (a -> b) -> [a] -> [b]
map Message -> Message
go (ChatMessage -> [Message]
forall a. NonEmpty a -> [a]
NE.toList ChatMessage
msgs)
where
toRole :: Role -> Role
toRole Role
r = case Role
r of
Role
LLM.System -> Role
System
Role
LLM.User -> Role
User
Role
LLM.Assistant -> Role
Assistant
Role
LLM.Tool -> Role
Tool
go :: LLM.Message -> Message
go :: Message -> Message
go Message
msg =
Message
defaultMessage
{ role = toRole $ LLM.role msg
, content = Just $ StringContent (LLM.content msg)
}