ether-0.3.1.0: Monad transformers and classes

Safe HaskellNone
LanguageHaskell2010

Control.Monad.Ether.Except

Contents

Description

Synopsis

MonadExcept class

class Monad m => MonadExcept tag e m | m tag -> e where Source

Methods

throw :: proxy tag -> e -> m a Source

Is used within a monadic computation to begin exception processing.

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

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

Instances

(LiftCatch t, Monad (t m), MonadExcept tag e m) => MonadExcept tag e (t m) Source 
MonadExcept tag e m => MonadExcept tag e (WrappedEther tag' m) Source 
Monad m => MonadExcept tag e (ExceptT tag e m) Source 

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.

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

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

Handle functions

handleT :: Functor m => proxy tag -> (e -> a) -> ExceptT tag e m a -> m a Source

Runs an ExceptT and handles the exception with the given function.

handle :: proxy tag -> (e -> a) -> Except tag e a -> a Source

Runs an Except and handles the exception with the given function.