How do I create dynamic exceptions

Bayley, Alistair Alistair_Bayley@ldn.invesco.com
Tue, 22 Jul 2003 14:59:12 +0100


> The documentation for Data.Dynamic is pretty clear for this and I
> believe with GHC6 you can derive Typeable.
> 
> {-# NOINLINE myExceptionTyCon #-}
> -- the documentation suggests a fully qualified name
> myExceptionTyCon = mkTyCon "MyException" 
> 
> instance Typeable MyException where
>     typeOf _ = mkAppTy myExceptionTyCon []
> 


I disagree that the docs are clear. I could see that I needed a value of
type TypeRep (a datatype with no constructors - so I can't create one
directly), and also the mkApplyTy, mkFunTy, and applyTy functions, but it
wasn't clear how to use them to get a TypeRep (which one do I use? and
how?). An example like this is more helpful. Is there somewhere else I could
have read about this? (I took a quick look at the wiki first.)

I should have realised I could derive Typeable with ghc6; there was an itch
in the back of my brain (now I remember reading about deriving Typeable in
ghc6) that was trying to tell me there was an easy way...


This is what I have at present, but it still doesn't catch the exception:

> module Main where
> import Prelude hiding (catch)
> import Control.Exception
> import Data.Dynamic

> data MyException = MkExc Int String
>    deriving Typeable

> mkErr :: Int -> String -> MyException
> mkErr n s = MkExc n s

> temp :: IO ()
> temp = do
>   putStrLn "line 1"
>   throwIO (DynException (toDyn (mkErr 2 "my temp")))

> handler :: Dynamic -> IO ()
> handler e = do
>   case (fromDynamic e) of
>    Nothing -> putStrLn ("dynamic cast failed")
>    Just (MkExc n s) -> putStrLn ("exception: " ++ (show n) ++ " " ++ s)

> main :: IO ()
> main = catchDyn temp handler


*****************************************************************
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.
*****************************************************************