[GHC] #16241: Avoid orphan instances with OVERLAPPABLE (sometimes)

#16241: Avoid orphan instances with OVERLAPPABLE (sometimes) -------------------------------------+------------------------------------- Reporter: AntC | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.6.1 Keywords: | Operating System: Windows Architecture: | Type of failure: Poor/confusing Unknown/Multiple | error message Test Case: | Blocked By: Blocking: | Related Tickets: #15135 Differential Rev(s): | Wiki Page: -------------------------------------+------------------------------------- Not sure whether to count this as a bug or a feature. If it's 'intended behaviour', what is the intent, exactly? GHC is on the verge of doing something useful, but it's inconsistent and "fragile" (as the warning does tell me). Consider the standard example of what goes wrong with orphan instances, from the [https://downloads.haskell.org/~ghc/8.6.3/docs/html/users_guide/glasgow_exts.... #overlapping-instances big red **warning** in the Users Guide]. (Version 1 lightly adapted to use `OVERLAPPING` rather than the now-deprecated `Overlapping Instances`.) {{{#!hs {-# LANGUAGE FlexibleInstances, FlexibleContexts #-} module Help where class MyShow a where myshow :: a -> String instance MyShow a => MyShow [a] where -- version 1 -- instance {-# OVERLAPPABLE #-} -- version 2 -- MyShow a => MyShow [a] where myshow xs = concatMap myshow xs showHelp :: MyShow a => [a] -> String -- version 1 -- showHelp :: MyShow [a] => [a] -> String -- version 2 showHelp xs = myshow xs {-# LANGUAGE FlexibleInstances #-} module Main where import Help data T = MkT instance MyShow T where myshow x = "Used generic instance" instance {# OVERLAPPING #} MyShow [T] where myshow xs = "Used more specific instance" main = do { print (myshow [MkT]); print (showHelp [MkT]) } }}} Version 1 gives the as-warned incoherent behaviour ("different instance choices are made in different parts of the program" -- that is, in different modules for the (apparently) same code `myshow xs`.) If and only if both changes marked `version 2` are in place, `myshow xs` returns the same result from both calls consistently. Why? Because the `MyShow [a] =>` constraint on `showHelp`'s sig sees that exactly matches an instance head, and that the head is marked `OVERLAPPABLE`. But GHC is not happy {{{ ... warning: [-Wsimplifiable-class-constraints] * The constraint `MyShow [a]' matches an instance declaration instance [overlappable] MyShow a => MyShow [a] This makes type inference for inner bindings fragile; either use MonoLocalBinds, or simplify it using the instance }}} Hmm: wrong advice: simplifying the constraint using the instance gives us the version 1 signature, which exactly makes `showHelp` use the orphan instance. ''Does'' version 2 make inference for inner bindings fragile? I think only if the instance is not marked `OVERLAPPABLE`. IOW a tentative rule would be 'OVERLAPPABLE constraints should not be simplified!' Inconsistencies I see: * Marking overlappable instances as `OVERLAPPABLE` is not merely the mirror-image of marking the overlapping instance as `OVERLAPPING`: you get different behaviour. * The `OVERLAPPABLE` pragma, when you already have `OVERLAPPING` to accept the instances, is not merely a comment. * This makes an observable difference under separate compilation, contra SPJ's ticket:15135#comment:9 . * ticket:15135#comment:1 is also relevant "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/16241 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#16241: Avoid orphan instances with OVERLAPPABLE (sometimes) -------------------------------------+------------------------------------- Reporter: AntC | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.6.1 Resolution: | Keywords: Operating System: Windows | Architecture: Type of failure: Poor/confusing | Unknown/Multiple error message | Test Case: Blocked By: | Blocking: Related Tickets: #15135 | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by AntC): Ah, I see that I don't have orphan instances here, by the letter of the law: * `instance MyShow [a]` is declared in the same module as the class, so isn't an orphan; * `instance MyShow T` and `instance MyShow [T]` are declared in the same module as `data T`, so aren't orphans. Never the less, the problem is in the same ballpark as orphan instances: incoherence due to not all applicable instances being visible in all modules. Specifically, `instance MyShow [T]` is not visible in module `Help`, where constraint `MyShow [a] =>` on the signature for `showHelp` needs it. Then `OVERLAPPABLE` on `instance MyShow [a]` says 'beware! there are other instances in other scopes.' Is there a more accurate term or keyword I should use? ('orphan instance' seems to get bandied around on Stackoverflow in that more general sense.) -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/16241#comment:1 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#16241: Avoid orphan instances with OVERLAPPABLE (sometimes) -------------------------------------+------------------------------------- Reporter: AntC | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.6.1 Resolution: | Keywords: Operating System: Windows | Architecture: Type of failure: Poor/confusing | Unknown/Multiple error message | Test Case: Blocked By: | Blocking: Related Tickets: #15135 | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by simonpj):
I think only if the instance is not marked OVERLAPPABLE
I'm not sure that's right. Currently [http://downloads.haskell.org/~ghc/master/users-guide/glasgow_exts.html #overlapping-instances the user manual for instance resolution] says this {{{ Eliminate any candidate IX for which there is another candidate IY such that both of the following hold: * IY is strictly more specific than IX. That is, IY is a substitution instance of IX but not vice versa. * Either IX is overlappable, or IY is overlapping. (This “either/or” design, rather than a “both/and” design, allow a client to deliberately override an instance from a library, without requiring a change to the library.) }}} The second bullet means that you don't need to say "OVERLAPPABLE" for an instance to be overlappable. It's enough to say "OVERLAPPING" in the overlapping instance. So you can't deduce anything much from the absence of "OVERLAPPABLE", sadly. I don't know if this is the right design. If we you could only overlap an explicitly-overlappable instance, we could commit to them more aggressively. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/16241#comment:2 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#16241: Avoid orphan instances with OVERLAPPABLE (sometimes) -------------------------------------+------------------------------------- Reporter: AntC | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.6.1 Resolution: | Keywords: Operating System: Windows | Architecture: Type of failure: Poor/confusing | Unknown/Multiple error message | Test Case: Blocked By: | Blocking: Related Tickets: #15135 | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by AntC): Thanks Simon,
Currently the user manual ...
is only talking about compiling within a single module, or at least when all instances are visible from imports in a single module. I.e. compiling module `Main` in the example. Or if you squish all the code into a single module then indeed
you don't need to say "OVERLAPPABLE" for an instance to be overlappable.
But when compiling version 2 of module `Help` * there is only one visible instance of `MyShow` (so the quote from the manual doesn't apply: there's no alternative candidates to eliminate); * its head `[a]` does indeed match the wanted constraint `MyShow [a] =>` from the signature for `showHelp`, so it's the "prime candidate" per the user manual; and yet * the instance is marked `OVERLAPPABLE`, then GHC ''doesn't'' select that instance, contra what the user manual says. * I know it doesn't select that instance, because it doesn't simplify to constraint `MyShow a =>`. * Then in compiling module `Main`, we maintain referential transparency: `showHelp [MkT]` ===> `myshow [MkT]`, which wants `instance MyShow [T]` in preference to `instance MyShow [a]`. * So both calls in `main` produce the same result, viz `"Used more specific instance"`. So I'm disagreeing with your
It's enough to say "OVERLAPPING" in the overlapping instance.
It is enough only providing those overlapping instance(s) are in the same module. If the overlapping instance(s) are in a separate module that's importing the `OVERLAPPABLE` instance, then you must say the imported instance is OVERLAPPABLE.
So you can't deduce anything much from the absence of "OVERLAPPABLE", sadly.
Well, you can deduce you're liable to see "fragile"/"incoherent" behaviour ;-).
If we you could only overlap an explicitly-overlappable instance, we could commit to them more aggressively.
I think you have that back-to-front: this ticket is showing currently GHC does commit aggressively to an eligible instance ''unless'' it's explicitly-overlappable. (And BTW per #15135, with `-O2` GHC commits aggressively anyway and ignores `OVERLAPPABLE`.) -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/16241#comment:3 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler
participants (1)
-
GHC