dynamics on polymorphic datatype

Hal Daume t-hald@microsoft.com
Sat, 26 Jul 2003 12:06:51 -0700


If you only ever want to use dynamics on 'forall a. Foo a's, you can
say:

> module Foo where
> import Data.Dynamic
> data Foo a =3D Foo a
> trFoo =3D mkTyCon "Foo"
> forall_a =3D mkTyCon "a"
> instance Typeable (Foo a) where
>     typeOf (x :: Foo a) =3D mkAppTy trFoo [mkAppTy forall_a []]

You can use this:

*Foo> typeOf (undefined :: Foo a)
Foo a

You can even introduce (so long as you have
-fallow-overlapping-instances) specific other instances:

> instance Typeable (Foo Int) where
>     typeOf _ =3D mkAppTy trFoo [typeOf (undefined :: Int)]
> instance Typeable (Foo Bool) where
>     typeOf _ =3D mkAppTy trFoo [typeOf (undefined :: Bool)]

But sadly you cannot use the original then:

*Foo> typeOf (undefined :: Foo Int)
Foo Int
*Foo> typeOf (undefined :: Foo Bool)
Foo Bool
*Foo> typeOf (undefined :: Foo a)

<interactive>:1:
    No instance for (Typeable (Foo a))
      arising from use of `typeOf' at <interactive>:1
    In the definition of `it':
	it =3D typeOf (undefined :: forall a. Foo a)


i'm not sure why this happens (someone who knows the type system better
than me can probably tell me).  my guess is: it doesn't know what 'a'
is, so it doesn't know whether to choose the generic instance or one of
the overlapped instances (in case 'a' happened to be Int)...this seems
to take away a lot of the power of overlapping instances, which i always
saw as being able to define a "default" case.

however, if you try something you haven't written an instance of, you do
get this default case:

*Foo> typeOf (undefined :: Foo Double)
Foo a

so, it kind of depends on what you want.  probably you want exactly what
didn't work; perhaps someone else has a more ingenious solution than
mine...

 - hal


 --
 Hal Daume III                                   | hdaume@isi.edu
 "Arrest this man, he talks in maths."           | www.isi.edu/~hdaume


> -----Original Message-----
> From: haskell-admin@haskell.org=20
> [mailto:haskell-admin@haskell.org] On Behalf Of Wang Meng
> Sent: Friday, July 25, 2003 9:13 PM
> To: haskell@haskell.org
> Subject: dynamics on polymorphic datatype
>=20
>=20
> Hi All,
>=20
> I am trying to perform dynamic casting on polymorphic types.
> Let's say I have a data type like:
>=20
> > data Foo a =3D Foo a
>=20
> Is there any way to use dynamics to convert a value of type Foo a to a
> type reprentation? I try to use the toDyn in the dynamic libray, it
> complains for ambigours a. Is there a solution to it?
>=20
> Thank you very much.
>=20
>=20
>  -W-M-
>   @ @
>    |
>   \_/
>=20
>=20
> _______________________________________________
> Haskell mailing list
> Haskell@haskell.org
> http://www.haskell.org/mailman/listinfo/haskell
>=20