How to catch an exception
Bayley, Alistair
Alistair_Bayley@ldn.invesco.com
Mon, 21 Jul 2003 14:12:02 +0100
Trying to get the hang of exceptions...
I would expect this program:
> module Main where
> import Control.Exception hiding (GHC.Prelude.catch)
> temp :: IO ()
> temp = do
> putStrLn "line 1"
> ioError (AssertionFailed "my temp")
> handler :: Exception -> IO ()
> handler e = putStrLn ("exception: " ++ (show e))
> main :: IO ()
> main = catch temp handler
.. to output:
line 1
exception: AssertionFailed: my temp (or whatever "show" produces for the
AssertionFailed exception)
... but all I get is:
line 1
Fail: my temp
This implies that the handler is not called. So what am I doing wrong?
*****************************************************************
The information in this email and in any attachments is
confidential and intended solely for the attention and use
of the named addressee(s). This information may be
subject to legal professional or other privilege or may
otherwise be protected by work product immunity or other
legal rules. It must not be disclosed to any person without
our authority.
If you are not the intended recipient, or a person
responsible for delivering it to the intended recipient, you
are not authorised to and must not disclose, copy,
distribute, or retain this message or any part of it.
*****************************************************************