| Safe Haskell | None |
|---|---|
| Language | Haskell2010 |
Claude.V1.Messages
Description
/v1/messages
This module provides types and utilities for the Claude Messages API.
Synopsis
- data CreateMessage = CreateMessage {
- model :: Text
- messages :: Vector Message
- max_tokens :: Natural
- system :: Maybe Text
- temperature :: Maybe Double
- top_p :: Maybe Double
- top_k :: Maybe Natural
- stop_sequences :: Maybe (Vector Text)
- stream :: Maybe Bool
- metadata :: Maybe (Map Text Text)
- tools :: Maybe (Vector ToolDefinition)
- tool_choice :: Maybe ToolChoice
- container :: Maybe Text
- _CreateMessage :: CreateMessage
- data MessageResponse = MessageResponse {
- id :: Text
- type_ :: Text
- role :: Role
- content :: Vector ContentBlock
- model :: Text
- stop_reason :: Maybe StopReason
- stop_sequence :: Maybe Text
- usage :: Usage
- container :: Maybe ContainerInfo
- data MessageStreamEvent
- = Message_Start { }
- | Content_Block_Start { }
- | Content_Block_Delta { }
- | Content_Block_Stop { }
- | Message_Delta { }
- | Message_Stop
- | Ping
- | Error { }
- data Content
- = Content_Text { }
- | Content_Image { }
- | Content_Tool_Use { }
- | Content_Server_Tool_Use { }
- | Content_Tool_Result { }
- data ContentBlock
- data TextContent = TextContent {}
- data ImageSource = ImageSource {}
- data ToolUseContent = ToolUseContent {}
- data ToolResultContent = ToolResultContent {}
- data Message = Message {
- role :: Role
- content :: Vector Content
- cache_control :: Maybe CacheControl
- data Role
- data StopReason
- data Usage = Usage {}
- data ServerToolUseUsage = ServerToolUseUsage {}
- data ToolReference = ToolReference {}
- data ToolSearchToolResultContent
- = ToolSearchResult {
- tool_references :: Vector ToolReference
- | ToolSearchError {
- error_code :: Text
- | ToolSearchResultContent_Unknown Value
- = ToolSearchResult {
- data ContainerInfo = ContainerInfo {
- id :: Text
- expires_at :: UTCTime
- data ToolCaller
- data CodeExecutionResult = CodeExecutionResult {}
- data CodeExecutionToolResultContent
- contentBlockToContent :: ContentBlock -> Maybe Content
- data Tool = Tool {
- name :: Text
- description :: Maybe Text
- input_schema :: InputSchema
- data ToolChoice
- data InputSchema = InputSchema {}
- data ToolDefinition
- = ToolDef_Function {
- tool :: Tool
- defer_loading :: Maybe Bool
- allowed_callers :: Maybe (Vector Text)
- | ToolDef_SearchTool ToolSearchTool
- | ToolDef_CodeExecutionTool { }
- = ToolDef_Function {
- data ToolSearchTool = ToolSearchTool {
- name :: Text
- type_ :: ToolSearchToolType
- data ToolSearchToolType
- functionTool :: Text -> Maybe Text -> Value -> Tool
- inlineTool :: Tool -> ToolDefinition
- deferredTool :: Tool -> ToolDefinition
- toolSearchRegex :: ToolDefinition
- toolSearchBm25 :: ToolDefinition
- codeExecutionTool :: ToolDefinition
- allowedCallersCodeExecution :: Vector Text
- allowCallers :: Vector Text -> ToolDefinition -> ToolDefinition
- toolChoiceAuto :: ToolChoice
- toolChoiceAny :: ToolChoice
- toolChoiceTool :: Text -> ToolChoice
- data ContentBlockDelta
- = Delta_Text_Delta { }
- | Delta_Input_Json_Delta {
- partial_json :: Text
- data TextDelta = TextDelta {}
- data InputJsonDelta = InputJsonDelta {
- partial_json :: Text
- data MessageDelta = MessageDelta {}
- data StreamUsage = StreamUsage {}
- data CountTokensRequest = CountTokensRequest {
- model :: Text
- messages :: Vector Message
- system :: Maybe Text
- tools :: Maybe (Vector ToolDefinition)
- tool_choice :: Maybe ToolChoice
- _CountTokensRequest :: CountTokensRequest
- data TokenCount = TokenCount {}
- data CacheControl = CacheControl {}
- ephemeralCache :: CacheControl
- textContent :: Text -> Content
- imageContent :: ImageSource -> Content
- type API = "messages" :> (MessagesAPI :<|> CountTokensAPI)
- type MessagesAPI = ReqBody '[JSON] CreateMessage :> Post '[JSON] MessageResponse
- type CountTokensAPI = "count_tokens" :> (ReqBody '[JSON] CountTokensRequest :> Post '[JSON] TokenCount)
Main types
data CreateMessage Source #
Request body for /v1/messages
For programmatic tool calling (PTC), use the container field to reuse
a code execution container from a previous response.
Constructors
| CreateMessage | |
Fields
| |
Instances
_CreateMessage :: CreateMessage Source #
Default CreateMessage with only required fields
data MessageResponse Source #
Response from the Messages API
For programmatic tool calling (PTC), the container field contains
information about the code execution container, which can be reused
across turns by passing its id in subsequent requests.
Constructors
| MessageResponse | |
Fields
| |
Instances
| FromJSON MessageResponse Source # | |||||
Defined in Claude.V1.Messages Methods parseJSON :: Value -> Parser MessageResponse # parseJSONList :: Value -> Parser [MessageResponse] # | |||||
| ToJSON MessageResponse Source # | |||||
Defined in Claude.V1.Messages Methods toJSON :: MessageResponse -> Value # toEncoding :: MessageResponse -> Encoding # toJSONList :: [MessageResponse] -> Value # toEncodingList :: [MessageResponse] -> Encoding # omitField :: MessageResponse -> Bool # | |||||
| Generic MessageResponse Source # | |||||
Defined in Claude.V1.Messages Associated Types
Methods from :: MessageResponse -> Rep MessageResponse x # to :: Rep MessageResponse x -> MessageResponse # | |||||
| Show MessageResponse Source # | |||||
Defined in Claude.V1.Messages Methods showsPrec :: Int -> MessageResponse -> ShowS # show :: MessageResponse -> String # showList :: [MessageResponse] -> ShowS # | |||||
| type Rep MessageResponse Source # | |||||
Defined in Claude.V1.Messages type Rep MessageResponse = D1 ('MetaData "MessageResponse" "Claude.V1.Messages" "claude-1.0.0-1j0Plg9n3EjAvfVKcV8Pl0" 'False) (C1 ('MetaCons "MessageResponse" 'PrefixI 'True) (((S1 ('MetaSel ('Just "id") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Text) :*: S1 ('MetaSel ('Just "type_") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Text)) :*: (S1 ('MetaSel ('Just "role") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Role) :*: S1 ('MetaSel ('Just "content") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Vector ContentBlock)))) :*: ((S1 ('MetaSel ('Just "model") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Text) :*: S1 ('MetaSel ('Just "stop_reason") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe StopReason))) :*: (S1 ('MetaSel ('Just "stop_sequence") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe Text)) :*: (S1 ('MetaSel ('Just "usage") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Usage) :*: S1 ('MetaSel ('Just "container") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe ContainerInfo))))))) | |||||
data MessageStreamEvent Source #
Streaming events for /v1/messages
Constructors
| Message_Start | |
Fields | |
| Content_Block_Start | |
Fields | |
| Content_Block_Delta | |
Fields
| |
| Content_Block_Stop | |
| Message_Delta | |
Fields | |
| Message_Stop | |
| Ping | |
| Error | |
Instances
| FromJSON MessageStreamEvent Source # | |||||
Defined in Claude.V1.Messages Methods parseJSON :: Value -> Parser MessageStreamEvent # parseJSONList :: Value -> Parser [MessageStreamEvent] # | |||||
| ToJSON MessageStreamEvent Source # | |||||
Defined in Claude.V1.Messages Methods toJSON :: MessageStreamEvent -> Value # toEncoding :: MessageStreamEvent -> Encoding # toJSONList :: [MessageStreamEvent] -> Value # toEncodingList :: [MessageStreamEvent] -> Encoding # omitField :: MessageStreamEvent -> Bool # | |||||
| Generic MessageStreamEvent Source # | |||||
Defined in Claude.V1.Messages Associated Types
Methods from :: MessageStreamEvent -> Rep MessageStreamEvent x # to :: Rep MessageStreamEvent x -> MessageStreamEvent # | |||||
| Show MessageStreamEvent Source # | |||||
Defined in Claude.V1.Messages Methods showsPrec :: Int -> MessageStreamEvent -> ShowS # show :: MessageStreamEvent -> String # showList :: [MessageStreamEvent] -> ShowS # | |||||
| type Rep MessageStreamEvent Source # | |||||
Defined in Claude.V1.Messages type Rep MessageStreamEvent = D1 ('MetaData "MessageStreamEvent" "Claude.V1.Messages" "claude-1.0.0-1j0Plg9n3EjAvfVKcV8Pl0" 'False) (((C1 ('MetaCons "Message_Start" 'PrefixI 'True) (S1 ('MetaSel ('Just "message") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 MessageResponse)) :+: C1 ('MetaCons "Content_Block_Start" 'PrefixI 'True) (S1 ('MetaSel ('Just "index") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Natural) :*: S1 ('MetaSel ('Just "content_block") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 ContentBlock))) :+: (C1 ('MetaCons "Content_Block_Delta" 'PrefixI 'True) (S1 ('MetaSel ('Just "index") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Natural) :*: S1 ('MetaSel ('Just "delta") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 ContentBlockDelta)) :+: C1 ('MetaCons "Content_Block_Stop" 'PrefixI 'True) (S1 ('MetaSel ('Just "index") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Natural)))) :+: ((C1 ('MetaCons "Message_Delta" 'PrefixI 'True) (S1 ('MetaSel ('Just "message_delta") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 MessageDelta) :*: S1 ('MetaSel ('Just "usage") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 StreamUsage)) :+: C1 ('MetaCons "Message_Stop" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "Ping" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "Error" 'PrefixI 'True) (S1 ('MetaSel ('Just "error") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Value))))) | |||||
Content types
Content block in a message (for requests)
For programmatic tool calling (PTC), replay assistant messages using:
Content_Tool_Usewith optionalcallerfieldContent_Server_Tool_Usefor code execution invocations
Constructors
| Content_Text | |
Fields
| |
| Content_Image | |
Fields | |
| Content_Tool_Use | |
| Content_Server_Tool_Use | |
| Content_Tool_Result | |
Instances
| FromJSON Content Source # | |||||
Defined in Claude.V1.Messages | |||||
| ToJSON Content Source # | |||||
| Generic Content Source # | |||||
Defined in Claude.V1.Messages Associated Types
| |||||
| Show Content Source # | |||||
| type Rep Content Source # | |||||
Defined in Claude.V1.Messages type Rep Content = D1 ('MetaData "Content" "Claude.V1.Messages" "claude-1.0.0-1j0Plg9n3EjAvfVKcV8Pl0" 'False) ((C1 ('MetaCons "Content_Text" 'PrefixI 'True) (S1 ('MetaSel ('Just "text") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Text) :*: S1 ('MetaSel ('Just "cache_control") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe CacheControl))) :+: C1 ('MetaCons "Content_Image" 'PrefixI 'True) (S1 ('MetaSel ('Just "source") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 ImageSource) :*: S1 ('MetaSel ('Just "cache_control") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe CacheControl)))) :+: (C1 ('MetaCons "Content_Tool_Use" 'PrefixI 'True) ((S1 ('MetaSel ('Just "id") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Text) :*: S1 ('MetaSel ('Just "name") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Text)) :*: (S1 ('MetaSel ('Just "input") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Value) :*: S1 ('MetaSel ('Just "caller") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe ToolCaller)))) :+: (C1 ('MetaCons "Content_Server_Tool_Use" 'PrefixI 'True) (S1 ('MetaSel ('Just "id") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Text) :*: (S1 ('MetaSel ('Just "name") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Text) :*: S1 ('MetaSel ('Just "input") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Value))) :+: C1 ('MetaCons "Content_Tool_Result" 'PrefixI 'True) (S1 ('MetaSel ('Just "tool_use_id") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Text) :*: (S1 ('MetaSel ('Just "content") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe Text)) :*: S1 ('MetaSel ('Just "is_error") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe Bool))))))) | |||||
data ContentBlock Source #
Content block in a response
Extended to support:
server_tool_use: Server-initiated tool use (e.g., tool search, code execution)tool_search_tool_result: Results from server-side tool searchcode_execution_tool_result: Results from code execution (PTC)
For programmatic tool calling, ContentBlock_Tool_Use includes an optional
caller field indicating whether the tool was called directly by Claude
or programmatically by code execution.
Constructors
| ContentBlock_Text | |
| ContentBlock_Tool_Use | |
| ContentBlock_Server_Tool_Use | |
| ContentBlock_Tool_Search_Tool_Result | |
| ContentBlock_Code_Execution_Tool_Result | |
| ContentBlock_Unknown | |
Instances
| FromJSON ContentBlock Source # | |||||
Defined in Claude.V1.Messages | |||||
| ToJSON ContentBlock Source # | |||||
Defined in Claude.V1.Messages Methods toJSON :: ContentBlock -> Value # toEncoding :: ContentBlock -> Encoding # toJSONList :: [ContentBlock] -> Value # toEncodingList :: [ContentBlock] -> Encoding # omitField :: ContentBlock -> Bool # | |||||
| Generic ContentBlock Source # | |||||
Defined in Claude.V1.Messages Associated Types
| |||||
| Show ContentBlock Source # | |||||
Defined in Claude.V1.Messages Methods showsPrec :: Int -> ContentBlock -> ShowS # show :: ContentBlock -> String # showList :: [ContentBlock] -> ShowS # | |||||
| type Rep ContentBlock Source # | |||||
Defined in Claude.V1.Messages type Rep ContentBlock = D1 ('MetaData "ContentBlock" "Claude.V1.Messages" "claude-1.0.0-1j0Plg9n3EjAvfVKcV8Pl0" 'False) ((C1 ('MetaCons "ContentBlock_Text" 'PrefixI 'True) (S1 ('MetaSel ('Just "text") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Text)) :+: (C1 ('MetaCons "ContentBlock_Tool_Use" 'PrefixI 'True) ((S1 ('MetaSel ('Just "id") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Text) :*: S1 ('MetaSel ('Just "name") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Text)) :*: (S1 ('MetaSel ('Just "input") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Value) :*: S1 ('MetaSel ('Just "caller") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe ToolCaller)))) :+: C1 ('MetaCons "ContentBlock_Server_Tool_Use" 'PrefixI 'True) (S1 ('MetaSel ('Just "id") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Text) :*: (S1 ('MetaSel ('Just "name") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Text) :*: S1 ('MetaSel ('Just "input") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Value))))) :+: (C1 ('MetaCons "ContentBlock_Tool_Search_Tool_Result" 'PrefixI 'True) (S1 ('MetaSel ('Just "tool_use_id") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Text) :*: S1 ('MetaSel ('Just "tool_search_content") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 ToolSearchToolResultContent)) :+: (C1 ('MetaCons "ContentBlock_Code_Execution_Tool_Result" 'PrefixI 'True) (S1 ('MetaSel ('Just "tool_use_id") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Text) :*: S1 ('MetaSel ('Just "code_execution_content") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 CodeExecutionToolResultContent)) :+: C1 ('MetaCons "ContentBlock_Unknown" 'PrefixI 'True) (S1 ('MetaSel ('Just "type_") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Text) :*: S1 ('MetaSel ('Just "raw") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Value))))) | |||||
data TextContent Source #
Text content block
Constructors
| TextContent | |
Instances
| FromJSON TextContent Source # | |||||
Defined in Claude.V1.Messages | |||||
| ToJSON TextContent Source # | |||||
Defined in Claude.V1.Messages Methods toJSON :: TextContent -> Value # toEncoding :: TextContent -> Encoding # toJSONList :: [TextContent] -> Value # toEncodingList :: [TextContent] -> Encoding # omitField :: TextContent -> Bool # | |||||
| Generic TextContent Source # | |||||
Defined in Claude.V1.Messages Associated Types
| |||||
| Show TextContent Source # | |||||
Defined in Claude.V1.Messages Methods showsPrec :: Int -> TextContent -> ShowS # show :: TextContent -> String # showList :: [TextContent] -> ShowS # | |||||
| type Rep TextContent Source # | |||||
Defined in Claude.V1.Messages type Rep TextContent = D1 ('MetaData "TextContent" "Claude.V1.Messages" "claude-1.0.0-1j0Plg9n3EjAvfVKcV8Pl0" 'False) (C1 ('MetaCons "TextContent" 'PrefixI 'True) (S1 ('MetaSel ('Just "text") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Text))) | |||||
data ImageSource Source #
Image source for vision capabilities
Constructors
| ImageSource | |
Instances
| FromJSON ImageSource Source # | |||||
Defined in Claude.V1.Messages | |||||
| ToJSON ImageSource Source # | |||||
Defined in Claude.V1.Messages Methods toJSON :: ImageSource -> Value # toEncoding :: ImageSource -> Encoding # toJSONList :: [ImageSource] -> Value # toEncodingList :: [ImageSource] -> Encoding # omitField :: ImageSource -> Bool # | |||||
| Generic ImageSource Source # | |||||
Defined in Claude.V1.Messages Associated Types
| |||||
| Show ImageSource Source # | |||||
Defined in Claude.V1.Messages Methods showsPrec :: Int -> ImageSource -> ShowS # show :: ImageSource -> String # showList :: [ImageSource] -> ShowS # | |||||
| type Rep ImageSource Source # | |||||
Defined in Claude.V1.Messages type Rep ImageSource = D1 ('MetaData "ImageSource" "Claude.V1.Messages" "claude-1.0.0-1j0Plg9n3EjAvfVKcV8Pl0" 'False) (C1 ('MetaCons "ImageSource" 'PrefixI 'True) (S1 ('MetaSel ('Just "type_") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Text) :*: (S1 ('MetaSel ('Just "media_type") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Text) :*: S1 ('MetaSel ('Just "data_") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Text)))) | |||||
data ToolUseContent Source #
Tool use content block (in assistant messages)
Instances
| FromJSON ToolUseContent Source # | |||||
Defined in Claude.V1.Messages Methods parseJSON :: Value -> Parser ToolUseContent # parseJSONList :: Value -> Parser [ToolUseContent] # | |||||
| ToJSON ToolUseContent Source # | |||||
Defined in Claude.V1.Messages Methods toJSON :: ToolUseContent -> Value # toEncoding :: ToolUseContent -> Encoding # toJSONList :: [ToolUseContent] -> Value # toEncodingList :: [ToolUseContent] -> Encoding # omitField :: ToolUseContent -> Bool # | |||||
| Generic ToolUseContent Source # | |||||
Defined in Claude.V1.Messages Associated Types
Methods from :: ToolUseContent -> Rep ToolUseContent x # to :: Rep ToolUseContent x -> ToolUseContent # | |||||
| Show ToolUseContent Source # | |||||
Defined in Claude.V1.Messages Methods showsPrec :: Int -> ToolUseContent -> ShowS # show :: ToolUseContent -> String # showList :: [ToolUseContent] -> ShowS # | |||||
| type Rep ToolUseContent Source # | |||||
Defined in Claude.V1.Messages type Rep ToolUseContent = D1 ('MetaData "ToolUseContent" "Claude.V1.Messages" "claude-1.0.0-1j0Plg9n3EjAvfVKcV8Pl0" 'False) (C1 ('MetaCons "ToolUseContent" 'PrefixI 'True) (S1 ('MetaSel ('Just "id") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Text) :*: (S1 ('MetaSel ('Just "name") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Text) :*: S1 ('MetaSel ('Just "input") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Value)))) | |||||
data ToolResultContent Source #
Tool result content (in user messages, following tool use)
Constructors
| ToolResultContent | |
Instances
| FromJSON ToolResultContent Source # | |||||
Defined in Claude.V1.Messages Methods parseJSON :: Value -> Parser ToolResultContent # parseJSONList :: Value -> Parser [ToolResultContent] # | |||||
| ToJSON ToolResultContent Source # | |||||
Defined in Claude.V1.Messages Methods toJSON :: ToolResultContent -> Value # toEncoding :: ToolResultContent -> Encoding # toJSONList :: [ToolResultContent] -> Value # toEncodingList :: [ToolResultContent] -> Encoding # omitField :: ToolResultContent -> Bool # | |||||
| Generic ToolResultContent Source # | |||||
Defined in Claude.V1.Messages Associated Types
Methods from :: ToolResultContent -> Rep ToolResultContent x # to :: Rep ToolResultContent x -> ToolResultContent # | |||||
| Show ToolResultContent Source # | |||||
Defined in Claude.V1.Messages Methods showsPrec :: Int -> ToolResultContent -> ShowS # show :: ToolResultContent -> String # showList :: [ToolResultContent] -> ShowS # | |||||
| type Rep ToolResultContent Source # | |||||
Defined in Claude.V1.Messages type Rep ToolResultContent = D1 ('MetaData "ToolResultContent" "Claude.V1.Messages" "claude-1.0.0-1j0Plg9n3EjAvfVKcV8Pl0" 'False) (C1 ('MetaCons "ToolResultContent" 'PrefixI 'True) (S1 ('MetaSel ('Just "tool_use_id") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Text) :*: (S1 ('MetaSel ('Just "content") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe Text)) :*: S1 ('MetaSel ('Just "is_error") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe Bool))))) | |||||
Message types
A message in the conversation
The optional cache_control field allows setting cache breakpoints at
the message level (in addition to content-level caching).
Constructors
| Message | |
Fields
| |
Instances
| FromJSON Message Source # | |||||
Defined in Claude.V1.Messages | |||||
| ToJSON Message Source # | |||||
| Generic Message Source # | |||||
Defined in Claude.V1.Messages Associated Types
| |||||
| Show Message Source # | |||||
| type Rep Message Source # | |||||
Defined in Claude.V1.Messages type Rep Message = D1 ('MetaData "Message" "Claude.V1.Messages" "claude-1.0.0-1j0Plg9n3EjAvfVKcV8Pl0" 'False) (C1 ('MetaCons "Message" 'PrefixI 'True) (S1 ('MetaSel ('Just "role") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Role) :*: (S1 ('MetaSel ('Just "content") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Vector Content)) :*: S1 ('MetaSel ('Just "cache_control") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe CacheControl))))) | |||||
Role of a message participant
Response types
data StopReason Source #
Reason why the model stopped generating
Constructors
| End_Turn | |
| Max_Tokens | |
| Stop_Sequence | |
| Tool_Use |
Instances
| FromJSON StopReason Source # | |||||
Defined in Claude.V1.Messages | |||||
| ToJSON StopReason Source # | |||||
Defined in Claude.V1.Messages Methods toJSON :: StopReason -> Value # toEncoding :: StopReason -> Encoding # toJSONList :: [StopReason] -> Value # toEncodingList :: [StopReason] -> Encoding # omitField :: StopReason -> Bool # | |||||
| Generic StopReason Source # | |||||
Defined in Claude.V1.Messages Associated Types
| |||||
| Show StopReason Source # | |||||
Defined in Claude.V1.Messages Methods showsPrec :: Int -> StopReason -> ShowS # show :: StopReason -> String # showList :: [StopReason] -> ShowS # | |||||
| Eq StopReason Source # | |||||
Defined in Claude.V1.Messages | |||||
| type Rep StopReason Source # | |||||
Defined in Claude.V1.Messages type Rep StopReason = D1 ('MetaData "StopReason" "Claude.V1.Messages" "claude-1.0.0-1j0Plg9n3EjAvfVKcV8Pl0" 'False) ((C1 ('MetaCons "End_Turn" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "Max_Tokens" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "Stop_Sequence" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "Tool_Use" 'PrefixI 'False) (U1 :: Type -> Type))) | |||||
Token usage information
Constructors
| Usage | |
Instances
| FromJSON Usage Source # | |||||
Defined in Claude.V1.Messages | |||||
| ToJSON Usage Source # | |||||
| Generic Usage Source # | |||||
Defined in Claude.V1.Messages Associated Types
| |||||
| Show Usage Source # | |||||
| type Rep Usage Source # | |||||
Defined in Claude.V1.Messages type Rep Usage = D1 ('MetaData "Usage" "Claude.V1.Messages" "claude-1.0.0-1j0Plg9n3EjAvfVKcV8Pl0" 'False) (C1 ('MetaCons "Usage" 'PrefixI 'True) ((S1 ('MetaSel ('Just "input_tokens") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Natural) :*: S1 ('MetaSel ('Just "output_tokens") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Natural)) :*: (S1 ('MetaSel ('Just "cache_creation_input_tokens") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe Natural)) :*: (S1 ('MetaSel ('Just "cache_read_input_tokens") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe Natural)) :*: S1 ('MetaSel ('Just "server_tool_use") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe ServerToolUseUsage)))))) | |||||
data ServerToolUseUsage Source #
Server tool use usage information (e.g., tool search requests, web search requests)
Constructors
| ServerToolUseUsage | |
Fields | |
Instances
| FromJSON ServerToolUseUsage Source # | |||||
Defined in Claude.V1.Messages Methods parseJSON :: Value -> Parser ServerToolUseUsage # parseJSONList :: Value -> Parser [ServerToolUseUsage] # | |||||
| ToJSON ServerToolUseUsage Source # | |||||
Defined in Claude.V1.Messages Methods toJSON :: ServerToolUseUsage -> Value # toEncoding :: ServerToolUseUsage -> Encoding # toJSONList :: [ServerToolUseUsage] -> Value # toEncodingList :: [ServerToolUseUsage] -> Encoding # omitField :: ServerToolUseUsage -> Bool # | |||||
| Generic ServerToolUseUsage Source # | |||||
Defined in Claude.V1.Messages Associated Types
Methods from :: ServerToolUseUsage -> Rep ServerToolUseUsage x # to :: Rep ServerToolUseUsage x -> ServerToolUseUsage # | |||||
| Show ServerToolUseUsage Source # | |||||
Defined in Claude.V1.Messages Methods showsPrec :: Int -> ServerToolUseUsage -> ShowS # show :: ServerToolUseUsage -> String # showList :: [ServerToolUseUsage] -> ShowS # | |||||
| Eq ServerToolUseUsage Source # | |||||
Defined in Claude.V1.Messages Methods (==) :: ServerToolUseUsage -> ServerToolUseUsage -> Bool # (/=) :: ServerToolUseUsage -> ServerToolUseUsage -> Bool # | |||||
| type Rep ServerToolUseUsage Source # | |||||
Defined in Claude.V1.Messages type Rep ServerToolUseUsage = D1 ('MetaData "ServerToolUseUsage" "Claude.V1.Messages" "claude-1.0.0-1j0Plg9n3EjAvfVKcV8Pl0" 'False) (C1 ('MetaCons "ServerToolUseUsage" 'PrefixI 'True) (S1 ('MetaSel ('Just "web_search_requests") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe Natural)) :*: S1 ('MetaSel ('Just "tool_search_requests") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe Natural)))) | |||||
Tool search response types
data ToolReference Source #
A reference to a tool found by tool search
Constructors
| ToolReference | |
Instances
| FromJSON ToolReference Source # | |||||
Defined in Claude.V1.Messages Methods parseJSON :: Value -> Parser ToolReference # parseJSONList :: Value -> Parser [ToolReference] # | |||||
| ToJSON ToolReference Source # | |||||
Defined in Claude.V1.Messages Methods toJSON :: ToolReference -> Value # toEncoding :: ToolReference -> Encoding # toJSONList :: [ToolReference] -> Value # toEncodingList :: [ToolReference] -> Encoding # omitField :: ToolReference -> Bool # | |||||
| Generic ToolReference Source # | |||||
Defined in Claude.V1.Messages Associated Types
| |||||
| Show ToolReference Source # | |||||
Defined in Claude.V1.Messages Methods showsPrec :: Int -> ToolReference -> ShowS # show :: ToolReference -> String # showList :: [ToolReference] -> ShowS # | |||||
| Eq ToolReference Source # | |||||
Defined in Claude.V1.Messages Methods (==) :: ToolReference -> ToolReference -> Bool # (/=) :: ToolReference -> ToolReference -> Bool # | |||||
| type Rep ToolReference Source # | |||||
Defined in Claude.V1.Messages type Rep ToolReference = D1 ('MetaData "ToolReference" "Claude.V1.Messages" "claude-1.0.0-1j0Plg9n3EjAvfVKcV8Pl0" 'False) (C1 ('MetaCons "ToolReference" 'PrefixI 'True) (S1 ('MetaSel ('Just "tool_name") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Text))) | |||||
data ToolSearchToolResultContent Source #
Content of a tool search tool result
This can be either successful search results with tool references, an error, or an unknown type for forward compatibility.
Constructors
| ToolSearchResult | |
Fields
| |
| ToolSearchError | |
Fields
| |
| ToolSearchResultContent_Unknown Value | |
Instances
| FromJSON ToolSearchToolResultContent Source # | |
Defined in Claude.V1.Messages | |
| ToJSON ToolSearchToolResultContent Source # | |
Defined in Claude.V1.Messages Methods toJSON :: ToolSearchToolResultContent -> Value # toEncoding :: ToolSearchToolResultContent -> Encoding # toJSONList :: [ToolSearchToolResultContent] -> Value # toEncodingList :: [ToolSearchToolResultContent] -> Encoding # | |
| Show ToolSearchToolResultContent Source # | |
Defined in Claude.V1.Messages Methods showsPrec :: Int -> ToolSearchToolResultContent -> ShowS # show :: ToolSearchToolResultContent -> String # showList :: [ToolSearchToolResultContent] -> ShowS # | |
| Eq ToolSearchToolResultContent Source # | |
Defined in Claude.V1.Messages Methods (==) :: ToolSearchToolResultContent -> ToolSearchToolResultContent -> Bool # (/=) :: ToolSearchToolResultContent -> ToolSearchToolResultContent -> Bool # | |
Programmatic tool calling (PTC) types
data ContainerInfo Source #
Container information for programmatic tool calling (PTC)
When using code execution, Claude runs code in a container. The container
can be reused across multiple turns by passing its id in subsequent requests.
Constructors
| ContainerInfo | |
Fields
| |
Instances
| FromJSON ContainerInfo Source # | |||||
Defined in Claude.V1.Messages Methods parseJSON :: Value -> Parser ContainerInfo # parseJSONList :: Value -> Parser [ContainerInfo] # | |||||
| ToJSON ContainerInfo Source # | |||||
Defined in Claude.V1.Messages Methods toJSON :: ContainerInfo -> Value # toEncoding :: ContainerInfo -> Encoding # toJSONList :: [ContainerInfo] -> Value # toEncodingList :: [ContainerInfo] -> Encoding # omitField :: ContainerInfo -> Bool # | |||||
| Generic ContainerInfo Source # | |||||
Defined in Claude.V1.Messages Associated Types
| |||||
| Show ContainerInfo Source # | |||||
Defined in Claude.V1.Messages Methods showsPrec :: Int -> ContainerInfo -> ShowS # show :: ContainerInfo -> String # showList :: [ContainerInfo] -> ShowS # | |||||
| Eq ContainerInfo Source # | |||||
Defined in Claude.V1.Messages Methods (==) :: ContainerInfo -> ContainerInfo -> Bool # (/=) :: ContainerInfo -> ContainerInfo -> Bool # | |||||
| type Rep ContainerInfo Source # | |||||
Defined in Claude.V1.Messages type Rep ContainerInfo = D1 ('MetaData "ContainerInfo" "Claude.V1.Messages" "claude-1.0.0-1j0Plg9n3EjAvfVKcV8Pl0" 'False) (C1 ('MetaCons "ContainerInfo" 'PrefixI 'True) (S1 ('MetaSel ('Just "id") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Text) :*: S1 ('MetaSel ('Just "expires_at") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 UTCTime))) | |||||
data ToolCaller Source #
Identifies who called a tool (for programmatic tool calling)
ToolCaller_Direct: Claude called the tool directlyToolCaller_CodeExecution: Code execution called the tool programmaticallyToolCaller_Unknown: Unknown caller type (forward compatibility)
Instances
| FromJSON ToolCaller Source # | |
Defined in Claude.V1.Messages | |
| ToJSON ToolCaller Source # | |
Defined in Claude.V1.Messages Methods toJSON :: ToolCaller -> Value # toEncoding :: ToolCaller -> Encoding # toJSONList :: [ToolCaller] -> Value # toEncodingList :: [ToolCaller] -> Encoding # omitField :: ToolCaller -> Bool # | |
| Show ToolCaller Source # | |
Defined in Claude.V1.Messages Methods showsPrec :: Int -> ToolCaller -> ShowS # show :: ToolCaller -> String # showList :: [ToolCaller] -> ShowS # | |
| Eq ToolCaller Source # | |
Defined in Claude.V1.Messages | |
data CodeExecutionResult Source #
Result from code execution
Contains stdout, stderr, return code, and any additional content (e.g., generated files, images).
Constructors
| CodeExecutionResult | |
Instances
| FromJSON CodeExecutionResult Source # | |||||
Defined in Claude.V1.Messages Methods parseJSON :: Value -> Parser CodeExecutionResult # parseJSONList :: Value -> Parser [CodeExecutionResult] # | |||||
| ToJSON CodeExecutionResult Source # | |||||
Defined in Claude.V1.Messages Methods toJSON :: CodeExecutionResult -> Value # toEncoding :: CodeExecutionResult -> Encoding # toJSONList :: [CodeExecutionResult] -> Value # toEncodingList :: [CodeExecutionResult] -> Encoding # omitField :: CodeExecutionResult -> Bool # | |||||
| Generic CodeExecutionResult Source # | |||||
Defined in Claude.V1.Messages Associated Types
Methods from :: CodeExecutionResult -> Rep CodeExecutionResult x # to :: Rep CodeExecutionResult x -> CodeExecutionResult # | |||||
| Show CodeExecutionResult Source # | |||||
Defined in Claude.V1.Messages Methods showsPrec :: Int -> CodeExecutionResult -> ShowS # show :: CodeExecutionResult -> String # showList :: [CodeExecutionResult] -> ShowS # | |||||
| Eq CodeExecutionResult Source # | |||||
Defined in Claude.V1.Messages Methods (==) :: CodeExecutionResult -> CodeExecutionResult -> Bool # (/=) :: CodeExecutionResult -> CodeExecutionResult -> Bool # | |||||
| type Rep CodeExecutionResult Source # | |||||
Defined in Claude.V1.Messages type Rep CodeExecutionResult = D1 ('MetaData "CodeExecutionResult" "Claude.V1.Messages" "claude-1.0.0-1j0Plg9n3EjAvfVKcV8Pl0" 'False) (C1 ('MetaCons "CodeExecutionResult" 'PrefixI 'True) ((S1 ('MetaSel ('Just "stdout") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Text) :*: S1 ('MetaSel ('Just "stderr") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Text)) :*: (S1 ('MetaSel ('Just "return_code") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Int) :*: S1 ('MetaSel ('Just "content") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Vector Value))))) | |||||
data CodeExecutionToolResultContent Source #
Content of a code execution tool result
CodeExecutionResultContent: Successful execution with stdout/stderrCodeExecutionToolResultContent_Unknown: Unknown content type (forward compatibility)
Constructors
| CodeExecutionResultContent CodeExecutionResult | |
| CodeExecutionToolResultContent_Unknown Value |
Instances
| FromJSON CodeExecutionToolResultContent Source # | |
Defined in Claude.V1.Messages | |
| ToJSON CodeExecutionToolResultContent Source # | |
Defined in Claude.V1.Messages | |
| Show CodeExecutionToolResultContent Source # | |
Defined in Claude.V1.Messages Methods showsPrec :: Int -> CodeExecutionToolResultContent -> ShowS # show :: CodeExecutionToolResultContent -> String # showList :: [CodeExecutionToolResultContent] -> ShowS # | |
| Eq CodeExecutionToolResultContent Source # | |
Defined in Claude.V1.Messages | |
contentBlockToContent :: ContentBlock -> Maybe Content Source #
Convert a response ContentBlock to a request Content for replaying
This is useful for programmatic tool calling (PTC) where you need to replay assistant messages in subsequent requests.
Returns Nothing for content blocks that don't need to be replayed:
Tool types (re-exported from Claude.V1.Tool)
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 | |
Fields
| |
Instances
| FromJSON Tool Source # | |||||
Defined in Claude.V1.Tool | |||||
| ToJSON Tool Source # | |||||
| Generic Tool Source # | |||||
Defined in Claude.V1.Tool Associated Types
| |||||
| Show Tool Source # | |||||
| Eq Tool Source # | |||||
| type Rep Tool Source # | |||||
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 |
Instances
| FromJSON ToolChoice Source # | |||||
Defined in Claude.V1.Tool | |||||
| ToJSON ToolChoice Source # | |||||
Defined in Claude.V1.Tool Methods toJSON :: ToolChoice -> Value # toEncoding :: ToolChoice -> Encoding # toJSONList :: [ToolChoice] -> Value # toEncodingList :: [ToolChoice] -> Encoding # omitField :: ToolChoice -> Bool # | |||||
| Generic ToolChoice Source # | |||||
Defined in Claude.V1.Tool Associated Types
| |||||
| Show ToolChoice Source # | |||||
Defined in Claude.V1.Tool Methods showsPrec :: Int -> ToolChoice -> ShowS # show :: ToolChoice -> String # showList :: [ToolChoice] -> ShowS # | |||||
| type Rep ToolChoice Source # | |||||
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 | |
Instances
| FromJSON InputSchema Source # | |||||
Defined in Claude.V1.Tool | |||||
| ToJSON InputSchema Source # | |||||
Defined in Claude.V1.Tool Methods toJSON :: InputSchema -> Value # toEncoding :: InputSchema -> Encoding # toJSONList :: [InputSchema] -> Value # toEncodingList :: [InputSchema] -> Encoding # omitField :: InputSchema -> Bool # | |||||
| Generic InputSchema Source # | |||||
Defined in Claude.V1.Tool Associated Types
| |||||
| Show InputSchema Source # | |||||
Defined in Claude.V1.Tool Methods showsPrec :: Int -> InputSchema -> ShowS # show :: InputSchema -> String # showList :: [InputSchema] -> ShowS # | |||||
| Eq InputSchema Source # | |||||
Defined in Claude.V1.Tool | |||||
| type Rep InputSchema Source # | |||||
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)))))) | |||||
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.
Constructors
| ToolDef_Function | |
Fields
| |
| ToolDef_SearchTool ToolSearchTool | |
| ToolDef_CodeExecutionTool | |
Instances
| FromJSON ToolDefinition Source # | |
Defined in Claude.V1.Tool Methods parseJSON :: Value -> Parser ToolDefinition # parseJSONList :: Value -> Parser [ToolDefinition] # | |
| ToJSON ToolDefinition Source # | |
Defined in Claude.V1.Tool Methods toJSON :: ToolDefinition -> Value # toEncoding :: ToolDefinition -> Encoding # toJSONList :: [ToolDefinition] -> Value # toEncodingList :: [ToolDefinition] -> Encoding # omitField :: ToolDefinition -> Bool # | |
| Show ToolDefinition Source # | |
Defined in Claude.V1.Tool Methods showsPrec :: Int -> ToolDefinition -> ShowS # show :: ToolDefinition -> String # showList :: [ToolDefinition] -> ShowS # | |
| Eq ToolDefinition Source # | |
Defined in Claude.V1.Tool Methods (==) :: ToolDefinition -> ToolDefinition -> Bool # (/=) :: ToolDefinition -> ToolDefinition -> Bool # | |
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 | |
Fields
| |
Instances
| FromJSON ToolSearchTool Source # | |
Defined in Claude.V1.Tool Methods parseJSON :: Value -> Parser ToolSearchTool # parseJSONList :: Value -> Parser [ToolSearchTool] # | |
| ToJSON ToolSearchTool Source # | |
Defined in Claude.V1.Tool Methods toJSON :: ToolSearchTool -> Value # toEncoding :: ToolSearchTool -> Encoding # toJSONList :: [ToolSearchTool] -> Value # toEncodingList :: [ToolSearchTool] -> Encoding # omitField :: ToolSearchTool -> Bool # | |
| Show ToolSearchTool Source # | |
Defined in Claude.V1.Tool Methods showsPrec :: Int -> ToolSearchTool -> ShowS # show :: ToolSearchTool -> String # showList :: [ToolSearchTool] -> ShowS # | |
| Eq ToolSearchTool Source # | |
Defined in Claude.V1.Tool Methods (==) :: ToolSearchTool -> ToolSearchTool -> Bool # (/=) :: ToolSearchTool -> ToolSearchTool -> Bool # | |
data ToolSearchToolType Source #
Tool search tool type variants (for server-side tool search)
Instances
| FromJSON ToolSearchToolType Source # | |
Defined in Claude.V1.Tool Methods parseJSON :: Value -> Parser ToolSearchToolType # parseJSONList :: Value -> Parser [ToolSearchToolType] # | |
| ToJSON ToolSearchToolType Source # | |
Defined in Claude.V1.Tool Methods toJSON :: ToolSearchToolType -> Value # toEncoding :: ToolSearchToolType -> Encoding # toJSONList :: [ToolSearchToolType] -> Value # toEncodingList :: [ToolSearchToolType] -> Encoding # omitField :: ToolSearchToolType -> Bool # | |
| Show ToolSearchToolType Source # | |
Defined in Claude.V1.Tool Methods showsPrec :: Int -> ToolSearchToolType -> ShowS # show :: ToolSearchToolType -> String # showList :: [ToolSearchToolType] -> ShowS # | |
| Eq ToolSearchToolType Source # | |
Defined in Claude.V1.Tool Methods (==) :: ToolSearchToolType -> ToolSearchToolType -> Bool # (/=) :: ToolSearchToolType -> ToolSearchToolType -> Bool # | |
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.
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.
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)
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
Streaming types
data ContentBlockDelta Source #
Content block delta in streaming
Constructors
| Delta_Text_Delta | |
| Delta_Input_Json_Delta | |
Fields
| |
Instances
| FromJSON ContentBlockDelta Source # | |||||
Defined in Claude.V1.Messages Methods parseJSON :: Value -> Parser ContentBlockDelta # parseJSONList :: Value -> Parser [ContentBlockDelta] # | |||||
| ToJSON ContentBlockDelta Source # | |||||
Defined in Claude.V1.Messages Methods toJSON :: ContentBlockDelta -> Value # toEncoding :: ContentBlockDelta -> Encoding # toJSONList :: [ContentBlockDelta] -> Value # toEncodingList :: [ContentBlockDelta] -> Encoding # omitField :: ContentBlockDelta -> Bool # | |||||
| Generic ContentBlockDelta Source # | |||||
Defined in Claude.V1.Messages Associated Types
Methods from :: ContentBlockDelta -> Rep ContentBlockDelta x # to :: Rep ContentBlockDelta x -> ContentBlockDelta # | |||||
| Show ContentBlockDelta Source # | |||||
Defined in Claude.V1.Messages Methods showsPrec :: Int -> ContentBlockDelta -> ShowS # show :: ContentBlockDelta -> String # showList :: [ContentBlockDelta] -> ShowS # | |||||
| type Rep ContentBlockDelta Source # | |||||
Defined in Claude.V1.Messages type Rep ContentBlockDelta = D1 ('MetaData "ContentBlockDelta" "Claude.V1.Messages" "claude-1.0.0-1j0Plg9n3EjAvfVKcV8Pl0" 'False) (C1 ('MetaCons "Delta_Text_Delta" 'PrefixI 'True) (S1 ('MetaSel ('Just "text") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Text)) :+: C1 ('MetaCons "Delta_Input_Json_Delta" 'PrefixI 'True) (S1 ('MetaSel ('Just "partial_json") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Text))) | |||||
Text delta in streaming
data InputJsonDelta Source #
Input JSON delta in streaming (for tool use)
Constructors
| InputJsonDelta | |
Fields
| |
Instances
| FromJSON InputJsonDelta Source # | |||||
Defined in Claude.V1.Messages Methods parseJSON :: Value -> Parser InputJsonDelta # parseJSONList :: Value -> Parser [InputJsonDelta] # | |||||
| ToJSON InputJsonDelta Source # | |||||
Defined in Claude.V1.Messages Methods toJSON :: InputJsonDelta -> Value # toEncoding :: InputJsonDelta -> Encoding # toJSONList :: [InputJsonDelta] -> Value # toEncodingList :: [InputJsonDelta] -> Encoding # omitField :: InputJsonDelta -> Bool # | |||||
| Generic InputJsonDelta Source # | |||||
Defined in Claude.V1.Messages Associated Types
Methods from :: InputJsonDelta -> Rep InputJsonDelta x # to :: Rep InputJsonDelta x -> InputJsonDelta # | |||||
| Show InputJsonDelta Source # | |||||
Defined in Claude.V1.Messages Methods showsPrec :: Int -> InputJsonDelta -> ShowS # show :: InputJsonDelta -> String # showList :: [InputJsonDelta] -> ShowS # | |||||
| type Rep InputJsonDelta Source # | |||||
Defined in Claude.V1.Messages type Rep InputJsonDelta = D1 ('MetaData "InputJsonDelta" "Claude.V1.Messages" "claude-1.0.0-1j0Plg9n3EjAvfVKcV8Pl0" 'False) (C1 ('MetaCons "InputJsonDelta" 'PrefixI 'True) (S1 ('MetaSel ('Just "partial_json") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Text))) | |||||
data MessageDelta Source #
Message delta in streaming (for stop_reason, etc.)
Constructors
| MessageDelta | |
Fields | |
Instances
| FromJSON MessageDelta Source # | |||||
Defined in Claude.V1.Messages | |||||
| ToJSON MessageDelta Source # | |||||
Defined in Claude.V1.Messages Methods toJSON :: MessageDelta -> Value # toEncoding :: MessageDelta -> Encoding # toJSONList :: [MessageDelta] -> Value # toEncodingList :: [MessageDelta] -> Encoding # omitField :: MessageDelta -> Bool # | |||||
| Generic MessageDelta Source # | |||||
Defined in Claude.V1.Messages Associated Types
| |||||
| Show MessageDelta Source # | |||||
Defined in Claude.V1.Messages Methods showsPrec :: Int -> MessageDelta -> ShowS # show :: MessageDelta -> String # showList :: [MessageDelta] -> ShowS # | |||||
| type Rep MessageDelta Source # | |||||
Defined in Claude.V1.Messages type Rep MessageDelta = D1 ('MetaData "MessageDelta" "Claude.V1.Messages" "claude-1.0.0-1j0Plg9n3EjAvfVKcV8Pl0" 'False) (C1 ('MetaCons "MessageDelta" 'PrefixI 'True) (S1 ('MetaSel ('Just "stop_reason") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe StopReason)) :*: S1 ('MetaSel ('Just "stop_sequence") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe Text)))) | |||||
data StreamUsage Source #
Usage in streaming message_delta events
Constructors
| StreamUsage | |
Fields | |
Instances
| FromJSON StreamUsage Source # | |||||
Defined in Claude.V1.Messages | |||||
| ToJSON StreamUsage Source # | |||||
Defined in Claude.V1.Messages Methods toJSON :: StreamUsage -> Value # toEncoding :: StreamUsage -> Encoding # toJSONList :: [StreamUsage] -> Value # toEncodingList :: [StreamUsage] -> Encoding # omitField :: StreamUsage -> Bool # | |||||
| Generic StreamUsage Source # | |||||
Defined in Claude.V1.Messages Associated Types
| |||||
| Show StreamUsage Source # | |||||
Defined in Claude.V1.Messages Methods showsPrec :: Int -> StreamUsage -> ShowS # show :: StreamUsage -> String # showList :: [StreamUsage] -> ShowS # | |||||
| type Rep StreamUsage Source # | |||||
Defined in Claude.V1.Messages type Rep StreamUsage = D1 ('MetaData "StreamUsage" "Claude.V1.Messages" "claude-1.0.0-1j0Plg9n3EjAvfVKcV8Pl0" 'False) (C1 ('MetaCons "StreamUsage" 'PrefixI 'True) (S1 ('MetaSel ('Just "output_tokens") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Natural))) | |||||
Token counting
data CountTokensRequest Source #
Request body for /v1/messages/count_tokens
Note: This differs from CreateMessage - it doesn't include max_tokens and other generation parameters.
Constructors
| CountTokensRequest | |
Fields
| |
Instances
| FromJSON CountTokensRequest Source # | |||||
Defined in Claude.V1.Messages Methods parseJSON :: Value -> Parser CountTokensRequest # parseJSONList :: Value -> Parser [CountTokensRequest] # | |||||
| ToJSON CountTokensRequest Source # | |||||
Defined in Claude.V1.Messages Methods toJSON :: CountTokensRequest -> Value # toEncoding :: CountTokensRequest -> Encoding # toJSONList :: [CountTokensRequest] -> Value # toEncodingList :: [CountTokensRequest] -> Encoding # omitField :: CountTokensRequest -> Bool # | |||||
| Generic CountTokensRequest Source # | |||||
Defined in Claude.V1.Messages Associated Types
Methods from :: CountTokensRequest -> Rep CountTokensRequest x # to :: Rep CountTokensRequest x -> CountTokensRequest # | |||||
| Show CountTokensRequest Source # | |||||
Defined in Claude.V1.Messages Methods showsPrec :: Int -> CountTokensRequest -> ShowS # show :: CountTokensRequest -> String # showList :: [CountTokensRequest] -> ShowS # | |||||
| type Rep CountTokensRequest Source # | |||||
Defined in Claude.V1.Messages type Rep CountTokensRequest = D1 ('MetaData "CountTokensRequest" "Claude.V1.Messages" "claude-1.0.0-1j0Plg9n3EjAvfVKcV8Pl0" 'False) (C1 ('MetaCons "CountTokensRequest" 'PrefixI 'True) ((S1 ('MetaSel ('Just "model") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Text) :*: S1 ('MetaSel ('Just "messages") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Vector Message))) :*: (S1 ('MetaSel ('Just "system") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe Text)) :*: (S1 ('MetaSel ('Just "tools") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe (Vector ToolDefinition))) :*: S1 ('MetaSel ('Just "tool_choice") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe ToolChoice)))))) | |||||
_CountTokensRequest :: CountTokensRequest Source #
Default CountTokensRequest
data TokenCount Source #
Response from the token counting endpoint
Constructors
| TokenCount | |
Fields | |
Instances
| FromJSON TokenCount Source # | |||||
Defined in Claude.V1.Messages | |||||
| ToJSON TokenCount Source # | |||||
Defined in Claude.V1.Messages Methods toJSON :: TokenCount -> Value # toEncoding :: TokenCount -> Encoding # toJSONList :: [TokenCount] -> Value # toEncodingList :: [TokenCount] -> Encoding # omitField :: TokenCount -> Bool # | |||||
| Generic TokenCount Source # | |||||
Defined in Claude.V1.Messages Associated Types
| |||||
| Show TokenCount Source # | |||||
Defined in Claude.V1.Messages Methods showsPrec :: Int -> TokenCount -> ShowS # show :: TokenCount -> String # showList :: [TokenCount] -> ShowS # | |||||
| type Rep TokenCount Source # | |||||
Defined in Claude.V1.Messages type Rep TokenCount = D1 ('MetaData "TokenCount" "Claude.V1.Messages" "claude-1.0.0-1j0Plg9n3EjAvfVKcV8Pl0" 'False) (C1 ('MetaCons "TokenCount" 'PrefixI 'True) (S1 ('MetaSel ('Just "input_tokens") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Natural))) | |||||
Prompt caching
data CacheControl Source #
Cache control for prompt caching
Constructors
| CacheControl | |
Instances
| FromJSON CacheControl Source # | |||||
Defined in Claude.V1.Messages | |||||
| ToJSON CacheControl Source # | |||||
Defined in Claude.V1.Messages Methods toJSON :: CacheControl -> Value # toEncoding :: CacheControl -> Encoding # toJSONList :: [CacheControl] -> Value # toEncodingList :: [CacheControl] -> Encoding # omitField :: CacheControl -> Bool # | |||||
| Generic CacheControl Source # | |||||
Defined in Claude.V1.Messages Associated Types
| |||||
| Show CacheControl Source # | |||||
Defined in Claude.V1.Messages Methods showsPrec :: Int -> CacheControl -> ShowS # show :: CacheControl -> String # showList :: [CacheControl] -> ShowS # | |||||
| type Rep CacheControl Source # | |||||
Defined in Claude.V1.Messages type Rep CacheControl = D1 ('MetaData "CacheControl" "Claude.V1.Messages" "claude-1.0.0-1j0Plg9n3EjAvfVKcV8Pl0" 'False) (C1 ('MetaCons "CacheControl" 'PrefixI 'True) (S1 ('MetaSel ('Just "type_") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Text))) | |||||
ephemeralCache :: CacheControl Source #
Convenience constructor for ephemeral cache control
Convenience constructors
textContent :: Text -> Content Source #
Create a text content block without cache control
imageContent :: ImageSource -> Content Source #
Create an image content block without cache control
Servant
type API = "messages" :> (MessagesAPI :<|> CountTokensAPI) Source #
Combined Servant API
type MessagesAPI = ReqBody '[JSON] CreateMessage :> Post '[JSON] MessageResponse Source #
Servant API for /v1/messages
type CountTokensAPI = "count_tokens" :> (ReqBody '[JSON] CountTokensRequest :> Post '[JSON] TokenCount) Source #
Servant API for /v1/messages/count_tokens