transformers-0.4.1.0: Concrete functor and monad transformers

Portabilityportable
Stabilityexperimental
Maintainerross@soi.city.ac.uk
Safe HaskellSafe-Inferred

Control.Monad.Trans.Except

Contents

Description

This monad transformer extends a monad with the ability throw exceptions.

A sequence of actions terminates normally, producing a value, only if none of the actions in the sequence throws an exception. If one throws an exception, the rest of the sequence is skipped and the composite action exits with that exception.

If the value of the exception is not required, the variant in Control.Monad.Trans.Maybe may be used instead.

Synopsis

The Except monad

type Except e = ExceptT e IdentitySource

The parameterizable exception monad.

Computations are either exceptions or normal values.

The return function returns a normal value, while >>= exits on the first exception.

except :: Either e a -> Except e aSource

Constructor for computations in the exception monad. (The inverse of runExcept).

runExcept :: Except e a -> Either e aSource

Extractor for computations in the exception monad. (The inverse of except).

mapExcept :: (Either e a -> Either e' b) -> Except e a -> Except e' bSource

Map the unwrapped computation using the given function.

withExcept :: (e -> e') -> Except e a -> Except e' aSource

Transform any exceptions thrown by the computation using the given function (a specialization of withExceptT).

The ExceptT monad transformer

newtype ExceptT e m a Source

A monad transformer that adds exceptions to other monads.

ExceptT constructs a monad parameterized over two things:

  • e - The exception type.
  • m - The inner monad.

The return function yields a computation that produces the given value, while >>= sequences two subcomputations, exiting on the first exception.

Constructors

ExceptT (m (Either e a)) 

Instances

MonadTrans (ExceptT e) 
Monad m => Monad (ExceptT e m) 
Functor m => Functor (ExceptT e m) 
MonadFix m => MonadFix (ExceptT e m) 
(Monad m, Monoid e) => MonadPlus (ExceptT e m) 
(Functor m, Monad m) => Applicative (ExceptT e m) 
Foldable f => Foldable (ExceptT e f) 
Traversable f => Traversable (ExceptT e f) 
(Functor m, Monad m, Monoid e) => Alternative (ExceptT e m) 
MonadIO m => MonadIO (ExceptT e m) 
(Show e, Show1 m) => Show1 (ExceptT e m) 
(Read e, Read1 m) => Read1 (ExceptT e m) 
(Ord e, Ord1 m) => Ord1 (ExceptT e m) 
(Eq e, Eq1 m) => Eq1 (ExceptT e m) 
(Eq e, Eq1 m, Eq a) => Eq (ExceptT e m a) 
(Ord e, Ord1 m, Ord a) => Ord (ExceptT e m a) 
(Read e, Read1 m, Read a) => Read (ExceptT e m a) 
(Show e, Show1 m, Show a) => Show (ExceptT e m a) 

runExceptT :: ExceptT e m a -> m (Either e a)Source

The inverse of ExceptT.

mapExceptT :: (m (Either e a) -> n (Either e' b)) -> ExceptT e m a -> ExceptT e' n bSource

Map the unwrapped computation using the given function.

withExceptT :: Functor m => (e -> e') -> ExceptT e m a -> ExceptT e' m aSource

Transform any exceptions thrown by the computation using the given function.

Exception operations

throwE :: Monad m => e -> ExceptT e m aSource

Signal an exception value e.

catchESource

Arguments

:: Monad m 
=> ExceptT e m a

the inner computation

-> (e -> ExceptT e' m a)

a handler for exceptions in the inner computation

-> ExceptT e' m a 

Handle an exception.

Lifting other operations

liftCallCC :: CallCC m (Either e a) (Either e b) -> CallCC (ExceptT e m) a bSource

Lift a callCC operation to the new monad.

liftListen :: Monad m => Listen w m (Either e a) -> Listen w (ExceptT e m) aSource

Lift a listen operation to the new monad.

liftPass :: Monad m => Pass w m (Either e a) -> Pass w (ExceptT e m) aSource

Lift a pass operation to the new monad.