ether-0.5.1.0: Monad transformers and classes

Safe HaskellNone
LanguageHaskell2010

Ether.Except

Contents

Synopsis

MonadExcept class

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

Minimal complete definition

throw, catch

Methods

throw :: e -> m a Source #

Is used within a monadic computation to begin exception processing.

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

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

Instances

(LiftCatch t, Monad (t m), MonadExcept k tag e m) => MonadExcept k tag e (t m) Source # 

Methods

throw :: t m -> m a Source #

catch :: m a -> (t m -> m a) -> m a Source #

(MonadExcept k1 tNew e m, (~) ((* -> *) -> * -> *) trans (IdentityT *)) => MonadExcept k tOld e (TaggedTrans * (* -> *) * (TAG_REPLACE k1 k tOld tNew) trans m) Source # 

Methods

throw :: TaggedTrans * (* -> *) * (TAG_REPLACE k1 k tOld tNew) trans m -> m a Source #

catch :: m a -> (TaggedTrans * (* -> *) * (TAG_REPLACE k1 k tOld tNew) trans m -> m a) -> m a Source #

throw :: MonadExcept tag e m => e -> m a Source #

Is used within a monadic computation to begin exception processing.

catch :: MonadExcept tag e m => m a -> (e -> m a) -> m a Source #

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

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 :: forall tag e a. Except tag e a -> Either e a Source #

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

The ExceptT monad transformer

type ExceptT tag e = TaggedTrans (TAGGED EXCEPT tag) (ExceptT e) Source #

The exception monad transformer.

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

exceptT :: forall tag e m a. m (Either e a) -> ExceptT tag e m a Source #

Constructor for computations in the exception monad transformer.

runExceptT :: forall tag e m a. ExceptT tag e m a -> m (Either e a) Source #

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

MonadExcept class (implicit)

throw' :: forall e m a. MonadExcept' e m => e -> m a Source #

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

The Except monad (implicit)

type Except' e = Except e e Source #

The ExceptT monad transformer (implicit)

type ExceptT' e = ExceptT e e Source #

exceptT' :: m (Either e a) -> ExceptT' e m a Source #

runExceptT' :: ExceptT' e m a -> m (Either e a) Source #

Internal labels

data TAGGED e t Source #

data EXCEPT Source #

Encode type-level information for ExceptT.

Instances

Handle * * EXCEPT e (ExceptT e) Source # 

Methods

handling :: Monad m => (HandleConstraint EXCEPT e (ExceptT e) p trans m -> r) -> r Source #

type HandleSuper kp * EXCEPT e trans Source # 
type HandleSuper kp * EXCEPT e trans = ()
type HandleConstraint * * EXCEPT e trans m Source # 
type HandleConstraint * * EXCEPT e trans m = MonadError e (trans m)