[GHC] #13209: ghc panic with optimization.

#13209: ghc panic with optimization. -------------------------------------+------------------------------------- Reporter: 1chb | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 7.10.3 Keywords: | Operating System: Linux Architecture: x86 | Type of failure: GHC rejects | valid program Test Case: | Blocked By: Blocking: | Related Tickets: Differential Rev(s): | Wiki Page: -------------------------------------+------------------------------------- ghc eqFn && ./eqFn Works fine and the program runs fine too, but a bit slow. Adding optimization (-O) makes ghc panic (even after setting a bigger 'tick' factor): ghc -fsimpl-tick-factor=2000 -O eqFn && ./eqFn [1 of 1] Compiling Main ( eqFn.hs, eqFn.o ) ghc: panic! (the 'impossible' happened) (GHC version 7.10.3 for i386-unknown-linux): Simplifier ticks exhausted When trying UnfoldingDone f_XOO 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: 700804 My program eqFn.hs: {{{ {-# LANGUAGE FlexibleInstances #-} instance Eq a => Eq (Bool -> a) where f == g = f True == g True && f False == g False nand a b = not (a && b) xor a b = nand (nand a c) (nand b c) where c=nand a b halfAdder a b = (xor a b, a && b) -- (sum, cOut) fullAdder cIn a b = let (s, c') = halfAdder a b (sum, c'') = halfAdder cIn s in (sum, c' || c'') adder2 cIn a0 b0 a1 b1 = let (o0, cTmp) = fullAdder cIn a0 b0 (o1, cOut) = fullAdder cTmp a1 b1 in (o0, o1, cOut) adder4 cIn a0 b0 a1 b1 a2 b2 a3 b3 = let (o0, o1, cTmp) = adder2 cIn a0 b0 a1 b1 (o2, o3, cOut) = adder2 cTmp a2 b2 a3 b3 in (o0, o1, o2, o3, cOut) adder8 cIn a0 b0 a1 b1 a2 b2 a3 b3 a4 b4 a5 b5 a6 b6 a7 b7 = let (o0, o1, o2, o3, cTmp) = adder4 cIn a0 b0 a1 b1 a2 b2 a3 b3 (o4, o5, o6, o7, cOut) = adder4 cTmp a4 b4 a5 b5 a6 b6 a7 b7 in (o0, o1, o2, o3, o4, o5, o6, o7, cOut) main = print (adder8 == adder8) }}} Btw, it works if I replace adder8 with adder4 in the last line. I think this is a bug because, if the problem is too complicated for the optimizer it should just skip that part instead of failing. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/13209 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#13209: ghc panic with optimization. -------------------------------------+------------------------------------- Reporter: 1chb | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 7.10.3 Resolution: | Keywords: Operating System: Linux | Architecture: x86 Type of failure: GHC rejects | Test Case: valid program | Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Changes (by 1chb): * Attachment "eqFn.hs" added. Source code. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/13209 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#13209: ghc panic with optimization. -------------------------------------+------------------------------------- Reporter: 1chb | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 7.10.3 Resolution: | Keywords: Operating System: Linux | Architecture: x86 Type of failure: GHC rejects | Test Case: valid program | Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Description changed by 1chb: @@ -1,1 +1,6 @@ - ghc eqFn && ./eqFn + {{{ + > ghc eqFn && ./eqFn + [1 of 1] Compiling Main ( eqFn.hs, eqFn.o ) + Linking eqFn ... + True + }}} @@ -8,1 +13,2 @@ - ghc -fsimpl-tick-factor=2000 -O eqFn && ./eqFn + {{{ + > ghc -fsimpl-tick-factor=2000 -O eqFn && ./eqFn @@ -18,0 +24,1 @@ + }}} New description: {{{
ghc eqFn && ./eqFn [1 of 1] Compiling Main ( eqFn.hs, eqFn.o ) Linking eqFn ... True }}}
Works fine and the program runs fine too, but a bit slow. Adding optimization (-O) makes ghc panic (even after setting a bigger 'tick' factor): {{{
ghc -fsimpl-tick-factor=2000 -O eqFn && ./eqFn [1 of 1] Compiling Main ( eqFn.hs, eqFn.o ) ghc: panic! (the 'impossible' happened) (GHC version 7.10.3 for i386-unknown-linux): Simplifier ticks exhausted When trying UnfoldingDone f_XOO 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: 700804 }}}
My program eqFn.hs: {{{ {-# LANGUAGE FlexibleInstances #-} instance Eq a => Eq (Bool -> a) where f == g = f True == g True && f False == g False nand a b = not (a && b) xor a b = nand (nand a c) (nand b c) where c=nand a b halfAdder a b = (xor a b, a && b) -- (sum, cOut) fullAdder cIn a b = let (s, c') = halfAdder a b (sum, c'') = halfAdder cIn s in (sum, c' || c'') adder2 cIn a0 b0 a1 b1 = let (o0, cTmp) = fullAdder cIn a0 b0 (o1, cOut) = fullAdder cTmp a1 b1 in (o0, o1, cOut) adder4 cIn a0 b0 a1 b1 a2 b2 a3 b3 = let (o0, o1, cTmp) = adder2 cIn a0 b0 a1 b1 (o2, o3, cOut) = adder2 cTmp a2 b2 a3 b3 in (o0, o1, o2, o3, cOut) adder8 cIn a0 b0 a1 b1 a2 b2 a3 b3 a4 b4 a5 b5 a6 b6 a7 b7 = let (o0, o1, o2, o3, cTmp) = adder4 cIn a0 b0 a1 b1 a2 b2 a3 b3 (o4, o5, o6, o7, cOut) = adder4 cTmp a4 b4 a5 b5 a6 b6 a7 b7 in (o0, o1, o2, o3, o4, o5, o6, o7, cOut) main = print (adder8 == adder8) }}} Btw, it works if I replace adder8 with adder4 in the last line. I think this is a bug because, if the problem is too complicated for the optimizer it should just skip that part instead of failing. -- -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/13209#comment:1 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#13209: ghc panic with optimization. -------------------------------------+------------------------------------- Reporter: 1chb | Owner: Type: bug | Status: closed Priority: normal | Milestone: Component: Compiler | Version: 7.10.3 Resolution: wontfix | Keywords: Operating System: Linux | Architecture: x86 Type of failure: GHC rejects | Test Case: valid program | Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Changes (by mpickering): * status: new => closed * resolution: => wontfix @@ -1,6 +1,1 @@ - {{{ - > ghc eqFn && ./eqFn - [1 of 1] Compiling Main ( eqFn.hs, eqFn.o ) - Linking eqFn ... - True - }}} + ghc eqFn && ./eqFn @@ -13,2 +8,1 @@ - {{{ - > ghc -fsimpl-tick-factor=2000 -O eqFn && ./eqFn + ghc -fsimpl-tick-factor=2000 -O eqFn && ./eqFn @@ -24,1 +18,0 @@ - }}} New description: ghc eqFn && ./eqFn Works fine and the program runs fine too, but a bit slow. Adding optimization (-O) makes ghc panic (even after setting a bigger 'tick' factor): ghc -fsimpl-tick-factor=2000 -O eqFn && ./eqFn [1 of 1] Compiling Main ( eqFn.hs, eqFn.o ) ghc: panic! (the 'impossible' happened) (GHC version 7.10.3 for i386-unknown-linux): Simplifier ticks exhausted When trying UnfoldingDone f_XOO 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: 700804 My program eqFn.hs: {{{ {-# LANGUAGE FlexibleInstances #-} instance Eq a => Eq (Bool -> a) where f == g = f True == g True && f False == g False nand a b = not (a && b) xor a b = nand (nand a c) (nand b c) where c=nand a b halfAdder a b = (xor a b, a && b) -- (sum, cOut) fullAdder cIn a b = let (s, c') = halfAdder a b (sum, c'') = halfAdder cIn s in (sum, c' || c'') adder2 cIn a0 b0 a1 b1 = let (o0, cTmp) = fullAdder cIn a0 b0 (o1, cOut) = fullAdder cTmp a1 b1 in (o0, o1, cOut) adder4 cIn a0 b0 a1 b1 a2 b2 a3 b3 = let (o0, o1, cTmp) = adder2 cIn a0 b0 a1 b1 (o2, o3, cOut) = adder2 cTmp a2 b2 a3 b3 in (o0, o1, o2, o3, cOut) adder8 cIn a0 b0 a1 b1 a2 b2 a3 b3 a4 b4 a5 b5 a6 b6 a7 b7 = let (o0, o1, o2, o3, cTmp) = adder4 cIn a0 b0 a1 b1 a2 b2 a3 b3 (o4, o5, o6, o7, cOut) = adder4 cTmp a4 b4 a5 b5 a6 b6 a7 b7 in (o0, o1, o2, o3, o4, o5, o6, o7, cOut) main = print (adder8 == adder8) }}} Btw, it works if I replace adder8 with adder4 in the last line. I think this is a bug because, if the problem is too complicated for the optimizer it should just skip that part instead of failing. -- Comment: If you actually want the inliner to work really hard for you then you can set the tick factor to 0. Just looking at the definition of `==` and `adder8` it is clear that very aggressive inlining will at some point create an exponentially big program. When `==` is inlined at the first step we get {{{ adder8 == adder8 = adder8 True == adder8 True && adder8 False == adder8 False = adder8 True True == adder8 True True && adder8 True False == adder8 True False && adder8 False True == adder8 False True && adder8 False False == adder8 False False = .... }}} There is little difference between the compiler taking a very long time (as it does in this example) and looping forever. Some kind of limit on the simplifier is prudent to stop the compiler appearing to hang. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/13209#comment:2 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#13209: ghc panic with optimization. -------------------------------------+------------------------------------- Reporter: 1chb | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 7.10.3 Resolution: | Keywords: Operating System: Linux | Architecture: x86 Type of failure: GHC rejects | Test Case: valid program | Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Changes (by rwbarton): * status: closed => new * resolution: wontfix => -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/13209#comment:3 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#13209: ghc panic with optimization. -------------------------------------+------------------------------------- Reporter: 1chb | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 7.10.3 Resolution: | Keywords: Operating System: Linux | Architecture: x86 Type of failure: GHC rejects | Test Case: valid program | Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by 1chb): This is just a toy example. But what happens when I have a bigger program/system that contains one for the optimizer too heavy construct? Do I have to forget optimization for the rest of my program/system too? That is not practical. I think the optimizer should give up that part and optimize the rest. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/13209#comment:4 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#13209: ghc panic with optimization. -------------------------------------+------------------------------------- Reporter: 1chb | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 7.10.3 Resolution: | Keywords: Operating System: Linux | Architecture: x86 Type of failure: GHC rejects | Test Case: valid program | Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by j.waldmann): Perhaps the error type and error message should be changed here. "1chb" literally followed the suggestion to report a bug. {{{ ghc: panic! (the 'impossible' happened) ... Please report this as a GHC bug: http://www.haskell.org/ghc/reportabug }}} -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/13209#comment:5 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

There is little difference between the compiler taking a very long time (as it does in this example) and looping forever. Some kind of limit on
#13209: ghc panic with optimization. -------------------------------------+------------------------------------- Reporter: 1chb | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 7.10.3 Resolution: | Keywords: Operating System: Linux | Architecture: x86 Type of failure: GHC rejects | Test Case: valid program | Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by 1chb): Replying to [comment:2 mpickering]: the simplifier is prudent to stop the compiler appearing to hang. This my toy example is not important. But what happens when I have a bigger program/system that contains one for the optimizer too heavy construct? Do I have to forget optimization for the rest of the program/system too? That is not practical. I think the optimizer should give up that part and optimize the rest. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/13209#comment:6 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#13209: ghc panic with optimization. -------------------------------------+------------------------------------- Reporter: 1chb | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 7.10.3 Resolution: | Keywords: Operating System: Linux | Architecture: x86 Type of failure: GHC rejects | Test Case: valid program | Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by 1chb): Replying to [comment:5 j.waldmann]:
Perhaps the error type and error message should be changed here.
"1chb" literally followed the suggestion to report a bug. {{{ ghc: panic! (the 'impossible' happened) Yes, actually not that impossible.
... Please report this as a GHC bug: http://www.haskell.org/ghc/reportabug }}}
Well, it is still a bug. Maybe explain that it is a known bug and need not be reported again. As a workaround, choose another compiler/language. :) -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/13209#comment:7 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#13209: ghc panic with optimization. -------------------------------------+------------------------------------- Reporter: 1chb | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 7.10.3 Resolution: | Keywords: Operating System: Linux | Architecture: x86 Type of failure: GHC rejects | Test Case: valid program | Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by mpickering): You can tell the compiler to not inline `==` by saying `{-# NOINLINE (==) #-}`. This causes the program to compile quickly. Reid reopened this ticket as he says (on IRC) that he doesn't expect the simplifier to behave like this without an `INLINE` pragma. He said he would reply here shortly. You example is quite interesting as the type class allows the compiler to repeatably inline `==` but at different types each time. Normal recursive definitions, even with a fixed input, are not unrolled but with the "recursion" happening in this way it is easier to trick the compiler. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/13209#comment:8 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#13209: ghc panic with optimization. -------------------------------------+------------------------------------- Reporter: 1chb | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 7.10.3 Resolution: | Keywords: Operating System: Linux | Architecture: x86 Type of failure: GHC rejects | Test Case: valid program | Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by j.waldmann): The compiler does ( `./compiler/simplCore/Simplify.hs` ) {{{ completeCall ... = do case maybe_inline of Just .. -> do checkedTick ... Nothing -> ... }}} where `checkedTick` could raise the panic. It might be possible to check the tick counter, and take the `Nothing` branch if it's full. But do we want this? I guess it would prohibit *all* inlinings and rule applications from that point on (and until the end of the module?) which might produce really bad code. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/13209#comment:9 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler
participants (1)
-
GHC