marvin-0.2.2: A framework for modular, portable chat bots.

Copyright(c) Justus Adam 2016
LicenseBSD3
Maintainerdev@justus.science
Stabilityexperimental
PortabilityPOSIX
Safe HaskellNone
LanguageHaskell2010

Marvin

Contents

Description

For the proper, verbose documentation see https://marvin.readthedocs.org/en/latest/scripting.html.

Synopsis

The Script

data Script a Source #

An abstract type describing a marvin script.

This is basically a collection of event handlers.

Internal structure is exposed for people wanting to extend this.

Instances

defineScript :: ScriptId -> ScriptDefinition a () -> ScriptInit a Source #

Define a new script for marvin

You need to provide a ScriptId (which can be written as a non-empty string, needs the OverloadedStrings language extension). This id is used as the key for the section in the bot config belonging to this script and in logging output.

Roughly equivalent to "module.exports" in hubot.

data ScriptInit a Source #

Initializer for a script. This gets run by the server during startup and creates a Script

data ScriptId Source #

A type, basically a String, which identifies a script to the config and the logging facilities.

For conversion please use mkScriptId and unwrapScriptId. They will perform necessary checks.

data ScriptDefinition a r Source #

A monad for gradually defining a Script using respond and hear as well as any IO action.

Instances

MonadBase IO (ScriptDefinition a) Source # 

Methods

liftBase :: IO α -> ScriptDefinition a α #

Monad (ScriptDefinition a) Source # 
Functor (ScriptDefinition a) Source # 

Methods

fmap :: (a -> b) -> ScriptDefinition a a -> ScriptDefinition a b #

(<$) :: a -> ScriptDefinition a b -> ScriptDefinition a a #

Applicative (ScriptDefinition a) Source # 
MonadIO (ScriptDefinition a) Source # 

Methods

liftIO :: IO a -> ScriptDefinition a a #

MonadLogger (ScriptDefinition a) Source # 

Methods

monadLoggerLog :: ToLogStr msg => Loc -> LogSource -> LogLevel -> msg -> ScriptDefinition a () #

HasConfigAccess (ScriptDefinition a) Source # 
AccessAdapter (ScriptDefinition a) Source # 

Associated Types

type AdapterT (ScriptDefinition a :: * -> *) :: * Source #

IsScript (ScriptDefinition a) Source # 
type AdapterT (ScriptDefinition a) Source # 

class IsAdapter a Source #

Basic functionality required of any adapter

Associated Types

type User a Source #

Concrete, adapter specific representation of a user. Could be an id string or a full object for instance

type Channel a Source #

Concrete, adapter specific representation of a channel. Could be an id string or a full object for instance

Instances

IsAdapter IRCAdapter Source # 
IsAdapter ShellAdapter Source # 
MkTelegram a => IsAdapter (TelegramAdapter a) Source # 

Reacting

data BotReacting a d r Source #

Monad for reacting in the bot. Allows use of functions like send, reply and messageChannel as well as any arbitrary IO action using liftIO.

The type parameter d is the accessible data provided by the trigger for this action and can be obtained with getData or other custom functions like getMessage and getMatch which typically depend on a particular type of data in d.

For completeness: a is the adapter type and r is the return type of the monadic computation.

This is also a MonadReader instance, there you can inspect the entire state of this reaction. This is typically only used in internal or utility functions and not necessary for the user. To inspect particular pieces of this state refer to the *Lenses* section.

Instances

MonadBase IO (BotReacting a d) Source # 

Methods

liftBase :: IO α -> BotReacting a d α #

Monad (BotReacting a d) Source # 

Methods

(>>=) :: BotReacting a d a -> (a -> BotReacting a d b) -> BotReacting a d b #

(>>) :: BotReacting a d a -> BotReacting a d b -> BotReacting a d b #

return :: a -> BotReacting a d a #

fail :: String -> BotReacting a d a #

Functor (BotReacting a d) Source # 

Methods

fmap :: (a -> b) -> BotReacting a d a -> BotReacting a d b #

(<$) :: a -> BotReacting a d b -> BotReacting a d a #

Applicative (BotReacting a d) Source # 

Methods

pure :: a -> BotReacting a d a #

(<*>) :: BotReacting a d (a -> b) -> BotReacting a d a -> BotReacting a d b #

(*>) :: BotReacting a d a -> BotReacting a d b -> BotReacting a d b #

(<*) :: BotReacting a d a -> BotReacting a d b -> BotReacting a d a #

MonadIO (BotReacting a d) Source # 

Methods

liftIO :: IO a -> BotReacting a d a #

MonadLogger (BotReacting a d) Source # 

Methods

monadLoggerLog :: ToLogStr msg => Loc -> LogSource -> LogLevel -> msg -> BotReacting a d () #

MonadLoggerIO (BotReacting a d) Source # 

Methods

askLoggerIO :: BotReacting a d (Loc -> LogSource -> LogLevel -> LogStr -> IO ()) #

HasConfigAccess (BotReacting a b) Source # 
AccessAdapter (BotReacting a b) Source # 

Associated Types

type AdapterT (BotReacting a b :: * -> *) :: * Source #

IsScript (BotReacting a b) Source # 
MonadReader (BotActionState a d) (BotReacting a d) Source # 

Methods

ask :: BotReacting a d (BotActionState a d) #

local :: (BotActionState a d -> BotActionState a d) -> BotReacting a d a -> BotReacting a d a #

reader :: (BotActionState a d -> a) -> BotReacting a d a #

type AdapterT (BotReacting a b) Source # 
type AdapterT (BotReacting a b) = a

Reaction Functions

hear :: Regex -> BotReacting a (User' a, Channel' a, Match, Message, TimeStamp) () -> ScriptDefinition a () Source #

Whenever any message matches the provided regex this handler gets run.

Equivalent to "robot.hear" in hubot

respond :: Regex -> BotReacting a (User' a, Channel' a, Match, Message, TimeStamp) () -> ScriptDefinition a () Source #

Runs the handler only if the bot was directly addressed.

Equivalent to "robot.respond" in hubot

enter :: BotReacting a (User' a, Channel' a, TimeStamp) () -> ScriptDefinition a () Source #

This handler runs whenever a user enters any channel (which the bot is subscribed to)

The payload contains the entering user and the channel which was entered.

exit :: BotReacting a (User' a, Channel' a, TimeStamp) () -> ScriptDefinition a () Source #

This handler runs whenever a user exits any channel (which the bot is subscribed to)

The payload contains the exiting user and the channel which was exited.

enterIn :: Text -> BotReacting a (User' a, Channel' a, TimeStamp) () -> ScriptDefinition a () Source #

This handler runs whenever a user enters the specified channel.

The argument is the human readable name for the channel.

The payload contains the entering user.

exitFrom :: Text -> BotReacting a (User' a, Channel' a, TimeStamp) () -> ScriptDefinition a () Source #

This handler runs whenever a user exits the specified channel, provided the bot is subscribed to the channel in question.

The argument is the human readable name for the channel.

The payload contains the exting user.

topic :: BotReacting a (User' a, Channel' a, Topic, TimeStamp) () -> ScriptDefinition a () Source #

This handler runs when the topic in any channel the bot is subscribed to changes.

The payload contains the new topic and the channel in which it was set.

topicIn :: Text -> BotReacting a (User' a, Channel' a, Topic, TimeStamp) () -> ScriptDefinition a () Source #

This handler runs when the topic in the specified channel is changed, provided the bot is subscribed to the channel in question.

The argument is the human readable channel name.

customTrigger :: (Event a -> Maybe d) -> BotReacting a d () -> ScriptDefinition a () Source #

Extension point for the user

Allows you to handle the raw event yourself. Returning Nothing from the trigger function means you dont want to react to the event. The value returned inside the Just is available in the handler later using getData.

Getting data

getData :: BotReacting a d d Source #

Obtain the event reaction data.

The type of this data depends on the reaction function used. For instance hear and respond will contain MessageReactionData. The actual contents comes from the event itself and was put together by the trigger.

getMessage :: Get m Message => BotReacting a m Message Source #

Get the message that triggered this action Includes sender, target channel, as well as the full, untruncated text of the original message

getMatch :: Get m Match => BotReacting a m Match Source #

Get the results from matching the regular expression.

Equivalent to "msg.match" in hubot.

getTopic :: Get m Topic => BotReacting a m Topic Source #

Get the the new topic.

getChannel :: forall a m. Get m (Channel' a) => BotReacting a m (Channel a) Source #

Get the stored channel in which something happened.

getUser :: forall m a. Get m (User' a) => BotReacting a m (User a) Source #

Get the user which was part of the triggered action.

getUsername :: (HasConfigAccess m, AccessAdapter m, IsAdapter a, MonadIO m, AdapterT m ~ a) => User a -> m Text Source #

Get the username of a registered user. The type signature is so large to allow this function to be used both in BotReacting and ScriptDefinition.

getChannelName :: (HasConfigAccess m, AccessAdapter m, IsAdapter a, MonadIO m, AdapterT m ~ a) => Channel a -> m Text Source #

Get the human readable name of a channel. The type signature is so large to allow this function to be used both in BotReacting and ScriptDefinition.

resolveUser :: (HasConfigAccess m, AccessAdapter m, IsAdapter a, MonadIO m, AdapterT m ~ a) => Text -> m (Maybe (User a)) Source #

Try to get the user with a particular username. The type signature is so large to allow this function to be used both in BotReacting and ScriptDefinition.

resolveChannel :: (HasConfigAccess m, AccessAdapter m, IsAdapter a, MonadIO m, AdapterT m ~ a) => Text -> m (Maybe (Channel a)) Source #

Try to get the channel with a particular human readable name. The type signature is so large to allow this function to be used both in BotReacting and ScriptDefinition.

Sending messages

send :: (IsAdapter a, Get d (Channel' a)) => Text -> BotReacting a d () Source #

Send a message to the channel the triggering message came from.

Equivalent to "robot.send" in hubot

reply :: (IsAdapter a, Get d (User' a), Get d (Channel' a)) => Text -> BotReacting a d () Source #

Send a message to the channel the original message came from and address the user that sent the original message.

Equivalent to "robot.reply" in hubot

messageChannel :: (HasConfigAccess m, AccessAdapter m, IsAdapter (AdapterT m), MonadLoggerIO m) => Text -> Text -> m () Source #

Send a message to a Channel (by name)

messageChannel' :: (HasConfigAccess m, AccessAdapter m, IsAdapter (AdapterT m), MonadIO m) => Channel (AdapterT m) -> Text -> m () Source #

Send a message to a channel (by adapter dependent channel object)

Interaction with the config

getConfigVal :: (Configured a, HasConfigAccess m) => Name -> m (Maybe a) Source #

Get a value out of the config, returns Nothing if the value didn't exist.

This config is the config for this script. Ergo all config vars registered under the config section for the ScriptId of this script.

The HasConfigAccess Constraint means this function can be used both during script definition and when a handler is run.

requireConfigVal :: (Configured a, HasConfigAccess m) => Name -> m a Source #

Get a value out of the config and fail with an error if the specified key is not found.

This config is the config for this script. Ergo all config vars registered under the config section for the ScriptId of this script.

The HasConfigAccess Constraint means this function can be used both during script definition and when a handler is run.

getBotName :: HasConfigAccess m => m Text Source #

Get the configured name of the bot.

Handler Types

type Message = Text Source #

The contents of a recieved message

type Topic = Text Source #

The topic in a channel

Advanced actions

extractAction :: BotReacting a () o -> ScriptDefinition a (IO o) Source #

Take an action and produce an IO action with the same effect. Useful for creating actions which can be scheduled to execute a certain time or asynchronous. The idea is that one can conveniently send messages from inside a schedulable action.

extractReaction :: BotReacting a s o -> BotReacting a s (IO o) Source #

Take a reaction and produce an IO action with the same effect. Useful for creating actions which can be scheduled to execute a certain time or asynchronous. The idea is that one can conveniently send messages from inside a schedulable action.