marvin-0.0.9: A modular chat bot

Safe HaskellNone
LanguageHaskell2010

Marvin.Internal.Types

Contents

Synopsis

Documentation

data Event a Source #

Representation for the types of events which can occur

Instances

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

Methods

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

newtype AdapterM a r Source #

Constructors

AdapterM 

Instances

MonadBaseControl IO (AdapterM a) Source # 

Associated Types

type StM (AdapterM a :: * -> *) a :: * #

Methods

liftBaseWith :: (RunInBase (AdapterM a) IO -> IO a) -> AdapterM a a #

restoreM :: StM (AdapterM a) a -> AdapterM a a #

MonadBase IO (AdapterM a) Source # 

Methods

liftBase :: IO α -> AdapterM a α #

Monad (AdapterM a) Source # 

Methods

(>>=) :: AdapterM a a -> (a -> AdapterM a b) -> AdapterM a b #

(>>) :: AdapterM a a -> AdapterM a b -> AdapterM a b #

return :: a -> AdapterM a a #

fail :: String -> AdapterM a a #

Functor (AdapterM a) Source # 

Methods

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

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

Applicative (AdapterM a) Source # 

Methods

pure :: a -> AdapterM a a #

(<*>) :: AdapterM a (a -> b) -> AdapterM a a -> AdapterM a b #

(*>) :: AdapterM a a -> AdapterM a b -> AdapterM a b #

(<*) :: AdapterM a a -> AdapterM a b -> AdapterM a a #

MonadIO (AdapterM a) Source # 

Methods

liftIO :: IO a -> AdapterM a a #

MonadLogger (AdapterM a) Source # 

Methods

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

MonadLoggerIO (AdapterM a) Source # 

Methods

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

AccessAdapter (AdapterM a) Source # 

Associated Types

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

type AdapterT (AdapterM a) Source # 
type AdapterT (AdapterM a) = a
type StM (AdapterM a) r Source # 
type StM (AdapterM a) r = r

type EventHandler a = Event a -> IO () Source #

class IsAdapter a where Source #

Basic functionality required of any adapter

Associated Types

type User a Source #

type Channel a Source #

Methods

adapterId :: AdapterId a Source #

Used for scoping config and logging

messageChannel :: Channel a -> Text -> AdapterM a () Source #

Post a message to a channel given the internal channel identifier

initAdapter :: RunnerM a Source #

Initialize the adapter state

runWithAdapter :: RunWithAdapter a Source #

Initialize and run the bot

getUsername :: User a -> AdapterM a Text Source #

Resolve a username given the internal user identifier

getChannelName :: Channel a -> AdapterM a Text Source #

Resolve the human readable name for a channel given the internal channel identifier

resolveChannel :: Text -> AdapterM a (Maybe (Channel a)) Source #

Resolve to the internal channel identifier given a human readable name

Instances

IsAdapter ShellAdapter Source # 
MkTelegram a => IsAdapter (TelegramAdapter a) Source # 
MkSlack a => IsAdapter (SlackAdapter a) Source # 

newtype User' a Source #

Constructors

User' 

Fields

Instances

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 # 
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 # 
Get (User' a, b, c) (User' a) Source # 

Methods

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

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

Methods

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

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

Methods

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

newtype Channel' a Source #

Constructors

Channel' 

Fields

Instances

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 # 
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 # 
Get (a, Channel' b, c) (Channel' b) Source # 

Methods

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

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

Methods

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

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

Methods

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

newtype TimeStamp Source #

Constructors

TimeStamp 

Instances

Show TimeStamp Source # 
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 # 
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 # 
Get (a, b, TimeStamp) TimeStamp Source # 
Get (a, b, c, TimeStamp) TimeStamp Source # 

Methods

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

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

Methods

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

newtype ScriptId Source #

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

Constructors

ScriptId 

Fields

newtype AdapterId a Source #

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

Constructors

AdapterId 

Instances

verifyIdString :: String -> (String -> a) -> String -> a Source #

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

Minimal complete definition

scriptId

Methods

scriptId :: Lens' s a Source #

class (IsScript m, MonadIO m) => HasConfigAccess m where Source #

Denotes a place from which we may access the configuration.

During script definition or when handling a request we can obtain the config with getConfigVal or requireConfigVal.

Minimal complete definition

getConfigInternal

Methods

getConfigInternal :: m Config Source #

INTERNAL USE WITH CARE

Obtain the entire config structure

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 #

Orphan instances