| Safe Haskell | None |
|---|---|
| Language | Haskell2010 |
Control.Monad.Constrained.Error
Description
This module is a duplication of the Control.Monad.Error module from the mtl, for constrained monads.
- class Monad m => MonadError e m | m -> e where
- type SuitableError m a :: Constraint
- newtype ExceptT e m a :: * -> (* -> *) -> * -> * = ExceptT (m (Either e a))
- type Except e = ExceptT e Identity
Documentation
class Monad m => MonadError e m | m -> e where Source #
A class for monads which can error out.
Minimal complete definition
Associated Types
type SuitableError m a :: Constraint Source #
Methods
throwError :: SuitableError m a => e -> m a Source #
Raise an error.
catchError :: SuitableError m a => m a -> (e -> m a) -> m a Source #
A handler function to handle previous errors and return to normal execution. A common idiom is:
do { action1; action2; action3 } `catchError` handlerwhere the action functions can call throwError.
Note that handler and the do-block must have the same return type.
Instances
| (MonadError e m, Monad (Unconstrained m)) => MonadError e (MaybeT m) Source # | |
| MonadError e (Either e) Source # | |
| (MonadError e m, Monad (Unconstrained m)) => MonadError e (StateT s m) Source # | |
| (MonadError e m, Monad (Unconstrained m)) => MonadError e (StateT s m) Source # | |
| MonadError e m => MonadError e (IdentityT * m) Source # | |
| (Monad m, Monad (Unconstrained m)) => MonadError e (ExceptT e m) Source # | |
| (MonadError e m, Monad (Unconstrained m)) => MonadError e (WriterT w m) Source # | |
| MonadError e m => MonadError e (ReaderT * r m) Source # | |
newtype ExceptT e m a :: * -> (* -> *) -> * -> * #
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.
Instances