monad-task-0.1.0: A monad transformer that turns event processing into co-routine programming.

Safe HaskellSafe-Infered

Control.Monad.Task

Contents

Description

Task monad transformer can help refactor event and callback heavy programs into monads via co-routines. The idea is loosely based on Combining Events And Threads For Scalable Network Services, by Peng Li and Steve Zdancewic, in PLDI, 2007. (http://www.cis.upenn.edu/~stevez/papers/abstracts.html#LZ07), but with deterministic and co-oprative lightweight threads, also known as co-routines, so that the base monad can be anything ranging from IO to state monads, or your favorite monad transformer stack.

Besides, Task monad transformer also provides a simple mechanism to signal and watch for events, which allows complex event processing logic to be expressed as streamlined monadic co-routines.

Task monad transformer is essentially a ContT, or continuation transformer, defined to extract the control flow of monadic programs with co-operative multi-threading. After the CPS transformation, the program trace is then executed with a simple round-robin scheduler.

Synopsis

MonadTask class

class Monad m => MonadTask e m | m -> e whereSource

MonadTask specifies a task monad m over an event type e.

Methods

yield :: m ()Source

yield temporarily suspends current task to let others run.

fork :: m a -> m ()Source

fork spawns a task and runs it immediate until it ends or suspends before returning to current task.

watch :: (e -> Maybe a) -> m aSource

watch suspends current task to wait for future events, and will resume execution when an event triggers its watching function.

signal :: e -> m ()Source

signal broadcasts an event to all other tasks that are watching, and give those who wake up the priority to run.

exit :: m ()Source

exit ends all tasks and return immediately.

Instances

(Monad m, MonadTask a m) => MonadTask a (MaybeT m) 
(Monad m, MonadTask a m) => MonadTask a (ListT m) 
(Monad m, MonadTask a m) => MonadTask a (IdentityT m) 
(Monoid w, Monad m, MonadTask a m) => MonadTask a (WriterT w m) 
(Monoid w, Monad m, MonadTask a m) => MonadTask a (WriterT w m) 
(Monad m, MonadTask a m) => MonadTask a (ReaderT r m) 
(Error e, Monad m, MonadTask a m) => MonadTask a (ErrorT e m) 
Monad m => MonadTask e (TaskT e m) 

TaskT monad transformer

newtype TaskT e m a Source

Task monad transformer.

Constructors

TaskT 

Fields

runTaskT :: ContT (Trace m e) m a
 

Instances

MonadReader s m => MonadReader s (TaskT e m) 
MonadState s m => MonadState s (TaskT e m) 
Monad m => MonadTask e (TaskT e m) 
MonadTrans (TaskT e) 
Monad m => Monad (TaskT e m) 
Functor (TaskT e m) 
Applicative (TaskT e m) 
MonadIO m => MonadIO (TaskT e m) 

Functions

runTask :: Monad m => TaskT e m a -> m ()Source

runTask runs a task monad until to its completion, i.e., no more active tasks to run, or until it exits.

orElse :: (e -> Maybe a) -> (e -> Maybe b) -> e -> Maybe (Either a b)Source

orElse is a helper function for combining two trigger functions disjuctively, favoring the first one.