
Thinking about this a bit more, and renaming some of the variables: {-# LANGUAGE GADTs #-} module Foo where data TemplateValue t where TemplateList :: [x] -> TemplateValue [x] instance (Eq a) => Eq (TemplateValue a) where (==) (TemplateList b) (TemplateList c) = (==) b c -- here we have a == [x] Could not deduce (Eq x) from the context (a ~ [x1]) It looks as though it has decided to use the (instance Eq x => Eq [x]) instance, and hence is searching for Eq x (which can't be deduced) rather than using the (Eq a / Eq [x]) directly. So, I guess that's an interesting question why that happens... --Ben On 17 Aug 2010, at 20:04, Ben Moseley wrote:
It looks to me as though that wouldn't be expected to work because 'a' and 't' are different type variables... which seems to be essentially what the error msg is saying...
...am I missing something?
--Ben
On 17 Aug 2010, at 19:54, Dan Knapp 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. This is on ghc 6.12.1.20100203, but if people can't reproduce it I'll install a newer one; I'm just not eager to do that because of course it means rebuilding quite a lot of things.
{-# LANGUAGE GADTs #-} module Foo where
data TemplateValue t where TemplateList :: [a] -> TemplateValue [a] instance (Eq a) => Eq (TemplateValue a) where (==) (TemplateList a) (TemplateList b) = (==) a b
Foo.hs:7:45: Could not deduce (Eq a1) from the context (a ~ [a2]) arising from a use of `==' at Foo.hs:7:45-52 Possible fix: add (Eq a1) to the context of the constructor `TemplateList' In the expression: (==) a b In the definition of `==': == (TemplateList a) (TemplateList b) = (==) a b In the instance declaration for `Eq (TemplateValue a)'
-- Dan Knapp "An infallible method of conciliating a tiger is to allow oneself to be devoured." (Konrad Adenauer) _______________________________________________ Glasgow-haskell-users mailing list Glasgow-haskell-users@haskell.org http://www.haskell.org/mailman/listinfo/glasgow-haskell-users
_______________________________________________ Glasgow-haskell-users mailing list Glasgow-haskell-users@haskell.org http://www.haskell.org/mailman/listinfo/glasgow-haskell-users