| Safe Haskell | None |
|---|
Control.Monad.Interface.Exception
Contents
Description
This module exports:
- The
MonadExceptiontype class and its operationsthrowandcatch. - Instances of
MonadExceptionforIO,Either,STMand theErrorTmonad transformer from thetransformerspackage. - An orphan instance of
Errorfor theSomeExceptiontype: this is a necessary hack in order to makeErrorTan instance ofMonadException. - A universal pass-through instance of
MonadExceptionfor any existingMonadExceptionwrapped by aMonadLayerControl. - The utility operations
catches,catchJust,handle,handleJust,tryandtryJust.
- class Monad m => MonadException m where
- catches :: MonadException m => m a -> [Handler m a] -> m a
- data Handler m a = forall e . Exception e => Handler (e -> m a)
- catchJust :: (MonadException m, Exception e) => (e -> Maybe b) -> m a -> (b -> m a) -> m a
- handle :: (MonadException m, Exception e) => (e -> m a) -> m a -> m a
- handleJust :: (MonadException m, Exception e) => (e -> Maybe b) -> (b -> m a) -> m a -> m a
- try :: (MonadException m, Exception e) => m a -> m (Either e a)
- tryJust :: (MonadException m, Exception e) => (e -> Maybe b) -> m a -> m (Either b a)
- data SomeException
The MonadException class
class Monad m => MonadException m whereSource
The MonadException type class represents the class of monads which can
throw and catch exceptions. This includes IO-based monads as well as
Either-like monads.
Methods
throw :: Exception e => e -> m aSource
Throw an exception that can be caught by the monad m.
catch :: Exception e => m a -> (e -> m a) -> m aSource
This is the simplest of the exception-catching functions. It takes a single argument, runs it, and if an exception is raised the "handler" is executed, with the value of the exception passed as an argument. Otherwise, the result is returned as normal. For example:
catch (readFile f) (\(e :: IOException) -> do
hPutStr stderr ("Warning: Couldn't open " ++ f ++ ": " ++ show e)
return "")
Note that we have to give a type signature to e, or the program will not typecheck as the type is ambiguous. While it is possible to catch exceptions of any type, see the section "Catching all exceptions" in Control.Exception for an explanation of the problems with doing so.
For catching exceptions in pure (non-IO) expressions, see the function evaluate.
Note that due to Haskell's unspecified evaluation order, an expression
may throw one of several possible exceptions: consider the expression
(error "urk") + (1 . Does the expression throw
div 0)ErrorCall "urk", or DivideByZero?
The answer is "it might throw either"; the choice is
non-deterministic. If you are catching any type of exception then you
might catch either. If you are calling catch with type
m Int -> (ArithException -> m Int) -> m Int then the handler may get
run with DivideByZero as an argument, or an ErrorCall "urk"
exception may be propogated further up. If you call it again, you might
get a the opposite behaviour. This is ok, because catch is a monadic
computation.
Instances
| MonadException IO | |
| (MonadLayerControl m, MonadException (Inner m)) => MonadException m | |
| MonadException STM | |
| ~ * e SomeException => MonadException (Either e) | |
| (~ * e SomeException, Monad m) => MonadException (ErrorT e m) | |
| (MonadException f, MonadException g) => MonadException (Product f g) |
catches :: MonadException m => m a -> [Handler m a] -> m aSource
Sometimes you want to catch two different sorts of exception. You could do something like
f = expr `catch` \(ex :: ArithException) -> handleArith ex
`catch` \(ex :: IOException) -> handleIO ex
However, there are a couple of problems with this approach. The first is
that having two exception handlers is inefficient. However, the more
serious issue is that the second exception handler will catch exceptions
in the first, e.g. in the example above, if handleArith throws an
IOException then the second exception handler will catch it.
Instead, we provide a function catches, which would be used thus:
f = expr `catches` [Handler (\ (ex :: ArithException) -> handleArith ex),
Handler (\ (ex :: IOException) -> handleIO ex)]
You need this when using catches.
catchJust :: (MonadException m, Exception e) => (e -> Maybe b) -> m a -> (b -> m a) -> m aSource
The function catchJust is like catch, but it takes an extra argument
which is an exception predicate, a function which selects which type of
exceptions we're interested in.
catchJust (\e -> if isDoesNotExistErrorType (ioeGetErrorType e)
then Just ()
else Nothing)
(readFile f)
(\_ -> do
hPutStrLn stderr ("No such file: " ++ show f)
return "")
Any other exceptions which are not matched by the predicate are re-raised,
and may be caught by an enclosing catch, catchJust, etc.
handle :: (MonadException m, Exception e) => (e -> m a) -> m a -> m aSource
A version of catch with the arguments swapped around; useful in
situations where the code for the handler is shorter. For example:
do handle (\NonTermination -> exitWith (ExitFailure 1)) $
...
handleJust :: (MonadException m, Exception e) => (e -> Maybe b) -> (b -> m a) -> m a -> m aSource
try :: (MonadException m, Exception e) => m a -> m (Either e a)Source
Similar to catch, but returns an Either result which is (
if no exception of type Right a)e was raised, or ( if an exception of
type Left ex)e was raised and its value is ex. If any other type of exception
is raised than it will be propogated up to the next enclosing exception
handler.
try a = catch (Right `liftM` a) (return . Left)
data SomeException
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.
Instances
| Show SomeException | |
| Typeable SomeException | |
| Exception SomeException | |
| Error SomeException | Cheeky orphan instance of |