monadLib-3.7.3: A collection of monad transformers.

Safe HaskellTrustworthy
LanguageHaskell98

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 Lift a Source

Computation with no effects (strict).

data IdT m a Source

Adds no new features. Useful as a placeholder.

Instances

MonadT IdT 
MonadPlus m => Alternative (IdT m) 
Monad m => Monad (IdT m) 
Monad m => Functor (IdT m) 
MonadFix m => MonadFix (IdT m) 
MonadPlus m => MonadPlus (IdT m) 
Monad m => Applicative (IdT m) 
ContM m => ContM (IdT m) 
AbortM m i => AbortM (IdT m) i 
RunExceptionM m i => RunExceptionM (IdT m) i 
RunWriterM m j => RunWriterM (IdT m) j 
RunReaderM m j => RunReaderM (IdT m) j 
ExceptionM m j => ExceptionM (IdT m) j 
StateM m j => StateM (IdT m) j 
WriterM m j => WriterM (IdT m) j 
ReaderM m j => ReaderM (IdT m) j 
BaseM m n => BaseM (IdT m) n 
RunM m a r => RunM (IdT m) a r 

data ReaderT i m a Source

Add support for propagating a context of type i.

Instances

MonadT (ReaderT i) 
MonadPlus m => Alternative (ReaderT i m) 
Monad m => Monad (ReaderT i m) 
Monad m => Functor (ReaderT i m) 
MonadFix m => MonadFix (ReaderT i m) 
MonadPlus m => MonadPlus (ReaderT i m) 
Monad m => Applicative (ReaderT i m) 
ContM m => ContM (ReaderT i m) 
AbortM m i => AbortM (ReaderT j m) i 
RunExceptionM m i => RunExceptionM (ReaderT j m) i 
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 
RunM m a r => RunM (ReaderT i m) a (i -> r) 

data WriterT i m a Source

Add support for collecting values of type i. The type i should be a monoid, whose unit is used to represent a lack of a value, and whose binary operation is used to combine multiple values. This transformer is strict in its output component.

Instances

Monoid i => MonadT (WriterT i) 
(MonadPlus m, Monoid i) => Alternative (WriterT i m) 
(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) 
(Monad m, Monoid i) => Applicative (WriterT i m) 
(ContM m, Monoid i) => ContM (WriterT i m) 
(AbortM m i, Monoid j) => AbortM (WriterT j m) i 
(RunExceptionM m i, Monoid j) => RunExceptionM (WriterT j m) i 
(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 
(Monoid i, RunM m (a, i) r) => RunM (WriterT i m) a r 

data StateT i m a Source

Add support for threading state of type i.

Instances

MonadT (StateT i) 
MonadPlus m => Alternative (StateT i m) 
Monad m => Monad (StateT i m) 
Monad m => Functor (StateT i m) 
MonadFix m => MonadFix (StateT i m) 
MonadPlus m => MonadPlus (StateT i m) 
Monad m => Applicative (StateT i m) 
ContM m => ContM (StateT i m) 
AbortM m i => AbortM (StateT j m) i 
RunExceptionM m i => RunExceptionM (StateT j 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 
RunM m (a, i) r => RunM (StateT i m) a (i -> r) 

data ExceptionT i m a Source

Add support for exceptions of type i.

Instances

MonadT (ExceptionT i) 
MonadPlus m => Alternative (ExceptionT i m) 
Monad m => Monad (ExceptionT i m) 
Monad m => Functor (ExceptionT i m) 
MonadFix m => MonadFix (ExceptionT i m) 
MonadPlus m => MonadPlus (ExceptionT i m) 
Monad m => Applicative (ExceptionT i m) 
ContM m => ContM (ExceptionT i m) 
AbortM m i => AbortM (ExceptionT j m) i 
Monad m => RunExceptionM (ExceptionT i m) i 
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 
RunM m (Either i a) r => RunM (ExceptionT i m) a r 

About the WriterM instance: If an exception is risen while we are collecting output, then the output is lost. If the output is important, then use try to ensure that no exception may occur. Example:

do (r,w) <- collect (try m)
   case r of
     Left err -> ...do something...
     Right a  -> ...do something...

data ChoiceT m a Source

Add support for multiple answers.

Instances

MonadT ChoiceT 
Monad m => Alternative (ChoiceT m) 
Monad m => Monad (ChoiceT m) 
Monad m => Functor (ChoiceT m) 
Monad m => MonadPlus (ChoiceT m) 
Monad m => Applicative (ChoiceT m) 
ContM m => ContM (ChoiceT m) 
AbortM m i => AbortM (ChoiceT m) i 
ExceptionM m j => ExceptionM (ChoiceT m) j 
StateM m j => StateM (ChoiceT m) j 
WriterM m j => WriterM (ChoiceT m) j 
ReaderM m j => ReaderM (ChoiceT m) j 
BaseM m n => BaseM (ChoiceT m) n 
RunM m (Maybe (a, ChoiceT m a)) r => RunM (ChoiceT m) a r 

data ContT i m a Source

Add support for continuations within a prompt of type i.

Instances

MonadT (ContT i) 
MonadPlus m => Alternative (ContT i m) 
Monad m => Monad (ContT i m) 
Monad m => Functor (ContT i m) 
MonadPlus m => MonadPlus (ContT i m) 
Monad m => Applicative (ContT i m) 
Monad m => ContM (ContT i m) 
Monad m => AbortM (ContT i m) i 
(RunWriterM m j, MonadFix m) => RunWriterM (ContT i m) j 
RunReaderM m j => RunReaderM (ContT i m) j 
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 
RunM m i r => RunM (ContT i m) a ((a -> m i) -> r) 

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 where Source

Methods

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

Promote a computation from the underlying monad.

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

Methods

inBase :: n a -> m a Source

Promote a computation from the base monad.

Instances

BaseM [] [] 
BaseM IO IO 
BaseM Maybe Maybe 
BaseM Lift Lift 
BaseM Id Id 
BaseM m n => BaseM (ChoiceT m) n 
BaseM m n => BaseM (IdT m) n 
BaseM (ST s) (ST s) 
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 where Source

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

Methods

ask :: m i Source

Get the context.

Instances

ReaderM m j => ReaderM (ChoiceT m) j 
ReaderM m j => ReaderM (IdT m) j 
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 where Source

Classifies monads that can collect values of type i.

Methods

put :: i -> m () Source

Add a value to the collection.

Instances

WriterM m j => WriterM (ChoiceT m) j 
WriterM m j => WriterM (IdT m) j 
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 where Source

Classifies monads that propagate a state component of type i.

Methods

get :: m i Source

Get the state.

set :: i -> m () Source

Set the state.

Instances

StateM m j => StateM (ChoiceT m) j 
StateM m j => StateM (IdT m) j 
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 where Source

Classifies monads that support raising exceptions of type i.

Methods

raise :: i -> m a Source

Raise an exception.

Instances

class Monad m => ContM m where Source

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

Methods

callWithCC :: ((a -> Label m) -> m a) -> m a Source

Capture the current continuation.

Instances

ContM m => ContM (ChoiceT m) 
ContM m => ContM (IdT m) 
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) 

class Monad m => AbortM m i where Source

Classifies monads that support aborting the program and returning a given final result of type i.

Methods

abort :: i -> m a Source

Abort the program with the given value as final result.

Instances

AbortM IO ExitCode 
AbortM m i => AbortM (ChoiceT m) i 
AbortM m i => AbortM (IdT m) i 
Monad m => AbortM (ContT i m) i 
AbortM m i => AbortM (ExceptionT j m) i 
AbortM m i => AbortM (StateT j m) i 
(AbortM m i, Monoid j) => AbortM (WriterT j m) i 
AbortM m i => AbortM (ReaderT j m) i 

data Label m Source

An explicit representation for monadic continuations.

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

Capture the current continuation. This function is like return, except that it also captures the current continuation. Later, we can use jump to repeat the computation from this point onwards but with a possibly different value.

labelCC_ :: forall m. ContM m => m (Label m) Source

Capture the current continuation. Later we can use jump to restart the program from this point.

jump :: Label m -> m a Source

Restart a previously captured computation.

labelC :: (forall b. m b) -> Label m Source

Label a given continuation.

callCC :: ContM m => ((a -> m b) -> m a) -> m a Source

A version of callWithCC that avoids the need for an explicit use of the jump function.

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 exceptions are Id and Lift which are not transformers but ordinary monads and so, their run operations simply eliminate the monad.)

runId :: Id a -> a Source

Get the result of a pure computation.

runLift :: Lift a -> a Source

Get the result of a pure strict computation.

runIdT :: IdT m a -> m a Source

Remove an identity layer.

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

Execute a reader computation in the given context.

runWriterT :: Monad m => 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 i Source

Execute a computation with the given continuation.

runChoiceT :: Monad m => ChoiceT m a -> m (Maybe (a, ChoiceT m a)) Source

Execute a computation that may return multiple answers. The resulting computation returns Nothing if no answers were found, or Just (answer,new_comp), where answer is an answer, and new_comp is a computation that may produce more answers. The search is depth-first and left-biased with respect to the mplus operation.

findOne :: Monad m => ChoiceT m a -> m (Maybe a) Source

Execute a computation that may return multiple answers, returning at most one answer.

findAll :: Monad m => ChoiceT m a -> m [a] Source

Execute a computation that may return multiple answers, collecting all possible answers.

class Monad m => RunM m a r | m a -> r where Source

Generalized running.

Methods

runM :: m a -> r Source

Instances

RunM Lift a a 
RunM Id a a 
RunM IO a (IO a) 
RunM m (Maybe (a, ChoiceT m a)) r => RunM (ChoiceT m) a r 
RunM m a r => RunM (IdT m) a r 
RunM m (Either i a) r => RunM (ExceptionT i m) a r 
(Monoid i, RunM m (a, i) r) => RunM (WriterT i m) a r 
RunM m i r => RunM (ContT i m) a ((a -> m i) -> r) 
RunM m (a, i) r => RunM (StateT i m) a (i -> r) 
RunM m a r => RunM (ReaderT i m) a (i -> r) 

Nested Execution

The following classes define operations that are overloaded versions of the run operations. Unlike the run operations, these functions do not change the type of the computation (i.e., they do not remove a layer). Instead, they perform the effects in a ``separate effect thread''.

class ReaderM m i => RunReaderM m i | m -> i where Source

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

Methods

local :: i -> m a -> m a Source

Change the context for the duration of a sub-computation.

Instances

RunReaderM m j => RunReaderM (IdT m) j 
RunReaderM (Reader i) i 
RunReaderM m j => RunReaderM (ContT i m) j 
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 where Source

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

Methods

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

Collect the output from a sub-computation.

Instances

RunWriterM m j => RunWriterM (IdT m) j 
Monoid i => RunWriterM (Writer i) i 
(RunWriterM m j, MonadFix m) => RunWriterM (ContT i m) j 
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 ExceptionM m i => RunExceptionM m i | m -> i where Source

Classifies monads that support handling of exceptions.

Methods

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

Convert computations that may raise an exception into computations that do not raise exception but instead, yield a tagged results. Exceptions are tagged with Left, successful computations are tagged with Right.

Utility functions

asks :: ReaderM m r => (r -> a) -> m a Source

Apply a function to the environment. Useful for accessing environmnt components.

puts :: WriterM m w => (a, w) -> m a Source

Add content the output and return a result.

sets :: StateM m s => (s -> (a, s)) -> m a Source

Update the state and return a result.

sets_ :: StateM m s => (s -> s) -> m () Source

Updates the state with the given function.

raises :: ExceptionM m x => Either x a -> m a Source

Either raise an exception or return a value. Left values signify the we should raise an exception, Right values indicate success.

mapReader :: RunReaderM m r => (r -> r) -> m a -> m a Source

Modify the environment for the duration of a computation.

mapWriter :: RunWriterM m w => (w -> w) -> m a -> m a Source

Modify the output of a computation.

mapException :: RunExceptionM m x => (x -> x) -> m a -> m a Source

Modify the exception that was risen by a computation.

handle :: RunExceptionM m x => m a -> (x -> m a) -> m a Source

Apply the given exception handler, if a computation raises an exception.

Miscellaneous

version :: (Int, Int, Int) Source

The current version of the library.