Copyright | (C) 2013 Ross Paterson |
---|---|
License | BSD-style (see the file LICENSE) |
Maintainer | R.Paterson@city.ac.uk |
Stability | experimental |
Portability | portable |
Safe Haskell | Safe |
Language | Haskell2010 |
This monad transformer extends a monad with the ability to throw and catch 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
- type Except e = ExceptT e Identity
- except :: forall (m :: Type -> Type) e a. Monad m => Either e a -> ExceptT e m a
- runExcept :: Except e a -> Either e a
- mapExcept :: (Either e a -> Either e' b) -> Except e a -> Except e' b
- withExcept :: (e -> e') -> Except e a -> Except e' a
- newtype ExceptT e (m :: Type -> Type) a = ExceptT (m (Either e a))
- runExceptT :: ExceptT e m a -> m (Either e a)
- mapExceptT :: (m (Either e a) -> n (Either e' b)) -> ExceptT e m a -> ExceptT e' n b
- withExceptT :: forall (m :: Type -> Type) e e' a. Functor m => (e -> e') -> ExceptT e m a -> ExceptT e' m a
- throwE :: forall (m :: Type -> Type) e a. Monad m => e -> ExceptT e m a
- catchE :: forall (m :: Type -> Type) e a e'. Monad m => ExceptT e m a -> (e -> ExceptT e' m a) -> ExceptT e' m a
- handleE :: forall (m :: Type -> Type) e e' a. Monad m => (e -> ExceptT e' m a) -> ExceptT e m a -> ExceptT e' m a
- tryE :: forall (m :: Type -> Type) e a. Monad m => ExceptT e m a -> ExceptT e m (Either e a)
- finallyE :: forall (m :: Type -> Type) e a. Monad m => ExceptT e m a -> ExceptT e m () -> ExceptT e m a
- liftCallCC :: CallCC m (Either e a) (Either e b) -> CallCC (ExceptT e m) a b
- liftListen :: Monad m => Listen w m (Either e a) -> Listen w (ExceptT e m) a
- liftPass :: Monad m => Pass w m (Either e a) -> Pass w (ExceptT e m) a
The Except monad
type Except e = ExceptT e Identity Source #
The parameterizable exception monad.
Computations are either exceptions (of any type) or normal values.
These computations are plain values, and are unrelated to the
Control.Exception mechanism, which is tied to the IO
monad.
The return
function returns a normal value, while >>=
exits on
the first exception. For a variant that continues after an error
and collects all the errors, see Errors
.
except :: forall (m :: Type -> Type) e a. Monad m => Either e a -> ExceptT e m a Source #
Constructor for computations in the exception monad.
(The inverse of runExcept
).
runExcept :: Except e a -> Either e a Source #
Extractor for computations in the exception monad.
(The inverse of except
).
withExcept :: (e -> e') -> Except e a -> Except e' a Source #
Transform any exceptions thrown by the computation using the given
function (a specialization of withExceptT
).
The ExceptT monad transformer
newtype ExceptT e (m :: Type -> Type) a Source #
A monad transformer that adds exceptions to other monads.
ExceptT
constructs a monad parameterized over two things:
- e - An arbitrary exception type.
- m - The inner monad.
The monadic computations are a plain values. They are unrelated to
the Control.Exception mechanism, which is tied to the IO
monad.
The return
function yields a computation that produces the given
value, while >>=
sequences two subcomputations, exiting on the
first exception.
Instances
mapExceptT :: (m (Either e a) -> n (Either e' b)) -> ExceptT e m a -> ExceptT e' n b Source #
Map the unwrapped computation using the given function.
runExceptT
(mapExceptT
f m) = f (runExceptT
m)
withExceptT :: forall (m :: Type -> Type) e e' a. Functor m => (e -> e') -> ExceptT e m a -> ExceptT e' m a Source #
Transform any exceptions thrown by the computation using the given function.
Exception operations
handleE :: forall (m :: Type -> Type) e e' a. Monad m => (e -> ExceptT e' m a) -> ExceptT e m a -> ExceptT e' m a Source #
tryE :: forall (m :: Type -> Type) e a. Monad m => ExceptT e m a -> ExceptT e m (Either e a) Source #
finallyE :: forall (m :: Type -> Type) e a. Monad m => ExceptT e m a -> ExceptT e m () -> ExceptT e m a Source #
executes computation finallyE
a ba
followed by computation b
,
even if a
exits early by throwing an exception. In the latter case,
the exception is re-thrown after b
has been executed.
Lifting other operations
liftCallCC :: CallCC m (Either e a) (Either e b) -> CallCC (ExceptT e m) a b Source #
Lift a callCC
operation to the new monad.