[GHC] #9565: T3500b exhaust simplifier ticks (loops?) on WAY=optasm
GHC
ghc-devs at haskell.org
Mon Sep 8 19:50:55 UTC 2014
#9565: T3500b exhaust simplifier ticks (loops?) on WAY=optasm
-------------------------------------+-------------------------------------
Reporter: slyfox | Owner:
Type: bug | Status: new
Priority: normal | Milestone:
Component: Compiler | Version: 7.9
Keywords: | Operating System:
Architecture: x86_64 (amd64) | Unknown/Multiple
Difficulty: Unknown | Type of failure: Compile-
Blocked By: | time crash
Related Tickets: | Test Case: T3500b
| Blocking:
| Differential Revisions:
-------------------------------------+-------------------------------------
{{{
$ make fulltest TEST="T3500b" WAY=optasm
=====> T3500b(optasm) 3767 of 4101 [0, 0, 0]
cd ./typecheck/should_run && '/home/slyfox/dev/git/ghc-
validate/inplace/bin/ghc-stage2' -fforce-recomp -dcore-lint -dcmm-lint
-dno-debug-output -no-user-package-db -rtsopts -fno-ghci-history -o T3500b
T3500b.hs -O -fasm >T3500b.comp.stderr 2>&1
Compile failed (status 256) errors were:
[1 of 1] Compiling Main ( T3500b.hs, T3500b.o )
ghc-stage2: panic! (the 'impossible' happened)
(GHC version 7.9.20140907 for x86_64-unknown-linux):
Simplifier ticks exhausted
When trying RuleFired foldr/augment
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: 12441
Please report this as a GHC bug: http://www.haskell.org/ghc/reportabug
}}}
Attempt to increase '''-fsimpl-tick-factor''' does not help copiling
sample.
Looks like infinite inlining pass.
The test source itself:
{{{#!hs
{-# LANGUAGE TypeFamilies, FlexibleContexts, UndecidableInstances #-}
module Main where
newtype Mu f = Mu (f (Mu f))
type family Id m
type instance Id m = m
instance Show (Id (f (Mu f))) => Show (Mu f) where
show (Mu f) = show f
showMu :: Mu (Either ()) -> String
showMu = show
item :: Mu (Either ())
item = Mu (Right (Mu (Left ())))
main = print (showMu item)
}}}
--
Ticket URL: <http://ghc.haskell.org/trac/ghc/ticket/9565>
GHC <http://www.haskell.org/ghc/>
The Glasgow Haskell Compiler
More information about the ghc-tickets
mailing list