contstuff-1.2.6: Fast, easy to use CPS-based monad transformers

Stabilityexperimental
MaintainerErtugrul Soeylemez <es@ertes.de>

Control.ContStuff.Classes

Contents

Description

This module implements the various effect classes supported by contstuff.

Synopsis

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

A jump label for labelCC and goto.

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.

Multithreading

Forking

class Monad m => Forkable m whereSource

Monads with support for forking threads.

Methods

forkIO :: m () -> m ThreadIdSource

Generalization of forkIO.

forkOS :: m () -> m ThreadIdSource

Generalization of forkOS.

Instances

Forkable IO 
Forkable m => Forkable (MaybeT () m) 
Forkable m => Forkable (ContT () m) 
Forkable m => Forkable (StateT () s m) 
Forkable m => Forkable (EitherT () e m) 
(Applicative m, Forkable m) => Forkable (ChoiceT r i m) 

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 E.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 E.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), MonadTrans 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), MonadTrans t) => m Bool -> t m ()Source

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

Functor lifting

class LiftFunctor t whereSource

Type class for lifting functor computations.

Associated Types

type InnerFunctor t :: * -> *Source

Inner functor.

Methods

liftF :: Monad m => m (InnerFunctor t a) -> t m aSource

Unwrap inner functor.

State

Reading

class Readable m whereSource

Monads with environment (reader monads).

Associated Types

type StateOf m Source

Environment type of m.

Methods

get :: m (StateOf m)Source

Get the current state.

Instances

(Monad m, Readable m) => Readable (IdentityT m) 
Readable (ReaderT e m) 
(Monad m, Readable m) => Readable (MaybeT r m) 
(Monad m, Readable m) => Readable (ContT r m) 
Readable (StateT r s m) 
(Monad m, Readable m) => Readable (EitherT r e m) 
(Monad m, Readable m) => Readable (ChoiceT r i m) 

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

Get a certain field.

Writing

class Stateful m whereSource

Stateful monads, i.e. having a modifyable environment (stateful monads).

Minimal complete definition: putLazy.

Methods

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 (IdentityT m) 
(Monad m, Stateful m) => Stateful (MaybeT r m) 
(Monad m, Stateful m) => Stateful (ContT r m) 
Stateful (StateT r s m) 
(Monad m, Stateful m) => Stateful (EitherT r e m) 
(Monad m, Stateful m) => Stateful (ChoiceT r i m) 

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

Apply a function to the current state.

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

Get a field and modify the state.

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

Get a field and modify the state. Lazy version.

modifyLazy :: (Monad m, Readable 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