module OpenAI.V1.Tool
(
Tool(..)
, RankingOptions(..)
, FileSearch(..)
, Function(..)
, ToolChoice(..)
) where
import OpenAI.Prelude
data RankingOptions = RankingOptions
{ RankingOptions -> Maybe Text
ranker :: Maybe Text
, RankingOptions -> Double
score_threshold :: Double
} deriving stock ((forall x. RankingOptions -> Rep RankingOptions x)
-> (forall x. Rep RankingOptions x -> RankingOptions)
-> Generic RankingOptions
forall x. Rep RankingOptions x -> RankingOptions
forall x. RankingOptions -> Rep RankingOptions x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cfrom :: forall x. RankingOptions -> Rep RankingOptions x
from :: forall x. RankingOptions -> Rep RankingOptions x
$cto :: forall x. Rep RankingOptions x -> RankingOptions
to :: forall x. Rep RankingOptions x -> RankingOptions
Generic, Int -> RankingOptions -> ShowS
[RankingOptions] -> ShowS
RankingOptions -> String
(Int -> RankingOptions -> ShowS)
-> (RankingOptions -> String)
-> ([RankingOptions] -> ShowS)
-> Show RankingOptions
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> RankingOptions -> ShowS
showsPrec :: Int -> RankingOptions -> ShowS
$cshow :: RankingOptions -> String
show :: RankingOptions -> String
$cshowList :: [RankingOptions] -> ShowS
showList :: [RankingOptions] -> ShowS
Show)
deriving anyclass (Maybe RankingOptions
Value -> Parser [RankingOptions]
Value -> Parser RankingOptions
(Value -> Parser RankingOptions)
-> (Value -> Parser [RankingOptions])
-> Maybe RankingOptions
-> FromJSON RankingOptions
forall a.
(Value -> Parser a)
-> (Value -> Parser [a]) -> Maybe a -> FromJSON a
$cparseJSON :: Value -> Parser RankingOptions
parseJSON :: Value -> Parser RankingOptions
$cparseJSONList :: Value -> Parser [RankingOptions]
parseJSONList :: Value -> Parser [RankingOptions]
$comittedField :: Maybe RankingOptions
omittedField :: Maybe RankingOptions
FromJSON, [RankingOptions] -> Value
[RankingOptions] -> Encoding
RankingOptions -> Bool
RankingOptions -> Value
RankingOptions -> Encoding
(RankingOptions -> Value)
-> (RankingOptions -> Encoding)
-> ([RankingOptions] -> Value)
-> ([RankingOptions] -> Encoding)
-> (RankingOptions -> Bool)
-> ToJSON RankingOptions
forall a.
(a -> Value)
-> (a -> Encoding)
-> ([a] -> Value)
-> ([a] -> Encoding)
-> (a -> Bool)
-> ToJSON a
$ctoJSON :: RankingOptions -> Value
toJSON :: RankingOptions -> Value
$ctoEncoding :: RankingOptions -> Encoding
toEncoding :: RankingOptions -> Encoding
$ctoJSONList :: [RankingOptions] -> Value
toJSONList :: [RankingOptions] -> Value
$ctoEncodingList :: [RankingOptions] -> Encoding
toEncodingList :: [RankingOptions] -> Encoding
$comitField :: RankingOptions -> Bool
omitField :: RankingOptions -> Bool
ToJSON)
data FileSearch = FileSearch
{ FileSearch -> Maybe Natural
max_num_results :: Maybe Natural
, FileSearch -> Maybe RankingOptions
ranking_options :: Maybe RankingOptions
} deriving stock ((forall x. FileSearch -> Rep FileSearch x)
-> (forall x. Rep FileSearch x -> FileSearch) -> Generic FileSearch
forall x. Rep FileSearch x -> FileSearch
forall x. FileSearch -> Rep FileSearch x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cfrom :: forall x. FileSearch -> Rep FileSearch x
from :: forall x. FileSearch -> Rep FileSearch x
$cto :: forall x. Rep FileSearch x -> FileSearch
to :: forall x. Rep FileSearch x -> FileSearch
Generic, Int -> FileSearch -> ShowS
[FileSearch] -> ShowS
FileSearch -> String
(Int -> FileSearch -> ShowS)
-> (FileSearch -> String)
-> ([FileSearch] -> ShowS)
-> Show FileSearch
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> FileSearch -> ShowS
showsPrec :: Int -> FileSearch -> ShowS
$cshow :: FileSearch -> String
show :: FileSearch -> String
$cshowList :: [FileSearch] -> ShowS
showList :: [FileSearch] -> ShowS
Show)
deriving anyclass (Maybe FileSearch
Value -> Parser [FileSearch]
Value -> Parser FileSearch
(Value -> Parser FileSearch)
-> (Value -> Parser [FileSearch])
-> Maybe FileSearch
-> FromJSON FileSearch
forall a.
(Value -> Parser a)
-> (Value -> Parser [a]) -> Maybe a -> FromJSON a
$cparseJSON :: Value -> Parser FileSearch
parseJSON :: Value -> Parser FileSearch
$cparseJSONList :: Value -> Parser [FileSearch]
parseJSONList :: Value -> Parser [FileSearch]
$comittedField :: Maybe FileSearch
omittedField :: Maybe FileSearch
FromJSON, [FileSearch] -> Value
[FileSearch] -> Encoding
FileSearch -> Bool
FileSearch -> Value
FileSearch -> Encoding
(FileSearch -> Value)
-> (FileSearch -> Encoding)
-> ([FileSearch] -> Value)
-> ([FileSearch] -> Encoding)
-> (FileSearch -> Bool)
-> ToJSON FileSearch
forall a.
(a -> Value)
-> (a -> Encoding)
-> ([a] -> Value)
-> ([a] -> Encoding)
-> (a -> Bool)
-> ToJSON a
$ctoJSON :: FileSearch -> Value
toJSON :: FileSearch -> Value
$ctoEncoding :: FileSearch -> Encoding
toEncoding :: FileSearch -> Encoding
$ctoJSONList :: [FileSearch] -> Value
toJSONList :: [FileSearch] -> Value
$ctoEncodingList :: [FileSearch] -> Encoding
toEncodingList :: [FileSearch] -> Encoding
$comitField :: FileSearch -> Bool
omitField :: FileSearch -> Bool
ToJSON)
data Function = Function
{ Function -> Maybe Text
description :: Maybe Text
, Function -> Text
name :: Text
, Function -> Maybe Value
parameters :: Maybe Value
, Function -> Maybe Bool
strict :: Maybe Bool
} deriving stock ((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, 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)
deriving anyclass (Maybe Function
Value -> Parser [Function]
Value -> Parser Function
(Value -> Parser Function)
-> (Value -> Parser [Function])
-> Maybe Function
-> FromJSON Function
forall a.
(Value -> Parser a)
-> (Value -> Parser [a]) -> Maybe a -> FromJSON a
$cparseJSON :: Value -> Parser Function
parseJSON :: Value -> Parser Function
$cparseJSONList :: Value -> Parser [Function]
parseJSONList :: Value -> Parser [Function]
$comittedField :: Maybe Function
omittedField :: Maybe Function
FromJSON, [Function] -> Value
[Function] -> Encoding
Function -> Bool
Function -> Value
Function -> Encoding
(Function -> Value)
-> (Function -> Encoding)
-> ([Function] -> Value)
-> ([Function] -> Encoding)
-> (Function -> Bool)
-> ToJSON Function
forall a.
(a -> Value)
-> (a -> Encoding)
-> ([a] -> Value)
-> ([a] -> Encoding)
-> (a -> Bool)
-> ToJSON a
$ctoJSON :: Function -> Value
toJSON :: Function -> Value
$ctoEncoding :: Function -> Encoding
toEncoding :: Function -> Encoding
$ctoJSONList :: [Function] -> Value
toJSONList :: [Function] -> Value
$ctoEncodingList :: [Function] -> Encoding
toEncodingList :: [Function] -> Encoding
$comitField :: Function -> Bool
omitField :: Function -> Bool
ToJSON)
data Tool
= Tool_Code_Interpreter
| Tool_File_Search{ Tool -> FileSearch
file_search :: FileSearch }
| Tool_Function{ Tool -> Function
function :: Function }
deriving stock ((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, 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)
toolOptions :: Options
toolOptions :: Options
toolOptions = Options
aesonOptions
{ sumEncoding =
TaggedObject{ tagFieldName = "type", contentsFieldName = "" }
, tagSingleConstructors = True
, constructorTagModifier = stripPrefix "Tool_"
}
instance FromJSON Tool where
parseJSON :: Value -> Parser Tool
parseJSON = Options -> Value -> Parser Tool
forall a.
(Generic a, GFromJSON Zero (Rep a)) =>
Options -> Value -> Parser a
genericParseJSON Options
toolOptions
instance ToJSON Tool where
toJSON :: Tool -> Value
toJSON = Options -> Tool -> Value
forall a.
(Generic a, GToJSON' Value Zero (Rep a)) =>
Options -> a -> Value
genericToJSON Options
toolOptions
data ToolChoice
= ToolChoiceNone
| ToolChoiceAuto
| ToolChoiceRequired
| ToolChoiceTool Tool
deriving stock ((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, 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)
instance FromJSON ToolChoice where
parseJSON :: Value -> Parser ToolChoice
parseJSON Value
"none" = ToolChoice -> Parser ToolChoice
forall a. a -> Parser a
forall (f :: * -> *) a. Applicative f => a -> f a
pure ToolChoice
ToolChoiceNone
parseJSON Value
"auto" = ToolChoice -> Parser ToolChoice
forall a. a -> Parser a
forall (f :: * -> *) a. Applicative f => a -> f a
pure ToolChoice
ToolChoiceAuto
parseJSON Value
"required" = ToolChoice -> Parser ToolChoice
forall a. a -> Parser a
forall (f :: * -> *) a. Applicative f => a -> f a
pure ToolChoice
ToolChoiceRequired
parseJSON Value
other = (Tool -> ToolChoice) -> Parser Tool -> Parser ToolChoice
forall a b. (a -> b) -> Parser a -> Parser b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap Tool -> ToolChoice
ToolChoiceTool (Value -> Parser Tool
forall a. FromJSON a => Value -> Parser a
parseJSON Value
other)
instance ToJSON ToolChoice where
toJSON :: ToolChoice -> Value
toJSON ToolChoice
ToolChoiceNone = Value
"none"
toJSON ToolChoice
ToolChoiceAuto = Value
"auto"
toJSON ToolChoice
ToolChoiceRequired = Value
"required"
toJSON (ToolChoiceTool Tool
tool) = Tool -> Value
forall a. ToJSON a => a -> Value
toJSON Tool
tool