[Haskell-cafe] GADT and problems with rigid type variables

Felipe Lessa felipe.lessa at gmail.com
Sun Aug 22 18:50:28 EDT 2010


On Sun, Aug 22, 2010 at 7:47 PM, Daniel Peebles <pumpkingod at gmail.com> wrote:
> You could also do some (in my opinion) fairly nasty stuff with
> Dynamic or Typeable, adding a constraint to the Eq and
> attempting to cast at runtime (returning False if the cast
> returns Nothing).

This is what he's talking about:

> {-# LANGUAGE GADTs #-}
>
> import Data.Typeable (Typeable, cast)
>
> data Foo where
>  Foo :: (Typeable t, Eq t) => t -> Foo
>
> instance Eq Foo where
>  (Foo a) == (Foo b) = maybe False (== b) (cast a)

Cheers,

--
Felipe.


More information about the Haskell-Cafe mailing list