claude-1.0.0: Servant bindings to Anthropic's Claude API
Safe HaskellNone
LanguageHaskell2010

Claude.V1.Tool

Description

Tool types for Claude API

This module provides types and utilities for defining tools that Claude can use.

Example usage:

import Claude.V1.Tool

-- Define a simple tool
weatherTool :: Tool
weatherTool = functionTool "get_weather"
    (Just "Get the current weather for a location")
    (Aeson.object
        [ "type" .= ("object" :: Text)
        , "properties" .= Aeson.object
            [ "location" .= Aeson.object
                [ "type" .= ("string" :: Text)
                , "description" .= ("City and state, e.g. San Francisco, CA" :: Text)
                ]
            ]
        , "required" .= (["location"] :: [Text])
        ])
Synopsis

Types

data Tool Source #

A tool that can be used by Claude

Tools allow Claude to call external functions. When Claude decides to use a tool, it will return a tool_use content block with the tool name and input arguments.

Constructors

Tool 

Instances

Instances details
FromJSON Tool Source # 
Instance details

Defined in Claude.V1.Tool

ToJSON Tool Source # 
Instance details

Defined in Claude.V1.Tool

Generic Tool Source # 
Instance details

Defined in Claude.V1.Tool

Associated Types

type Rep Tool 
Instance details

Defined in Claude.V1.Tool

type Rep Tool = D1 ('MetaData "Tool" "Claude.V1.Tool" "claude-1.0.0-1j0Plg9n3EjAvfVKcV8Pl0" 'False) (C1 ('MetaCons "Tool" 'PrefixI 'True) (S1 ('MetaSel ('Just "name") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Text) :*: (S1 ('MetaSel ('Just "description") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe Text)) :*: S1 ('MetaSel ('Just "input_schema") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 InputSchema))))

Methods

from :: Tool -> Rep Tool x #

to :: Rep Tool x -> Tool #

Show Tool Source # 
Instance details

Defined in Claude.V1.Tool

Methods

showsPrec :: Int -> Tool -> ShowS #

show :: Tool -> String #

showList :: [Tool] -> ShowS #

Eq Tool Source # 
Instance details

Defined in Claude.V1.Tool

Methods

(==) :: Tool -> Tool -> Bool #

(/=) :: Tool -> Tool -> Bool #

type Rep Tool Source # 
Instance details

Defined in Claude.V1.Tool

type Rep Tool = D1 ('MetaData "Tool" "Claude.V1.Tool" "claude-1.0.0-1j0Plg9n3EjAvfVKcV8Pl0" 'False) (C1 ('MetaCons "Tool" 'PrefixI 'True) (S1 ('MetaSel ('Just "name") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Text) :*: (S1 ('MetaSel ('Just "description") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe Text)) :*: S1 ('MetaSel ('Just "input_schema") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 InputSchema))))

data ToolChoice Source #

Controls which tool the model should use

Constructors

ToolChoice_Auto

Let Claude decide whether to use tools

ToolChoice_Any

Force Claude to use one of the provided tools

ToolChoice_Tool

Force Claude to use a specific tool

Fields

Instances

Instances details
FromJSON ToolChoice Source # 
Instance details

Defined in Claude.V1.Tool

ToJSON ToolChoice Source # 
Instance details

Defined in Claude.V1.Tool

Generic ToolChoice Source # 
Instance details

Defined in Claude.V1.Tool

Associated Types

type Rep ToolChoice 
Instance details

Defined in Claude.V1.Tool

type Rep ToolChoice = D1 ('MetaData "ToolChoice" "Claude.V1.Tool" "claude-1.0.0-1j0Plg9n3EjAvfVKcV8Pl0" 'False) (C1 ('MetaCons "ToolChoice_Auto" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "ToolChoice_Any" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "ToolChoice_Tool" 'PrefixI 'True) (S1 ('MetaSel ('Just "name") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Text))))
Show ToolChoice Source # 
Instance details

Defined in Claude.V1.Tool

type Rep ToolChoice Source # 
Instance details

Defined in Claude.V1.Tool

type Rep ToolChoice = D1 ('MetaData "ToolChoice" "Claude.V1.Tool" "claude-1.0.0-1j0Plg9n3EjAvfVKcV8Pl0" 'False) (C1 ('MetaCons "ToolChoice_Auto" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "ToolChoice_Any" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "ToolChoice_Tool" 'PrefixI 'True) (S1 ('MetaSel ('Just "name") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Text))))

data InputSchema Source #

Tool input schema (JSON Schema)

The schema follows JSON Schema format. At minimum, specify type_ as "object".

Constructors

InputSchema 

Fields

Instances

Instances details
FromJSON InputSchema Source # 
Instance details

Defined in Claude.V1.Tool

ToJSON InputSchema Source # 
Instance details

Defined in Claude.V1.Tool

Generic InputSchema Source # 
Instance details

Defined in Claude.V1.Tool

Associated Types

type Rep InputSchema 
Instance details

Defined in Claude.V1.Tool

type Rep InputSchema = D1 ('MetaData "InputSchema" "Claude.V1.Tool" "claude-1.0.0-1j0Plg9n3EjAvfVKcV8Pl0" 'False) (C1 ('MetaCons "InputSchema" 'PrefixI 'True) (S1 ('MetaSel ('Just "type_") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Text) :*: (S1 ('MetaSel ('Just "properties") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe Value)) :*: S1 ('MetaSel ('Just "required") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe (Vector Text))))))
Show InputSchema Source # 
Instance details

Defined in Claude.V1.Tool

Eq InputSchema Source # 
Instance details

Defined in Claude.V1.Tool

type Rep InputSchema Source # 
Instance details

Defined in Claude.V1.Tool

type Rep InputSchema = D1 ('MetaData "InputSchema" "Claude.V1.Tool" "claude-1.0.0-1j0Plg9n3EjAvfVKcV8Pl0" 'False) (C1 ('MetaCons "InputSchema" 'PrefixI 'True) (S1 ('MetaSel ('Just "type_") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Text) :*: (S1 ('MetaSel ('Just "properties") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe Value)) :*: S1 ('MetaSel ('Just "required") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe (Vector Text))))))

Tool definition (heterogeneous tools array)

data ToolDefinition Source #

A tool definition for the tools array

The tools array in Claude API requests is heterogeneous:

  • Function tools: regular tools with name, description, and input schema
  • Tool search tools: server-side tool search configuration
  • Code execution tool: for programmatic tool calling (PTC)

Use inlineTool or deferredTool to wrap a Tool, or toolSearchRegex/toolSearchBm25 to add tool search capability. Use codeExecutionTool for PTC.

data ToolSearchTool Source #

Tool search tool configuration

Used to enable server-side tool search, which allows Claude to efficiently search through large numbers of tools using regex or BM25 matching.

Constructors

ToolSearchTool 

Tool constructors

functionTool Source #

Arguments

:: Text

Tool name (must match [a-zA-Z0-9_-]+)

-> Maybe Text

Description of what the tool does

-> Value

JSON Schema for the input parameters

-> Tool 

Create a function tool with a name, description, and JSON schema for parameters

This is the primary way to define tools for Claude.

simpleInputSchema Source #

Arguments

:: Value

Properties object

-> Vector Text

Required field names

-> InputSchema 

Create a simple input schema with properties and required fields

ToolDefinition constructors

inlineTool :: Tool -> ToolDefinition Source #

Wrap a tool for inline (non-deferred) loading

deferredTool :: Tool -> ToolDefinition Source #

Wrap a tool for deferred loading (used with tool search)

toolSearchRegex :: ToolDefinition Source #

Tool search using regex matching

Requires anthropic-beta: advanced-tool-use-2025-11-20 header.

toolSearchBm25 :: ToolDefinition Source #

Tool search using BM25 matching

Requires anthropic-beta: advanced-tool-use-2025-11-20 header.

Code execution tool (PTC)

codeExecutionTool :: ToolDefinition Source #

Code execution tool for programmatic tool calling (PTC)

Requires anthropic-beta: advanced-tool-use-2025-11-20 header. When included in the tools array, Claude can write and execute code to call other tools programmatically.

allowedCallersCodeExecution :: Vector Text Source #

Allowed callers for code execution (PTC)

Use with allowCallers to mark a function tool as callable by code execution.

allowCallers :: Vector Text -> ToolDefinition -> ToolDefinition Source #

Set allowed_callers on a function tool definition

Only affects ToolDef_Function; other tool types are returned unchanged.

Example:

allowCallers allowedCallersCodeExecution (inlineTool myTool)

ToolChoice constructors

toolChoiceAuto :: ToolChoice Source #

Convenience: auto tool choice (let Claude decide)

toolChoiceAny :: ToolChoice Source #

Convenience: any tool choice (force tool use)

toolChoiceTool :: Text -> ToolChoice Source #

Convenience: specific tool choice

Helpers for processing tool calls

isToolUse :: Value -> Bool Source #

Content block types (duplicated here for helper functions) These mirror the types in Messages but are needed for the helper functions.

Check if a content block is a tool use block

getToolUseBlocks :: Vector Value -> [(Text, Text, Value)] Source #

Extract tool use blocks from a response's content array

Returns a list of (id, name, input) tuples for each tool_use block

makeToolResult Source #

Arguments

:: Text

tool_use_id from the tool_use block

-> Text

Result content (typically JSON encoded)

-> Value 

Create a tool result content block for a successful tool call

makeToolResultError Source #

Arguments

:: Text

tool_use_id from the tool_use block

-> Text

Error message

-> Value 

Create a tool result content block for a failed tool call