monadology-0.3: The best ideas in monad-related classes and types.
Safe HaskellSafe-Inferred
LanguageHaskell2010

Control.Monad.Ology.General.Catch

Synopsis

Documentation

class MonadThrow e m => MonadCatch e m where Source #

Monads that can catch this type of exception.

Methods

catch :: forall a. m a -> (e -> m a) -> m a Source #

Instances

Instances details
Exception e => MonadCatch e IO Source # 
Instance details

Defined in Control.Monad.Ology.General.Catch

Methods

catch :: IO a -> (e -> IO a) -> IO a Source #

MonadCatch e m => MonadCatch e (LifecycleT m) Source # 
Instance details

Defined in Control.Monad.Ology.Specific.LifecycleT

Methods

catch :: LifecycleT m a -> (e -> LifecycleT m a) -> LifecycleT m a Source #

MonadCatch e m => MonadCatch e (WithT m) Source # 
Instance details

Defined in Control.Monad.Ology.Specific.WithT

Methods

catch :: WithT m a -> (e -> WithT m a) -> WithT m a Source #

MonadCatch e m => MonadCatch e (IdentityT m) Source # 
Instance details

Defined in Control.Monad.Ology.Specific.IdentityT

Methods

catch :: IdentityT m a -> (e -> IdentityT m a) -> IdentityT m a Source #

MonadCatch e m => MonadCatch e (ReaderT r m) Source # 
Instance details

Defined in Control.Monad.Ology.Specific.ReaderT

Methods

catch :: ReaderT r m a -> (e -> ReaderT r m a) -> ReaderT r m a Source #

MonadCatch e m => MonadCatch e (StateT s m) Source # 
Instance details

Defined in Control.Monad.Ology.Specific.StateT

Methods

catch :: StateT s m a -> (e -> StateT s m a) -> StateT s m a Source #

(MonadCatch e m, Monoid w) => MonadCatch e (WriterT w m) Source # 
Instance details

Defined in Control.Monad.Ology.Specific.WriterT

Methods

catch :: WriterT w m a -> (e -> WriterT w m a) -> WriterT w m a Source #

MonadCatch e m => MonadCatch (Maybe e) (MaybeT m) Source # 
Instance details

Defined in Control.Monad.Ology.Specific.MaybeT

Methods

catch :: MaybeT m a -> (Maybe e -> MaybeT m a) -> MaybeT m a Source #

TransConstraint (MonadCatch e) (LifecycleT :: (Type -> Type) -> Type -> TYPE LiftedRep) Source # 
Instance details

Defined in Control.Monad.Ology.Specific.LifecycleT

Methods

hasTransConstraint :: forall (m :: Type -> Type). MonadCatch e m => Dict (MonadCatch e (LifecycleT m)) Source #

TransConstraint (MonadCatch e) (IdentityT :: (Type -> Type) -> Type -> Type) Source # 
Instance details

Defined in Control.Monad.Ology.Specific.IdentityT

Methods

hasTransConstraint :: forall (m :: Type -> Type). MonadCatch e m => Dict (MonadCatch e (IdentityT m)) Source #

TransConstraint (MonadCatch e) (ReaderT r) Source # 
Instance details

Defined in Control.Monad.Ology.Specific.ReaderT

Methods

hasTransConstraint :: forall (m :: Type -> Type). MonadCatch e m => Dict (MonadCatch e (ReaderT r m)) Source #

TransConstraint (MonadCatch e) (StateT s) Source # 
Instance details

Defined in Control.Monad.Ology.Specific.StateT

Methods

hasTransConstraint :: forall (m :: Type -> Type). MonadCatch e m => Dict (MonadCatch e (StateT s m)) Source #

Monoid w => TransConstraint (MonadCatch e) (WriterT w) Source # 
Instance details

Defined in Control.Monad.Ology.Specific.WriterT

Methods

hasTransConstraint :: forall (m :: Type -> Type). MonadCatch e m => Dict (MonadCatch e (WriterT w m)) Source #

MonadCatch ex m => MonadCatch (Either e ex) (ExceptT e m) Source # 
Instance details

Defined in Control.Monad.Ology.Specific.ExceptT

Methods

catch :: ExceptT e m a -> (Either e ex -> ExceptT e m a) -> ExceptT e m a Source #

try :: forall m e a. MonadCatch e m => m a -> m (Result e a) Source #

handle :: forall m e a. MonadCatch e m => (e -> m a) -> m a -> m a Source #