marvin-0.0.9: A modular chat bot

Safe HaskellNone
LanguageHaskell2010

Marvin.Internal

Contents

Synopsis

Exposed API

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

Define a new script for marvin

You need to provide a ScriptId (which can simple be written as a non-empty string). 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.

Reacting

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

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.

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.

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.

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)

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.

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

Get the user whihc was part of the triggered action.

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

Get the results from matching the regular expression.

Equivalent to "msg.match" in hubot.

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

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

Get the stored channel in which something happened.

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

Get the the new topic.

getBotName :: HasConfigAccess m => m Text Source #

Get the configured name of the bot.

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

Get the human readable name of a channel.

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

Get the username of a registered user.

Interacting 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.

Access config (advanced, internal)

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

INTERNAL, USE WITH CARE

Get a value from the bot config (should be "bot" subconfig)

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

INTERNAL, USE WITH CARE

Get a value from the bot config (should be "bot" subconfig)

getConfig :: HasConfigAccess m => m Config Source #

Get the config part for the currect script

getConfigInternal :: HasConfigAccess m => m Config Source #

INTERNAL USE WITH CARE

Obtain the entire config structure

Types

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.

Internals

Values

Functions

Types

data BotActionState a d Source #

Read only data available to a handler when the bot reacts to an event.

Constructors

BotActionState ScriptId Config a d 

newtype 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 message handlers like hear and respond this would be a regex Match and a Message for instance.

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.

Constructors

BotReacting 

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 ()) #

AccessAdapter (BotReacting a b) Source # 

Associated Types

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

IsScript (BotReacting a b) Source # 
HasConfigAccess (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

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.

Constructors

Script (Handlers a) ScriptId Config a 

newtype ScriptDefinition a r Source #

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

Constructors

ScriptDefinition 

Fields

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 () #

AccessAdapter (ScriptDefinition a) Source # 

Associated Types

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

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

newtype ScriptInit a Source #

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

Constructors

ScriptInit (ScriptId, a -> Config -> RunnerM (Script a)) 

newtype ScriptId Source #

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

Constructors

ScriptId 

Fields

data Handlers a Source #

Instances

Monoid (Handlers a) Source # 

Methods

mempty :: Handlers a #

mappend :: Handlers a -> Handlers a -> Handlers a #

mconcat :: [Handlers a] -> Handlers a #

HasTopicChange (Handlers a0) (Vector ((User' a0, Channel' a0, Topic, TimeStamp) -> RunnerM ())) Source # 
HasResponds (Handlers a0) (Vector (Regex, (User' a0, Channel' a0, Match, Message, TimeStamp) -> RunnerM ())) Source # 
HasLeaves (Handlers a0) (Vector ((User' a0, Channel' a0, TimeStamp) -> RunnerM ())) Source # 

Methods

leaves :: Lens' (Handlers a0) (Vector ((User' a0, Channel' a0, TimeStamp) -> RunnerM ())) Source #

HasJoins (Handlers a0) (Vector ((User' a0, Channel' a0, TimeStamp) -> RunnerM ())) Source # 

Methods

joins :: Lens' (Handlers a0) (Vector ((User' a0, Channel' a0, TimeStamp) -> RunnerM ())) Source #

HasHears (Handlers a0) (Vector (Regex, (User' a0, Channel' a0, Match, Message, TimeStamp) -> RunnerM ())) Source # 
HasCustoms (Handlers a0) (Vector (Event a0 -> Maybe (RunnerM ()))) Source # 

Methods

customs :: Lens' (Handlers a0) (Vector (Event a0 -> Maybe (RunnerM ()))) Source #

HasActions (Script a0) (Handlers a0) Source # 

Methods

actions :: Lens' (Script a0) (Handlers a0) Source #

HasTopicChangeIn (Handlers a0) (HashMap Text (Vector ((User' a0, Channel' a0, Topic, TimeStamp) -> RunnerM ()))) Source # 
HasLeavesFrom (Handlers a0) (HashMap Text (Vector ((User' a0, Channel' a0, TimeStamp) -> RunnerM ()))) Source # 
HasJoinsIn (Handlers a0) (HashMap Text (Vector ((User' a0, Channel' a0, TimeStamp) -> RunnerM ()))) Source # 

Helper lenses

class HasActions s a | s -> a where Source #

Minimal complete definition

actions

Methods

actions :: Lens' s a Source #

Instances

class HasHears s a | s -> a where Source #

Minimal complete definition

hears

Methods

hears :: Lens' s a Source #

class HasResponds s a | s -> a where Source #

Minimal complete definition

responds

Methods

responds :: Lens' s a Source #

class HasJoins s a | s -> a where Source #

Minimal complete definition

joins

Methods

joins :: Lens' s a Source #

Instances

HasJoins (Handlers a0) (Vector ((User' a0, Channel' a0, TimeStamp) -> RunnerM ())) Source # 

Methods

joins :: Lens' (Handlers a0) (Vector ((User' a0, Channel' a0, TimeStamp) -> RunnerM ())) Source #

class HasCustoms s a | s -> a where Source #

Minimal complete definition

customs

Methods

customs :: Lens' s a Source #

Instances

HasCustoms (Handlers a0) (Vector (Event a0 -> Maybe (RunnerM ()))) Source # 

Methods

customs :: Lens' (Handlers a0) (Vector (Event a0 -> Maybe (RunnerM ()))) Source #

class HasJoinsIn s a | s -> a where Source #

Minimal complete definition

joinsIn

Methods

joinsIn :: Lens' s a Source #

Instances

class HasLeaves s a | s -> a where Source #

Minimal complete definition

leaves

Methods

leaves :: Lens' s a Source #

Instances

HasLeaves (Handlers a0) (Vector ((User' a0, Channel' a0, TimeStamp) -> RunnerM ())) Source # 

Methods

leaves :: Lens' (Handlers a0) (Vector ((User' a0, Channel' a0, TimeStamp) -> RunnerM ())) Source #

class HasLeavesFrom s a | s -> a where Source #

Minimal complete definition

leavesFrom

Methods

leavesFrom :: Lens' s a Source #

class HasTopicChange s a | s -> a where Source #

Minimal complete definition

topicChange

Methods

topicChange :: Lens' s a Source #

class HasTopicChangeIn s a | s -> a where Source #

Minimal complete definition

topicChangeIn

Methods

topicChangeIn :: Lens' s a Source #

HelperClasses

class AccessAdapter m where Source #

Minimal complete definition

getAdapter

Associated Types

type AdapterT m Source #

Methods

getAdapter :: m (AdapterT m) Source #

Instances

AccessAdapter (AdapterM a) Source # 

Associated Types

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

AccessAdapter (ScriptDefinition a) Source # 

Associated Types

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

AccessAdapter (BotReacting a b) Source # 

Associated Types

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

class Get a b where Source #

Class which says that there is a way to get to a Message from this type m.

Minimal complete definition

getLens

Methods

getLens :: Lens' a b Source #

Instances

Get (a, b, TimeStamp) TimeStamp Source # 
Get (a, Channel' b, c) (Channel' b) Source # 

Methods

getLens :: Lens' (a, Channel' b, c) (Channel' b) Source #

Get (User' a, b, c) (User' a) Source # 

Methods

getLens :: Lens' (User' a, b, c) (User' a) Source #

Get (a, b, Topic, d) Topic Source # 

Methods

getLens :: Lens' (a, b, Topic, d) Topic Source #

Get (a, b, c, TimeStamp) TimeStamp Source # 

Methods

getLens :: Lens' (a, b, c, TimeStamp) TimeStamp Source #

Get (a, Channel' b, c, d) (Channel' b) Source # 

Methods

getLens :: Lens' (a, Channel' b, c, d) (Channel' b) Source #

Get (User' a, b, c, d) (User' a) Source # 

Methods

getLens :: Lens' (User' a, b, c, d) (User' a) Source #

Get (a, b, c, Message, e) Message Source # 

Methods

getLens :: Lens' (a, b, c, Message, e) Message Source #

Get (a, b, Match, d, e) Match Source # 

Methods

getLens :: Lens' (a, b, Match, d, e) Match Source #

Get (a, b, c, d, TimeStamp) TimeStamp Source # 

Methods

getLens :: Lens' (a, b, c, d, TimeStamp) TimeStamp Source #

Get (a, Channel' b, c, d, e) (Channel' b) Source # 

Methods

getLens :: Lens' (a, Channel' b, c, d, e) (Channel' b) Source #

Get (User' a, b, c, d, e) (User' a) Source # 

Methods

getLens :: Lens' (User' a, b, c, d, e) (User' a) Source #