typechain-0.2.0.0: An implementation of LangChain in Haskell
Safe HaskellSafe-Inferred
LanguageHaskell2010

TypeChain.ChatModels.Types

Synopsis

Documentation

type TypeChain model = StateT model IO Source #

data Role Source #

Way of distinguising who said what in a conversation

Constructors

User 
Assistant 
System 

Instances

Instances details
FromJSON Role Source # 
Instance details

Defined in TypeChain.ChatModels.Types

ToJSON Role Source # 
Instance details

Defined in TypeChain.ChatModels.Types

Show Role Source # 
Instance details

Defined in TypeChain.ChatModels.Types

Methods

showsPrec :: Int -> Role -> ShowS #

show :: Role -> String #

showList :: [Role] -> ShowS #

data Message Source #

A message with a role and content (lenses role and content)

Constructors

Message 

Fields

Instances

Instances details
FromJSON Message Source # 
Instance details

Defined in TypeChain.ChatModels.Types

ToJSON Message Source # 
Instance details

Defined in TypeChain.ChatModels.Types

Generic Message Source # 
Instance details

Defined in TypeChain.ChatModels.Types

Associated Types

type Rep Message :: Type -> Type #

Methods

from :: Message -> Rep Message x #

to :: Rep Message x -> Message #

Show Message Source # 
Instance details

Defined in TypeChain.ChatModels.Types

MsgList Message Source # 
Instance details

Defined in TypeChain.ChatModels.Types

MsgList [Message] Source # 
Instance details

Defined in TypeChain.ChatModels.Types

Methods

toMsgList :: [Message] -> [Message] Source #

type Rep Message Source # 
Instance details

Defined in TypeChain.ChatModels.Types

type Rep Message = D1 ('MetaData "Message" "TypeChain.ChatModels.Types" "typechain-0.2.0.0-LA4O1qfC7CvCuiVwSS7NO6" 'False) (C1 ('MetaCons "Message" 'PrefixI 'True) (S1 ('MetaSel ('Just "_role") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Role) :*: S1 ('MetaSel ('Just "_content") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 String)))

pattern UserMessage :: String -> Message Source #

Pattern synonym for creating a Message with User role

pattern AssistantMessage :: String -> Message Source #

Pattern synonym for creating a Message with Assistant role

pattern SystemMessage :: String -> Message Source #

Pattern synonym for creating a Message with System role

class MsgList a where Source #

Helper typeclass to allow for multiple types to be passed to the ChatModel functions.

NOTE: If this is used with the OverloadedStrings extension, you will need type annotations when using the String instance.

Methods

toMsgList :: a -> [Message] Source #

Convert to a list of messages

Instances

Instances details
MsgList Message Source # 
Instance details

Defined in TypeChain.ChatModels.Types

MsgList String Source # 
Instance details

Defined in TypeChain.ChatModels.Types

MsgList [Message] Source # 
Instance details

Defined in TypeChain.ChatModels.Types

Methods

toMsgList :: [Message] -> [Message] Source #

class ChatModel a where Source #

A class for Chat Models In order to achieve compatibility with as many different kinds of LLMS as possible, the predict function is constrained to MonadIO so that it has the capability to either make an API call, run a local model, or any other action that may require IO.

Computations with a ChatModel are expected to be run in a StateT monad (see TypeChain and TypeChainT for specific types) so that the model can be updated with new messages and the output messages can be logged.

Functions that operate in a context where multiple models are available (e.g. predicts and addMsgsTo) use lenses to allow extraction and modification of the model without knowing the specific state type.

Exmaple: If working with two models, you can use (model1, model2) as the state type and pass the _1 and _2 lenses to predicts and addMsgsTo to specify which model to use in the function.

Minimal complete definition

predicts

Methods

predict :: (MonadIO m, MonadThrow m, MsgList msg) => msg -> TypeChainT a m [Message] Source #

Predict for current and only model This function should prompt the model (either via API or locally), and return the response.

NOTE: If a model has the capability to remember previous messages, it should implement RememberingChatModel and automatically manage this functionality in the predict function.

predicts :: (MonadIO m, MonadThrow m, MsgList msg) => Lens' s a -> msg -> TypeChainT s m [Message] Source #

Predict for a specific model via lens This function should prompt the model (either via API or locally), log the input messages, log the output messages, and return the output messages.

NOTE: If a model has the capability to remember previous messages, it should implement RememberingChatModel and automatically manage this functionality in the predicts function.

Instances

Instances details
ChatModel OpenAIChat Source # 
Instance details

Defined in TypeChain.ChatModels.OpenAI

Methods

predict :: forall (m :: Type -> Type) msg. (MonadIO m, MonadThrow m, MsgList msg) => msg -> TypeChainT OpenAIChat m [Message] Source #

predicts :: forall (m :: Type -> Type) msg s. (MonadIO m, MonadThrow m, MsgList msg) => Lens' s OpenAIChat -> msg -> TypeChainT s m [Message] Source #

class ChatModel a => RememberingChatModel a where Source #

Minimal complete definition

setMemoryEnabledFor, forgetFor, memorizes, rememberFor

Methods

setMemoryEnabled :: Monad m => Bool -> TypeChainT a m () Source #

Enable/Disable memory for current and only model

setMemoryEnabledFor :: Monad m => Lens' s a -> Bool -> TypeChainT s m () Source #

Enable/Disable memory for specific model

forget :: Monad m => TypeChainT a m () Source #

Remove all remembered messages for the current and only model. This does not affect a model's ability to remember future messages.

forgetFor :: Monad m => Lens' s a -> TypeChainT s m () Source #

Remove all remebered messages for a specific model. This does not affect a model's ability to remember future messages.

memorize :: Monad m => [Message] -> TypeChainT a m () Source #

Remember a list of messages for the current and only model. This does not affect a model's ability to remember future messages and should respect the current memory setting.

memorizes :: Monad m => Lens' s a -> [Message] -> TypeChainT s m () Source #

Remember a list of messages for a specific model. This does not affect a model's ability to remember future messages and should respect the current memory setting.

remember :: Monad m => TypeChainT a m [Message] Source #

Retrieve all remembered messages for the current and only model. This does not forget any messages nor affect a model's ability to remember future messages.

rememberFor :: Monad m => Lens' s a -> TypeChainT s m [Message] Source #

Retrieve all remembered messages for a specific model. This does not forget any messages nor affect a model's ability to remember future messages.

Instances

Instances details
RememberingChatModel OpenAIChat Source # 
Instance details

Defined in TypeChain.ChatModels.OpenAI

Methods

setMemoryEnabled :: forall (m :: Type -> Type). Monad m => Bool -> TypeChainT OpenAIChat m () Source #

setMemoryEnabledFor :: forall (m :: Type -> Type) s. Monad m => Lens' s OpenAIChat -> Bool -> TypeChainT s m () Source #

forget :: forall (m :: Type -> Type). Monad m => TypeChainT OpenAIChat m () Source #

forgetFor :: forall (m :: Type -> Type) s. Monad m => Lens' s OpenAIChat -> TypeChainT s m () Source #

memorize :: forall (m :: Type -> Type). Monad m => [Message] -> TypeChainT OpenAIChat m () Source #

memorizes :: forall (m :: Type -> Type) s. Monad m => Lens' s OpenAIChat -> [Message] -> TypeChainT s m () Source #

remember :: forall (m :: Type -> Type). Monad m => TypeChainT OpenAIChat m [Message] Source #

rememberFor :: forall (m :: Type -> Type) s. Monad m => Lens' s OpenAIChat -> TypeChainT s m [Message] Source #