| Safe Haskell | None |
|---|---|
| Language | Haskell2010 |
Claude.V1
Description
/v1
Example usage:
{-# LANGUAGE DuplicateRecordFields #-}
{-# LANGUAGE NamedFieldPuns #-}
{-# LANGUAGE OverloadedStrings #-}
{-# LANGUAGE OverloadedLists #-}
module Main where
import Data.Foldable (traverse_)
import Claude.V1
import Claude.V1.Messages
import qualified Data.Text as Text
import qualified Data.Text.IO as Text.IO
import qualified System.Environment as Environment
main :: IO ()
main = do
key <- Environment.getEnv "ANTHROPIC_KEY"
clientEnv <- getClientEnv "https://api.anthropic.com"
let Methods{ createMessage } = makeMethods clientEnv (Text.pack key) (Just "2023-06-01")
text <- Text.IO.getLine
MessageResponse{ content } <- createMessage _CreateMessage
{ model = "claude-sonnet-4-20250514"
, messages =
[ Message
{ role = User
, content = [ Content_Text{ text } ]
}
]
, max_tokens = 1024
}
let display (ContentBlock_Text{ text = t }) = Text.IO.putStrLn t
display _ = pure ()
traverse_ display content
Synopsis
- data Methods = Methods {
- createMessage :: CreateMessage -> IO MessageResponse
- createMessageStream :: CreateMessage -> (Either Text Value -> IO ()) -> IO ()
- createMessageStreamTyped :: CreateMessage -> (Either Text MessageStreamEvent -> IO ()) -> IO ()
- countTokens :: CountTokensRequest -> IO TokenCount
- createBatch :: CreateBatch -> IO BatchObject
- retrieveBatch :: Text -> IO BatchObject
- listBatches :: Maybe Natural -> Maybe Text -> Maybe Text -> IO ListBatchesResponse
- cancelBatch :: Text -> IO BatchObject
- getClientEnv :: Text -> IO ClientEnv
- makeMethods :: ClientEnv -> Text -> Maybe Text -> Methods
- makeMethodsWith :: ClientEnv -> ClientOptions -> Methods
- data ClientOptions = ClientOptions {}
- defaultClientOptions :: ClientOptions
- type API = Header' '[Required, Strict] "x-api-key" Text :> (Header' '[Optional, Strict] "anthropic-version" Text :> (Header' '[Optional, Strict] "anthropic-beta" Text :> ("v1" :> (API :<|> API))))
Methods
API methods
Constructors
| Methods | |
Fields
| |
Arguments
| :: Text | Base URL for API (e.g., "https://api.anthropic.com") |
| -> IO ClientEnv |
Convenient utility to get a ClientEnv for the most common use case
Arguments
| :: ClientEnv | |
| -> Text | API key |
| -> Maybe Text | Anthropic-Version header (e.g., "2023-06-01") |
| -> Methods |
Get a record of API methods after providing an API key
This is a convenience wrapper around makeMethodsWith for common usage.
makeMethodsWith :: ClientEnv -> ClientOptions -> Methods Source #
Get a record of API methods with full configuration options
Use this when you need to pass beta headers (e.g., for tool search):
let options = defaultClientOptions
{ apiKey = key
, anthropicBeta = Just "advanced-tool-use-2025-11-20"
}
let Methods{ createMessage } = makeMethodsWith clientEnv options
data ClientOptions Source #
Client configuration options
Constructors
| ClientOptions | |
Fields
| |
Instances
| Show ClientOptions Source # | |
Defined in Claude.V1 Methods showsPrec :: Int -> ClientOptions -> ShowS # show :: ClientOptions -> String # showList :: [ClientOptions] -> ShowS # | |
defaultClientOptions :: ClientOptions Source #
Default client options (requires setting apiKey)