| Safe Haskell | Safe-Inferred |
|---|---|
| Language | Haskell2010 |
TypeChain.ChatModels.Types
Synopsis
- type TypeChain model = StateT model IO
- type TypeChainT = StateT
- type ApiKey = ByteString
- data Role
- data Message = Message {}
- role :: Lens' Message Role
- content :: Lens' Message String
- pattern UserMessage :: String -> Message
- pattern AssistantMessage :: String -> Message
- pattern SystemMessage :: String -> Message
- class MsgList a where
- class ChatModel a where
- predict :: (MonadIO m, MonadThrow m, MsgList msg) => msg -> TypeChainT a m [Message]
- predicts :: (MonadIO m, MonadThrow m, MsgList msg) => Lens' s a -> msg -> TypeChainT s m [Message]
- class ChatModel a => RememberingChatModel a where
- setMemoryEnabled :: Monad m => Bool -> TypeChainT a m ()
- setMemoryEnabledFor :: Monad m => Lens' s a -> Bool -> TypeChainT s m ()
- forget :: Monad m => TypeChainT a m ()
- forgetFor :: Monad m => Lens' s a -> TypeChainT s m ()
- memorize :: Monad m => [Message] -> TypeChainT a m ()
- memorizes :: Monad m => Lens' s a -> [Message] -> TypeChainT s m ()
- remember :: Monad m => TypeChainT a m [Message]
- rememberFor :: Monad m => Lens' s a -> TypeChainT s m [Message]
- module Control.Monad.State
Documentation
type TypeChainT = StateT Source #
type ApiKey = ByteString Source #
Way of distinguising who said what in a conversation
A message with a role and content (lenses role and content)
Instances
| FromJSON Message Source # | |
Defined in TypeChain.ChatModels.Types | |
| ToJSON Message Source # | |
| Generic Message Source # | |
| Show Message Source # | |
| MsgList Message Source # | |
| MsgList [Message] Source # | |
| type Rep Message Source # | |
Defined in TypeChain.ChatModels.Types type Rep Message = D1 ('MetaData "Message" "TypeChain.ChatModels.Types" "typechain-0.1.1.0-6DHXijN1iHv4RlSV1kkYyg" '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.
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
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
| ChatModel OpenAIChat Source # | |
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
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
| RememberingChatModel OpenAIChat Source # | |
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 # | |
module Control.Monad.State