Avoid orphan instances with OVERLAPPABLE (sometimes)
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 big red **warning** in the Users Guide. (Version 1 lightly adapted to use OVERLAPPING
rather than the now-deprecated Overlapping Instances
.)
{-# 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 asOVERLAPPING
: you get different behaviour. - The
OVERLAPPABLE
pragma, when you already haveOVERLAPPING
to accept the instances, is not merely a comment. - This makes an observable difference under separate compilation, contra SPJ's ticket:15135#comment:162745 .
-
ticket:15135#comment:153032 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."
Trac metadata
Trac field | Value |
---|---|
Version | 8.6.1 |
Type | Bug |
TypeOfFailure | OtherFailure |
Priority | normal |
Resolution | Unresolved |
Component | Compiler |
Test case | |
Differential revisions | |
BlockedBy | |
Related | |
Blocking | |
CC | |
Operating system | |
Architecture |