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

Control.Monad.Exception

Synopsis

Documentation

type EM l = EMT l IdentitySource

evalEM :: EM (AnyException l) a -> Either SomeException aSource

Run a computation explicitly handling exceptions

runEM :: EM NoExceptions a -> aSource

Run a safe computation

runEMParanoid :: EM ParanoidMode a -> aSource

Run a safe computation checking even unchecked (UncaughtExceptions) exceptions

data EMT l m a Source

Instances

(Monoid w, MonadRWS r w s m) => MonadRWS r w s (EMT l m) 
MonadReader r m => MonadReader r (EMT l m) 
MonadState s m => MonadState s (EMT l m) 
(Monoid w, MonadWriter w m) => MonadWriter w (EMT l m) 
(Exception e, Throws e l, Monad m) => MonadThrow e (EMT l m) 
(Exception e, Monad m) => MonadCatch e (EMT (Caught e l) m) (EMT l m) 
MonadTrans (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) 
MonadCont m => MonadCont (EMT l m) 
(Throws SomeException l, MonadIO m) => MonadIO (EMT l m) 
Monad m => WithSrcLoc (EMT l m a) 

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

Run explicitly handling exceptions

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

Run a safe computation

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

Run a safe computation checking even unchecked (UncaughtException) exceptions

class WithSrcLoc a whereSource

Generating stack traces for exceptions

Methods

withLoc :: String -> a -> aSource

withLoc records the given source location in the exception stack trace when used to wrap a EMT computation.

On any other monad or value, withLoc is defined as the identity | hello

Instances

WithSrcLoc a 
Monad m => WithSrcLoc (EMT l m a) 

withLocTH :: Q ExpSource

withLocTH is a convenient TH macro which expands to withLoc <source location> Usage:

 f x = $withLocTH $ do