| Stability | experimental |
|---|---|
| Maintainer | Ertugrul Soeylemez <es@ertes.de> |
Control.ContStuff.Classes
Contents
Description
This module implements the various effect classes supported by contstuff.
- class Abortable m where
- class CallCC m where
- callCC :: ((a -> m b) -> m a) -> m a
- data Label m a
- labelCC :: (Applicative m, CallCC m) => a -> m (a, Label m a)
- goto :: Label m a -> a -> m ()
- class HasExceptions m where
- bracket :: (HasExceptions m, Monad m) => m res -> (res -> m b) -> (res -> m a) -> m a
- bracket_ :: (HasExceptions m, Monad m) => m a -> m b -> m c -> m c
- catch :: (HasExceptions m, Monad m) => m a -> (Exception m -> m a) -> m a
- finally :: (HasExceptions m, Monad m) => m a -> m b -> m a
- forbid :: (Exception (t m) ~ (), HasExceptions (t m), Monad m, Monad (t m), Transformer t) => m Bool -> t m ()
- handle :: (HasExceptions m, Monad m) => (Exception m -> m a) -> m a -> m a
- raiseUnless :: (HasExceptions m, Monad m) => Exception m -> m Bool -> m ()
- raiseWhen :: (HasExceptions m, Monad m) => Exception m -> m Bool -> m ()
- require :: (Exception (t m) ~ (), HasExceptions (t m), Monad m, Monad (t m), Transformer t) => m Bool -> t m ()
- class Transformer t where
- class LiftBase m where
- io :: (LiftBase m, Base m ~ IO) => Base m a -> m a
- class Runnable t r m a where
- class Stateful m where
- getField :: (Functor m, Stateful m) => (StateOf m -> a) -> m a
- modify :: (Monad m, Stateful m) => (StateOf m -> StateOf m) -> m ()
- modifyField :: (Monad m, Stateful m) => (StateOf m -> a) -> (a -> StateOf m) -> m ()
- modifyFieldLazy :: (Monad m, Stateful m) => (StateOf m -> a) -> (a -> StateOf m) -> m ()
- modifyLazy :: (Monad m, Stateful m) => (StateOf m -> StateOf m) -> m ()
- class Writable m w where
Effect classes
Abortion
Monads supporting abortion.
Instances
| Applicative m => Abortable (ContT r m) | |
| Applicative m => Abortable (MaybeT r m) | |
| Applicative m => Abortable (ChoiceT r i m) | |
| Applicative m => Abortable (EitherT r e m) | |
| Applicative m => Abortable (StateT r s m) |
Call with current continuation
Monads supporting *call-with-current-continuation* (aka callCC).
labelCC :: (Applicative m, CallCC m) => a -> m (a, Label m a)Source
Capture the current continuation for later use.
Exceptions
class HasExceptions m whereSource
Monads with exception support.
Methods
raise :: Exception m -> m aSource
Raise an exception.
try :: m a -> m (Either (Exception m) a)Source
Run computation catching exceptions.
Instances
| HasExceptions IO | |
| HasExceptions Maybe | |
| HasExceptions (Either e) | |
| HasExceptions (MaybeT r m) | |
| HasExceptions (EitherT r e m) |
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), 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.
Instances
| Transformer IdT | |
| Transformer (ContT r) | |
| Transformer (MaybeT r) | |
| Transformer (ChoiceT r i) | |
| Transformer (EitherT r e) | |
| Transformer (StateT r s) |
Monads, which support lifting base monad computations.
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 (ContT r m) | |
| (LiftBase m, Monad m) => LiftBase (MaybeT r m) | |
| (LiftBase m, Monad m) => LiftBase (ChoiceT r i m) | |
| (LiftBase m, Monad m) => LiftBase (EitherT r e m) | |
| (LiftBase m, Monad m) => LiftBase (StateT r s m) |
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.
State
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*.
Instances
| (Functor m, Monoid w) => Writable (ContT (r, w) m) w | |
| Alternative m => Writable (ContT r m) r | |
| (Functor m, Monoid w) => Writable (MaybeT (r, w) m) w | |
| Alternative m => Writable (MaybeT r m) r | |
| (Functor m, Monoid w) => Writable (EitherT (r, w) e m) w | |
| Alternative m => Writable (EitherT r e m) r | |
| (Functor m, Monoid w) => Writable (StateT (r, w) s m) w | |
| Alternative m => Writable (StateT r s m) r |