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

Markus Barenhoff alios at alios.org
Sun Aug 22 18:36:06 EDT 2010


Hello,
playing with GADTs I ran into a problem with rigid type variables
which is ilustrated by the following example. I think it should be
pretty clear what I'am trying to express... Any suggestions?

---- snip ----
{-# LANGUAGE GADTs #-}

data Foo where
  Foo :: (Eq t) => t -> Foo

instance Eq Foo where
  (Foo a) == (Foo b) = a == b

{-
Scratch.hs:7:28:
    Couldn't match expected type `t' against inferred type `t1'
      `t' is a rigid type variable bound by
          the constructor `Foo' at /home/alios/src/lab/Scratch.hs:7:3
      `t1' is a rigid type variable bound by
           the constructor `Foo' at /home/alios/src/lab/Scratch.hs:7:14
    In the second argument of `(==)', namely `b'
    In the expression: a == b
    In the definition of `==': (Foo a) == (Foo b) = a == b
Failed, modules loaded: none.
-}
---- snip ----

thnx
Markus


More information about the Haskell-Cafe mailing list