contstuff-0.6.1: Fast, easy to use CPS-based monads

Stabilityexperimental
MaintainerErtugrul Soeylemez <es@ertes.de>

Control.ContStuff

Contents

Description

This module implements a number of monad transformers using a CPS approach internally.

Synopsis

Monad transformers

Identity transformer

newtype IdT m a Source

The identity monad transformer. This monad transformer represents computations themselves without further side effects. Unlike most other monad transformers in this module it is not implemented in terms of continuation passing style.

Constructors

IdT 

Fields

getIdT :: m a
 

Instances

ContT

newtype ContT r m a Source

The continuation passing style monad transformer. This monad transformer models the most basic form of CPS.

Constructors

ContT 

Fields

getContT :: (a -> m r) -> m r
 

Instances

Transformer (ContT r) 
Runnable (ContT r) r m a 
Monad (ContT r m) 
Functor (ContT r m) 
Alternative m => MonadPlus (ContT r m) 
Applicative (ContT r m) 
Alternative m => Alternative (ContT r m) 
(Monad m, Stateful m) => Stateful (ContT r m) 
(LiftBase m, Monad m) => LiftBase (ContT r m) 
CallCC (ContT r m) 
Applicative m => Abortable (ContT r m) 
(Functor m, Monoid w) => Writable (ContT (r, w) m) w 
Alternative m => Writable (ContT r m) r 

runContT :: (a -> m r) -> ContT r m a -> m rSource

Run a CPS-style computation given the supplied final continuation.

evalContT :: Applicative m => ContT r m r -> m rSource

Evaluate a CPS-style computation to its final result.

modifyContT :: Functor m => (r -> r) -> ContT r m ()Source

Transform the final result along the way.

Choice/nondeterminism

newtype ChoiceT r i m a Source

The choice monad transformer, which models, as the most common interpretation, nondeterminism. Internally a list of choices is represented as a CPS-based left-fold function.

Constructors

ChoiceT 

Fields

getChoiceT :: (i -> a -> (i -> m r) -> m r) -> i -> (i -> m r) -> m r
 

Instances

Transformer (ChoiceT r i) 
Monad (ChoiceT r i m) 
Functor (ChoiceT r i m) 
MonadPlus (ChoiceT r i m) 
Applicative (ChoiceT r i m) 
Alternative (ChoiceT r i m) 
(LiftBase m, Monad m) => LiftBase (ChoiceT r i m) 
Applicative m => Abortable (ChoiceT r i m) 

runChoiceT :: (i -> a -> (i -> m r) -> m r) -> i -> (i -> m r) -> ChoiceT r i m a -> m rSource

Run a choice computation.

choice :: [a] -> ChoiceT r i m aSource

Turn a list into a ChoiceT computation efficiently.

findAll :: (Alternative f, Applicative m) => ChoiceT (f a) (f a) m a -> m (f a)Source

Find all solutions.

findAll_ :: Applicative m => ChoiceT () i m a -> m ()Source

Find all solutions and ignore them.

findFirst :: (Alternative f, Applicative m) => ChoiceT (f a) (f a) m a -> m (f a)Source

Find the first solution.

findFirst_ :: Applicative m => ChoiceT () i m a -> m ()Source

Find the first solution and ignore it.

listA :: Alternative f => [a] -> f aSource

Turn a list into a computation with alternatives.

listChoiceT :: Applicative m => ChoiceT [a] [a] m a -> m [a]Source

Get list of solutions (faster than findAll, but returns solutions in reversed order).

maybeChoiceT :: Applicative m => ChoiceT (Maybe a) (Maybe a) m a -> m (Maybe a)Source

Get one solution (faster than findFirst).

Exceptions

newtype EitherT r e m a Source

Monad transformer for CPS computations with an additional exception continuation.

Constructors

EitherT 

Fields

getEitherT :: (a -> m r) -> (e -> m r) -> m r
 

Instances

Transformer (EitherT r e) 
Runnable (EitherT r e) r m a 
Monad (EitherT r e m) 
Functor (EitherT r e m) 
Alternative m => MonadPlus (EitherT r e m) 
Applicative (EitherT r e m) 
Alternative m => Alternative (EitherT r e m) 
(Monad m, Stateful m) => Stateful (EitherT r e m) 
(LiftBase m, Monad m) => LiftBase (EitherT r e m) 
HasExceptions (EitherT r e m) 
CallCC (EitherT r e m) 
Applicative m => Abortable (EitherT r e m) 
(Functor m, Monoid w) => Writable (EitherT (r, w) e m) w 
Alternative m => Writable (EitherT r e m) r 

runEitherT :: (a -> m r) -> (e -> m r) -> EitherT r e m a -> m rSource

Run an EitherT transformer.

evalEitherT :: Applicative m => EitherT (Either e a) e m a -> m (Either e a)Source

Run an EitherT transformer returning an Either result.

modifyEitherT :: Functor m => (r -> r) -> EitherT r e m ()Source

Modify the result of an EitherT computation along the way.

newtype MaybeT r m a Source

Monad transformer for CPS computations with an additional exception continuation with no argument.

Constructors

MaybeT 

Fields

getMaybeT :: (a -> m r) -> m r -> m r
 

Instances

Transformer (MaybeT r) 
Runnable (MaybeT r) r m a 
Monad (MaybeT r m) 
Functor (MaybeT r m) 
Alternative m => MonadPlus (MaybeT r m) 
Applicative (MaybeT r m) 
Alternative (MaybeT r m) 
(LiftBase m, Monad m) => LiftBase (MaybeT r m) 
HasExceptions (MaybeT r m) 
CallCC (MaybeT r m) 
Applicative m => Abortable (MaybeT r m) 
(Functor m, Monoid w) => Writable (MaybeT (r, w) m) w 
Alternative m => Writable (MaybeT r m) r 

runMaybeT :: (a -> m r) -> m r -> MaybeT r m a -> m rSource

Run a MaybeT transformer.

evalMaybeT :: Applicative m => MaybeT (Maybe a) m a -> m (Maybe a)Source

Run a MaybeT transformer returning a Maybe result.

modifyMaybeT :: Functor m => (r -> r) -> MaybeT r m ()Source

Modify the result of a MaybeT computation along the way.

State

newtype StateT r s m a Source

Monad transformer for stateful computations.

Constructors

StateT 

Fields

getStateT :: s -> (s -> a -> m r) -> m r
 

Instances

Transformer (StateT r s) 
Runnable (StateT r s) r m a 
Monad (StateT r s m) 
Functor (StateT r s m) 
Alternative m => MonadPlus (StateT r s m) 
Applicative (StateT r s m) 
Alternative m => Alternative (StateT r s m) 
Stateful (StateT r s m) 
(LiftBase m, Monad m) => LiftBase (StateT r s m) 
CallCC (StateT r s m) 
Applicative m => Abortable (StateT r s m) 
(Functor m, Monoid w) => Writable (StateT (r, w) s m) w 
Alternative m => Writable (StateT r s m) r 

runStateT :: s -> (s -> a -> m r) -> StateT r s m a -> m rSource

Run a state transformer.

evalStateT :: Applicative m => s -> StateT r s m r -> m rSource

Run a state transformer returning its result.

execStateT :: Applicative m => s -> StateT s s m a -> m sSource

Run a state transformer returning its final state.

Writer monads

type WriterT = ContTSource

The writer monad transformer. Supports logging effects.

runWriterT :: Alternative m => WriterT r m a -> m rSource

Run a writer transformer.

type OldWriterT r w m a = ContT (r, w) m aSource

The traditional writer monad transformer.

runOldWriterT :: (Applicative m, Monoid w) => OldWriterT r w m r -> m (r, w)Source

Run a traditional writer transformer.

evalOldWriterT :: (Applicative m, Monoid w) => OldWriterT r w m r -> m rSource

Run a traditional writer transformer and return its result.

execOldWriterT :: (Applicative m, Monoid w) => OldWriterT r w m r -> m wSource

Run a traditional writer transformer and return its log.

Monads

Identity monad

newtype Id a Source

The identity monad. This monad represents values themselves, i.e. computations without effects.

Constructors

Id 

Fields

getId :: a
 

Choice

type Choice r i a = ChoiceT r i Id aSource

The choice monad. Derived from ChoiceT.

listChoice :: Choice [a] [a] a -> [a]Source

Get list of solutions.

maybeChoice :: Choice (Maybe a) (Maybe a) a -> Maybe aSource

Get one solution.

Cont

type Cont r a = ContT r Id aSource

Pure CPS monad derived from ContT.

runCont :: (a -> r) -> Cont r a -> rSource

Run a pure CPS computation.

evalCont :: Cont r r -> rSource

Evaluate a pure CPS computation to its final result.

modifyCont :: (r -> r) -> Cont r ()Source

Modify the result of a CPS computation along the way.

State

type State r s a = StateT r s Id aSource

Pure state monad derived from StateT.

runState :: s -> (s -> a -> r) -> State r s a -> rSource

Run a stateful computation.

evalState :: s -> State r s r -> rSource

Run a stateful computation returning its result.

execState :: s -> State s s a -> sSource

Run a stateful computation returning its result.

Writer

type OldWriter r w a = ContT (r, w) Id aSource

The traditional writer monad.

runOldWriter :: Monoid w => OldWriter r w r -> (r, w)Source

Run a traditional writer computation.

evalOldWriter :: Monoid w => OldWriter r w r -> rSource

Run a traditional writer computation and return its result.

execOldWriter :: Monoid w => OldWriter r w r -> wSource

Run a traditional writer computation and return its log.

Effect classes

Abortion

class Abortable m whereSource

Monads supporting abortion.

Associated Types

type Result m Source

End result of the computation.

Methods

abort :: Result m -> m aSource

Ignore current continuation and abort.

Instances

Call with current continuation

class CallCC m whereSource

Monads supporting *call-with-current-continuation* (aka callCC).

Methods

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

Call with current continuation.

Instances

CallCC (MaybeT r m) 
CallCC (ContT r m) 
CallCC (StateT r s m) 
CallCC (EitherT r e m) 

data Label m a Source

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

Capture the current continuation for later use.

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

Jump to a label.

Exceptions

class HasExceptions m whereSource

Monads with exception support.

Associated Types

type Exception m Source

The exception type.

Methods

raise :: Exception m -> m aSource

Raise an exception.

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

Run computation catching exceptions.

bracket :: (HasExceptions m, Monad m) => m res -> (res -> m b) -> (res -> m a) -> m aSource

Get a resource, run a computation, then release the resource, even if an exception is raised:

 bracket acquire release use

Please note that this function behaves slightly different from the usual bracket. If both the user and the releaser throw an exception, the user exception is significant.

bracket_ :: (HasExceptions m, Monad m) => m a -> m b -> m c -> m cSource

Initialize, then run, then clean up safely, even if an exception is raised:

 bracket_ init cleanup run

Please note that this function behaves slightly different from the usual bracket_. If both the user and the releaser throw an exception, the user exception is significant.

catch :: (HasExceptions m, Monad m) => m a -> (Exception m -> m a) -> m aSource

Catch exceptions using an exception handler.

finally :: (HasExceptions m, Monad m) => m a -> m b -> m aSource

Run a final computation regardless of whether an exception was raised.

forbid :: (Exception (t m) ~ (), HasExceptions (t m), Monad m, Monad (t m), Transformer t) => m Bool -> t m ()Source

Fail (in the sense of the given transformer), if the given underlying computation returns True.

handle :: (HasExceptions m, Monad m) => (Exception m -> m a) -> m a -> m aSource

Catch exceptions using an exception handler (flip catch).

raiseUnless :: (HasExceptions m, Monad m) => Exception m -> m Bool -> m ()Source

Throw given exception, if the given computation returns False.

raiseWhen :: (HasExceptions m, Monad m) => Exception m -> m Bool -> m ()Source

Throw given exception, if the given computation returns True.

require :: (Exception (t m) ~ (), HasExceptions (t m), Monad m, Monad (t m), Transformer t) => m Bool -> t m ()Source

Fail (in the sense of the given transformer), if the given underlying computation returns False.

Lifting

class Transformer t whereSource

The monad transformer class. Lifting computations one level down the monad stack, or stated differently promoting a computation of the underlying monad to the transformer.

Methods

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

Promote a monadic computation to the transformer.

class LiftBase m whereSource

Monads, which support lifting base monad computations.

Associated Types

type Base m :: * -> *Source

Base monad of m.

Methods

base :: Base m a -> m aSource

Promote a base monad computation.

Instances

LiftBase [] 
LiftBase IO 
LiftBase Maybe 
LiftBase Id 
LiftBase ((->) r) 
LiftBase (ST s) 
(LiftBase m, Monad m) => LiftBase (IdT m) 
(LiftBase m, Monad m) => LiftBase (MaybeT r m) 
(LiftBase m, Monad m) => LiftBase (ContT r m) 
(LiftBase m, Monad m) => LiftBase (StateT r s m) 
(LiftBase m, Monad m) => LiftBase (EitherT r e m) 
(LiftBase m, Monad m) => LiftBase (ChoiceT r i m) 

io :: (LiftBase m, Base m ~ IO) => Base m a -> m aSource

Handy alias for lifting IO computations.

Running

class Runnable t r m a whereSource

Every monad transformer t that supports transforming t m a to m a can be an instance of this class.

Associated Types

type Argument t r m a Source

Arguments needed to run.

Methods

runT :: Argument t r m a -> t m a -> m rSource

Run the transformer.

Instances

Runnable IdT r m r 
Runnable (MaybeT r) r m a 
Runnable (ContT r) r m a 
Runnable (StateT r s) r m a 
Runnable (EitherT r e) r m a 

State

class Stateful m whereSource

Stateful monads.

Minimal complete definition: StateOf, get and putLazy.

Associated Types

type StateOf m Source

State type of m.

Methods

get :: m (StateOf m)Source

Get the current state.

put :: StateOf m -> m ()Source

Set the current state and force it.

putLazy :: StateOf m -> m ()Source

Set the current state, but don't force it.

Instances

(Monad m, Stateful m) => Stateful (ContT r m) 
Stateful (StateT r s m) 
(Monad m, Stateful m) => Stateful (EitherT r e m) 

getField :: (Functor m, Stateful m) => (StateOf m -> a) -> m aSource

Get a certain field.

modify :: (Monad m, Stateful m) => (StateOf m -> StateOf m) -> m ()Source

Apply a function to the current state.

modifyField :: (Monad m, Stateful m) => (StateOf m -> a) -> (a -> StateOf m) -> m ()Source

Get a field and modify the state.

modifyFieldLazy :: (Monad m, Stateful m) => (StateOf m -> a) -> (a -> StateOf m) -> m ()Source

Get a field and modify the state. Lazy version.

modifyLazy :: (Monad m, Stateful m) => (StateOf m -> StateOf m) -> m ()Source

Apply a function to the current state. Lazy version.

Logging support (writers)

class Writable m w whereSource

Monads with support for logging. Traditionally these are called *writer monads*.

Methods

tell :: w -> m ()Source

Log a value.

Instances

(Functor m, Monoid w) => Writable (MaybeT (r, w) m) w 
Alternative m => Writable (MaybeT r m) r 
(Functor m, Monoid w) => Writable (ContT (r, w) m) w 
Alternative m => Writable (ContT r m) r 
(Functor m, Monoid w) => Writable (StateT (r, w) s m) w 
Alternative m => Writable (StateT r s m) r 
(Functor m, Monoid w) => Writable (EitherT (r, w) e m) w 
Alternative m => Writable (EitherT r e m) r 

Module reexports