[GHC] #12881: GHC 8.0.2 regression involving OVERLAP annotations

#12881: GHC 8.0.2 regression involving OVERLAP annotations -------------------------------------+------------------------------------- Reporter: RyanGlScott | Owner: Type: bug | Status: new Priority: high | Milestone: Component: Compiler | Version: 8.0.2-rc1 Keywords: | Operating System: Unknown/Multiple Architecture: | Type of failure: None/Unknown Unknown/Multiple | Test Case: | Blocked By: Blocking: | Related Tickets: Differential Rev(s): | Wiki Page: -------------------------------------+------------------------------------- `quickcheck-combinators-0.0.1` fails to build with GHC 8.0.2-rc1 (but does build with GHC 8.0.1) due to this issue. Here is a simplified example: {{{#!hs {-# LANGUAGE FlexibleInstances #-} module Bug where class Arbitrary a where shrink :: a -> [a] shrink _ = [] instance Arbitrary a instance Arbitrary Int }}} Is this expected? If so, we should make a note of this in the 8.0.2 release notes. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/12881 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#12881: GHC 8.0.2 regression involving OVERLAP annotations -------------------------------------+------------------------------------- Reporter: RyanGlScott | Owner: Type: bug | Status: new Priority: high | Milestone: Component: Compiler | Version: 8.0.2-rc1 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by RyanGlScott): It should be noted that if you add explicit `OVERLAP*` annotations: {{{#!hs {-# LANGUAGE FlexibleInstances #-} module Bug where class Arbitrary a where shrink :: a -> [a] shrink _ = [] instance {-# OVERLAPPABLE #-} Arbitrary a instance {-# OVERLAPPING #-} Arbitrary Int }}} Then it will compile again, so there's at least a simple workaround. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/12881#comment:1 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#12881: GHC 8.0.2 regression involving OVERLAP annotations -------------------------------------+------------------------------------- Reporter: RyanGlScott | Owner: Type: bug | Status: new Priority: high | Milestone: Component: Compiler | Version: 8.0.2-rc1 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by RyanGlScott): I did a run of Stackage with GHC 8.0.2-rc1 recently, and here are all of the libraries which fail to install because of this issue: * `consul-haskell-0.3` * `ede-0.2.8.5` * `HaRe-0.8.3.0` * `hbayes-0.5.2` * `quickcheck-combinators-0.0.1` * `rethinkdb-2.2.0.7` * `vectortiles-1.2.0` -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/12881#comment:2 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#12881: GHC 8.0.2 regression involving OVERLAP annotations -------------------------------------+------------------------------------- Reporter: RyanGlScott | Owner: Type: bug | Status: new Priority: high | Milestone: 8.0.2 Component: Compiler | Version: 8.0.2-rc1 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Changes (by RyanGlScott): * cc: simonpj (added) * milestone: => 8.0.2 Comment: Simon, this commit ( https://ghc.haskell.org/trac/ghc/changeset/d2958bd08a049b61941f078e51809c7e6... ) once again appears to be responsible. Thoughts? -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/12881#comment:3 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#12881: GHC 8.0.2 regression involving OVERLAP annotations -------------------------------------+------------------------------------- Reporter: RyanGlScott | Owner: Type: bug | Status: new Priority: high | Milestone: 8.0.2 Component: Compiler | Version: 8.0.2-rc1 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- @@ -16,0 +16,15 @@ + {{{ + $ /opt/ghc/8.0.2/bin/ghc Bug.hs + [1 of 1] Compiling Bug ( Bug.hs, Bug.o ) + + Bug.hs:9:10: error: + • Overlapping instances for Arbitrary Int + arising from a use of ‘Bug.$dmshrink’ + Matching instances: + instance Arbitrary a -- Defined at Bug.hs:8:10 + instance Arbitrary Int -- Defined at Bug.hs:9:10 + • In the expression: Bug.$dmshrink @Int + In an equation for ‘shrink’: shrink = Bug.$dmshrink @Int + In the instance declaration for ‘Arbitrary Int’ + }}} + New description: `quickcheck-combinators-0.0.1` fails to build with GHC 8.0.2-rc1 (but does build with GHC 8.0.1) due to this issue. Here is a simplified example: {{{#!hs {-# LANGUAGE FlexibleInstances #-} module Bug where class Arbitrary a where shrink :: a -> [a] shrink _ = [] instance Arbitrary a instance Arbitrary Int }}} {{{ $ /opt/ghc/8.0.2/bin/ghc Bug.hs [1 of 1] Compiling Bug ( Bug.hs, Bug.o ) Bug.hs:9:10: error: • Overlapping instances for Arbitrary Int arising from a use of ‘Bug.$dmshrink’ Matching instances: instance Arbitrary a -- Defined at Bug.hs:8:10 instance Arbitrary Int -- Defined at Bug.hs:9:10 • In the expression: Bug.$dmshrink @Int In an equation for ‘shrink’: shrink = Bug.$dmshrink @Int In the instance declaration for ‘Arbitrary Int’ }}} Is this expected? If so, we should make a note of this in the 8.0.2 release notes. -- Comment (by RyanGlScott): Making this even stranger, if you explicitly implement `shrink`: {{{#!hs {-# LANGUAGE FlexibleInstances #-} module Bug where class Arbitrary a where shrink :: a -> [a] shrink _ = [] instance Arbitrary a where shrink _ = [] instance Arbitrary Int where shrink _ = [] }}} then it compiles and both versions of GHC 8.0. However, when you try something like this (which is basically what happens under the hood with default class method implementations): {{{#!hs {-# LANGUAGE FlexibleInstances #-} {-# LANGUAGE ScopedTypeVariables #-} {-# LANGUAGE TypeApplications #-} module Bug where class Arbitrary a where shrink :: a -> [a] shrink _ = [] instance Arbitrary a where shrink = dmshrink @a instance Arbitrary Int where shrink = dmshrink @Int dmshrink :: Arbitrary a => a -> [a] dmshrink _ = [] }}} Then this will fail to compile on GHC 8.0.1 //and// GHC 8.0.2. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/12881#comment:4 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#12881: GHC 8.0.2 regression involving OVERLAP annotations -------------------------------------+------------------------------------- Reporter: RyanGlScott | Owner: Type: bug | Status: new Priority: high | Milestone: 8.0.2 Component: Compiler | Version: 8.0.2-rc1 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by RyanGlScott): So it looks like what is going on here is that in GHC 8.0.1 and before, there was different code generated under the hood for default class method implementations. This code happened to work irrespective of whether any overlapping instances were marked with `OVERLAPPING` or not. That's not to say that leaving off `OVERLAPPING` pragmas couldn't have caused problems down the road in GHC 8.0.1, but in the particular case of default method implementations, it luckily didn't matter. In GHC 8.0.2, however (after https://ghc.haskell.org/trac/ghc/changeset/d2958bd08a049b61941f078e51809c7e6...), GHC switched to using visible type application to implement default class method implementations. This now poses an issue for any overlapping instances with default method implementations, because in the code that gets generated now, e.g., {{{#!hs instance Arbitrary Int where shrink = dmshrink @Int }}} `dmshrink @Int` is forced to choose a particular `Arbitrary` instance, and without the `OVERLAPPING` annotation, GHC can't decide between the `Arbitrary a` instance and the `Arbitrary Int` instance. So on one hand, there is a somewhat good reason why this code now fails to typecheck. On the other hand, it's quite annoying—a nontrivial number of packages in the wild now fail to build with GHC 8.0.2, and there are probably more examples outside of Stackage that I haven't found. I'm not sure how to address this. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/12881#comment:5 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#12881: GHC 8.0.2 regression involving OVERLAP annotations -------------------------------------+------------------------------------- Reporter: RyanGlScott | Owner: Type: bug | Status: new Priority: high | Milestone: 8.0.2 Component: Compiler | Version: 8.0.2-rc1 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- @@ -16,15 +16,0 @@ - {{{ - $ /opt/ghc/8.0.2/bin/ghc Bug.hs - [1 of 1] Compiling Bug ( Bug.hs, Bug.o ) - - Bug.hs:9:10: error: - • Overlapping instances for Arbitrary Int - arising from a use of ‘Bug.$dmshrink’ - Matching instances: - instance Arbitrary a -- Defined at Bug.hs:8:10 - instance Arbitrary Int -- Defined at Bug.hs:9:10 - • In the expression: Bug.$dmshrink @Int - In an equation for ‘shrink’: shrink = Bug.$dmshrink @Int - In the instance declaration for ‘Arbitrary Int’ - }}} - New description: `quickcheck-combinators-0.0.1` fails to build with GHC 8.0.2-rc1 (but does build with GHC 8.0.1) due to this issue. Here is a simplified example: {{{#!hs {-# LANGUAGE FlexibleInstances #-} module Bug where class Arbitrary a where shrink :: a -> [a] shrink _ = [] instance Arbitrary a instance Arbitrary Int }}} Is this expected? If so, we should make a note of this in the 8.0.2 release notes. -- Comment (by simonpj): Well there really is an issue here. Suppose you added to the program in the Description {{{ foo :: [Int] -> Int foo x = shrink x }}} then you'd ''expect'' to get the warning {{{ T12881.hs:15:9: error: • Overlapping instances for Arbitrary Int arising from a use of ‘shrink’ Matching instances: instance Arbitrary a -- Defined at T12881.hs:8:10 instance Arbitrary Int -- Defined at T12881.hs:10:10 • In the expression: shrink x In an equation for ‘foo’: foo x = shrink x }}} So, without the pragmas, or the global `-XOverlappingInstances`, the instance declarations for `Arbitrary` are effectively useless. Now, it's true that 8.0.2 is reporting that problem a bit more eagerly than before. I suppose we could switch on `-XOverlappingInstances` when typechecking the default methods in each instance declaration. But that feels like sweeping the real problem under the carpet: those instances really are useless unless you allow overlapping. So the right solution is to add those pragmas. We could mitigate for 8.0.3 (as suggested in the previous para) but I worry that the same thing would happen in 8.2. Advice? -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/12881#comment:6 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#12881: GHC 8.0.2 regression involving OVERLAP annotations -------------------------------------+------------------------------------- Reporter: RyanGlScott | Owner: Type: bug | Status: new Priority: high | Milestone: 8.0.2 Component: Compiler | Version: 8.0.2-rc1 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by RyanGlScott): Well, we're lucky in that: 1. There are "only" seven Stackage libraries affected by this bug 2. It's easy to convince people that their code in wrong in this case 3. There's an easy workaround I'll try to just patch up these libraries, add a note to the release guide about this, and declare victory. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/12881#comment:7 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#12881: GHC 8.0.2 regression involving OVERLAP annotations -------------------------------------+------------------------------------- Reporter: RyanGlScott | Owner: Type: bug | Status: new Priority: high | Milestone: 8.0.2 Component: Compiler | Version: 8.0.2-rc1 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by simonpj): That sounds good to me.. thanks Ryan. (Of course we are assuming that it is indeed "easy to convince people that their code is wrong". It could be that we have missed something, and there are good reasons... but let's see.) -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/12881#comment:8 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#12881: GHC 8.0.2 regression involving OVERLAP annotations -------------------------------------+------------------------------------- Reporter: RyanGlScott | Owner: Type: bug | Status: patch Priority: high | Milestone: 8.0.2 Component: Compiler | Version: 8.0.2-rc1 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Phab:D2760 Wiki Page: | -------------------------------------+------------------------------------- Changes (by RyanGlScott): * status: new => patch * differential: => Phab:D2760 -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/12881#comment:9 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#12881: GHC 8.0.2 regression involving OVERLAP annotations -------------------------------------+------------------------------------- Reporter: RyanGlScott | Owner: Type: bug | Status: patch Priority: high | Milestone: 8.0.2 Component: Compiler | Version: 8.0.2-rc1 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Phab:D2760 Wiki Page: | -------------------------------------+------------------------------------- Comment (by rwbarton): It is possible to write useful potentially-overlapping instances without marking them as overlapping, e.g. {{{#!hs {-# LANGUAGE FlexibleInstances #-} class C a where def :: a def = undefined instance C (Int, b) instance C (a, Char) }}} But happily GHC HEAD already accepts this case, somehow. (Maybe someone with 8.0.2-rc1 can confirm.) -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/12881#comment:10 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#12881: GHC 8.0.2 regression involving OVERLAP annotations -------------------------------------+------------------------------------- Reporter: RyanGlScott | Owner: Type: bug | Status: patch Priority: high | Milestone: 8.0.2 Component: Compiler | Version: 8.0.2-rc1 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Phab:D2760 Wiki Page: | -------------------------------------+------------------------------------- Comment (by RyanGlScott): Replying to [comment:10 rwbarton]:
But happily GHC HEAD already accepts this case, somehow. (Maybe someone with 8.0.2-rc1 can confirm.)
Indeed, GHC 8.0.2-rc1 accepts that program. Luckily, these instances aren't sufficiently overlapping to confuse GHC when it uses VTA to apply `@(Int, b)` or `@(a, Char)`. In any case, I made sure to use a phrase akin to "might fail to type- check" instead of "//will// fail to type-check" in Phab:D2760 so as not to exaggerate the severity of this problem ;) -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/12881#comment:11 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#12881: GHC 8.0.2 regression involving OVERLAP annotations
-------------------------------------+-------------------------------------
Reporter: RyanGlScott | Owner:
Type: bug | Status: patch
Priority: high | Milestone: 8.0.2
Component: Compiler | Version: 8.0.2-rc1
Resolution: | Keywords:
Operating System: Unknown/Multiple | Architecture:
| Unknown/Multiple
Type of failure: None/Unknown | Test Case:
Blocked By: | Blocking:
Related Tickets: | Differential Rev(s): Phab:D2760
Wiki Page: |
-------------------------------------+-------------------------------------
Comment (by Ryan Scott

#12881: GHC 8.0.2 regression involving OVERLAP annotations -------------------------------------+------------------------------------- Reporter: RyanGlScott | Owner: Type: bug | Status: merge Priority: high | Milestone: 8.0.2 Component: Compiler | Version: 8.0.2-rc1 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Phab:D2760 Wiki Page: | -------------------------------------+------------------------------------- Changes (by RyanGlScott): * status: patch => merge -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/12881#comment:13 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#12881: GHC 8.0.2 regression involving OVERLAP annotations -------------------------------------+------------------------------------- Reporter: RyanGlScott | Owner: Type: bug | Status: closed Priority: high | Milestone: 8.0.2 Component: Compiler | Version: 8.0.2-rc1 Resolution: fixed | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Phab:D2760 Wiki Page: | -------------------------------------+------------------------------------- Changes (by bgamari): * status: merge => closed * resolution: => fixed Comment: Merged to `ghc-8.0` as 80c26da81ff3764887f272845388248ba34cacde. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/12881#comment:14 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler
participants (1)
-
GHC