[GHC] #14272: GHC goes out of memory while compiling simple program with optimizations

#14272: GHC goes out of memory while compiling simple program with optimizations -------------------------------------+------------------------------------- Reporter: 39aldo39 | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 7.10.3 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: -------------------------------------+------------------------------------- When compiling the following program with `ghc -O Main.hs`, GHC goes out of memory. {{{#!hs import Data.Bits (bit) main :: IO () main = putStrLn (show (f undefined)) f :: [Int] -> Int f = sum . zipWith ((+) . bit) [0..] . map undefined . scanl undefined undefined }}} I have 6 GB RAM and 8 GB swap free, so that shouldn't be the problem. It only happens with optimizations on, and it happens during a simplifier. Any simpler expressions do work. It even happens when `[0..]` is replaced by `take 1 [0..]`, but it compiles with `take 0 [0..]`. A straightforward workaround is to replace `zipWith f [0..]` by `\xs -> zipWith f [0..length xs] xs`. I ran into this problem when updating to GHC 8.2.1 from 8.0.2. But the given program doesn't compile on older versions as well. GHC 7.10.3 was the lowest version I could run before running into other problems. All GHC versions I tested come from the Debian repo. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/14272 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#14272: GHC goes out of memory while compiling simple program with optimizations -------------------------------------+------------------------------------- Reporter: 39aldo39 | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 7.10.3 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: Compile-time | Unknown/Multiple crash or panic | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Changes (by 39aldo39): * failure: None/Unknown => Compile-time crash or panic -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/14272#comment:1 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#14272: GHC goes out of memory while compiling simple program with optimizations -------------------------------------+------------------------------------- Reporter: 39aldo39 | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 7.10.3 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: Compile-time | Unknown/Multiple crash or panic | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by osa1): It seems to me that this may not be caused by allocation but maybe some code generation bug. I tried this: {{{ $ ghc-stage2 main.hs -O -fforce-recomp -ddump-ds -ddump-simpl -ddump-stg -ddump-to-file -dsuppress-all +RTS -M10000 ghc-stage2: maximum heap size (-M) is smaller than minimum alloc area size (-A) ghc-stage2: internal error: getTopHandlerThread: neither a WEAK nor a DEAD_WEAK: 0x7f9baeaa7fd8 0x7f9bae621270 -1991765780 (GHC version 8.3.20170914 for x86_64_unknown_linux) Please report this as a GHC bug: http://www.haskell.org/ghc/reportabug [1] 30799 abort ghc-stage2 main.hs -O -fforce-recomp -ddump-ds -ddump-simpl -ddump-stg +RTS $ ghc-stage2 main.hs -O -fforce-recomp -ddump-ds -ddump-simpl -ddump-stg -ddump-to-file -dsuppress-all +RTS -M100000 ghc-stage2: maximum heap size (-M) is smaller than minimum alloc area size (-A) reportHeapOverflow ghc-stage2: Heap exhausted; ghc-stage2: Current maximum heap size is 98304 bytes (0 MB). ghc-stage2: Use `+RTS -M<size>' to increase it. $ ghc-stage2 main.hs -O -fforce-recomp -ddump-ds -ddump-simpl -ddump-stg -ddump-to-file -dsuppress-all +RTS -M1000000 ghc-stage2: maximum heap size (-M) is smaller than minimum alloc area size (-A) ghc-stage2: panic! (the 'impossible' happened) (GHC version 8.3.20170914 for x86_64-unknown-linux): heap overflow Please report this as a GHC bug: http://www.haskell.org/ghc/reportabug }}} When I run without any RSTS parameters the error is triggered by `Storage.c:allocate` with these parameters: {{{ RtsFlags.GcFlags.maxHeapSize = 0 req_blocks = 1 LARGE_OBJECT_THRESHOLD: 3276 n: 2 }}} I don't know if `maxHeapSize = 0` is normal. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/14272#comment:2 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#14272: GHC goes out of memory while compiling simple program with optimizations -------------------------------------+------------------------------------- Reporter: 39aldo39 | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 7.10.3 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: Compile-time | Unknown/Multiple crash or panic | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by simonpj): Can anyone else reproduce this? I can't. Works fine for me with 7.10, 8.0, 8.2, and HEAD. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/14272#comment:3 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#14272: GHC goes out of memory while compiling simple program with optimizations -------------------------------------+------------------------------------- Reporter: 39aldo39 | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 7.10.3 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: Compile-time | Unknown/Multiple crash or panic | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by bgamari): Wow, indeed I can reproduce, {{{ $ ghc hi.hs -O [1 of 1] Compiling Main ( hi.hs, hi.o ) ghc: Out of memory $ ghc --version The Glorious Glasgow Haskell Compilation System, version 8.2.1 }}} Fascinating. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/14272#comment:4 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#14272: GHC goes out of memory while compiling simple program with optimizations -------------------------------------+------------------------------------- Reporter: 39aldo39 | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 7.10.3 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: Compile-time | Unknown/Multiple crash or panic | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by bgamari): It seems like things go off the rails during the core-to-core phase, {{{ $ ghc hi.hs -O -v3 ... *** Worker Wrapper binds [Main]: Result size of Worker Wrapper binds = {terms: 221, types: 143, coercions: 17, joins: 0/7} !!! Worker Wrapper binds [Main]: finished in 0.25 milliseconds, allocated 0.166 megabytes *** Simplifier [Main]: Result size of Simplifier iteration=1 = {terms: 227, types: 138, coercions: 17, joins: 1/3} ghc: Out of memory }}} -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/14272#comment:5 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#14272: GHC goes out of memory while compiling simple program with optimizations -------------------------------------+------------------------------------- Reporter: 39aldo39 | Owner: (none) Type: bug | Status: new Priority: high | Milestone: 8.4.1 Component: Compiler | Version: 7.10.3 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: Compile-time | Unknown/Multiple crash or panic | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Changes (by bgamari): * priority: normal => high * milestone: => 8.4.1 Comment: This is still reproducible with `master`. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/14272#comment:6 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#14272: GHC goes out of memory while compiling simple program with optimizations
-------------------------------------+-------------------------------------
Reporter: 39aldo39 | Owner: (none)
Type: bug | Status: new
Priority: high | Milestone: 8.4.1
Component: Compiler | Version: 7.10.3
Resolution: | Keywords:
Operating System: Unknown/Multiple | Architecture:
Type of failure: Compile-time | Unknown/Multiple
crash or panic | Test Case:
Blocked By: | Blocking:
Related Tickets: | Differential Rev(s):
Wiki Page: |
-------------------------------------+-------------------------------------
Changes (by bgamari):
* cc: hvr (added)
Comment:
Hmm, so this is quite a hint,
{{{
Thread 1 "ghc" hit Breakpoint 1, OutOfHeapHook (request_size=0,
heap_size=0) at rts/hooks/OutOfHeap.c:17
17 rts/hooks/OutOfHeap.c: No such file or directory.
(gdb) bt
#0 OutOfHeapHook (request_size=0, heap_size=0) at
rts/hooks/OutOfHeap.c:17
#1 0x00007f59ecb71d37 in allocate (cap=0x7f59ecba2080 <MainCapability>,
n=144115188075855874) at rts/sm/Storage.c:848
#2 0x00007f59ecb7c65e in stg_newByteArrayzh () from
/opt/exp/ghc/roots/8.2.1-dwarf/lib/ghc-8.2.1/bin/../rts/libHSrts_thr-
ghc8.2.1.so
#3 0x0000000000000000 in ?? ()
(gdb) x/24a $rbp
0x42001edf88: 0x7f59ed060148

#14272: GHC goes out of memory while compiling simple program with optimizations -------------------------------------+------------------------------------- Reporter: 39aldo39 | Owner: (none) Type: bug | Status: new Priority: high | Milestone: 8.4.1 Component: Compiler | Version: 7.10.3 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: Compile-time | Unknown/Multiple crash or panic | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Phab:D4021 Wiki Page: | -------------------------------------+------------------------------------- Changes (by bgamari): * differential: => Phab:D4021 Comment: Hmm, so the `i#` argument of `bitBigNat` is `0x7fffffffffffffff` in the failing call. The crash can be easily reproduced with simply `Data.Bits.bit 0x7fffffffffffffff`. Phab:D4021 should make the heap overflow a proper exception instead of bringing down the entire process (making debugging much easier). I still have yet to figure out exactly how the simplifier is producing this huge literal but regardless GHC should clearly behave a bit better here. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/14272#comment:8 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#14272: GHC goes out of memory while compiling simple program with optimizations -------------------------------------+------------------------------------- Reporter: 39aldo39 | Owner: (none) Type: bug | Status: new Priority: high | Milestone: 8.4.1 Component: Compiler | Version: 7.10.3 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: Compile-time | Unknown/Multiple crash or panic | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Phab:D4021 Wiki Page: | -------------------------------------+------------------------------------- Comment (by bgamari): For the record, here is the full backtrace, {{{ *** Exception (reporting due to +RTS -xc): (base:GHC.Exception.SomeException), stack trace: GhcMonad.gcatch, called from HscTypes.handleSourceError, called from GHC.Integer.Type.newBigNat#, called from GHC.Integer.Type.runS, called from GHC.Integer.Type.bitBigNat, called from GHC.Integer.Type.bitInteger, called from GHC.Integer.Type.shiftLInteger, called from PrelRules.intOp2', called from PrelRules.intOp2, called from PrelRules.primOpRules, called from MkId.mkPrimOpId, called from PrelInfo.primOpIds, called from Rules.matchRule, called from Rules.lookupRule, called from Simplify.tryRules, called from Simplify.rebuildCall, called from Simplify.rebuild, called from Simplify.simplExprF1, called from Simplify.simplExprF, called from Simplify.simplLazyBind, called from Outputable.pprDebugAndThen, called from Outputable.pprTrace, called from Simplify.simplRecOrTopPair, called from Simplify.simplRecBind, called from Simplify.simplTopBinds, called from SimplCore.SimplTopBinds, called from SimplMonad.initSmpl, called from SimplCore.simplifyPgmIO, called from CoreMonad.liftIO, called from CoreMonad.liftIOWithCount, called from SimplCore.simplifyPgm, called from SimplCore.Simplify, called from SimplCore.doCorePass, called from CoreLint.lintAnnots, called from SimplCore.runCorePasses, called from IOEnv.thenM, called from CoreMonad.>>=, called from IOEnv.runIOEnv, called from CoreMonad.runCoreM, called from SimplCore.core2core, called from HscTypes.liftIO, called from HscMain.Core2Core, called from HscTypes.>>=, called from HscTypes.runHsc, called from HscMain.hscIncrementalCompile, called from DriverPipeline.compileOne', called from GhcMake.upsweep_mod.compile_it, called from GhcMake.upsweep_mod, called from GhcMake.upsweep.upsweep', called from GhcMake.upsweep, called from GhcMake.load, called from GhcMonad.>>=, }}} -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/14272#comment:9 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#14272: GHC goes out of memory while compiling simple program with optimizations -------------------------------------+------------------------------------- Reporter: 39aldo39 | Owner: (none) Type: bug | Status: new Priority: high | Milestone: 8.4.1 Component: Compiler | Version: 7.10.3 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: Compile-time | Unknown/Multiple crash or panic | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Phab:D4021, Wiki Page: | Phab:D4025 -------------------------------------+------------------------------------- Changes (by bgamari): * differential: Phab:D4021 => Phab:D4021, Phab:D4025 Comment: Alright, so the problem is fairly obvious: after some amount of simplification we end up with `... (GHC.Prim.uncheckedIShiftL# 1# x_a3q9) ...`. After a bit more simplification we learn (due to case analysis) that `x_a3q9 = 9223372036854775807#`. This allows the `uncheckedIShiftL#` constant folding rule to fire, which then blows up as the result is absurdly large. This is fixed by adding another constant folding rule to catch this case (which should result in `0#`). This is done in Phab:D4025. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/14272#comment:10 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#14272: GHC goes out of memory while compiling simple program with optimizations
-------------------------------------+-------------------------------------
Reporter: 39aldo39 | Owner: (none)
Type: bug | Status: new
Priority: high | Milestone: 8.4.1
Component: Compiler | Version: 7.10.3
Resolution: | Keywords:
Operating System: Unknown/Multiple | Architecture:
Type of failure: Compile-time | Unknown/Multiple
crash or panic | Test Case:
Blocked By: | Blocking:
Related Tickets: | Differential Rev(s): Phab:D4021,
Wiki Page: | Phab:D4025
-------------------------------------+-------------------------------------
Comment (by Ben Gamari

#14272: GHC goes out of memory while compiling simple program with optimizations
-------------------------------------+-------------------------------------
Reporter: 39aldo39 | Owner: (none)
Type: bug | Status: new
Priority: high | Milestone: 8.4.1
Component: Compiler | Version: 7.10.3
Resolution: | Keywords:
Operating System: Unknown/Multiple | Architecture:
Type of failure: Compile-time | Unknown/Multiple
crash or panic | Test Case:
Blocked By: | Blocking:
Related Tickets: | Differential Rev(s): Phab:D4021,
Wiki Page: | Phab:D4025
-------------------------------------+-------------------------------------
Comment (by Ben Gamari

#14272: GHC goes out of memory while compiling simple program with optimizations -------------------------------------+------------------------------------- Reporter: 39aldo39 | Owner: (none) Type: bug | Status: closed Priority: high | Milestone: 8.4.1 Component: Compiler | Version: 7.10.3 Resolution: fixed | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: Compile-time | Unknown/Multiple crash or panic | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Phab:D4021, Wiki Page: | Phab:D4025 -------------------------------------+------------------------------------- Changes (by bgamari): * status: new => closed * resolution: => fixed -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/14272#comment:13 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler
participants (1)
-
GHC