[GHC] #10562: GHC 7.10.2 RC cannot build boolsimplifier-0.1.8

#10562: GHC 7.10.2 RC cannot build boolsimplifier-0.1.8 -------------------------------------+------------------------------------- Reporter: snoyberg | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 7.10.2-rc1 Keywords: | Operating System: Linux Architecture: x86_64 | Type of failure: GHC rejects (amd64) | valid program Test Case: | Blocked By: Blocking: | Related Tickets: Differential Revisions: | -------------------------------------+------------------------------------- In running a Stackage Nightly build with GHC 7.10.2 (via Herbert's PPA), I discovered the following regression: http://lpaste.net/135057 Note that boolsimplifier-0.1.8 compiles just fine with GHC 7.10.1, but not with 7.10.2. I am still running the rest of the Stackage build. $ ghc --version The Glorious Glasgow Haskell Compilation System, version 7.10.1.20150619 -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/10562 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#10562: GHC 7.10.2 RC cannot build boolsimplifier-0.1.8 -------------------------------------+------------------------------------- Reporter: snoyberg | Owner: Type: bug | Status: new Priority: normal | Milestone: 7.10.2 Component: Compiler | Version: 7.10.2-rc1 Resolution: | Keywords: Operating System: Linux | Architecture: x86_64 Type of failure: GHC rejects | (amd64) valid program | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Revisions: -------------------------------------+------------------------------------- Changes (by snoyberg): * milestone: => 7.10.2 -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/10562#comment:1 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#10562: GHC 7.10.2 RC cannot build boolsimplifier-0.1.8 -------------------------------------+------------------------------------- Reporter: snoyberg | Owner: Type: bug | Status: new Priority: normal | Milestone: 7.10.2 Component: Compiler | Version: 7.10.2-rc1 Resolution: | Keywords: Operating System: Linux | Architecture: x86_64 Type of failure: GHC rejects | (amd64) valid program | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Revisions: -------------------------------------+------------------------------------- Comment (by gershomb): So the relevant lines seem to be: {{{ data QueryRep qtyp a where QAtom :: (Ord a) => a -> QueryRep QAtomTyp a QOp :: (Show qtyp, Ord a) => Set (QueryRep QAtomTyp a) -> Set (QueryRep (QFlipTyp qtyp) a) -> QueryRep qtyp a instance (Eq a) => Eq (QueryRep qtyp a) where (QAtom x) == (QAtom y) = x == y (QOp as cs) == (QOp as' cs') = as == as' && cs == cs' _ == _ = False -- can't happen instance (Ord a) => Ord (QueryRep qtyp a) where compare (QAtom x) (QAtom y) = compare x y compare (QOp as cs) (QOp as' cs') = compare as as' `mappend` compare cs cs' compare (QAtom _) _ = GT -- can't happen compare _ _ = LT -- can't happen }}} And the relevant error seems to be {{{ Overlapping instances for Eq (QueryRep (QFlipTyp qtyp) a) arising from a use of ‘compare’ }}} With the additional info: {{{ There exists a (perhaps superclass) match: from the context (Eq (QueryRep qtyp a), Ord a) bound by the instance declaration at Data/BoolSimplifier.hs:116:10-41 or from (Show qtyp, Ord a) bound by a pattern with constructor QOp :: forall qtyp a. (Show qtyp, Ord a) => Set (QueryRep QAtomTyp a) -> Set (QueryRep (QFlipTyp qtyp) a) -> QueryRep qtyp a, in an equation for ‘compare’ at Data/BoolSimplifier.hs:118:14-22 or from (Show qtyp, Ord a) bound by a pattern with constructor QOp :: forall qtyp a. (Show qtyp, Ord a) => Set (QueryRep QAtomTyp a) -> Set (QueryRep (QFlipTyp qtyp) a) -> QueryRep qtyp a, in an equation for ‘compare’ at Data/BoolSimplifier.hs:118:26-36 (The choice depends on the instantiation of ‘qtyp, a’ To pick the first instance above, use IncoherentInstances when compiling the other instance declarations) In the second argument of ‘mappend’, namely ‘compare cs cs'’ In the expression: compare as as' `mappend` compare cs cs' In an equation for ‘compare’: compare (QOp as cs) (QOp as' cs') = compare as as' `mappend` compare cs cs' }}} So what's happening is we've asserted there's an `Ord a` dictionary three different ways -- first and second from packing it in each of the two GADTs, and third from the constrain in the instance head. Interestingly, it doesn't seem to balk at duplicate `Ord` instances themselves, but from the fact that they lead to duplicate `Eq` instances. To be honest, I don't remember why the `Ord` constraint is ever packed with the GADT at all. But, regardless, this seems like something the compiler should be able to handle properly, and it seems like a regression if it can't? -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/10562#comment:2 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#10562: GHC 7.10.2 RC cannot build boolsimplifier-0.1.8 -------------------------------------+------------------------------------- Reporter: snoyberg | Owner: Type: bug | Status: new Priority: normal | Milestone: 7.10.2 Component: Compiler | Version: 7.10.2-rc1 Resolution: | Keywords: Operating System: Linux | Architecture: x86_64 Type of failure: GHC rejects | (amd64) valid program | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Revisions: -------------------------------------+------------------------------------- Changes (by gershomb): * cc: gershomb (added) -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/10562#comment:3 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#10562: GHC 7.10.2 RC cannot build boolsimplifier-0.1.8
-------------------------------------+-------------------------------------
Reporter: snoyberg | Owner:
Type: bug | Status: new
Priority: normal | Milestone: 7.10.2
Component: Compiler | Version: 7.10.2-rc1
Resolution: | Keywords:
Operating System: Linux | Architecture: x86_64
Type of failure: GHC rejects | (amd64)
valid program | Test Case:
Blocked By: | Blocking:
Related Tickets: | Differential Revisions:
-------------------------------------+-------------------------------------
Comment (by Simon Peyton Jones

#10562: GHC 7.10.2 RC cannot build boolsimplifier-0.1.8 -------------------------------------+------------------------------------- Reporter: snoyberg | Owner: Type: bug | Status: new Priority: normal | Milestone: 7.10.2 Component: Compiler | Version: 7.10.2-rc1 Resolution: | Keywords: Operating System: Linux | Architecture: x86_64 Type of failure: GHC rejects | (amd64) valid program | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Revisions: -------------------------------------+------------------------------------- Comment (by simonpj): Here is a smaller test case {{{ {-# LANGUAGE GADTs, TypeFamilies #-} module T10562 where type family Flip a data QueryRep qtyp a where QAtom :: a -> QueryRep () a QOp :: QueryRep (Flip qtyp) a -> QueryRep qtyp a instance (Eq a) => Eq (QueryRep qtyp a) instance (Ord a) => Ord (QueryRep qtyp a) where compare (QOp a) (QOp b) = a `compare` b }}} With 7.10 we get {{{ T10562.hs:13:31: Overlapping instances for Eq (QueryRep (Flip qtyp) a) arising from a use of ‘compare’ }}} The problem arises because of the "silent superclass" trick (which is happily gone from HEAD). The instance declaration that is actually checked is {{{ instance (Eq (QueryRep qtyp a), Ord a) => Ord (QueryRep qtyp a) }}} with an extra `Eq (QueryRep qtyp a)` constraint. That gets GHC confused when it tries to solve `Eq (QueryRep (Flip qtyp) a)` from a method. A workaround is to use `-XIncoherentInstances` for this module. Exactly the same failure happens with GHC 7.8.3 doesn't it? Though apparently not with 7.8.2, mysteriously. I'm sorry but it's not feasible to get HEAD's solution into 7.10 now. It works fine in HEAD, and I'll add the example as a test case, to check it stays working. Simon -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/10562#comment:5 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#10562: GHC 7.10.2 RC cannot build boolsimplifier-0.1.8 -------------------------------------+------------------------------------- Reporter: snoyberg | Owner: Type: bug | Status: closed Priority: normal | Milestone: 7.12.1 Component: Compiler | Version: 7.10.2-rc1 Resolution: fixed | Keywords: Operating System: Linux | Architecture: x86_64 Type of failure: GHC rejects | (amd64) valid program | Test Case: Blocked By: | tests/typecheck/should_compile/T10562 Related Tickets: | Blocking: | Differential Revisions: -------------------------------------+------------------------------------- Changes (by thoughtpolice): * status: new => closed * testcase: => tests/typecheck/should_compile/T10562 * resolution: => fixed * milestone: 7.10.2 => 7.12.1 Comment: After a quick discussion with Simon, due to the infeasibility of fixing this (and there being a workaround), we're going to punt this to 7.12.1. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/10562#comment:6 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler
participants (1)
-
GHC