Strafunski-StrategyLib-5.0.0.2: Library for strategic programming

Portabilityportable
Stabilityexperimental
MaintainerRalf Laemmel, Joost Visser
Safe HaskellNone

Control.Monad.Run

Contents

Description

This module is part of StrategyLib, a library of functional strategy combinators, including combinators for generic traversal. This module provides non-strategic functionality for running monads and unlifting monad transformers. In a sense, this is dual to the return and lift functionality of the Monad and MonadTrans classes.

Synopsis

Monad algebras

data MaybeAlg a b Source

The algebra for the partiality effect of Maybe and MaybeT.

Constructors

MaybeAlg 

Fields

nothing :: b
 
just :: a -> b
 

Instances

MonadUnTrans MaybeAlg MaybeT

Unlifting the partiality monad transformer.

MonadRun MaybeAlg Maybe

Running the Maybe monad.

data ErrorAlg e a b Source

The algebra for the error effect of Either and ErrorT.

Constructors

ErrorAlg 

Fields

left :: e -> b
 
right :: a -> b
 

Instances

MonadUnTrans (ErrorAlg e) (ErrorT e)

Unlifting the error monad transformer.

MonadRun (ErrorAlg e) (Either e)

Running the error monad.

data ListAlg a b Source

The algebra for the non-determinacy effect of '[]' and ListT.

Constructors

ListAlg 

Fields

nil :: b
 
cons :: a -> b -> b
 

Instances

MonadUnTrans ListAlg ListT

Unlifting the list monad transformer.

MonadRun ListAlg []

Running the list monad.

data StateAlg s a b Source

The algebra for the state effect of State and StateT.

Constructors

StateAlg 

Fields

first :: s

initial state

next :: (a, s) -> b

state transformer

Instances

MonadUnTrans (StateAlg s) (StateT s)

Unlifting the state monad transformer

MonadRun (StateAlg s) (State s)

Running the State monad.

Running monads

class MonadRun s m | m -> s whereSource

The class of monads for which a run function is defined that executes the computation of the monad.

Methods

run :: s a b -> m a -> bSource

The overloaded function run takes as first argument an algebra which captures the ingredients necessary to run the particular monad at hand. This algebra is parameterized with the domain and co-domain of run.

Instances

MonadRun (->) IO

Running the IO monad. Note: uses unsafePerformIO!

MonadRun (->) Identity

Running the Identity monad. The algebra for the Identity monad is a unary function.

MonadRun ListAlg []

Running the list monad.

MonadRun MaybeAlg Maybe

Running the Maybe monad.

MonadRun (StateAlg s) (State s)

Running the State monad.

MonadRun (ErrorAlg e) (Either e)

Running the error monad.

mrun :: (MonadRun s m, Monad m') => s a b -> m a -> m' bSource

Exchange one monad by another. This function runs one monad, and puts its value in another. This is basically a monadic version of the run function itself. Note that the two monads are unrelated, so none of the effects of the incoming monad are transferred to the result monad.

Unlifting monad transformers

class MonadUnTrans s t | t -> s whereSource

Just as a base monad can be run to remove the monad, so can a transformed monad be unlifted to remove the transformer and obtain the original monad.

Methods

unlift :: Monad m => s a b -> t m a -> m bSource

The overloaded function unlift for monad transformers takes as first argument an algebra just like the run function for base monads. For each monad transformer, the same algebra is used as for the base monad of which the transformer is the parameterized variant.

Instances

MonadUnTrans ListAlg ListT

Unlifting the list monad transformer.

MonadUnTrans MaybeAlg MaybeT

Unlifting the partiality monad transformer.

MonadUnTrans (StateAlg s) (StateT s)

Unlifting the state monad transformer

MonadUnTrans (ErrorAlg e) (ErrorT e)

Unlifting the error monad transformer.

Monadic choice combinators that confine the partiality effect

Monadic choice

mplus' :: (Monad m, MonadUnTrans MaybeAlg t) => t m b -> m b -> m bSource

Monadic choice combinator that confines the partiality effect to the first argument. This is a variation on mplus which allows the partiality effect to spread to both arguments and to the result.

mswitchSource

Arguments

:: (Monad m, MonadUnTrans MaybeAlg t) 
=> [t m b]

choice branches

-> m b

otherwise

-> m b

result

Monadic choice combinator. Generalization of mplus' that takes a list of choice arguments rather than a single one.

mayswitch :: Monad m => [MaybeT m b] -> m b -> m bSource

Specialization of mswitch for MaybeT.

Monadic function choice

mchoice' :: (Monad m, MonadUnTrans MaybeAlg t) => (a -> t m b) -> (a -> m b) -> a -> m bSource

Monadic function choice combinator that confines the partiality effect to the first argument. This is a variation on mchoice which allows the partiality effect to spread to both arguments and to the result.

mchoices :: (Monad m, MonadUnTrans MaybeAlg t, MonadPlus (t m)) => [a -> t m b] -> (a -> m b) -> a -> m bSource

Monadic function choice combinator. Generalization of mchoice' that takes a list of choice arguments rather than a single one.

Implementation variants

mswitch0 :: (Monad m, MonadUnTrans MaybeAlg t) => [t m b] -> m b -> m bSource

Implementation variant of mswitch in terms of foldr.

mswitch1 :: (Monad m, MonadUnTrans MaybeAlg t) => [t m b] -> m b -> m bSource

Implementation variant of mswitch with mplus' expanded:

mswitch' :: (Monad m, MonadUnTrans MaybeAlg t, MonadPlus (t m)) => [t m b] -> m b -> m bSource

Implementation variant of mswitch where the unlift is postponed to the very end.