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

#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

#8359: ConstraintKinds require UndecidableInstances when it doesn't need it ----------------------------------------------+---------------------------- Reporter: thomaseding | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 7.4.2 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: GHC rejects valid program | Unknown/Multiple Test Case: | Difficulty: Unknown Blocking: | Blocked By: | Related Tickets: ----------------------------------------------+---------------------------- Description changed by simonpj: Old description:
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)
New description: 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#comment:1 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#8359: ConstraintKinds require UndecidableInstances when it doesn't need it ----------------------------------------------+---------------------------- Reporter: thomaseding | Owner: simonpj Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 7.4.2 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: GHC rejects valid program | Unknown/Multiple Test Case: | Difficulty: Unknown Blocking: | Blocked By: | Related Tickets: ----------------------------------------------+---------------------------- Changes (by simonpj): * owner: => simonpj Comment: Excellent point, thank you. I have a patch done; will commit when I get home. Simon -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/8359#comment:2 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#8359: ConstraintKinds require UndecidableInstances when it doesn't need it
----------------------------------------------+----------------------------
Reporter: thomaseding | Owner: simonpj
Type: bug | Status: new
Priority: normal | Milestone:
Component: Compiler | Version: 7.4.2
Resolution: | Keywords:
Operating System: Unknown/Multiple | Architecture:
Type of failure: GHC rejects valid program | Unknown/Multiple
Test Case: | Difficulty: Unknown
Blocking: | Blocked By:
| Related Tickets:
----------------------------------------------+----------------------------
Comment (by unknown

#8359: ConstraintKinds require UndecidableInstances when it doesn't need it
----------------------------------------------+----------------------------
Reporter: thomaseding | Owner: simonpj
Type: bug | Status: new
Priority: normal | Milestone:
Component: Compiler | Version: 7.4.2
Resolution: | Keywords:
Operating System: Unknown/Multiple | Architecture:
Type of failure: GHC rejects valid program | Unknown/Multiple
Test Case: | Difficulty: Unknown
Blocking: | Blocked By:
| Related Tickets:
----------------------------------------------+----------------------------
Comment (by Simon Peyton Jones

#8359: ConstraintKinds require UndecidableInstances when it doesn't need it ----------------------------------------------+---------------------------- Reporter: thomaseding | Owner: simonpj Type: bug | Status: closed Priority: normal | Milestone: Component: Compiler | Version: 7.4.2 Resolution: fixed | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: GHC rejects valid program | Unknown/Multiple Test Case: polykinds/T8359 | Difficulty: Unknown Blocking: | Blocked By: | Related Tickets: ----------------------------------------------+---------------------------- Changes (by simonpj): * status: new => closed * testcase: => polykinds/T8359 * resolution: => fixed Comment: Thanks for pointing this out. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/8359#comment:5 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler
participants (1)
-
GHC