Safe Haskell | Safe-Inferred |
---|---|
Language | Haskell2010 |
IntelliMonad.Types
Contents
Documentation
Instances
FromJSON User Source # | |
Defined in IntelliMonad.Types | |
ToJSON User Source # | |
Generic User Source # | |
Show User Source # | |
Eq User Source # | |
Ord User Source # | |
PersistField User Source # | |
Defined in IntelliMonad.Types Methods toPersistValue :: User -> PersistValue # fromPersistValue :: PersistValue -> Either Text User # | |
PersistFieldSql User Source # | |
SymbolToField "user" Content User Source # | |
Defined in IntelliMonad.Types Methods | |
type Rep User Source # | |
Defined in IntelliMonad.Types type Rep User = D1 ('MetaData "User" "IntelliMonad.Types" "intelli-monad-0.1.0.0-6BpztJHho7HBDfRb11eSn6" 'False) ((C1 ('MetaCons "User" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "System" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "Assistant" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "Tool" 'PrefixI 'False) (U1 :: Type -> Type))) |
userToText :: User -> Text Source #
textToUser :: Text -> User Source #
Constructors
Message | |
Image | |
ToolCall | |
ToolReturn | |
Instances
data FinishReason Source #
Constructors
Stop | |
Length | |
ToolCalls | |
FunctionCall | |
ContentFilter | |
Null |
Instances
Show FinishReason Source # | |
Defined in IntelliMonad.Types Methods showsPrec :: Int -> FinishReason -> ShowS # show :: FinishReason -> String # showList :: [FinishReason] -> ShowS # | |
Eq FinishReason Source # | |
Defined in IntelliMonad.Types |
class ChatCompletion a where Source #
Methods
toRequest :: CreateChatCompletionRequest -> a -> CreateChatCompletionRequest Source #
fromResponse :: Text -> CreateChatCompletionResponse -> (a, FinishReason) Source #
Instances
ChatCompletion Contents Source # | |
Defined in IntelliMonad.Prompt Methods toRequest :: CreateChatCompletionRequest -> Contents -> CreateChatCompletionRequest Source # fromResponse :: Text -> CreateChatCompletionResponse -> (Contents, FinishReason) Source # |
class ChatCompletion a => Validate a b where Source #
Methods
tryConvert :: a -> Either a b Source #
toPV :: ToJSON a => a -> PersistValue Source #
Constructors
Content | |
Fields
|
Instances
Constructors
Context | |
Fields
|
Instances
class CustomInstruction a where Source #
Instances
CustomInstruction Math Source # | |
Defined in IntelliMonad.CustomInstructions |
data CustomInstructionProxy Source #
Constructors
forall t.CustomInstruction t => CustomInstructionProxy (Proxy t) |
Constructors
PromptEnv | |
Fields
|
type SessionName = Text Source #
Minimal complete definition
Methods
toolFunctionName :: Text Source #
default toolFunctionName :: HasFunctionObject a => Text Source #
toolSchema :: ChatCompletionTool Source #
default toolSchema :: (HasFunctionObject a, JSONSchema a, Generic a, GSchema a (Rep a)) => ChatCompletionTool Source #
Instances
Tool ValidateNumber Source # | |
Defined in IntelliMonad.CustomInstructions Associated Types data Output ValidateNumber Source # Methods toolFunctionName :: Text Source # toolSchema :: ChatCompletionTool Source # toolExec :: ValidateNumber -> IO (Output ValidateNumber) Source # | |
Tool Bash Source # | |
Defined in IntelliMonad.Tools.Bash | |
Tool DallE3 Source # | |
Defined in IntelliMonad.Tools.DallE3 | |
Tool TextToSpeech Source # | |
Defined in IntelliMonad.Tools.TextToSpeech Associated Types data Output TextToSpeech Source # Methods toolFunctionName :: Text Source # toolSchema :: ChatCompletionTool Source # toolExec :: TextToSpeech -> IO (Output TextToSpeech) Source # |
toChatCompletionTool :: forall a. (HasFunctionObject a, JSONSchema a) => ChatCompletionTool Source #
class HasFunctionObject r where Source #
Methods
getFunctionName :: String Source #
getFunctionDescription :: String Source #
getFieldDescription :: String -> String Source #
Instances
HasFunctionObject ValidateNumber Source # | |
Defined in IntelliMonad.CustomInstructions Methods getFunctionName :: String Source # getFunctionDescription :: String Source # getFieldDescription :: String -> String Source # | |
HasFunctionObject Bash Source # | |
Defined in IntelliMonad.Tools.Bash Methods getFunctionName :: String Source # getFunctionDescription :: String Source # getFieldDescription :: String -> String Source # | |
HasFunctionObject DallE3 Source # | |
Defined in IntelliMonad.Tools.DallE3 Methods getFunctionName :: String Source # getFunctionDescription :: String Source # getFieldDescription :: String -> String Source # | |
HasFunctionObject TextToSpeech Source # | |
Defined in IntelliMonad.Tools.TextToSpeech Methods getFunctionName :: String Source # getFunctionDescription :: String Source # getFieldDescription :: String -> String Source # |
class JSONSchema r where Source #
Minimal complete definition
Nothing
Methods
Instances
JSONSchema ValidateNumber Source # | |
Defined in IntelliMonad.CustomInstructions | |
JSONSchema Bash Source # | |
Defined in IntelliMonad.Tools.Bash | |
JSONSchema DallE3 Source # | |
Defined in IntelliMonad.Tools.DallE3 | |
JSONSchema TextToSpeech Source # | |
Defined in IntelliMonad.Tools.TextToSpeech | |
JSONSchema Text Source # | |
Defined in IntelliMonad.Types | |
JSONSchema String Source # | |
Defined in IntelliMonad.Types | |
JSONSchema Integer Source # | |
Defined in IntelliMonad.Types | |
JSONSchema () Source # | |
Defined in IntelliMonad.Types | |
JSONSchema Bool Source # | |
Defined in IntelliMonad.Types | |
JSONSchema Double Source # | |
Defined in IntelliMonad.Types | |
JSONSchema a => JSONSchema (Maybe a) Source # | |
Defined in IntelliMonad.Types | |
JSONSchema a => JSONSchema [a] Source # | |
Defined in IntelliMonad.Types |
class GSchema s f where Source #
Instances
(HasFunctionObject s, JSONSchema c) => GSchema s (U1 :: Type -> Type) Source # | |
(HasFunctionObject s, GSchema s a, GSchema s b) => GSchema s (a :*: b) Source # | |
(HasFunctionObject s, GSchema s a, GSchema s b) => GSchema s (a :+: b) Source # | |
(HasFunctionObject s, JSONSchema c) => GSchema s (K1 i c :: Type -> Type) Source # | |
(HasFunctionObject s, GSchema s f, Constructor c) => GSchema s (M1 C c f) Source # | Constructor Metadata |
(HasFunctionObject s, GSchema s f) => GSchema s (M1 D c f) Source # | Datatype |
(HasFunctionObject s, GSchema s f, Selector c) => GSchema s (M1 S c f) Source # | Selector Metadata |
toolAdd :: forall a. Tool a => CreateChatCompletionRequest -> CreateChatCompletionRequest Source #