Safe Haskell | Trustworthy |
---|---|
Language | Haskell98 |
Exception routines much like the IO
ones in Control.Exception (we
duplicate the documentation below). There are two differences,
however. First, LIO does not allow masking of asynchronous exceptions
(since these are relied upon to kill a misbehaving thread). Hence,
routines like onException
are not guaranteed to run if a thread is
unconditionally killed. Second, in a few cases (such as lWait
) it
is possible for the current label to be raised above the current
clearance as an exception is thrown, in which case these functions do
not catch the exception, either, since code cannot run under such
circumstances.
- class (Typeable * e, Show e) => Exception e where
- toException :: e -> SomeException
- fromException :: SomeException -> Maybe e
- displayException :: e -> String
- data SomeException :: * where
- throwLIO :: Exception e => e -> LIO l a
- catch :: (Label l, Exception e) => LIO l a -> (e -> LIO l a) -> LIO l a
- handle :: (Label l, Exception e) => (e -> LIO l a) -> LIO l a -> LIO l a
- try :: (Label l, Exception a1) => LIO l a -> LIO l (Either a1 a)
- onException :: Label l => LIO l a -> LIO l b -> LIO l a
- finally :: Label l => LIO l a -> LIO l b -> LIO l a
- bracket :: Label l => LIO l a -> (a -> LIO l c) -> (a -> LIO l b) -> LIO l b
- evaluate :: a -> LIO l a
Documentation
class (Typeable * e, Show e) => Exception e where #
Any type that you wish to throw or catch as an exception must be an
instance of the Exception
class. The simplest case is a new exception
type directly below the root:
data MyException = ThisException | ThatException deriving (Show, Typeable) instance Exception MyException
The default method definitions in the Exception
class do what we need
in this case. You can now throw and catch ThisException
and
ThatException
as exceptions:
*Main> throw ThisException `catch` \e -> putStrLn ("Caught " ++ show (e :: MyException)) Caught ThisException
In more complicated examples, you may wish to define a whole hierarchy of exceptions:
--------------------------------------------------------------------- -- Make the root exception type for all the exceptions in a compiler data SomeCompilerException = forall e . Exception e => SomeCompilerException e deriving Typeable instance Show SomeCompilerException where show (SomeCompilerException e) = show e instance Exception SomeCompilerException compilerExceptionToException :: Exception e => e -> SomeException compilerExceptionToException = toException . SomeCompilerException compilerExceptionFromException :: Exception e => SomeException -> Maybe e compilerExceptionFromException x = do SomeCompilerException a <- fromException x cast a --------------------------------------------------------------------- -- Make a subhierarchy for exceptions in the frontend of the compiler data SomeFrontendException = forall e . Exception e => SomeFrontendException e deriving Typeable instance Show SomeFrontendException where show (SomeFrontendException e) = show e instance Exception SomeFrontendException where toException = compilerExceptionToException fromException = compilerExceptionFromException frontendExceptionToException :: Exception e => e -> SomeException frontendExceptionToException = toException . SomeFrontendException frontendExceptionFromException :: Exception e => SomeException -> Maybe e frontendExceptionFromException x = do SomeFrontendException a <- fromException x cast a --------------------------------------------------------------------- -- Make an exception type for a particular frontend compiler exception data MismatchedParentheses = MismatchedParentheses deriving (Typeable, Show) instance Exception MismatchedParentheses where toException = frontendExceptionToException fromException = frontendExceptionFromException
We can now catch a MismatchedParentheses
exception as
MismatchedParentheses
, SomeFrontendException
or
SomeCompilerException
, but not other types, e.g. IOException
:
*Main> throw MismatchedParenthesescatch
e -> putStrLn ("Caught " ++ show (e :: MismatchedParentheses)) Caught MismatchedParentheses *Main> throw MismatchedParenthesescatch
e -> putStrLn ("Caught " ++ show (e :: SomeFrontendException)) Caught MismatchedParentheses *Main> throw MismatchedParenthesescatch
e -> putStrLn ("Caught " ++ show (e :: SomeCompilerException)) Caught MismatchedParentheses *Main> throw MismatchedParenthesescatch
e -> putStrLn ("Caught " ++ show (e :: IOException)) *** Exception: MismatchedParentheses
Nothing
data SomeException :: * where #
The SomeException
type is the root of the exception type hierarchy.
When an exception of type e
is thrown, behind the scenes it is
encapsulated in a SomeException
.
catch :: (Label l, Exception e) => LIO l a -> (e -> LIO l a) -> LIO l a Source #
A simple wrapper around IO catch. The only subtlety is that code
is not allowed to run unless the current label can flow to the
current clearance. Hence, if the label exceeds the clearance, the
exception is not caught. (Only a few conditions such as lWait
or
raising the clearance within scopeClearance
can lead to the label
exceeding the clarance, and an exception is always thrown at the
time this happens.)
handle :: (Label l, Exception e) => (e -> LIO l a) -> LIO l a -> LIO l a Source #
A version of catch
with the arguments swapped around.
onException :: Label l => LIO l a -> LIO l b -> LIO l a Source #
Like finally
, but only performs the final action if there was
an exception raised by the computation.
finally :: Label l => LIO l a -> LIO l b -> LIO l a Source #
A variant of bracket
where the return value from the first
computation is not required.
:: Label l | |
=> LIO l a | Computation to run first |
-> (a -> LIO l c) | Computation to run last |
-> (a -> LIO l b) | Computation to run in-between |
-> LIO l b |
When you want to acquire a resource, do some work with it, and
then release the resource, it is a good idea to use bracket
,
because bracket will install the necessary exception handler to
release the resource in the event that an exception is raised
during the computation. If an exception is raised, then bracket
will re-raise the exception (after performing the release).