
#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