MPC with fundeps: ghc-6.2.2 vs ghc-6.4

Christian Maeder maeder at tzi.de
Fri May 20 12:02:44 EDT 2005


Hi,

the following (reduced) example used to go through with ghc-6.2.2 but
fails with ghc-6.4. Which behaviour is correct? I compile with:

ghc -fglasgow-exts Context.hs


module Context where

class Language a
class Language a => Logic a b | a -> b
class (Language a, Logic b c, Logic d e)
    => Comorph a b c d e | a -> b, a -> d

instance (Comorph a1 b1 c1 d1 e1, Comorph a2 b2 c2 d2 e2)
    => Language (a1, a2)

instance (Comorph a1 b1 c1 d1 e1, Comorph a2 b2 c2 d2 e2)
    => Comorph (a1, a2) b1 c1 d2 e2

-- end of module

ghc-6.4 (or ghc-6.4.1) complains with:

Context.hs:11:0:
    Could not deduce (Comorph a2 b2 c21 d2 e21, Comorph a1 b1 c11 d1 e11)
      from the context (Comorph a1 b1 c1 d1 e1, Comorph a2 b2 c2 d2 e2)
      arising from the superclasses of an instance declaration at
Context.hs:11:0
    Probable fix:
      add (Comorph a2 b2 c21 d2 e21, Comorph a1 b1 c11 d1 e11)
      to the instance declaration superclass context
    In the instance declaration for `Comorph (a1, a2) b1 c1 d2 e2'


If I replace the first instance with
"instance (Language a1, Language a2) => Language (a1, a2)"
then ghc-6.4 is happy.

Cheers Christian


More information about the Glasgow-haskell-users mailing list