| Safe Haskell | Safe |
|---|---|
| Language | Haskell2010 |
Control.Monad.Trans.Lift.Catch
Description
Lifting the catch operation.
- class MonadTrans t => LiftCatch t where
- type Catch k e m a = m a -> (e -> m a) -> m a
- defaultLiftCatch :: (Monad m, LiftCatch n) => (forall x. n m x -> t m x) -> (forall o x. t o x -> n o x) -> Catch e m (StT n a) -> Catch e (t m) a
- module Control.Monad.Trans.Class
Documentation
class MonadTrans t => LiftCatch t where Source #
The class of monad transformers capable of lifting catch.
Minimal complete definition
Instances
| LiftCatch MaybeT Source # | |
| LiftCatch ListT Source # | |
| Monoid w => LiftCatch (WriterT w) Source # | |
| Monoid w => LiftCatch (WriterT w) Source # | |
| LiftCatch (StateT s) Source # | |
| LiftCatch (StateT s) Source # | |
| LiftCatch (IdentityT *) Source # | |
| LiftCatch (ExceptT e) Source # | |
| Monoid w => LiftCatch (WriterT w) Source # | |
| LiftCatch (ReaderT * r) Source # | |
| Monoid w => LiftCatch (RWST r w s) Source # | |
| Monoid w => LiftCatch (RWST r w s) Source # | |
| Monoid w => LiftCatch (RWST r w s) Source # | |
type Catch k e m a = m a -> (e -> m a) -> m a #
Signature of the catchE operation,
introduced in Control.Monad.Trans.Except.
Any lifting function liftCatch should satisfy
lift(cf m f) = liftCatch (lift. cf) (liftf)
Arguments
| :: (Monad m, LiftCatch n) | |
| => (forall x. n m x -> t m x) | Monad constructor |
| -> (forall o x. t o x -> n o x) | Monad deconstructor |
| -> Catch e m (StT n a) | |
| -> Catch e (t m) a |
Default definition for the liftCatch method.
module Control.Monad.Trans.Class