Existentials

Simon Marlow simonmar@microsoft.com
Thu, 17 Apr 2003 12:05:38 +0100


=20
> "Simon Peyton-Jones" <simonpj@microsoft.com> writes:
>=20
> > GHC and Hugs both do.  In fact, GHC supports arbitrary-rank=20
> universal
> > quantification.
>=20
> The example I tried failed, so I assumed it wasn't supported.
>=20
>     $ cat Exists.hs
>         module Exists where
>         data T =3D forall a. Enum a =3D> Foo (a->a)
>         f :: T -> (Int,Bool,Char)
>         f (Foo g) =3D (g 0, g False, g 'a')
>     $ ghc -fglasgow-exts -c Exists.hs
>=20
>     Exists.hs:4:
>         Couldn't match `Int' against `Bool'
>             Expected type: Int
>             Inferred type: Bool
>         In the first argument of `g', namely `False'
>         In the definition of `f': (g 0, g False, g 'a')

You've written an existential constructor.  For universal
quantification, write it like this:

   data T =3D Foo (forall a . Enum a =3D> a -> a)

a good illustration of the confusion caused by the dual use of forall, I
guess :-)

Cheers,
	Simon