#5051: Typechecker behaviour change
---------------------------+------------------------------------------------
Reporter: igloo | Owner: simonpj
Type: bug | Status: closed
Priority: high | Milestone: 7.2.1
Component: Compiler | Version: 7.0.2
Resolution: fixed | Keywords:
Testcase: | Blockedby:
Difficulty: | Os: Unknown/Multiple
Blocking: | Architecture: Unknown/Multiple
Failure: None/Unknown |
---------------------------+------------------------------------------------
Changes (by simonpj):
* cc: mechvel@… (added)
* status: new => closed
* resolution: => fixed
Comment:
GHC 7 indeed falls over on `DoCon` 2.12. It turns out to be a rather
subtle interaction of overlapping instances with the ill-fated "silent
superclass parameters" I introduced to solve a problem in the
typechecker's constraint solver.
The problem is demonstrated in minature by test `T5051`, which I have
added to the test suite, and I reproduce below for completeness.
Happily, silent parameters aren't needed any more (we solve the problem in
another nicer way), so this patch removes them
{{{
commit a9d48fd94ae92b979610f5efe5d66506928118eb
Author: Simon Peyton Jones <[email protected]>
Date: Wed Jun 22 11:46:03 2011 +0100
Remove "silent superclass parameters"
We introduced silent superclass parameters as a way to avoid
superclass loops, but we now solve that problem a different
way ("derived" superclass constraints carry no evidence). So
they aren't needed any more.
Apart from being a needless complication, they broke DoCon.
Admittedly in a very obscure way, but still the result is
hard to explain. To see the details see Trac #5051, with
test case typecheck/should_compile/T5051. (The test is
nice and small!)
compiler/basicTypes/Id.lhs | 7 +-
compiler/basicTypes/IdInfo.lhs | 12 +--
compiler/basicTypes/MkId.lhs | 17 +--
compiler/coreSyn/CoreSyn.lhs | 2 -
compiler/coreSyn/CoreUnfold.lhs | 1 -
compiler/coreSyn/CoreUtils.lhs | 2 +-
compiler/coreSyn/PprCore.lhs | 1 -
compiler/iface/BinIface.hs | 8 +-
compiler/iface/IfaceSyn.lhs | 4 +-
compiler/iface/MkIface.lhs | 2 +-
compiler/iface/TcIface.lhs | 5 +-
compiler/typecheck/TcErrors.lhs | 12 +--
compiler/typecheck/TcInstDcls.lhs | 163
++++++++++----------------
compiler/typecheck/TcInteract.lhs | 77 ++++--------
compiler/typecheck/TcMType.lhs | 22 +----
compiler/types/InstEnv.lhs | 13 +--
compiler/vectorise/Vectorise/Type/PADict.hs | 73 +++++-------
compiler/vectorise/Vectorise/Type/PRepr.hs | 28 ++++-
compiler/vectorise/Vectorise/Utils/PADict.hs | 16 +---
19 files changed, 165 insertions(+), 300 deletions(-)
}}}
The fix will be be in GHC 7.2, but probably not in GHC 7.0. I've verified
that 7.2 can compile DoCon 2.12 and run the `demotest`.
Here's the tiny test
{{{
{-# LANGUAGE FlexibleInstances, OverlappingInstances #-}
-- A very delicate interaction of overlapping instances
module T5051 where
data T = T deriving( Eq, Ord )
instance Eq [T]
foo :: Ord a => [a] -> Bool
foo x = x >= x
-- Bizarrely, the defn of 'foo' failed in GHC 7.0.3 with
-- T5051.hs:14:10:
-- Overlapping instances for Eq [a]
-- arising from a use of `>'
-- Matching instances:
-- instance Eq a => Eq [a] -- Defined in GHC.Classes
-- instance [overlap ok] Eq [T] -- Defined at T5051.hs:9:10-15
-- (The choice depends on the instantiation of `a'
-- To pick the first instance above, use -XIncoherentInstances
-- when compiling the other instance declarations)
-- In the expression: x > x
--
-- Reason: the dfun for Ord [a] (in the Prelude) had a "silent"
-- superclass parameter, thus
-- $dfOrdList :: forall a. (Eq [a], Ord a) => Ord [a]
-- Using the dfun means we need Eq [a], and that gives rise to the
-- overlap error.
--
-- This is terribly confusing: the use of (>=) means we need Ord [a],
-- and if we have Ord a (which we do) we should be done.
-- A very good reason for not having silent parameters!
}}}
--
Ticket URL: <http://hackage.haskell.org/trac/ghc/ticket/5051#comment:3>
GHC <http://www.haskell.org/ghc/>
The Glasgow Haskell Compiler
_______________________________________________
Glasgow-haskell-bugs mailing list
[email protected]
http://www.haskell.org/mailman/listinfo/glasgow-haskell-bugs