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

Safe HaskellNone

Control.Monad.Exception.Base

Description

A Monad Transformer for explicitly typed checked exceptions.

The exceptions thrown by a computation are inferred by the typechecker and appear in the type signature of the computation as Throws constraints.

Exceptions are defined using the extensible exceptions framework of Marlow (documented in Control.Exception):

  • An Extensible Dynamically-Typed Hierarchy of Exceptions, by Simon Marlow, in Haskell '06.

Example

 data DivideByZero = DivideByZero deriving (Show, Typeable)
 data SumOverflow  = SumOverflow  deriving (Show, Typeable)
 instance Exception DivideByZero
 instance Exception SumOverflow
 data Expr = Add Expr Expr | Div Expr Expr | Val Double
 eval (Val x)     = return x
 eval (Add a1 a2) = do
    v1 <- eval a1
    v2 <- eval a2
    let sum = v1 + v2
    if sum < v1 || sum < v2 then throw SumOverflow else return sum
 eval (Div a1 a2) = do
    v1 <- eval a1
    v2 <- eval a2
    if v2 == 0 then throw DivideByZero else return (v1 / v2)

GHCi infers the following types

 eval                                             :: (Throws DivideByZero l, Throws SumOverflow l) => Expr -> EM l Double
 eval `catch` \ (e::DivideByZero) -> return (-1)  :: Throws SumOverflow l => Expr -> EM l Double
 runEM(eval `catch` \ (e::SomeException) -> return (-1))
                                                  :: Expr -> Double

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) 
(Exception e, Monad m) => MonadCatch e (EMT (Caught e l) m) (EMT l m) 
Throws MonadZeroException l => MonadPlus (EM l) 
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) 
Monad m => MonadLoc (EMT l m) 

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

Run a computation explicitly handling exceptions

runEMT_gen :: forall l m a. Monad m => EMT l m a -> m aSource

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

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

The throw primitive

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

Rethrow an exception keeping the call trace

catch :: (Exception e, Monad m) => EMT (Caught e l) m a -> (e -> EMT l m a) -> EMT l m aSource

The catch primitive

catchWithSrcLoc :: (Exception e, Monad m) => EMT (Caught e l) m a -> (CallTrace -> e -> EMT l m a) -> EMT l m aSource

Like catch but makes the call trace available

finally :: Monad m => EMT l m a -> EMT l m b -> EMT l m aSource

Sequence two computations discarding the result of the second one. If the first computation rises an exception, the second computation is run and then the exception is rethrown.

onException :: Monad m => EMT l m a -> EMT l m b -> EMT l m aSource

Like finally, but performs the second computation only when the first one rises an exception

bracketSource

Arguments

:: Monad m 
=> EMT l m a

acquire resource

-> (a -> EMT l m b)

release resource

-> (a -> EMT l m c)

computation

-> EMT l m c 

wrapException :: (Exception e, Throws e' l, Monad m) => (e -> e') -> EMT (Caught e l) m a -> EMT l m aSource

Capture an exception e, wrap it, and rethrow. Keeps the original monadic 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 IdentitySource

A monad of explicitly typed, checked exceptions

tryEM :: EM AnyException 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 computation checking even unchecked (UncaughtExceptions) exceptions

data FailException Source

FailException is thrown by Monad fail

Constructors

FailException String 

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

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

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