[ 8 of 78] Compiling Distribution.Text ( Distribution/Text.hs, dist/build/Distribution/Text.o )[ 9 of 78] Compiling Distribution.Version ( Distribution/Version.hs, dist/build/Distribution/Version.o )ghc-stage2: panic! (the 'impossible' happened) (GHC version 7.9.20140911 for x86_64-unknown-linux): Simplifier ticks exhausted When trying UnfoldingDone GHC.Word.$fNumWord8_$c+ To increase the limit, use -fsimpl-tick-factor=N (default 100) If you need to do this, let GHC HQ know, and what factor you needed To see detailed counts use -ddump-simpl-stats Total ticks: 813720Please report this as a GHC bug: http://www.haskell.org/ghc/reportabug
I know that it still fails with tick factor 4096; I haven't found a tick amount which makes it succeed.
Trac metadata
Trac field
Value
Version
7.9
Type
Bug
TypeOfFailure
OtherFailure
Priority
highest
Resolution
Unresolved
Component
Compiler
Test case
Differential revisions
BlockedBy
Related
Blocking
CC
Operating system
Architecture
To upload designs, you'll need to enable LFS and have an admin enable hashed storage. More information
Child items
0
Show closed items
No child items are currently assigned. Use child items to break down this issue into smaller parts.
I've reduced the test case example. It appears to be related to the Generic binary implementation:
{-# LANGUAGE DeriveDataTypeable #-}{-# LANGUAGE DeriveGeneric #-}{-# OPTIONS_GHC -O #-}module Distribution.Version whereimport Data.Binary ( Binary(..) )import Data.Data ( Data )import Data.Typeable ( Typeable ) import GHC.Generics ( Generic )data T = A | B | C T | D T T | E T T deriving (Data, Generic, Typeable)instance Binary T
Displaying inlining information with -ddump-inlinings -ddump-rule-firings shows that after the first few unfoldings, the following repeats continually up until the failure. Increasing the tick cause simply causes more of this occurrence to display:
Rule fired: Class op gputRule fired: Class op gputRule fired: Class op gputRule fired: Class op gputInlining done: Data.Binary.Generic.unTaggedInlining done: Data.Binary.Generic.unTagged1Inlining done: GHC.Base.idInlining done: GHC.Word.$fOrdWord64_$c<=Inlining done: GHC.Word.$fNumWord64_$c-Inlining done: Data.Binary.Generic.$fSumSizeM1_$csumSizeInlining done: Data.Binary.Generic.$fSumSizeM1_$csumSizeRule fired: plusWord#Inlining done: GHC.Word.$fBitsWord64_$cfromIntegerRule fired: integerToWordRule fired: minusWord#Rule fired: leWord#Rule fired: tagToEnum#Inlining done: GHC.Word.$fBitsWord8_$cfromIntegerRule fired: integerToWordRule fired: narrow8Word#Inlining done: Data.Binary.Generic.$fSumSizeM1_$csumSizeInlining done: Data.Binary.Generic.$fSumSizeM1_$csumSizeRule fired: plusWord#Inlining done: GHC.Base.idRule fired: narrow8Word#Inlining done: GHC.Word.$fBitsWord8_$cshiftRRule fired: >=#Rule fired: tagToEnum#Rule fired: uncheckedShiftRL#Rule fired: Class op putSumInlining done: Data.Binary.Put.$fApplicativePutM_$c*>Inlining done: Data.Binary.Put.$fApplicativePutM2Rule fired: Class op putInlining done: Data.Binary.Put.putWord8Inlining done: GHC.Base.$Inlining done: GHC.Base.returnIOInlining done: GHC.Base.returnIO1Inlining done: GHC.Base.bindIOInlining done: GHC.Base.bindIO1Inlining done: GHC.Base.flipInlining done: Foreign.Storable.$fStorableWord8_$cpokeInlining done: Foreign.Storable.$fStorableWord19Rule fired: Class op gputInlining done: GHC.Word.$fNumWord8_$c+Rule fired: plusWord#Rule fired: narrow8Word#Inlining done: GHC.Word.$fNumWord8_$c-Rule fired: minusWord#Rule fired: narrow8Word#Rule fired: Class op putSumInlining done: Data.Binary.Put.$fApplicativePutM_$c*>Inlining done: Data.Binary.Put.$fApplicativePutM2Rule fired: Class op putInlining done: Data.Binary.Put.putWord8Inlining done: GHC.Base.$Inlining done: GHC.Base.returnIOInlining done: GHC.Base.returnIO1Inlining done: GHC.Base.bindIOInlining done: GHC.Base.bindIO1Inlining done: GHC.Base.flipInlining done: Foreign.Storable.$fStorableWord8_$cpokeInlining done: Foreign.Storable.$fStorableWord19
b9e49d3e9580e13d89efd1f779cb76f610e0d6e0 is the first bad commit [4/1912]commit b9e49d3e9580e13d89efd1f779cb76f610e0d6e0Author: Simon Peyton Jones <simonpj@microsoft.com>Date: Tue May 13 13:10:26 2014 +0100 Add -fspecialise-aggressively This flag specialises any imported overloaded function that has an unfolding, whether or not it was marked INLINEABLE. We get a lot of orphan SPEC rules as a result, but that doesn't matter provided we don't treat orphan auto-generated rules as causing the module itself to be an orphan module. See Note [Orphans and auto-generated rules] in MkIface.
I thought this was going to be very complicated but it turned out to be very simple! The occurrence analyser does something called "glomming" if the application of imported RULES means that something that didn't look recursive becomes recursive. See Note [Glomming] in OccurAnal. Under these circumstances we group all the top-level bindings into a single massive Rec.
But, crucially, I failed to repeat the occurrence analysis on this glommed set of bindings. That means that we weren't establishing the right loop breakers (indeed there were no loop breakers whatsoever), and that led immediately to the loop. The only surprising this is that it didn't happen before.
I've just pushed it. I'm getting a failure on perf/compiler/T783, but as usual I'm uncertain about whether the patch is the culprit or not. I suspect not, so since it's a blocker I'm pushing it anyway.
I've just pushed it. I'm getting a failure on perf/compiler/T783, but as usual I'm uncertain about whether the patch is the culprit or not. I suspect not, so since it's a blocker I'm pushing it anyway.
fwiw, Phab:harbormaster/build/952 built just fine (but that's for Linux/x86_64 thresholds)
Perhaps someone can confirm that Cabal is ok, and then close.
Pedro: the "deriving Binary" stuff still generates a gargantuan quantity of code!
Compiling Cabal within the GHC tree is not really ok (see comments in D183). It does compile, but it takes *several* minutes (somewhere beyond 7 minutes on the buildbot) as well as massive amount of memory (over 50% of the 4GiB mem available in the buildbot, causing it to fail w/ an out-of-mem exception since we build with CPUS=4) when trying to produce the libraries/Cabal/Cabal/dist-install/build/Language/Haskell/Extension.o module with ghc-stage1.
Well this ticket was about a bug in GHC that meant it really didn't compile *at all*. Now, from what you say, it does. But there may still be a problem with the amount of code that deriving Binary generates (hence copying Pedro), perhaps due to nested tuples (which might be helped by the new SOP approach) or perhaps due to over-enthusiastic INLINE pragmas.
In any case, I don't think there's a bug in GHC any more. But I'll leave this ticket open in the hope that we may make progress on the deriving Binary question.