module Claude.V1.Tool
(
Tool(..)
, ToolChoice(..)
, InputSchema(..)
, ToolDefinition(..)
, ToolSearchTool(..)
, ToolSearchToolType(..)
, functionTool
, strictFunctionTool
, simpleInputSchema
, inlineTool
, deferredTool
, toolSearchRegex
, toolSearchBm25
, codeExecutionTool
, allowedCallersCodeExecution
, allowCallers
, toolChoiceAuto
, toolChoiceAny
, toolChoiceTool
, isToolUse
, getToolUseBlocks
, makeToolResult
, makeToolResultError
) where
import Claude.Prelude
import qualified Data.Aeson as Aeson
import qualified Data.Aeson.Key as Key
import qualified Data.Aeson.KeyMap as KeyMap
import qualified Data.Vector as Vector
data InputSchema = InputSchema
{ InputSchema -> Text
type_ :: Text
, InputSchema -> Maybe Value
properties :: Maybe Value
, InputSchema -> Maybe (Vector Text)
required :: Maybe (Vector Text)
, InputSchema -> Maybe Bool
additionalProperties :: Maybe Bool
} deriving stock (InputSchema -> InputSchema -> Bool
(InputSchema -> InputSchema -> Bool)
-> (InputSchema -> InputSchema -> Bool) -> Eq InputSchema
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: InputSchema -> InputSchema -> Bool
== :: InputSchema -> InputSchema -> Bool
$c/= :: InputSchema -> InputSchema -> Bool
/= :: InputSchema -> InputSchema -> Bool
Eq, (forall x. InputSchema -> Rep InputSchema x)
-> (forall x. Rep InputSchema x -> InputSchema)
-> Generic InputSchema
forall x. Rep InputSchema x -> InputSchema
forall x. InputSchema -> Rep InputSchema x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cfrom :: forall x. InputSchema -> Rep InputSchema x
from :: forall x. InputSchema -> Rep InputSchema x
$cto :: forall x. Rep InputSchema x -> InputSchema
to :: forall x. Rep InputSchema x -> InputSchema
Generic, Int -> InputSchema -> ShowS
[InputSchema] -> ShowS
InputSchema -> String
(Int -> InputSchema -> ShowS)
-> (InputSchema -> String)
-> ([InputSchema] -> ShowS)
-> Show InputSchema
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> InputSchema -> ShowS
showsPrec :: Int -> InputSchema -> ShowS
$cshow :: InputSchema -> String
show :: InputSchema -> String
$cshowList :: [InputSchema] -> ShowS
showList :: [InputSchema] -> ShowS
Show)
instance FromJSON InputSchema where
parseJSON :: Value -> Parser InputSchema
parseJSON = String
-> (Object -> Parser InputSchema) -> Value -> Parser InputSchema
forall a. String -> (Object -> Parser a) -> Value -> Parser a
Aeson.withObject String
"InputSchema" ((Object -> Parser InputSchema) -> Value -> Parser InputSchema)
-> (Object -> Parser InputSchema) -> Value -> Parser InputSchema
forall a b. (a -> b) -> a -> b
$ \Object
o -> do
Text
type_ <- Object
o Object -> Key -> Parser Text
forall a. FromJSON a => Object -> Key -> Parser a
Aeson..: Key
"type"
Maybe Value
properties <- Object
o Object -> Key -> Parser (Maybe Value)
forall a. FromJSON a => Object -> Key -> Parser (Maybe a)
Aeson..:? Key
"properties"
Maybe (Vector Text)
required <- Object
o Object -> Key -> Parser (Maybe (Vector Text))
forall a. FromJSON a => Object -> Key -> Parser (Maybe a)
Aeson..:? Key
"required"
Maybe Bool
additionalProperties <- Object
o Object -> Key -> Parser (Maybe Bool)
forall a. FromJSON a => Object -> Key -> Parser (Maybe a)
Aeson..:? Key
"additionalProperties"
InputSchema -> Parser InputSchema
forall a. a -> Parser a
forall (f :: * -> *) a. Applicative f => a -> f a
pure InputSchema{ Text
type_ :: Text
type_ :: Text
type_, Maybe Value
properties :: Maybe Value
properties :: Maybe Value
properties, Maybe (Vector Text)
required :: Maybe (Vector Text)
required :: Maybe (Vector Text)
required, Maybe Bool
additionalProperties :: Maybe Bool
additionalProperties :: Maybe Bool
additionalProperties }
instance ToJSON InputSchema where
toJSON :: InputSchema -> Value
toJSON InputSchema{ Text
type_ :: InputSchema -> Text
type_ :: Text
type_, Maybe Value
properties :: InputSchema -> Maybe Value
properties :: Maybe Value
properties, Maybe (Vector Text)
required :: InputSchema -> Maybe (Vector Text)
required :: Maybe (Vector Text)
required, Maybe Bool
additionalProperties :: InputSchema -> Maybe Bool
additionalProperties :: Maybe Bool
additionalProperties } =
[Pair] -> Value
Aeson.object ([Pair] -> Value) -> [Pair] -> Value
forall a b. (a -> b) -> a -> b
$ (Pair -> Bool) -> [Pair] -> [Pair]
forall a. (a -> Bool) -> [a] -> [a]
filter ((Value -> Value -> Bool
forall a. Eq a => a -> a -> Bool
/= Value
Aeson.Null) (Value -> Bool) -> (Pair -> Value) -> Pair -> Bool
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Pair -> Value
forall a b. (a, b) -> b
snd)
[ Key
"type" Key -> Text -> Pair
forall v. ToJSON v => Key -> v -> Pair
forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
Aeson..= Text
type_
, Key
"properties" Key -> Maybe Value -> Pair
forall v. ToJSON v => Key -> v -> Pair
forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
Aeson..= Maybe Value
properties
, Key
"required" Key -> Maybe (Vector Text) -> Pair
forall v. ToJSON v => Key -> v -> Pair
forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
Aeson..= Maybe (Vector Text)
required
, Key
"additionalProperties" Key -> Maybe Bool -> Pair
forall v. ToJSON v => Key -> v -> Pair
forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
Aeson..= Maybe Bool
additionalProperties
]
simpleInputSchema
:: Value
-> Vector Text
-> InputSchema
simpleInputSchema :: Value -> Vector Text -> InputSchema
simpleInputSchema Value
props Vector Text
reqs = InputSchema
{ type_ :: Text
type_ = Text
"object"
, properties :: Maybe Value
properties = Value -> Maybe Value
forall a. a -> Maybe a
Just Value
props
, required :: Maybe (Vector Text)
required = Vector Text -> Maybe (Vector Text)
forall a. a -> Maybe a
Just Vector Text
reqs
, additionalProperties :: Maybe Bool
additionalProperties = Maybe Bool
forall a. Maybe a
Nothing
}
data Tool = Tool
{ Tool -> Text
name :: Text
, Tool -> Maybe Text
description :: Maybe Text
, Tool -> InputSchema
input_schema :: InputSchema
, Tool -> Maybe Bool
strict :: Maybe Bool
} deriving stock (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, 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)
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
aesonOptions
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
aesonOptions
functionTool
:: Text
-> Maybe Text
-> Value
-> Tool
functionTool :: Text -> Maybe Text -> Value -> Tool
functionTool Text
toolName Maybe Text
toolDescription Value
schema = Tool
{ name :: Text
name = Text
toolName
, description :: Maybe Text
description = Maybe Text
toolDescription
, input_schema :: InputSchema
input_schema = InputSchema
{ type_ :: Text
type_ = Text
"object"
, properties :: Maybe Value
properties = case Value
schema of
Aeson.Object Object
o -> case Text -> Object -> Maybe Value
forall {v}. Text -> KeyMap v -> Maybe v
lookupKey Text
"properties" Object
o of
Just Value
props -> Value -> Maybe Value
forall a. a -> Maybe a
Just Value
props
Maybe Value
Nothing -> Value -> Maybe Value
forall a. a -> Maybe a
Just Value
schema
Value
_ -> Value -> Maybe Value
forall a. a -> Maybe a
Just Value
schema
, required :: Maybe (Vector Text)
required = case Value
schema of
Aeson.Object Object
o -> case Text -> Object -> Maybe Value
forall {v}. Text -> KeyMap v -> Maybe v
lookupKey Text
"required" Object
o of
Just (Aeson.Array Array
arr) -> Vector Text -> Maybe (Vector Text)
forall a. a -> Maybe a
Just ((Value -> Maybe Text) -> Array -> Vector Text
forall a b. (a -> Maybe b) -> Vector a -> Vector b
Vector.mapMaybe Value -> Maybe Text
getString Array
arr)
Maybe Value
_ -> Maybe (Vector Text)
forall a. Maybe a
Nothing
Value
_ -> Maybe (Vector Text)
forall a. Maybe a
Nothing
, additionalProperties :: Maybe Bool
additionalProperties = Maybe Bool
forall a. Maybe a
Nothing
}
, strict :: Maybe Bool
strict = Maybe Bool
forall a. Maybe a
Nothing
}
where
getString :: Value -> Maybe Text
getString (Aeson.String Text
s) = Text -> Maybe Text
forall a. a -> Maybe a
Just Text
s
getString Value
_ = Maybe Text
forall a. Maybe a
Nothing
lookupKey :: Text -> KeyMap v -> Maybe v
lookupKey Text
k KeyMap v
obj = Key -> KeyMap v -> Maybe v
forall v. Key -> KeyMap v -> Maybe v
KeyMap.lookup (Text -> Key
Key.fromText Text
k) KeyMap v
obj
strictFunctionTool
:: Text
-> Maybe Text
-> Value
-> Tool
strictFunctionTool :: Text -> Maybe Text -> Value -> Tool
strictFunctionTool Text
toolName Maybe Text
toolDescription Value
schema =
let tool :: Tool
tool = Text -> Maybe Text -> Value -> Tool
functionTool Text
toolName Maybe Text
toolDescription Value
schema
inputSchema :: InputSchema
inputSchema = Tool -> InputSchema
input_schema Tool
tool
in Tool
tool
{ strict = Just True
, input_schema = inputSchema{ additionalProperties = Just False }
}
data ToolChoice
= ToolChoice_Auto
| ToolChoice_Any
| ToolChoice_Tool { ToolChoice -> Text
name :: Text }
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 (Aeson.Object Object
o) = do
Text
t <- Object
o Object -> Key -> Parser Text
forall a. FromJSON a => Object -> Key -> Parser a
Aeson..: Key
"type"
case (Text
t :: Text) of
Text
"auto" -> ToolChoice -> Parser ToolChoice
forall a. a -> Parser a
forall (f :: * -> *) a. Applicative f => a -> f a
pure ToolChoice
ToolChoice_Auto
Text
"any" -> ToolChoice -> Parser ToolChoice
forall a. a -> Parser a
forall (f :: * -> *) a. Applicative f => a -> f a
pure ToolChoice
ToolChoice_Any
Text
"tool" -> Text -> ToolChoice
ToolChoice_Tool (Text -> ToolChoice) -> Parser Text -> Parser ToolChoice
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Object
o Object -> Key -> Parser Text
forall a. FromJSON a => Object -> Key -> Parser a
Aeson..: Key
"name"
Text
_ -> String -> Parser ToolChoice
forall a. String -> Parser a
forall (m :: * -> *) a. MonadFail m => String -> m a
fail String
"Unknown tool choice type"
parseJSON Value
_ = String -> Parser ToolChoice
forall a. String -> Parser a
forall (m :: * -> *) a. MonadFail m => String -> m a
fail String
"Invalid tool choice"
instance ToJSON ToolChoice where
toJSON :: ToolChoice -> Value
toJSON ToolChoice
ToolChoice_Auto = [Pair] -> Value
Aeson.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
Aeson..= (Text
"auto" :: Text)]
toJSON ToolChoice
ToolChoice_Any = [Pair] -> Value
Aeson.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
Aeson..= (Text
"any" :: Text)]
toJSON (ToolChoice_Tool Text
n) = [Pair] -> Value
Aeson.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
Aeson..= (Text
"tool" :: Text)
, Key
"name" Key -> Text -> Pair
forall v. ToJSON v => Key -> v -> Pair
forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
Aeson..= Text
n
]
toolChoiceAuto :: ToolChoice
toolChoiceAuto :: ToolChoice
toolChoiceAuto = ToolChoice
ToolChoice_Auto
toolChoiceAny :: ToolChoice
toolChoiceAny :: ToolChoice
toolChoiceAny = ToolChoice
ToolChoice_Any
toolChoiceTool :: Text -> ToolChoice
toolChoiceTool :: Text -> ToolChoice
toolChoiceTool = Text -> ToolChoice
ToolChoice_Tool
data ToolSearchToolType
= ToolSearchTool_Regex_20251119
| ToolSearchTool_Bm25_20251119
deriving stock (ToolSearchToolType -> ToolSearchToolType -> Bool
(ToolSearchToolType -> ToolSearchToolType -> Bool)
-> (ToolSearchToolType -> ToolSearchToolType -> Bool)
-> Eq ToolSearchToolType
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: ToolSearchToolType -> ToolSearchToolType -> Bool
== :: ToolSearchToolType -> ToolSearchToolType -> Bool
$c/= :: ToolSearchToolType -> ToolSearchToolType -> Bool
/= :: ToolSearchToolType -> ToolSearchToolType -> Bool
Eq, Int -> ToolSearchToolType -> ShowS
[ToolSearchToolType] -> ShowS
ToolSearchToolType -> String
(Int -> ToolSearchToolType -> ShowS)
-> (ToolSearchToolType -> String)
-> ([ToolSearchToolType] -> ShowS)
-> Show ToolSearchToolType
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> ToolSearchToolType -> ShowS
showsPrec :: Int -> ToolSearchToolType -> ShowS
$cshow :: ToolSearchToolType -> String
show :: ToolSearchToolType -> String
$cshowList :: [ToolSearchToolType] -> ShowS
showList :: [ToolSearchToolType] -> ShowS
Show)
instance FromJSON ToolSearchToolType where
parseJSON :: Value -> Parser ToolSearchToolType
parseJSON = String
-> (Text -> Parser ToolSearchToolType)
-> Value
-> Parser ToolSearchToolType
forall a. String -> (Text -> Parser a) -> Value -> Parser a
Aeson.withText String
"ToolSearchToolType" ((Text -> Parser ToolSearchToolType)
-> Value -> Parser ToolSearchToolType)
-> (Text -> Parser ToolSearchToolType)
-> Value
-> Parser ToolSearchToolType
forall a b. (a -> b) -> a -> b
$ \Text
t -> case Text
t of
Text
"tool_search_tool_regex_20251119" -> ToolSearchToolType -> Parser ToolSearchToolType
forall a. a -> Parser a
forall (f :: * -> *) a. Applicative f => a -> f a
pure ToolSearchToolType
ToolSearchTool_Regex_20251119
Text
"tool_search_tool_bm25_20251119" -> ToolSearchToolType -> Parser ToolSearchToolType
forall a. a -> Parser a
forall (f :: * -> *) a. Applicative f => a -> f a
pure ToolSearchToolType
ToolSearchTool_Bm25_20251119
Text
_ -> String -> Parser ToolSearchToolType
forall a. String -> Parser a
forall (m :: * -> *) a. MonadFail m => String -> m a
fail (String -> Parser ToolSearchToolType)
-> String -> Parser ToolSearchToolType
forall a b. (a -> b) -> a -> b
$ String
"Unknown tool search tool type: " String -> ShowS
forall a. Semigroup a => a -> a -> a
<> Text -> String
forall a. Show a => a -> String
show Text
t
instance ToJSON ToolSearchToolType where
toJSON :: ToolSearchToolType -> Value
toJSON ToolSearchToolType
ToolSearchTool_Regex_20251119 = Text -> Value
Aeson.String Text
"tool_search_tool_regex_20251119"
toJSON ToolSearchToolType
ToolSearchTool_Bm25_20251119 = Text -> Value
Aeson.String Text
"tool_search_tool_bm25_20251119"
data ToolSearchTool = ToolSearchTool
{ ToolSearchTool -> Text
name :: Text
, ToolSearchTool -> ToolSearchToolType
type_ :: ToolSearchToolType
} deriving stock (ToolSearchTool -> ToolSearchTool -> Bool
(ToolSearchTool -> ToolSearchTool -> Bool)
-> (ToolSearchTool -> ToolSearchTool -> Bool) -> Eq ToolSearchTool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: ToolSearchTool -> ToolSearchTool -> Bool
== :: ToolSearchTool -> ToolSearchTool -> Bool
$c/= :: ToolSearchTool -> ToolSearchTool -> Bool
/= :: ToolSearchTool -> ToolSearchTool -> Bool
Eq, Int -> ToolSearchTool -> ShowS
[ToolSearchTool] -> ShowS
ToolSearchTool -> String
(Int -> ToolSearchTool -> ShowS)
-> (ToolSearchTool -> String)
-> ([ToolSearchTool] -> ShowS)
-> Show ToolSearchTool
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> ToolSearchTool -> ShowS
showsPrec :: Int -> ToolSearchTool -> ShowS
$cshow :: ToolSearchTool -> String
show :: ToolSearchTool -> String
$cshowList :: [ToolSearchTool] -> ShowS
showList :: [ToolSearchTool] -> ShowS
Show)
instance FromJSON ToolSearchTool where
parseJSON :: Value -> Parser ToolSearchTool
parseJSON = String
-> (Object -> Parser ToolSearchTool)
-> Value
-> Parser ToolSearchTool
forall a. String -> (Object -> Parser a) -> Value -> Parser a
Aeson.withObject String
"ToolSearchTool" ((Object -> Parser ToolSearchTool)
-> Value -> Parser ToolSearchTool)
-> (Object -> Parser ToolSearchTool)
-> Value
-> Parser ToolSearchTool
forall a b. (a -> b) -> a -> b
$ \Object
o -> do
Text
name <- Object
o Object -> Key -> Parser Text
forall a. FromJSON a => Object -> Key -> Parser a
Aeson..: Key
"name"
ToolSearchToolType
type_ <- Object
o Object -> Key -> Parser ToolSearchToolType
forall a. FromJSON a => Object -> Key -> Parser a
Aeson..: Key
"type"
ToolSearchTool -> Parser ToolSearchTool
forall a. a -> Parser a
forall (f :: * -> *) a. Applicative f => a -> f a
pure ToolSearchTool{ Text
name :: Text
name :: Text
name, ToolSearchToolType
type_ :: ToolSearchToolType
type_ :: ToolSearchToolType
type_ }
instance ToJSON ToolSearchTool where
toJSON :: ToolSearchTool -> Value
toJSON ToolSearchTool{ Text
name :: ToolSearchTool -> Text
name :: Text
name, ToolSearchToolType
type_ :: ToolSearchTool -> ToolSearchToolType
type_ :: ToolSearchToolType
type_ } = [Pair] -> Value
Aeson.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
Aeson..= Text
name
, Key
"type" Key -> ToolSearchToolType -> Pair
forall v. ToJSON v => Key -> v -> Pair
forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
Aeson..= ToolSearchToolType
type_
]
data ToolDefinition
= ToolDef_Function
{ ToolDefinition -> Tool
tool :: Tool
, ToolDefinition -> Maybe Bool
defer_loading :: Maybe Bool
, ToolDefinition -> Maybe (Vector Text)
allowed_callers :: Maybe (Vector Text)
}
| ToolDef_SearchTool ToolSearchTool
| ToolDef_CodeExecutionTool
{ ToolDefinition -> Text
name :: Text
, ToolDefinition -> Text
type_ :: Text
}
deriving stock (ToolDefinition -> ToolDefinition -> Bool
(ToolDefinition -> ToolDefinition -> Bool)
-> (ToolDefinition -> ToolDefinition -> Bool) -> Eq ToolDefinition
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: ToolDefinition -> ToolDefinition -> Bool
== :: ToolDefinition -> ToolDefinition -> Bool
$c/= :: ToolDefinition -> ToolDefinition -> Bool
/= :: ToolDefinition -> ToolDefinition -> Bool
Eq, Int -> ToolDefinition -> ShowS
[ToolDefinition] -> ShowS
ToolDefinition -> String
(Int -> ToolDefinition -> ShowS)
-> (ToolDefinition -> String)
-> ([ToolDefinition] -> ShowS)
-> Show ToolDefinition
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> ToolDefinition -> ShowS
showsPrec :: Int -> ToolDefinition -> ShowS
$cshow :: ToolDefinition -> String
show :: ToolDefinition -> String
$cshowList :: [ToolDefinition] -> ShowS
showList :: [ToolDefinition] -> ShowS
Show)
instance FromJSON ToolDefinition where
parseJSON :: Value -> Parser ToolDefinition
parseJSON = String
-> (Object -> Parser ToolDefinition)
-> Value
-> Parser ToolDefinition
forall a. String -> (Object -> Parser a) -> Value -> Parser a
Aeson.withObject String
"ToolDefinition" ((Object -> Parser ToolDefinition)
-> Value -> Parser ToolDefinition)
-> (Object -> Parser ToolDefinition)
-> Value
-> Parser ToolDefinition
forall a b. (a -> b) -> a -> b
$ \Object
o -> do
Maybe Text
mType <- Object
o Object -> Key -> Parser (Maybe Text)
forall a. FromJSON a => Object -> Key -> Parser (Maybe a)
Aeson..:? Key
"type"
case Maybe Text
mType of
Just Text
t | Text -> Bool
isToolSearchType Text
t -> do
ToolSearchTool
searchTool <- Value -> Parser ToolSearchTool
forall a. FromJSON a => Value -> Parser a
Aeson.parseJSON (Object -> Value
Aeson.Object Object
o)
ToolDefinition -> Parser ToolDefinition
forall a. a -> Parser a
forall (f :: * -> *) a. Applicative f => a -> f a
pure (ToolSearchTool -> ToolDefinition
ToolDef_SearchTool ToolSearchTool
searchTool)
Just Text
t | Text -> Bool
isCodeExecutionType Text
t -> do
Text
name <- Object
o Object -> Key -> Parser Text
forall a. FromJSON a => Object -> Key -> Parser a
Aeson..: Key
"name"
ToolDefinition -> Parser ToolDefinition
forall a. a -> Parser a
forall (f :: * -> *) a. Applicative f => a -> f a
pure ToolDef_CodeExecutionTool{ Text
name :: Text
name :: Text
name, type_ :: Text
type_ = Text
t }
Maybe Text
_ -> do
Tool
tool <- Value -> Parser Tool
forall a. FromJSON a => Value -> Parser a
Aeson.parseJSON (Object -> Value
Aeson.Object Object
o)
Maybe Bool
defer_loading <- Object
o Object -> Key -> Parser (Maybe Bool)
forall a. FromJSON a => Object -> Key -> Parser (Maybe a)
Aeson..:? Key
"defer_loading"
Maybe (Vector Text)
allowed_callers <- Object
o Object -> Key -> Parser (Maybe (Vector Text))
forall a. FromJSON a => Object -> Key -> Parser (Maybe a)
Aeson..:? Key
"allowed_callers"
ToolDefinition -> Parser ToolDefinition
forall a. a -> Parser a
forall (f :: * -> *) a. Applicative f => a -> f a
pure ToolDef_Function{ Tool
tool :: Tool
tool :: Tool
tool, Maybe Bool
defer_loading :: Maybe Bool
defer_loading :: Maybe Bool
defer_loading, Maybe (Vector Text)
allowed_callers :: Maybe (Vector Text)
allowed_callers :: Maybe (Vector Text)
allowed_callers }
where
isToolSearchType :: Text -> Bool
isToolSearchType :: Text -> Bool
isToolSearchType Text
t = Text
t Text -> Text -> Bool
forall a. Eq a => a -> a -> Bool
== Text
"tool_search_tool_regex_20251119"
Bool -> Bool -> Bool
|| Text
t Text -> Text -> Bool
forall a. Eq a => a -> a -> Bool
== Text
"tool_search_tool_bm25_20251119"
isCodeExecutionType :: Text -> Bool
isCodeExecutionType :: Text -> Bool
isCodeExecutionType Text
t = Text
t Text -> Text -> Bool
forall a. Eq a => a -> a -> Bool
== Text
"code_execution_20250825"
instance ToJSON ToolDefinition where
toJSON :: ToolDefinition -> Value
toJSON (ToolDef_Function Tool{ Text
name :: Tool -> Text
name :: Text
name, Maybe Text
description :: Tool -> Maybe Text
description :: Maybe Text
description, InputSchema
input_schema :: Tool -> InputSchema
input_schema :: InputSchema
input_schema, Maybe Bool
strict :: Tool -> Maybe Bool
strict :: Maybe Bool
strict } Maybe Bool
defer_loading Maybe (Vector Text)
allowed_callers) =
Object -> Value
Aeson.Object (Object
baseMap Object -> Object -> Object
forall a. Semigroup a => a -> a -> a
<> Object
optionalFields)
where
baseObj :: Value
baseObj = [Pair] -> Value
Aeson.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
Aeson..= Text
name
, Key
"input_schema" Key -> InputSchema -> Pair
forall v. ToJSON v => Key -> v -> Pair
forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
Aeson..= InputSchema
input_schema
] [Pair] -> [Pair] -> [Pair]
forall a. Semigroup 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
Aeson..= Text
d]) Maybe Text
description
baseMap :: Object
baseMap = case Value
baseObj of
Aeson.Object Object
m -> Object
m
Value
_ -> Object
forall v. KeyMap v
KeyMap.empty
optionalFields :: Object
optionalFields = [Pair] -> Object
forall v. [(Key, v)] -> KeyMap v
KeyMap.fromList ([Pair] -> Object) -> [Pair] -> Object
forall a b. (a -> b) -> a -> b
$
[Pair] -> (Bool -> [Pair]) -> Maybe Bool -> [Pair]
forall b a. b -> (a -> b) -> Maybe a -> b
maybe [] (\Bool
dl -> [(Key
"defer_loading", Bool -> Value
forall a. ToJSON a => a -> Value
Aeson.toJSON Bool
dl)]) Maybe Bool
defer_loading [Pair] -> [Pair] -> [Pair]
forall a. Semigroup a => a -> a -> a
<>
[Pair] -> (Vector Text -> [Pair]) -> Maybe (Vector Text) -> [Pair]
forall b a. b -> (a -> b) -> Maybe a -> b
maybe [] (\Vector Text
ac -> [(Key
"allowed_callers", Vector Text -> Value
forall a. ToJSON a => a -> Value
Aeson.toJSON Vector Text
ac)]) Maybe (Vector Text)
allowed_callers [Pair] -> [Pair] -> [Pair]
forall a. Semigroup a => a -> a -> a
<>
[Pair] -> (Bool -> [Pair]) -> Maybe Bool -> [Pair]
forall b a. b -> (a -> b) -> Maybe a -> b
maybe [] (\Bool
s -> [(Key
"strict", Bool -> Value
forall a. ToJSON a => a -> Value
Aeson.toJSON Bool
s)]) Maybe Bool
strict
toJSON (ToolDef_SearchTool ToolSearchTool
searchTool) = ToolSearchTool -> Value
forall a. ToJSON a => a -> Value
Aeson.toJSON ToolSearchTool
searchTool
toJSON (ToolDef_CodeExecutionTool Text
name Text
type_) = [Pair] -> Value
Aeson.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
Aeson..= Text
name
, Key
"type" Key -> Text -> Pair
forall v. ToJSON v => Key -> v -> Pair
forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
Aeson..= Text
type_
]
inlineTool :: Tool -> ToolDefinition
inlineTool :: Tool -> ToolDefinition
inlineTool Tool
t = ToolDef_Function{ tool :: Tool
tool = Tool
t, defer_loading :: Maybe Bool
defer_loading = Maybe Bool
forall a. Maybe a
Nothing, allowed_callers :: Maybe (Vector Text)
allowed_callers = Maybe (Vector Text)
forall a. Maybe a
Nothing }
deferredTool :: Tool -> ToolDefinition
deferredTool :: Tool -> ToolDefinition
deferredTool Tool
t = ToolDef_Function{ tool :: Tool
tool = Tool
t, defer_loading :: Maybe Bool
defer_loading = Bool -> Maybe Bool
forall a. a -> Maybe a
Just Bool
True, allowed_callers :: Maybe (Vector Text)
allowed_callers = Maybe (Vector Text)
forall a. Maybe a
Nothing }
codeExecutionTool :: ToolDefinition
codeExecutionTool :: ToolDefinition
codeExecutionTool = ToolDef_CodeExecutionTool
{ name :: Text
name = Text
"code_execution"
, type_ :: Text
type_ = Text
"code_execution_20250825"
}
allowedCallersCodeExecution :: Vector Text
allowedCallersCodeExecution :: Vector Text
allowedCallersCodeExecution = [Text
Item (Vector Text)
"code_execution_20250825"]
allowCallers :: Vector Text -> ToolDefinition -> ToolDefinition
allowCallers :: Vector Text -> ToolDefinition -> ToolDefinition
allowCallers Vector Text
callers (ToolDef_Function Tool
t Maybe Bool
dl Maybe (Vector Text)
_) = Tool -> Maybe Bool -> Maybe (Vector Text) -> ToolDefinition
ToolDef_Function Tool
t Maybe Bool
dl (Vector Text -> Maybe (Vector Text)
forall a. a -> Maybe a
Just Vector Text
callers)
allowCallers Vector Text
_ ToolDefinition
td = ToolDefinition
td
toolSearchRegex :: ToolDefinition
toolSearchRegex :: ToolDefinition
toolSearchRegex = ToolSearchTool -> ToolDefinition
ToolDef_SearchTool ToolSearchTool
{ name :: Text
name = Text
"tool_search_tool_regex"
, type_ :: ToolSearchToolType
type_ = ToolSearchToolType
ToolSearchTool_Regex_20251119
}
toolSearchBm25 :: ToolDefinition
toolSearchBm25 :: ToolDefinition
toolSearchBm25 = ToolSearchTool -> ToolDefinition
ToolDef_SearchTool ToolSearchTool
{ name :: Text
name = Text
"tool_search_tool_bm25"
, type_ :: ToolSearchToolType
type_ = ToolSearchToolType
ToolSearchTool_Bm25_20251119
}
isToolUse :: Value -> Bool
isToolUse :: Value -> Bool
isToolUse (Aeson.Object Object
o) = case Key -> Object -> Maybe Value
forall v. Key -> KeyMap v -> Maybe v
KeyMap.lookup (Text -> Key
Key.fromText Text
"type") Object
o of
Just (Aeson.String Text
"tool_use") -> Bool
True
Maybe Value
_ -> Bool
False
isToolUse Value
_ = Bool
False
getToolUseBlocks :: Vector Value -> [(Text, Text, Value)]
getToolUseBlocks :: Array -> [(Text, Text, Value)]
getToolUseBlocks Array
content = Vector (Text, Text, Value) -> [(Text, Text, Value)]
forall a. Vector a -> [a]
Vector.toList (Vector (Text, Text, Value) -> [(Text, Text, Value)])
-> Vector (Text, Text, Value) -> [(Text, Text, Value)]
forall a b. (a -> b) -> a -> b
$ (Value -> Maybe (Text, Text, Value))
-> Array -> Vector (Text, Text, Value)
forall a b. (a -> Maybe b) -> Vector a -> Vector b
Vector.mapMaybe Value -> Maybe (Text, Text, Value)
extractToolUse Array
content
where
extractToolUse :: Value -> Maybe (Text, Text, Value)
extractToolUse (Aeson.Object Object
o) = do
Aeson.String Text
"tool_use" <- Key -> Object -> Maybe Value
forall v. Key -> KeyMap v -> Maybe v
KeyMap.lookup (Text -> Key
Key.fromText Text
"type") Object
o
Aeson.String Text
toolId <- Key -> Object -> Maybe Value
forall v. Key -> KeyMap v -> Maybe v
KeyMap.lookup (Text -> Key
Key.fromText Text
"id") Object
o
Aeson.String Text
toolName <- Key -> Object -> Maybe Value
forall v. Key -> KeyMap v -> Maybe v
KeyMap.lookup (Text -> Key
Key.fromText Text
"name") Object
o
Value
toolInput <- Key -> Object -> Maybe Value
forall v. Key -> KeyMap v -> Maybe v
KeyMap.lookup (Text -> Key
Key.fromText Text
"input") Object
o
(Text, Text, Value) -> Maybe (Text, Text, Value)
forall a. a -> Maybe a
forall (f :: * -> *) a. Applicative f => a -> f a
pure (Text
toolId, Text
toolName, Value
toolInput)
extractToolUse Value
_ = Maybe (Text, Text, Value)
forall a. Maybe a
Nothing
makeToolResult
:: Text
-> Text
-> Value
makeToolResult :: Text -> Text -> Value
makeToolResult Text
toolUseId Text
resultContent = [Pair] -> Value
Aeson.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
Aeson..= (Text
"tool_result" :: Text)
, Key
"tool_use_id" Key -> Text -> Pair
forall v. ToJSON v => Key -> v -> Pair
forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
Aeson..= Text
toolUseId
, Key
"content" Key -> Text -> Pair
forall v. ToJSON v => Key -> v -> Pair
forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
Aeson..= Text
resultContent
]
makeToolResultError
:: Text
-> Text
-> Value
makeToolResultError :: Text -> Text -> Value
makeToolResultError Text
toolUseId Text
errorMsg = [Pair] -> Value
Aeson.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
Aeson..= (Text
"tool_result" :: Text)
, Key
"tool_use_id" Key -> Text -> Pair
forall v. ToJSON v => Key -> v -> Pair
forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
Aeson..= Text
toolUseId
, Key
"content" Key -> Text -> Pair
forall v. ToJSON v => Key -> v -> Pair
forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
Aeson..= Text
errorMsg
, Key
"is_error" Key -> Bool -> Pair
forall v. ToJSON v => Key -> v -> Pair
forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
Aeson..= Bool
True
]