transformers-lift-0.2.0.2: Ad-hoc type classes for lifting

Safe HaskellSafe
LanguageHaskell2010

Control.Monad.Trans.Lift.Catch

Description

Lifting the catch operation.

Synopsis

Documentation

class MonadTrans t => LiftCatch t where Source #

The class of monad transformers capable of lifting catch.

Methods

liftCatch :: Monad m => Catch e m (StT t a) -> Catch e (t m) a Source #

Lift the catch operation. Should satisfy the uniformity property

Instances
LiftCatch MaybeT Source # 
Instance details

Defined in Control.Monad.Trans.Lift.Catch

Methods

liftCatch :: Monad m => Catch e m (StT MaybeT a) -> Catch e (MaybeT m) a Source #

LiftCatch ListT Source # 
Instance details

Defined in Control.Monad.Trans.Lift.Catch

Methods

liftCatch :: Monad m => Catch e m (StT ListT a) -> Catch e (ListT m) a Source #

Monoid w => LiftCatch (WriterT w) Source # 
Instance details

Defined in Control.Monad.Trans.Lift.Catch

Methods

liftCatch :: Monad m => Catch e m (StT (WriterT w) a) -> Catch e (WriterT w m) a Source #

Monoid w => LiftCatch (AccumT w) Source # 
Instance details

Defined in Control.Monad.Trans.Lift.Catch

Methods

liftCatch :: Monad m => Catch e m (StT (AccumT w) a) -> Catch e (AccumT w m) a Source #

Monoid w => LiftCatch (WriterT w) Source # 
Instance details

Defined in Control.Monad.Trans.Lift.Catch

Methods

liftCatch :: Monad m => Catch e m (StT (WriterT w) a) -> Catch e (WriterT w m) a Source #

LiftCatch (StateT s) Source # 
Instance details

Defined in Control.Monad.Trans.Lift.Catch

Methods

liftCatch :: Monad m => Catch e m (StT (StateT s) a) -> Catch e (StateT s m) a Source #

LiftCatch (StateT s) Source # 
Instance details

Defined in Control.Monad.Trans.Lift.Catch

Methods

liftCatch :: Monad m => Catch e m (StT (StateT s) a) -> Catch e (StateT s m) a Source #

LiftCatch (IdentityT :: (Type -> Type) -> Type -> Type) Source # 
Instance details

Defined in Control.Monad.Trans.Lift.Catch

Methods

liftCatch :: Monad m => Catch e m (StT IdentityT a) -> Catch e (IdentityT m) a Source #

LiftCatch (ExceptT e) Source # 
Instance details

Defined in Control.Monad.Trans.Lift.Catch

Methods

liftCatch :: Monad m => Catch e0 m (StT (ExceptT e) a) -> Catch e0 (ExceptT e m) a Source #

Monoid w => LiftCatch (WriterT w) Source # 
Instance details

Defined in Control.Monad.Trans.Lift.Catch

Methods

liftCatch :: Monad m => Catch e m (StT (WriterT w) a) -> Catch e (WriterT w m) a Source #

LiftCatch (ReaderT r :: (Type -> Type) -> Type -> Type) Source # 
Instance details

Defined in Control.Monad.Trans.Lift.Catch

Methods

liftCatch :: Monad m => Catch e m (StT (ReaderT r) a) -> Catch e (ReaderT r m) a Source #

Monoid w => LiftCatch (RWST r w s) Source # 
Instance details

Defined in Control.Monad.Trans.Lift.Catch

Methods

liftCatch :: Monad m => Catch e m (StT (RWST r w s) a) -> Catch e (RWST r w s m) a Source #

Monoid w => LiftCatch (RWST r w s) Source # 
Instance details

Defined in Control.Monad.Trans.Lift.Catch

Methods

liftCatch :: Monad m => Catch e m (StT (RWST r w s) a) -> Catch e (RWST r w s m) a Source #

Monoid w => LiftCatch (RWST r w s) Source # 
Instance details

Defined in Control.Monad.Trans.Lift.Catch

Methods

liftCatch :: Monad m => Catch e m (StT (RWST r w s) a) -> Catch e (RWST r w s m) a Source #

type Catch e (m :: k -> Type) (a :: k) = 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) (lift f)

defaultLiftCatch Source #

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.