[GHC] #8359: ConstraintKinds require UndecidableInstances when it doesn't need it

GHC ghc-devs at haskell.org
Wed Sep 25 23:44:49 CEST 2013


#8359: ConstraintKinds require UndecidableInstances when it doesn't need it
----------------------------+----------------------------------------------
       Reporter:            |             Owner:
  thomaseding               |            Status:  new
           Type:  bug       |         Milestone:
       Priority:  normal    |           Version:  7.4.2
      Component:  Compiler  |  Operating System:  Unknown/Multiple
       Keywords:            |   Type of failure:  GHC rejects valid program
   Architecture:            |         Test Case:
  Unknown/Multiple          |          Blocking:
     Difficulty:  Unknown   |
     Blocked By:            |
Related Tickets:            |
----------------------------+----------------------------------------------
 Using ConstraintKinds to alias a bunch of class constraints fails to
 compile without UndecidableInstances. The same code that manually spells
 out class constraints without ConstraintKinds compiles just fine though.

 Test case below

 -------------------------------------

 {-# LANGUAGE ConstraintKinds #-}

 {-# LANGUAGE MultiParamTypeClasses #-}

 class DifferentTypes a b

 type DifferentTypes3 a b c = (DifferentTypes a b, DifferentTypes b c,
 DifferentTypes a c)

 class Foo a

 class Bar a

 -- Buggy instance requires UndecidableInstances to compile

 instance (DifferentTypes3 a b c, Bar a, Bar b, Bar c) => Foo (a, b, c)

 -- Equivalent instance compiles when manually expanding constraint type

 instance (DifferentTypes a b, DifferentTypes b c, DifferentTypes a c, Bar
 a, Bar b, Bar c) => Foo (a, b, c)

-- 
Ticket URL: <http://ghc.haskell.org/trac/ghc/ticket/8359>
GHC <http://www.haskell.org/ghc/>
The Glasgow Haskell Compiler



More information about the ghc-tickets mailing list