[GHC] #11427: TypeSynonyms not deduced
GHC
ghc-devs at haskell.org
Fri Jan 15 10:12:19 UTC 2016
#11427: TypeSynonyms not deduced
-------------------------------------+-------------------------------------
Reporter: phadej | Owner:
Type: bug | Status: new
Priority: normal | Milestone:
Component: Compiler | Version: 8.0.1-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):
This is very delicate. And regrettably un-documented.
It's explained in great detail in `Note [Recursive superclasses]` in
`TcInstDcls`. I append the text below.
In this case GHC is being a little over-conservative, but I don't know how
to do it better. You can work around it in your example in comment:3 by
adding `MyEq a` to the offending instance declaration:
{{{
instance (MyEq a, MyOrd a) => MyClass a where
mydef x = myeq x x
}}}
Simon
{{{
Note [Recursive superclasses]
~~~~~~~~~~~~~~~~~~~~~~~~~~~~~
See Trac #3731, #4809, #5751, #5913, #6117, #6161, which all
describe somewhat more complicated situations, but ones
encountered in practice.
See also tests tcrun020, tcrun021, tcrun033, and Trac #11427
----- THE PROBLEM --------
The problem is that it is all too easy to create a class whose
superclass is bottom when it should not be.
Consider the following (extreme) situation:
class C a => D a where ...
instance D [a] => D [a] where ... (dfunD)
instance C [a] => C [a] where ... (dfunC)
Although this looks wrong (assume D [a] to prove D [a]), it is only a
more extreme case of what happens with recursive dictionaries, and it
can, just about, make sense because the methods do some work before
recursing.
To implement the dfunD we must generate code for the superclass C [a],
which we had better not get by superclass selection from the supplied
argument:
dfunD :: forall a. D [a] -> D [a]
dfunD = \d::D [a] -> MkD (scsel d) ..
Otherwise if we later encounter a situation where
we have a [Wanted] dw::D [a] we might solve it thus:
dw := dfunD dw
Which is all fine except that now ** the superclass C is bottom **!
The instance we want is:
dfunD :: forall a. D [a] -> D [a]
dfunD = \d::D [a] -> MkD (dfunC (scsel d)) ...
----- THE SOLUTION --------
The basic solution is simple: be very careful about using superclass
selection to generate a superclass witness in a dictionary function
definition. More precisely:
Superclass Invariant: in every class dictionary,
every superclass dictionary field
is non-bottom
To achieve the Superclass Invariant, in a dfun definition we can
generate a guaranteed-non-bottom superclass witness from:
(sc1) one of the dictionary arguments itself (all non-bottom)
(sc2) an immediate superclass of a smaller dictionary
(sc3) a call of a dfun (always returns a dictionary constructor)
The tricky case is (sc2). We proceed by induction on the size of
the (type of) the dictionary, defined by TcValidity.sizeTypes.
Let's suppose we are building a dictionary of size 3, and
suppose the Superclass Invariant holds of smaller dictionaries.
Then if we have a smaller dictionary, its immediate superclasses
will be non-bottom by induction.
What does "we have a smaller dictionary" mean? It might be
one of the arguments of the instance, or one of its superclasses.
Here is an example, taken from CmmExpr:
class Ord r => UserOfRegs r a where ...
(i1) instance UserOfRegs r a => UserOfRegs r (Maybe a) where
(i2) instance (Ord r, UserOfRegs r CmmReg) => UserOfRegs r CmmExpr where
For (i1) we can get the (Ord r) superclass by selection from (UserOfRegs r
a),
since it is smaller than the thing we are building (UserOfRegs r (Maybe
a).
But for (i2) that isn't the case, so we must add an explicit, and
perhaps surprising, (Ord r) argument to the instance declaration.
Here's another example from Trac #6161:
class Super a => Duper a where ...
class Duper (Fam a) => Foo a where ...
(i3) instance Foo a => Duper (Fam a) where ...
(i4) instance Foo Float where ...
It would be horribly wrong to define
dfDuperFam :: Foo a -> Duper (Fam a) -- from (i3)
dfDuperFam d = MkDuper (sc_sel1 (sc_sel2 d)) ...
dfFooFloat :: Foo Float -- from (i4)
dfFooFloat = MkFoo (dfDuperFam dfFooFloat) ...
Now the Super superclass of Duper is definitely bottom!
This won't happen because when processing (i3) we can use the
superclasses of (Foo a), which is smaller, namely Duper (Fam a). But
that is *not* smaller than the target so we can't take *its*
superclasses. As a result the program is rightly rejected, unless you
add (Super (Fam a)) to the context of (i3).
}}}
--
Ticket URL: <http://ghc.haskell.org/trac/ghc/ticket/11427#comment:4>
GHC <http://www.haskell.org/ghc/>
The Glasgow Haskell Compiler
More information about the ghc-tickets
mailing list