[GHC] #14959: Heep overflow in optimizer

#14959: Heep overflow in optimizer -------------------------------------+------------------------------------- Reporter: darchon | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.4.1 Keywords: | Operating System: Unknown/Multiple Architecture: | Type of failure: None/Unknown Unknown/Multiple | Test Case: | Blocked By: Blocking: | Related Tickets: Differential Rev(s): | Wiki Page: -------------------------------------+------------------------------------- Compiling the following with optimisations: {{{ module Test where import Data.Bits (setBit) f = foldl setBit 0 [x | (x,_) <- zip [0..] [1]] :: Integer }}} fails with: {{{ $ ghc -O0 -fforce-recomp Test.hs [1 of 1] Compiling Test ( Test.hs, Test.o ) $ ghc -O -fforce-recomp Test.hs [1 of 1] Compiling Test ( Test.hs, Test.o ) ghc: panic! (the 'impossible' happened) (GHC version 8.4.1 for x86_64-unknown-linux): heap overflow }}} Fails on 8.0.2, 8.2.2, and 8.4.1 -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/14959 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#14959: Heap overflow in optimizer -------------------------------------+------------------------------------- Reporter: darchon | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.4.1 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by RyanGlScott): Stunning. This bug goes all the way back to GHC 8.0.1, even (note that before 8.4.1, you would simply get the error message `ghc: Out of memory` instead of a panic). GHC 7.10.3 does not suffer from this issue. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/14959#comment:1 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#14959: Heap overflow in optimizer -------------------------------------+------------------------------------- Reporter: darchon | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.4.1 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by darchon): Some notes which I forgot to mention: * Result need to be `Integer`, no heap overflow on `Int` or `Word` * The folded computation needs to be `setBit`, no heap overflow on `+` or `div` * The `[0..]` needs to be the first argument of `zip`, no heap overflow on `zip [1] [0..]` -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/14959#comment:2 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#14959: Heap overflow in optimizer -------------------------------------+------------------------------------- Reporter: darchon | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.4.1 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by RyanGlScott): The `-ddump-rule-rewrites` output for this program is rather interesting: {{{ $ ghc -O -fforce-recomp -ddump-rule-rewrites Bug.hs [1 of 1] Compiling Test ( Bug.hs, Bug.o ) <elided> Rule fired Rule: ==# Module: (BUILTIN) Before: GHC.Prim.==# ValArg x_a2Lu ValArg 9223372036854775807# After: case x_a2Lu of wild_00 { __DEFAULT -> 0#; 9223372036854775807# -> 1# } Cont: StrictArg GHC.Prim.tagToEnum# Select nodup wild1_a2Lw Stop[RhsCtxt] [GHC.Integer.Type.Integer] -> GHC.Integer.Type.Integer -> GHC.Integer.Type.Integer Rule fired Rule: tagToEnum# Module: (BUILTIN) Before: GHC.Prim.tagToEnum# TyArg GHC.Types.Bool ValArg 0# After: GHC.Types.False Cont: Select ok wild1_a2Lw Stop[BoringCtxt] [GHC.Integer.Type.Integer] -> GHC.Integer.Type.Integer -> GHC.Integer.Type.Integer Rule fired Rule: tagToEnum# Module: (BUILTIN) Before: GHC.Prim.tagToEnum# TyArg GHC.Types.Bool ValArg 1# After: GHC.Types.True Cont: Select ok wild1_a2Lw Stop[BoringCtxt] [GHC.Integer.Type.Integer] -> GHC.Integer.Type.Integer -> GHC.Integer.Type.Integer Rule fired Rule: bitInteger Module: (BUILTIN) Before:ghc: Out of memory }}} -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/14959#comment:3 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#14959: Heap overflow in optimizer -------------------------------------+------------------------------------- Reporter: darchon | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.4.1 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by darchon): Incidentally, the `bitInteger` rule was updated/changed/added in 8.0.1 according to: * https://github.com/ghc/ghc/blob/abaf43d9d88d6fdf7345b936a571d17cfe1fa140/com... * https://ghc.haskell.org/trac/ghc/ticket/8832 -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/14959#comment:4 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#14959: Heap overflow in optimizer -------------------------------------+------------------------------------- Reporter: darchon | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.4.1 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by simonpj): See also dup report #14962 -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/14959#comment:5 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#14959: Heap overflow in optimizer -------------------------------------+------------------------------------- Reporter: darchon | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.4.1 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by simonpj): I see this code in Core {{{ go_a2Rl = \ (x_a2Rm :: GHC.Prim.Int#) (eta_B1 :: [Integer]) (eta_X2 :: Integer) -> case eta_B1 of { [] -> eta_X2; : y_a2SA ys_a2SB -> let { eta_Xn :: Integer eta_Xn = GHC.Integer.Type.orInteger eta_X2 (GHC.Integer.Type.bitInteger x_a2Rm) } in case x_a2Rm of wild_XL { __DEFAULT -> go_a2Rl (GHC.Prim.+# wild_XL 1#) ys_a2SB eta_Xn; 9223372036854775807# -> eta_Xn } } }}} If we inline `eta_Xn` (which is only used once) we get {{{ ...(case x_a2Rm of wild_XL { __DEFAULT -> ... 9223372036854775807# -> GHC.Integer.Type.orInteger eta_X2 (GHC.Integer.Type.bitInteger x_a2Rm) )... }}} Now GHC sees that in the branch of the case it knows that `x = 9223372036854775807#`. So it tries to do constant folding. But the result is a rather big Integer: {{{ Prelude Data.Bits GHC.Exts> bit (I# 3#) :: Integer 8 Prelude Data.Bits GHC.Exts> bit (I# 4#) :: Integer 16 Prelude Data.Bits GHC.Exts> bit (I# 20#) :: Integer 1048576 Prelude Data.Bits GHC.Exts> bit (I# 60#) :: Integer 1152921504606846976 Prelude Data.Bits GHC.Exts> bit (I# 200#) :: Integer 1606938044258990275541962092341162602522202993782792835301376 }}} I'll leave you to imagine how big `bit 9223372036854775807#` is. Solution: the `bitInteger` rule should only work if its argument is "small enough". I suggest that "small enough" means "smaller than wordSizeInBits", ie x<64 on a 64 bit machine. I'm validating a patch. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/14959#comment:6 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#14959: Heap overflow in optimizer
-------------------------------------+-------------------------------------
Reporter: darchon | Owner: (none)
Type: bug | Status: new
Priority: normal | Milestone:
Component: Compiler | Version: 8.4.1
Resolution: | Keywords:
Operating System: Unknown/Multiple | Architecture:
| Unknown/Multiple
Type of failure: None/Unknown | Test Case:
Blocked By: | Blocking:
Related Tickets: | Differential Rev(s):
Wiki Page: |
-------------------------------------+-------------------------------------
Comment (by Simon Peyton Jones

#14959: Heap overflow in optimizer -------------------------------------+------------------------------------- Reporter: darchon | Owner: (none) Type: bug | Status: merge Priority: normal | Milestone: Component: Compiler | Version: 8.4.1 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: | simplCore/should_compile/T14959 Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Changes (by simonpj): * status: new => merge * testcase: => simplCore/should_compile/T14959 -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/14959#comment:8 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#14959: Heap overflow in optimizer -------------------------------------+------------------------------------- Reporter: darchon | Owner: (none) Type: bug | Status: closed Priority: normal | Milestone: 8.4.2 Component: Compiler | Version: 8.4.1 Resolution: fixed | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: | simplCore/should_compile/T14959 Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Changes (by bgamari): * status: merge => closed * resolution: => fixed * milestone: => 8.4.2 Comment: Merged to `ghc-8.4`. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/14959#comment:9 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler
participants (1)
-
GHC