[GHC] #15135: Overlapping typeclass instance selection depends on the optimisation level

#15135: Overlapping typeclass instance selection depends on the optimisation level -------------------------------------+------------------------------------- Reporter: nicuveo | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: 8.6.1 Component: Compiler | Version: 8.4.2 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: -------------------------------------+------------------------------------- A file A defines a typeclass, and gives an instance for all types a, and exports a function relying on said typeclass. A file B defines a data type, makes it a specific `OVERLAPPING` instance of that class, and uses the function defined in A. Which instance ends up being picked for B depends on the optimisation level those files are compiled with. **Minimal test case** //A.hs// {{{#!hs {-# LANGUAGE FlexibleInstances #-} {-# OPTIONS_GHC -fno-warn-simplifiable-class-constraints #-} module A where import Data.Maybe class A a where someValue :: a -> Maybe Int instance A a where someValue = const Nothing getInt :: A a => a -> Int getInt x = fromMaybe 0 $ someValue x }}} //B.hs// {{{#!hs module B where import A data B = B Int instance {-# OVERLAPPING #-} A B where someValue (B x) = Just x getBInt :: Int getBInt = getInt $ B 42 }}} //Main.hs// {{{#!hs import B main :: IO () main = putStrLn $ "B: " ++ show getBInt }}} To reproduce: {{{ $ ghc -O0 -fforce-recomp Main.hs && ./Main [1 of 3] Compiling A ( A.hs, A.o ) [2 of 3] Compiling B ( B.hs, B.o ) [3 of 3] Compiling Main ( Main.hs, Main.o ) Linking Main ... B: 42 $ ghc -O2 -fforce-recomp Main.hs && ./Main [1 of 3] Compiling A ( A.hs, A.o ) [2 of 3] Compiling B ( B.hs, B.o ) [3 of 3] Compiling Main ( Main.hs, Main.o ) Linking Main ... B: 0 }}} The fix introduced to fix ticket:14434 instructs the "short-cut solver" to not automatically choose a matching instance if it marked as `INCOHERENT` or `OVERLAPPABLE`, but in this case the instance is not marked in any way. This might be the source of the bug? Additionally, whatever the optimisation level, ghc emits a warning about the `A a =>` class constraint being simplifiable; but if it is removed, then the program prints "0" in both cases. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/15135 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#15135: Overlapping typeclass instance selection depends on the optimisation level -------------------------------------+------------------------------------- Reporter: nicuveo | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: 8.6.1 Component: Compiler | Version: 8.4.2 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): You are on thin ice here. In `getInt`: {{{ getInt :: A a => a -> Int getInt x = fromMaybe 0 $ someValue x }}} we have a "wanted" constraint `A a`. How can we solve it? In two ways: * From the instance * From the `A a =>` given to `getInt`. GHC chooses to solve it from the instance. But then you later overlap the instance, so that decision was arguably wrong. But the same thing would happen if you tried to infer a type for `getInt`: {{{ getInt x = fromMaybe 0 $ someValue x }}} Again, GHC will use the instance and infer {{{ getInt :: a -> Int }}} If you want to signal to GHC that the instance might be overlapped, use `{-# OVERLAPPABLE #-}`; and then you'll always get 42. I think it's arguable that an instance should only be overlappable if it says `{-# OVERLAPPABLE #-}`. But that's not our current spec. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/15135#comment:1 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#15135: Overlapping typeclass instance selection depends on the optimisation level -------------------------------------+------------------------------------- Reporter: nicuveo | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: 8.8.1 Component: Compiler | Version: 8.4.2 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 baramoglo): Here is an example that exhibits the same bug (I think) in a single file: {{{ {-# LANGUAGE FlexibleInstances #-} {-# LANGUAGE GADTs #-} {-# LANGUAGE MultiParamTypeClasses #-} data A = A deriving (Show) data B a = B a deriving (Show) class Project a b where project :: b -> Maybe a instance {-# OVERLAPPING #-} Project a b where project _ = Nothing instance {-# OVERLAPPING #-} Project a a where project = Just instance {-# OVERLAPPING #-} Project a b => Project a (B b) where project (B a) = project a main = print (project (B A) :: Maybe A) }}} Prints `Just A` when compiled with `-O0` and `Nothing` when compiled with `-O1`. Note that the first instance should really say `{-# OVERLAPPABLE #-}` (AFAIU). If I change to that, the bug goes away. Let me know if you think this should be filed as a different bug. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/15135#comment:3 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#15135: Overlapping typeclass instance selection depends on the optimisation level -------------------------------------+------------------------------------- Reporter: nicuveo | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: 8.8.1 Component: Compiler | Version: 8.4.2 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 AntC): Replying to [comment:3 baramoglo]:
Here is an example that exhibits the same bug (I think) in a single file:
... Prints `Just A` when compiled with `-O0` and `Nothing` when compiled with `-O1`.
I agree the optimisation level shouldn't change the behaviour when everything's in a single module.
Note that the first instance should really say `{-# OVERLAPPABLE #-}` (AFAIU). If I change to that, the bug goes away.
Ugh! Strictly speaking, the second and third instances are `INCOHERENT` because in no substitution ordering. But your `project (B A) :: Maybe A`, by giving a type annotation means it's apart from the second instance. (It should resolve to the third, which is marked `OVERLAPPING` so that's OK against the other eligible instance, i.e. the first one.)
Let me know if you think this should be filed as a different bug.
The O.P. is a classic 'Orphan Instances' problem, so expected behaviour. And as Simon's comment:2 says, use `OVERLAPPABLE` to avoid premature instance resolution in the imported module. I'm surprised that also seems to be required when in a single module. That seems too subtle for my liking. BTW what happens if you change all the pragmas to `OVERLAPS`? (That's supposed to give the effect of both `OVERLAPPING` and `OVERLAPPABLE`.) -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/15135#comment:4 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#15135: Overlapping typeclass instance selection depends on the optimisation level -------------------------------------+------------------------------------- Reporter: nicuveo | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: 8.8.1 Component: Compiler | Version: 8.4.2 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 baramoglo): Replying to [comment:4 AntC]:
BTW what happens if you change all the pragmas to `OVERLAPS`?
Then it works correctly. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/15135#comment:5 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#15135: Overlapping typeclass instance selection depends on the optimisation level -------------------------------------+------------------------------------- Reporter: nicuveo | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: 8.8.1 Component: Compiler | Version: 8.4.2 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): This is all caused by `-fsolve-constant-dicts`: see [http://downloads.haskell.org/~ghc/master/users-guide/using- optimisation.html#ghc-flag--fsolve-constant-dicts the manual], and Trac #12791 and #5835. The reason that behaviour differs with -O is because `-fsolve-constant- dicts` is implied by `-O`. The problem comes in {{{ instance Project a b => Project a (B b) where project (B a) = project a }}} From the RHS we get {{{ [W] Project a b }}} Shall we solve it from the dict passed into the instance? Or from the top-level instance declaration? {{{ instance {-# OVERLAPPING #-} Project a b where project _ = Nothing }}} With `-fsolve-constant-dicts`, GHC chooses the latter, wrongly. When you declare that instance as OVERLAPPABLE, thus {{{ instance {-# OVERLAPPABLE #-} Project a b where project _ = Nothing }}} GHC carefully refrains from using it, precisely because it might be overlapped (Trac #14434). Sadly, ''any'' instance declaration can be overlapped; GHC gives no way to say "this instance declaration cannot and must not be overlapped". Instead, in the presence of overlapping instances, the soundness of `-fsolve-constant-dicts` relies on the user specifying that an instance can be overlapped, by saying OVERLAPPABLE. This is terribly unsatisfactory, but at least we now understand what is going on. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/15135#comment:6 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#15135: Overlapping typeclass instance selection depends on the optimisation level
-------------------------------------+-------------------------------------
Reporter: nicuveo | Owner: (none)
Type: bug | Status: new
Priority: normal | Milestone: 8.8.1
Component: Compiler | Version: 8.4.2
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 Simon Peyton Jones

#15135: Overlapping typeclass instance selection depends on the optimisation level -------------------------------------+------------------------------------- Reporter: nicuveo | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: 8.8.1 Component: Compiler | Version: 8.4.2 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 AntC): Replying to [comment:6 simonpj]: Thank you Simon for such a clear explanation. Oh dear! I see GHC has to do something like this under separate compilation. I'm not seeing why in a single module it doesn't at least inspect all instances in scope.
Sadly, ''any'' instance declaration can be overlapped; GHC gives no way
to say "this instance declaration cannot and must not be overlapped". This is terribly unsatisfactory, but at least we now understand what is going on. Then (?) we need a pragma for that, and it might need to be used in combo with other pragmas {-# OVERLAPPING, NOTOVERLAPPABLE #-}. Ugh! This'll get particularly ugh!ly if instances are in no substitution ordering. There's something to be said for statically validating all instances are in a strict substitution order. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/15135#comment:8 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#15135: Overlapping typeclass instance selection depends on the optimisation level -------------------------------------+------------------------------------- Reporter: nicuveo | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: 8.8.1 Component: Compiler | Version: 8.4.2 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): I don't think this has anything to do with separate compilation. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/15135#comment:9 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#15135: Overlapping typeclass instance selection depends on the optimisation level -------------------------------------+------------------------------------- Reporter: nicuveo | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: 8.8.1 Component: Compiler | Version: 8.4.2 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 baramoglo): Thanks for the clarifications! -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/15135#comment:10 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler
participants (1)
-
GHC