#5539: GHC panic - Simplifier ticks exhausted
---------------------------------+------------------------------------------
Reporter: hvr | Owner: simonpj
Type: bug | Status: new
Priority: high | Milestone: 7.4.1
Component: Compiler | Version: 7.3
Resolution: | Keywords:
Os: Linux | Architecture: x86_64 (amd64)
Failure: Compile-time crash | Difficulty: Unknown
Testcase: | Blockedby:
Blocking: | Related:
---------------------------------+------------------------------------------
Comment(by hvr):
Replying to [comment:23 ezyang]:
> If someone has the free time to generate a minimal test case, that would
probably be *very* useful. The less files, the better. The smaller, the
better.
Does the following test-case help?
{{{
#!hs
{-# LANGUAGE CPP #-}
module Bug5539 where
bar0 v = undefined
{-# INLINE bar0 #-}
bar1 v = v
{-# INLINE bar1 #-}
bar2 v = v + v
{-# INLINE bar2 #-}
bar3 v = v + v + v
{-# INLINE bar3 #-}
barn n v | n == 0 = bar0 v
| n == 1 = bar1 v
| n == 2 = bar2 v
| n == 3 = bar3 v
| otherwise = v + barn (n-1) v
{-# INLINE barn #-}
foo 0 v = bar0 v
foo 1 v = bar1 v
foo 2 v = bar2 v
foo 3 v = bar3 v
foo n v = barn n v
{-# INLINE foo #-}
#define GEN2(a,b) \
a 0 v = b 0 v + b 1 v ; \
a 1 v = b 1 v + b 2 v ; \
a 2 v = b 2 v + b 3 v ; \
a 3 v = b 3 v + b 4 v ; \
a 4 v = b 4 v + b 5 v ; \
a n v = b n v + b (n+1) v ; \
{-# INLINE a #-} ; \
GEN2(baz0, foo)
GEN2(baz1, baz0)
GEN2(baz2, baz1)
GEN2(baz3, baz2)
-- EOF
}}}
{{{
$ ghc-7.4.0.20111215 -fforce-recomp -O Bug5539.hs
[1 of 1] Compiling Bug5539 ( Bug5539.hs, Bug5539.o )
ghc: panic! (the 'impossible' happened)
(GHC version 7.4.0.20111215 for x86_64-unknown-linux):
Simplifier ticks exhausted
When trying UnfoldingDone ( main:Bug5539.bar3{v r9P} [lidx] :: forall
( a{tv ahs} [sk] :: ghc-prim:GHC.Prim.*{(w) tc 34d} ).
base:GHC.Num.Num{tc 2b}
(
a{tv ahs} [sk] :: ghc-prim:GHC.Prim.*{(w) tc 34d} ) =>
( a{tv
ahs} [sk] :: ghc-prim:GHC.Prim.*{(w) tc 34d} )
-> (
a{tv ahs} [sk] :: ghc-prim:GHC.Prim.*{(w) tc 34d} ) )
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: 46322
}}}
--
Ticket URL: <http://hackage.haskell.org/trac/ghc/ticket/5539#comment:24>
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