[Haskell-cafe] Weird issue with ConstraintKinds

Jacques Carette carette at mcmaster.ca
Sat Oct 26 13:49:16 UTC 2013


Consider the following (minimal, for illustration purposes) code:

{-# LANGUAGE ConstraintKinds #-}
module Weird where

class A a where
class B b where
class C c where

data X a = X a
data Y a = Y a

-- works fine, but can be verbose when things multiply
instance (A a, B a) => C (X a) where

-- So use ConstraintKinds:
type D a = (A a, B a)
instance D a => C (Y a) where

=====
and now I get
     Variable `a' occurs more often than in the instance head
       in the constraint: D a
     (Use -XUndecidableInstances to permit this)
     In the instance declaration for `C (Y a)'

Why??  Since D is an abbreviation, why would it behave differently than 
when I hand expand it?
[This is with GHC 7.6.3]

Jacques


More information about the Haskell-Cafe mailing list