monadLib-3.0.0: A collection of monad transformers.

MonadLib

Contents

Description

This library provides a collection of monad transformers that can be combined to produce various monads.

Synopsis

Types

The following types define the representations of the computation types supported by the library. Each type adds support for a different effect.

data Id a Source

Computations with no effects.

data ReaderT i m a Source

Add support for propagating a context.

Instances

MonadT (ReaderT i) 
Monad m => Monad (ReaderT i m) 
Monad m => Functor (ReaderT i m) 
MonadFix m => MonadFix (ReaderT i m) 
MonadPlus m => MonadPlus (ReaderT i m) 
ContM m => ContM (ReaderT i m) 
RunExceptionM m i => RunExceptionM (ReaderT j m) i 
RunStateM m j => RunStateM (ReaderT i m) j 
RunWriterM m j => RunWriterM (ReaderT i m) j 
Monad m => RunReaderM (ReaderT i m) i 
ExceptionM m j => ExceptionM (ReaderT i m) j 
StateM m j => StateM (ReaderT i m) j 
WriterM m j => WriterM (ReaderT i m) j 
Monad m => ReaderM (ReaderT i m) i 
BaseM m n => BaseM (ReaderT i m) n 

data WriterT i m a Source

Add support for collecting values.

Instances

Monoid i => MonadT (WriterT i) 
(Monad m, Monoid i) => Monad (WriterT i m) 
(Monad m, Monoid i) => Functor (WriterT i m) 
(MonadFix m, Monoid i) => MonadFix (WriterT i m) 
(MonadPlus m, Monoid i) => MonadPlus (WriterT i m) 
(ContM m, Monoid i) => ContM (WriterT i m) 
(RunExceptionM m i, Monoid j) => RunExceptionM (WriterT j m) i 
(RunStateM m j, Monoid i) => RunStateM (WriterT i m) j 
(Monad m, Monoid i) => RunWriterM (WriterT i m) i 
(RunReaderM m j, Monoid i) => RunReaderM (WriterT i m) j 
(ExceptionM m j, Monoid i) => ExceptionM (WriterT i m) j 
(StateM m j, Monoid i) => StateM (WriterT i m) j 
(Monad m, Monoid i) => WriterM (WriterT i m) i 
(ReaderM m j, Monoid i) => ReaderM (WriterT i m) j 
(BaseM m n, Monoid i) => BaseM (WriterT i m) n 

data StateT i m a Source

Add support for threading state.

Instances

MonadT (StateT i) 
Monad m => Monad (StateT i m) 
Monad m => Functor (StateT i m) 
MonadFix m => MonadFix (StateT i m) 
MonadPlus m => MonadPlus (StateT i m) 
ContM m => ContM (StateT i m) 
RunExceptionM m i => RunExceptionM (StateT j m) i 
Monad m => RunStateM (StateT i m) i 
RunWriterM m j => RunWriterM (StateT i m) j 
RunReaderM m j => RunReaderM (StateT i m) j 
ExceptionM m j => ExceptionM (StateT i m) j 
Monad m => StateM (StateT i m) i 
WriterM m j => WriterM (StateT i m) j 
ReaderM m j => ReaderM (StateT i m) j 
BaseM m n => BaseM (StateT i m) n 

data ExceptionT i m a Source

Add support for exceptions.

Instances

MonadT (ExceptionT i) 
Monad m => Monad (ExceptionT i m) 
Monad m => Functor (ExceptionT i m) 
MonadFix m => MonadFix (ExceptionT i m) 
MonadPlus m => MonadPlus (ExceptionT i m) 
ContM m => ContM (ExceptionT i m) 
Monad m => RunExceptionM (ExceptionT i m) i 
RunStateM m j => RunStateM (ExceptionT i m) j 
RunWriterM m j => RunWriterM (ExceptionT i m) j 
RunReaderM m j => RunReaderM (ExceptionT i m) j 
Monad m => ExceptionM (ExceptionT i m) i 
StateM m j => StateM (ExceptionT i m) j 
WriterM m j => WriterM (ExceptionT i m) j 
ReaderM m j => ReaderM (ExceptionT i m) j 
BaseM m n => BaseM (ExceptionT i m) n 

data ContT i m a Source

Add support for jumps.

Instances

MonadT (ContT i) 
Monad m => Monad (ContT i m) 
Monad m => Functor (ContT i m) 
Monad m => ContM (ContT i m) 
ExceptionM m j => ExceptionM (ContT i m) j 
StateM m j => StateM (ContT i m) j 
WriterM m j => WriterM (ContT i m) j 
ReaderM m j => ReaderM (ContT i m) j 
BaseM m n => BaseM (ContT i m) n 

Lifting

The following operations allow us to promote computations in the underlying monad to computations that support an extra effect. Computations defined in this way do not make use of the new effect but can be combined with other operations that utilize the effect.

class MonadT t whereSource

Methods

lift :: Monad m => m a -> t m aSource

Promote a computation from the underlying monad.

Instances

class (Monad m, Monad n) => BaseM m n | m -> n whereSource

Methods

inBase :: n a -> m aSource

Promote a computation from the base monad.

Instances

BaseM [] [] 
BaseM IO IO 
BaseM Maybe Maybe 
BaseM Id Id 
BaseM (Cont i) (Cont i) 
BaseM (Exception i) (Exception i) 
BaseM (State i) (State i) 
Monoid i => BaseM (Writer i) (Writer i) 
BaseM (Reader i) (Reader i) 
BaseM m n => BaseM (ContT i m) n 
BaseM m n => BaseM (ExceptionT i m) n 
BaseM m n => BaseM (StateT i m) n 
(BaseM m n, Monoid i) => BaseM (WriterT i m) n 
BaseM m n => BaseM (ReaderT i m) n 

Effect Classes

The following classes define overloaded operations that can be used to define effectful computations.

class Monad m => ReaderM m i | m -> i whereSource

Classifies monads that provide access to a context of type i.

Methods

ask :: m iSource

Get the context.

Instances

ReaderM (Reader i) i 
ReaderM m j => ReaderM (ContT i m) j 
ReaderM m j => ReaderM (ExceptionT i m) j 
ReaderM m j => ReaderM (StateT i m) j 
(ReaderM m j, Monoid i) => ReaderM (WriterT i m) j 
Monad m => ReaderM (ReaderT i m) i 

class Monad m => WriterM m i | m -> i whereSource

Classifies monads that can collect values of type i.

Methods

put :: i -> m ()Source

Add a value to the collection.

Instances

Monoid i => WriterM (Writer i) i 
WriterM m j => WriterM (ContT i m) j 
WriterM m j => WriterM (ExceptionT i m) j 
WriterM m j => WriterM (StateT i m) j 
(Monad m, Monoid i) => WriterM (WriterT i m) i 
WriterM m j => WriterM (ReaderT i m) j 

class Monad m => StateM m i | m -> i whereSource

Classifies monads that propagate a state component of type i.

Methods

get :: m iSource

Get the state.

set :: i -> m ()Source

Set the state.

Instances

StateM (State i) i 
StateM m j => StateM (ContT i m) j 
StateM m j => StateM (ExceptionT i m) j 
Monad m => StateM (StateT i m) i 
(StateM m j, Monoid i) => StateM (WriterT i m) j 
StateM m j => StateM (ReaderT i m) j 

class Monad m => ExceptionM m i | m -> i whereSource

Classifies monads that support raising exceptions of type i.

Methods

raise :: i -> m aSource

Raise an exception.

Instances

ExceptionM (Exception i) i 
ExceptionM m j => ExceptionM (ContT i m) j 
Monad m => ExceptionM (ExceptionT i m) i 
ExceptionM m j => ExceptionM (StateT i m) j 
(ExceptionM m j, Monoid i) => ExceptionM (WriterT i m) j 
ExceptionM m j => ExceptionM (ReaderT i m) j 

class Monad m => ContM m whereSource

Classifies monads that provide access to a computation's continuation.

Methods

callCC :: ((a -> m b) -> m a) -> m aSource

Capture the current continuation.

Instances

ContM (Cont i) 
Monad m => ContM (ContT i m) 
ContM m => ContM (ExceptionT i m) 
ContM m => ContM (StateT i m) 
(ContM m, Monoid i) => ContM (WriterT i m) 
ContM m => ContM (ReaderT i m) 

data Label m a Source

An explicit representation for continuations that store a value.

labelCC :: ContM m => a -> m (a, Label m a)Source

Capture the current continuation. This function is like return, except that it also captures the current continuation. Later we can use jump to go back to the continuation with a possibly different value.

jump :: ContM m => a -> Label m a -> m bSource

Change the value passed to a previously captured continuation.

Execution

Eliminating Effects

The following functions eliminate the outermost effect of a computation by translating a computation into an equivalent computation in the underlying monad. (The exception is Id which is not a monad transformer but an ordinary monad, and so, its run operation simply eliminates the monad.)

runId :: Id a -> aSource

Get the result of a pure computation.

runReaderT :: i -> ReaderT i m a -> m aSource

Execute a reader computation in the given context.

runWriterT :: WriterT i m a -> m (a, i)Source

Execute a writer computation. Returns the result and the collected output.

runStateT :: i -> StateT i m a -> m (a, i)Source

Execute a stateful computation in the given initial state. The second component of the result is the final state.

runExceptionT :: ExceptionT i m a -> m (Either i a)Source

Execute a computation with exceptions. Successful results are tagged with Right, exceptional results are tagged with Left.

runContT :: (a -> m i) -> ContT i m a -> m iSource

Execute a computation with the given continuation.

Nested Execution

The following classes define operations that are overloaded versions of the run operations. Unlike the run operations, functions do not change the type of the computation (i.e, they do not remove a layer). However, they do not perform any side-effects in the corresponding layer. Instead, they execute a computation in a ``separate thread'' with respect to the corresponding effect.

class ReaderM m i => RunReaderM m i | m -> i whereSource

Classifies monads that support changing the context for a sub-computation.

Methods

local :: i -> m a -> m aSource

Change the context for the duration of a computation.

Instances

RunReaderM (Reader i) i 
RunReaderM m j => RunReaderM (ExceptionT i m) j 
RunReaderM m j => RunReaderM (StateT i m) j 
(RunReaderM m j, Monoid i) => RunReaderM (WriterT i m) j 
Monad m => RunReaderM (ReaderT i m) i 

class WriterM m i => RunWriterM m i | m -> i whereSource

Classifies monads that support collecting the output of a sub-computation.

Methods

collect :: m a -> m (a, i)Source

Collect the output from a computation.

Instances

Monoid i => RunWriterM (Writer i) i 
RunWriterM m j => RunWriterM (ExceptionT i m) j 
RunWriterM m j => RunWriterM (StateT i m) j 
(Monad m, Monoid i) => RunWriterM (WriterT i m) i 
RunWriterM m j => RunWriterM (ReaderT i m) j 

class StateM m i => RunStateM m i | m -> i whereSource

Classifies monads that support separate state threads.

Methods

runS :: i -> m a -> m (a, i)Source

Modify the state for the duration of a computation. Returns the final state.

Instances

RunStateM (State i) i 
RunStateM m j => RunStateM (ExceptionT i m) j 
Monad m => RunStateM (StateT i m) i 
(RunStateM m j, Monoid i) => RunStateM (WriterT i m) j 
RunStateM m j => RunStateM (ReaderT i m) j 

class ExceptionM m i => RunExceptionM m i | m -> i whereSource

Classifies monads that support handling of exceptions.

Methods

try :: m a -> m (Either i a)Source

Exceptions are explicit in the result.

Miscellaneous

version :: (Int, Int, Int)Source

The current version of the library.