Dynamic types: GHCI works, GHC doesn't?

Andre Pang andrep@cse.unsw.EDU.AU
Sun, 2 Jun 2002 12:11:49 +1000


On Sat, Jun 01, 2002 at 07:56:39PM +0100, Alastair Reid wrote:

> Your Typeable instance looks like this:
> 
> > instance Typeable FootnoteData where
> >    typeOf _ = mkAppTy (mkTyCon "FootnoteData") [typeOf ("Foo" :: String), typeOf (7 :: Int)]
> 
> This should be written:
> 
> > instance Typeable FootnoteData where
> >    typeOf _ = mkAppTy fdtc [typeOf ("Foo" :: String), typeOf (7 :: Int)]
> >
> > fdtc = mkTyCon "FootnoteData"
> 
> That is, the TyCon definition has to be a CAF (i.e., a top level
> definition with no arguments).  The reason is somewhat grubby but
> comes down to 'things go much faster if you do this').  

I see, thanks.  I'll try to update the documentation with this
note.

> While we're at it, I'd like to repeat my request that the word
> 'unsafe' be made part of the classname Typeable or the method name
> typeOf.  The reason is that a badly written Typeable definition can
> break typesafety.  Here's a superficially plausible but broken 
> instance for IO which demonstrates it
> 
> > instance Typeable (IO a) where
> >    typeOf _ = mkAppTy iotc []
> >
> > iotc = mkTyCon "IO"
> 
> With this definition
> 
>   typeOf (return 1 :: IO Int) == typeOf (return () :: IO ())
> 
> and so you can coerce back and forth between these types using
> from/toDynamic.

Ahem, this is what I actually did to get my Dynamic types working
in the first place (oops) :).  mkAppTy was being given an empty
list of TypeReps, since I was confused about how to generate
those TypeReps.

It would be much neater if you could do something like

    instance Typeable Foo where
       typeOf _ = mkAppTy constructor [Char, Char, Int]

This is what I expected the Dynamic module interface would look
like, since when do you "typeOf 'a'" in GHCI, it does reply with
"Char".

I guess a possible workaround would be something like

    charT = typeOf ('a' :: Char)

    intT = typeOf (69 :: Int)

    instance Typeable Foo where
       typeOf _ = mkAppTy constructor [charT, charT, intT]

which is what I'm doing right now.  Maybe these type definitions
can go into the Dynamic module itself?


-- 
#ozone/algorithm <andrep@cse.unsw.EDU.AU>          - b.sc (comp. sci+psych)