Possible bug with GADTs?

Andrea Vezzosi sanzhiyan at gmail.com
Wed Aug 18 06:02:20 EDT 2010


On Tue, Aug 17, 2010 at 8:54 PM, Dan Knapp <dankna at gmail.com> wrote:
> Below, please find a snippet from a program I'm working on, and the
> error it produces.  I was told in #haskell that this was "pretty
> suspect" and could conceivably be a ghc bug.  So I'm reporting it
> here.  I'd also be grateful for workarounds.
> [...]

I've just found a fairly simple one: make instance resolution happen
where the equality constraints are not in scope.

{-# LANGUAGE GADTs  #-}

data TemplateValue a where
    TemplateList :: [a] -> TemplateValue [a]

instance Eq a => Eq (TemplateValue a) where
    (==) = eqBy (==)

eqBy :: (a -> a -> Bool) -> TemplateValue a -> TemplateValue a -> Bool
eqBy (==) (TemplateList xs) (TemplateList ys) = xs == ys


I've also found that, surprisingly at this point, the following typechecks:

eq :: Eq a => TemplateValue a -> Bool
eq (TemplateList xs) = xs == xs


More information about the Glasgow-haskell-users mailing list