
Hello all, I think (hope) this question is different from the ones about GADTs recently discussed on this list. The following program compiles under ghc 6.8.2 but not under ghc 6.10.1:
{-# LANGUAGE MultiParamTypeClasses, FunctionalDependencies, GADTs, KindSignatures, ScopedTypeVariables #-}
class Foo a fa | a -> fa where n :: a -> Int
data Bar :: * -> * -> * where Id :: Bar a a
baz :: forall a fa b fb. (Foo a fa, Foo b fb) => Bar a b -> Int baz Id = n (undefined :: a)
ghc 6.10.1's error message: /tmp/fundep.hs:10:0: Couldn't match expected type `fb' against inferred type `fa' `fb' is a rigid type variable bound by the type signature for `baz' at /tmp/fundep.hs:9:21 `fa' is a rigid type variable bound by the type signature for `baz' at /tmp/fundep.hs:9:16 When using functional dependencies to combine Foo a fa, arising from a use of `n' at /tmp/fundep.hs:10:9-26 Foo a fb, arising from the type signature for `baz' at /tmp/fundep.hs:10:0-26 When generalising the type(s) for `baz' I find the message about the `Foo a fb' constraint quite confusing. Can anyone explain this error message to me? If I change the type of Id to Id :: Bar a b, then the program compiles. Regards, Reid