langchain-hs-0.0.1.0: Haskell implementation of Langchain
Copyright(c) 2025 Tushar Adhatrao
LicenseMIT
MaintainerTushar Adhatrao <tusharadhatrao@gmail.com>
Safe HaskellSafe-Inferred
LanguageHaskell2010

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

Documentation

data AgentAction Source #

Represents an action to be taken by the agent

Constructors

AgentAction 

Fields

Instances

Instances details
Show AgentAction Source # 
Instance details

Defined in Langchain.Agents.Core

Eq AgentAction Source # 
Instance details

Defined in Langchain.Agents.Core

data AgentFinish Source #

Represents that agent has finished work with final value

Constructors

AgentFinish 

Instances

Instances details
Show AgentFinish Source # 
Instance details

Defined in Langchain.Agents.Core

Eq AgentFinish Source # 
Instance details

Defined in Langchain.Agents.Core

data AgentStep Source #

Type that will be return from LLM Could be either Continue, making another call to LLM or Finish with final value

Instances

Instances details
Show AgentStep Source # 
Instance details

Defined in Langchain.Agents.Core

Eq AgentStep Source # 
Instance details

Defined in Langchain.Agents.Core

class Agent a where Source #

Core agent class defining required operations

  • Plan next action based on state
  • Provide prompt template
  • Expose available tools

Instances

Instances details
LLM llm => Agent (ReactAgent llm) Source # 
Instance details

Defined in Langchain.Agents.React

data 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

Instances details
(BaseMemory m, Show m) => Show (AgentState m) Source # 
Instance details

Defined in Langchain.Agents.Core

(BaseMemory m, Eq m) => Eq (AgentState m) Source # 
Instance details

Defined in Langchain.Agents.Core

Methods

(==) :: AgentState m -> AgentState m -> Bool #

(/=) :: AgentState m -> AgentState m -> Bool #

data AgentExecutor a m Source #

Agent execution engine

Constructors

AgentExecutor 

Fields

Instances

Instances details
(Show a, Show m) => Show (AgentExecutor a m) Source # 
Instance details

Defined in Langchain.Agents.Core

(Eq a, Eq m) => Eq (AgentExecutor a m) Source # 
Instance details

Defined in Langchain.Agents.Core

Methods

(==) :: AgentExecutor a m -> AgentExecutor a m -> Bool #

(/=) :: AgentExecutor a m -> AgentExecutor a m -> Bool #

(Agent a, BaseMemory m) => Runnable (AgentExecutor a m) Source #

Runnable instance for agent execution Allows integration with LangChain workflows.

Example:

response <- invoke myAgentExecutor "Solve 5+3"
case response of
  Right result -> print result
  Left err -> print err
Instance details

Defined in Langchain.Agents.Core

type RunnableInput (AgentExecutor a m) Source # 
Instance details

Defined in Langchain.Agents.Core

type RunnableOutput (AgentExecutor a m) Source # 
Instance details

Defined in Langchain.Agents.Core

runAgent :: (Agent a, BaseMemory m) => a -> AgentState m -> Text -> IO (Either String AgentFinish) Source #

Run the full agent execution loop Handles:

  1. Memory updates
  2. Action planning
  3. Tool execution
  4. Iteration control

Example flow:

  1. User input -> memory
  2. Plan action -> execute tool
  3. Store result -> memory
  4. 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

customAnyTool :: Tool a => a -> (Text -> Input a) -> (Output a -> Text) -> AnyTool Source #

Helper for creating custom tool wrappers Requires conversion functions between Text and tool-specific types.

Example:

weatherTool = customAnyTool
  WeatherAPI
  parseLocation
  formatWeatherResponse