monad-levels-0.1.0.0: Specific levels of monad transformers

Copyright(c) Ivan Lazar Miljenovic
License3-Clause BSD-style
MaintainerIvan.Miljenovic@gmail.com
Safe HaskellTrustworthy
LanguageHaskell2010

Control.Monad.Levels.Except

Description

Computations which may fail or throw exceptions.

Synopsis

Documentation

throwError :: forall e m a. HasError e m => e -> m a Source

Begin exception processing.

catchError :: forall e m a. HasError e m => m a -> (e -> m a) -> m a Source

Handle exception processing.

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.

Constructors

ExceptT (m (Either e a)) 

Instances

MonadTower m => IsError e (ExceptT e m) 
MonadTrans (ExceptT e) 
MonadLevel m => ConstraintPassThrough (IsTransformer (ExceptT e)) (ListT m) True 
(Functor m, Monad m, Monoid e) => Alternative (ExceptT e m) 
Monad m => Monad (ExceptT e m) 
Functor m => Functor (ExceptT e m) 
MonadFix m => MonadFix (ExceptT e m) 
(Monad m, Monoid e) => MonadPlus (ExceptT e m) 
(Functor m, Monad m) => Applicative (ExceptT e m) 
Foldable f => Foldable (ExceptT e f) 
Traversable f => Traversable (ExceptT e f) 
(Eq e, Eq1 m) => Eq1 (ExceptT e m) 
(Ord e, Ord1 m) => Ord1 (ExceptT e m) 
(Read e, Read1 m) => Read1 (ExceptT e m) 
(Show e, Show1 m) => Show1 (ExceptT e m) 
MonadIO m => MonadIO (ExceptT e m) 
MonadTower m => MonadLevel_ (ExceptT e m) 
MonadTower m => MonadTower_ (ExceptT e m) 
(Eq e, Eq1 m, Eq a) => Eq (ExceptT e m a) 
(Ord e, Ord1 m, Ord a) => Ord (ExceptT e m a) 
(Read e, Read1 m, Read a) => Read (ExceptT e m a) 
(Show e, Show1 m, Show a) => Show (ExceptT e m a) 
type LowerMonad (ExceptT e m) = m 
type WithLower_ (ExceptT e m) = AddIG 
type AllowOtherValues (ExceptT e m) = True 
type DefaultAllowConstraints (ExceptT e m) = True 
type BaseMonad (ExceptT e m) = BaseMonad m 
type InnerValue (ExceptT e m) a = Either e a 

type HasError e m = SatisfyConstraint (IsError e) m Source

A monad stack that can throw and handle exceptions of type e.

class MonadTower m => IsError e m Source

Constraint for monads that can throw and handle exceptions.