control-monad-exception-0.11.2: Explicitly typed, checked exceptions with stack traces

Safe HaskellNone
LanguageHaskell98

Control.Monad.Exception.Base

Synopsis

Documentation

newtype EMT l m a Source

A Monad Transformer for explicitly typed checked exceptions.

Constructors

EMT 

Fields

unEMT :: m (Either (CallTrace, CheckedException l) a)
 

Instances

(Exception e, Throws e l, Monad m) => Failure e (EMT l m) 
MonadBase b m => MonadBase b (EMT l m) 
MonadBaseControl b m => MonadBaseControl b (EMT l m) 
(Exception e, MonadBaseControl IO m) => MonadCatch e (EMT (Caught e l) m) (EMT l m) 
(Exception e, Monad m) => MonadCatch e (EMT (Caught e l) m) (EMT l m) 
Throws MonadZeroException l => Alternative (EM l) 
Throws MonadZeroException l => MonadPlus (EM l) 
MonadTrans (EMT l) 
MonadTransControl (EMT l) 
Monad m => Monad (EMT l m) 
Monad m => Functor (EMT l m) 
MonadFix m => MonadFix (EMT l m) 
Monad m => Applicative (EMT l m) 
Monad m => MonadLoc (EMT l m) 
MonadIO m => MonadIO (EMT l m) 
type StT (EMT l) a = Either (CallTrace, CheckedException l) a 
type StM (EMT l m) a = ComposeSt (EMT l) m a 

tryEMT :: Monad m => EMT AnyException m a -> m (Either SomeException a) Source

Run a computation explicitly handling exceptions

runEMTGen :: forall l m a. Monad m => EMT l m a -> m a Source

runEMT :: Monad m => EMT NoExceptions m a -> m a Source

Run a safe computation

runEMTParanoid :: Monad m => EMT ParanoidMode m a -> m a Source

Run a safe computation checking even unchecked (UncaughtException) exceptions

throw :: (Exception e, Throws e l, Monad m) => e -> EMT l m a Source

The throw primitive

rethrow :: (Throws e l, Monad m) => CallTrace -> e -> EMT l m a Source

Rethrow an exception keeping the call trace

class Exception e => UncaughtException e Source

UncaughtException models unchecked exceptions

In order to declare an unchecked exception E, all that is needed is to make e an instance of UncaughtException

instance UncaughtException E

Note that declaring an exception E as unchecked does not automatically turn its children unchecked too. This is a shortcoming of the current encoding.

type EM l = EMT l Identity Source

A monad of explicitly typed, checked exceptions

tryEM :: EM AnyException a -> Either SomeException a Source

Run a computation explicitly handling exceptions

runEM :: EM NoExceptions a -> a Source

Run a safe computation

runEMParanoid :: EM ParanoidMode a -> a Source

Run a computation checking even unchecked (UncaughtExceptions) exceptions

data FailException Source

FailException is thrown by Monad fail

Constructors

FailException String 

data MonadZeroException Source

MonadZeroException is thrown by MonadPlus mzero

Constructors

MonadZeroException 

mplusDefault :: Monad m => EMT l m a -> EMT l m a -> EMT l m a Source

This function may be used as a value for mplus in MonadPlus

mapLeft :: (a -> b) -> Either a r -> Either b r Source