Copyright | (c) 2025 Tushar Adhatrao |
---|---|
License | MIT |
Maintainer | Tushar Adhatrao <tusharadhatrao@gmail.com> |
Safe Haskell | Safe-Inferred |
Language | Haskell2010 |
Langchain.Agents.Core
Description
Agents use LLMs as reasoning engines to determine actions dynamically This module implements the core agent execution loop and interfaces, supporting tool interaction and memory management.
Example agent execution flow:
executor <- AgentExecutor { executor = myAgent , executorMemory = emptyMemory , maxIterations = 5 , returnIntermediateSteps = True } result <- runAgentExecutor executor "Explain quantum computing"
Synopsis
- data AgentAction = AgentAction {
- actionToolName :: Text
- actionInput :: Text
- actionLog :: Text
- data AgentFinish = AgentFinish {}
- data AgentStep
- class Agent a where
- planNextAction :: BaseMemory m => a -> AgentState m -> IO (Either String AgentStep)
- agentPrompt :: a -> IO PromptTemplate
- agentTools :: a -> IO [AnyTool]
- data AnyTool = forall a.Tool a => AnyTool {
- anyTool :: a
- textToInput :: Text -> Input a
- outputToText :: Output a -> Text
- data BaseMemory m => AgentState m = AgentState {
- agentMemory :: m
- agentToolResults :: [(Text, Text)]
- agentSteps :: [AgentAction]
- data AgentExecutor a m = AgentExecutor {
- executor :: a
- executorMemory :: m
- maxIterations :: Int
- returnIntermediateSteps :: Bool
- runAgent :: (Agent a, BaseMemory m) => a -> AgentState m -> Text -> IO (Either String AgentFinish)
- runAgentLoop :: (Agent a, BaseMemory m) => a -> AgentState m -> Int -> Int -> IO (Either String AgentFinish)
- runAgentExecutor :: (Agent a, BaseMemory m) => AgentExecutor a m -> Text -> IO (Either String (Maybe AgentFinish))
- executeTool :: [AnyTool] -> Text -> Text -> IO (Either String Text)
- runSingleStep :: (Agent a, BaseMemory m) => a -> AgentState m -> IO (Either String AgentStep)
- customAnyTool :: Tool a => a -> (Text -> Input a) -> (Output a -> Text) -> AnyTool
Documentation
data AgentAction Source #
Represents an action to be taken by the agent
Constructors
AgentAction | |
Fields
|
Instances
Show AgentAction Source # | |
Defined in Langchain.Agents.Core Methods showsPrec :: Int -> AgentAction -> ShowS # show :: AgentAction -> String # showList :: [AgentAction] -> ShowS # | |
Eq AgentAction Source # | |
Defined in Langchain.Agents.Core |
data AgentFinish Source #
Represents that agent has finished work with final value
Constructors
AgentFinish | |
Instances
Show AgentFinish Source # | |
Defined in Langchain.Agents.Core Methods showsPrec :: Int -> AgentFinish -> ShowS # show :: AgentFinish -> String # showList :: [AgentFinish] -> ShowS # | |
Eq AgentFinish Source # | |
Defined in Langchain.Agents.Core |
Type that will be return from LLM Could be either Continue, making another call to LLM or Finish with final value
Constructors
Continue AgentAction | |
Finish AgentFinish |
Core agent class defining required operations
- Plan next action based on state
- Provide prompt template
- Expose available tools
Methods
planNextAction :: BaseMemory m => a -> AgentState m -> IO (Either String AgentStep) Source #
agentPrompt :: a -> IO PromptTemplate Source #
agentTools :: a -> IO [AnyTool] Source #
Instances
LLM llm => Agent (ReactAgent llm) Source # | |
Defined in Langchain.Agents.React Methods planNextAction :: BaseMemory m => ReactAgent llm -> AgentState m -> IO (Either String AgentStep) Source # agentPrompt :: ReactAgent llm -> IO PromptTemplate Source # agentTools :: ReactAgent llm -> IO [AnyTool] Source # |
Dynamic tool wrapper allowing heterogeneous tool collections Converts between Text and tool-specific input/output types.
Example usage:
calculatorTool :: AnyTool calculatorTool = customAnyTool Calculator (\t -> read (T.unpack t) :: (Int, Int)) (T.pack . show)
Constructors
forall a.Tool a => AnyTool | |
Fields
|
data BaseMemory m => AgentState m Source #
Type for maintaining state of the agent
Constructors
AgentState | |
Fields
|
Instances
(BaseMemory m, Show m) => Show (AgentState m) Source # | |
Defined in Langchain.Agents.Core Methods showsPrec :: Int -> AgentState m -> ShowS # show :: AgentState m -> String # showList :: [AgentState m] -> ShowS # | |
(BaseMemory m, Eq m) => Eq (AgentState m) Source # | |
Defined in Langchain.Agents.Core |
data AgentExecutor a m Source #
Agent execution engine
Constructors
AgentExecutor | |
Fields
|
Instances
runAgent :: (Agent a, BaseMemory m) => a -> AgentState m -> Text -> IO (Either String AgentFinish) Source #
Run the full agent execution loop Handles:
- Memory updates
- Action planning
- Tool execution
- Iteration control
Example flow:
- User input -> memory
- Plan action -> execute tool
- Store result -> memory
- Repeat until finish
Throws errors for:
- Tool not found [[5]]
- Execution errors
- Iteration limits
runAgentLoop :: (Agent a, BaseMemory m) => a -> AgentState m -> Int -> Int -> IO (Either String AgentFinish) Source #
Helper function for runAgent
runAgentExecutor :: (Agent a, BaseMemory m) => AgentExecutor a m -> Text -> IO (Either String (Maybe AgentFinish)) Source #
Similar to runAgent, but for AgentExecutor
executeTool :: [AnyTool] -> Text -> Text -> IO (Either String Text) Source #
Execute a single tool call Handles tool lookup and input/output conversion.
Example:
tools = [calculatorTool, wikipediaTool] executeTool tools "calculator" "(5, 3)" -- Returns Right "8"
runSingleStep :: (Agent a, BaseMemory m) => a -> AgentState m -> IO (Either String AgentStep) Source #
Alias for planNextAction