Next Previous Contents

6. Exception

The Exception library provides an interface for raising and catching both built-in and user defined exceptions.

Exceptions are defined by the following (non-abstract) datatype:

data Exception
  = IOException         IOError         -- IO exceptions (from 'fail')
  | ArithException      ArithException  -- Arithmetic exceptions
  | ErrorCall           String          -- Calls to 'error'
  | NoMethodError       String          -- A non-existent method was invoked
  | PatternMatchFail    String          -- A pattern match failed
  | NonExhaustiveGuards String          -- A guard match failed
  | RecSelError         String          -- Selecting a non-existent field
  | RecConError         String          -- Field missing in record construction
  | RecUpdError         String          -- Record doesn't contain updated field
  | AssertionFailed     String          -- Assertions
  | DynException        Dynamic         -- Dynamic exceptions
  | AsyncException      AsyncException  -- Externally generated errors

instance Eq   Exception
instance Ord  Exception
instance Show Exception

data ArithException
  = Overflow
  | Underflow
  | LossOfPrecision
  | DivideByZero
  | Denormal

instance Eq   ArithError
instance Ord  ArithError
instance Show ArithError

data AsyncException
  = StackOverflow
  | HeapOverflow
  | ThreadKilled
  deriving (Eq, Ord)

instance Eq   AsyncException
instance Ord  AsyncException
instance Show AsyncException

An implementation should raise the appropriate exception when one of the above conditions arises. Note: GHC currently doesn't generate the arithmetic or the async exceptions.

Exceptions may be thrown explicitly from anywhere:

throw :: Exception -> a

6.1 The try functions

There are several functions for catching and examining exceptions; all of them may only be used from within the IO monad. Firstly the try family of functions:

tryAll    :: a    -> IO (Either Exception a)
tryAllIO  :: IO a -> IO (Either Exception a)
try       :: (Exception -> Maybe b) -> a    -> IO (Either b a)
tryIO     :: (Exception -> Maybe b) -> IO a -> IO (Either b a)

The simplest version is tryAll. It takes a single argument, evaluates it (as if you'd applied seq to it), and returns either Right a if the evaluation succeeded with result a, or Left e if an exception was raised, where e is the exception. Note that due to Haskell's unspecified evaluation order, an expression may return one of several possible exceptions: consider the expression error "urk" + 1 `div` 0. Does tryAll return Just (ErrorCall "urk") or Just (ArithError DivideByZero)? The answer is "either": tryAll makes a non-deterministic choice about which exception to return. If you call it again, you might get a different exception back. This is ok, because tryAll is an IO computation.

tryAllIO is the same as tryAll except that the argument to evaluate is an IO computation. Don't try to use tryAll to catch exceptions in IO computations: in GHC an expression of type IO a is in fact a function, so evaluating it does nothing at all (and therefore raises no exceptions). Hence the need for tryAllIO, which runs IO computations properly.

The functions try and tryIO take an extra argument which is an exception predicate, a function which selects which type of exceptions we're interested in. The full set of exception predicates is given below:

justIoErrors            :: Exception -> Maybe IOError
justArithExceptions     :: Exception -> Maybe ArithException
justErrors              :: Exception -> Maybe String
justDynExceptions       :: Exception -> Maybe Dynamic
justAssertions          :: Exception -> Maybe String
justAsyncExceptions     :: Exception -> Maybe AsyncException

For example, to catch just calls to 'error' we could use something like

    result <- try justErrors thing_to_try

Any other exceptions which aren't matched by the predicate are re-raised, and may be caught by an enclosing try or catch.

6.2 The catch functions

The catch family is similar to the try family:

catchAll   :: a    -> (Exception -> IO a) -> IO a
catchAllIO :: IO a -> (Exception -> IO a) -> IO a
catch      :: (Exception -> Maybe b) -> a    -> (b -> IO a) -> IO a
catchIO    :: (Exception -> Maybe b) -> IO a -> (b -> IO a) -> IO a

The difference is that instead of returning an Either type as the result, the catch functions take a handler argument which is invoked in the case that an exception was raised while evaluating the first argument.

catch and catchIO take exception predicate arguments in the same way as try and tryIO.

Note that catchIO justIoErrors is identical to IO.catch. In fact, the implementation of IO errors in GHC uses exceptions "under the hood".

Also, don't forget to import Prelude hidiing (catch) when using this library, to avoid the name clash between Exception.catch and IO.catch.

6.3 Dynamic Exceptions

Because the Exception datatype isn't extendible, we added an interface for throwing and catching exceptions of type Dynamic (see Section Dynamic), which allows exception values of any type in the Typeable class to be thrown and caught.

throwDyn :: Typeable exception => exception -> b
catchDyn :: Typeable exception => IO a -> (exception -> IO a) -> IO a

The catchDyn function only catches exceptions of the required type; all other exceptions are re-thrown as with catchIO and friends above.

6.4 Other Utilities

The bracket functions are useful for making sure that resources are released properly by code that may raise exceptions:

        bracket         :: IO a -> (a -> IO b) -> (a -> IO c) -> IO c
        bracket_        :: IO a -> IO b -> IO c -> IO c
        finally         :: IO a -> IO b -> IO b

For example, to open a file, do some work on it and then close it again, we might use something like:

process_file = bracket (openFile "filename") closeFile 
               (do 
                 ...
                )

bracket works as follows: it executes its first argument ("open"), then its third argument, followed finally by its second argument ("close"). If the third argument happened to raise an exception, then the close operation will still be performed, and the exception will be re-raised.

This means that in the example above the file will always be closed, even if an error occurs during processing.

The arguments to bracket are in this order so that we can partially apply it, like:

withFile name = bracket (openFile name) closeFile

The bracket_ function is a variant of bracket that throws away the result of the open, and finally is an even simpler version where we just want some closing code.


Next Previous Contents