ether-0.3.0.0: Monad transformers and classes

Safe HaskellNone
LanguageHaskell2010

Control.Monad.Trans.Ether.Except

Contents

Description

Synopsis

The Except monad

type Except tag e = ExceptT tag e Identity Source

The parameterizable exception monad.

Computations are either exceptions or normal values.

The return function returns a normal value, while >>= exits on the first exception.

except :: Monad m => proxy tag -> Either e a -> ExceptT tag e m a Source

Constructor for computations in the exception monad (the inverse of runExcept).

runExcept :: proxy tag -> Except tag e a -> Either e a Source

Runs an Except and returns either an exception or a normal value.

The ExceptT monad transformer

data ExceptT tag e m a Source

The exception monad transformer.

The return function returns a normal value, while >>= exits on the first exception.

Instances

MonadState tag s m => MonadState tag s (ExceptT tag' e m) 
Monad m => MonadExcept tag e (ExceptT tag e m) 
MonadBase b m => MonadBase b (ExceptT tag e m) 
MonadBaseControl b m => MonadBaseControl b (ExceptT tag e m) 
MonadError e' m => MonadError e' (ExceptT tag e m) 
MonadReader r m => MonadReader r (ExceptT tag e m) 
MonadState s m => MonadState s (ExceptT tag e m) 
MonadWriter w m => MonadWriter w (ExceptT tag e m) 
MFunctor (ExceptT tag e) 
MMonad (ExceptT tag e) 
MonadTrans (ExceptT tag e) 
MonadTransControl (ExceptT tag e) 
LiftLocal (ExceptT tag e) 
LiftCallCC (ExceptT tag e) 
LiftPass (ExceptT tag e) 
LiftListen (ExceptT tag e) 
LiftCatch (ExceptT tag e) 
(Monad m, Functor m, Monoid e) => Alternative (ExceptT tag e m) 
Monad m => Monad (ExceptT tag e m) 
Functor m => Functor (ExceptT tag e m) 
MonadFix m => MonadFix (ExceptT tag e m) 
(Monad m, Monoid e) => MonadPlus (ExceptT tag e m) 
(Monad m, Functor m) => Applicative (ExceptT tag e m) 
MonadIO m => MonadIO (ExceptT tag e m) 
MonadCont m => MonadCont (ExceptT tag e m) 
Taggable (ExceptT tag e m) 
Tagged (ExceptT tag e m) tag 
Generic (ExceptT tag e m a) 
Newtype (ExceptT tag e m a) 
type StT (ExceptT tag e) a = StT (ExceptT e) a 
type StT (ExceptT tag e) a = StT (ExceptT tag e) a 
type Untagged (ExceptT tag e m) = ExceptT e m 
type Tag (ExceptT tag e m) = Just * tag 
type Inner (ExceptT tag e m) = Just (* -> *) m 
type StM (ExceptT tag e m) a = ComposeSt (ExceptT tag e) m a 
type Rep (ExceptT tag e m a) 
type O (ExceptT tag e m a) = GO (Rep (ExceptT tag e m a)) 

exceptT :: proxy tag -> m (Either e a) -> ExceptT tag e m a Source

Constructor for computations in the exception monad transformer.

runExceptT :: proxy tag -> ExceptT tag e m a -> m (Either e a) Source

Runs an ExceptT and returns either an exception or a normal value.

Exception operations

throw :: Monad m => proxy tag -> e -> ExceptT tag e m a Source

Is used within a monadic computation to begin exception processing.

catch :: Monad m => proxy tag -> ExceptT tag e m a -> (e -> ExceptT tag e m a) -> ExceptT tag e m a Source

A handler function to handle previous exceptions and return to normal execution.