[Haskell-cafe] problem with type equality constraints
Ganesh Sittampalam
ganesh at earth.li
Sun Mar 16 17:35:50 EDT 2008
Hi,
When I try to compile this code with ghc-6.9.20080310:
module Test2 where
type family Id a
type instance Id Int = Int
type instance Id (a, b) = (Id a, Id b)
class Id a ~ ida => Foo a ida
instance Foo Int Int
instance (Foo a ida, Foo b idb) => Foo (a, b) (ida, idb)
I get these errors:
Test2.hs:12:0:
Couldn't match expected type `ida' against inferred type `Id a'
`ida' is a rigid type variable bound by
the instance declaration at Test2.hs:12:16
When checking the super-classes of an instance declaration
In the instance declaration for `Foo (a, b) (ida, idb)'
Test2.hs:12:0:
Couldn't match expected type `idb' against inferred type `Id b'
`idb' is a rigid type variable bound by
the instance declaration at Test2.hs:12:27
When checking the super-classes of an instance declaration
In the instance declaration for `Foo (a, b) (ida, idb)'
It seems to me that since Foo a ida and Foo b idb are
superclassess, Id a ~ ida and Id b ~ idb should be known and so this
should have worked - am I missing something?
Cheers,
Ganesh
More information about the Haskell-Cafe
mailing list