[GHC] #14379: GHC 2.8.1 Consumes All Memory On Build

#14379: GHC 2.8.1 Consumes All Memory On Build -------------------------------------+------------------------------------- Reporter: jm4games | Owner: (none) Type: bug | Status: new Priority: high | Milestone: Component: Compiler | Version: 8.2.1 Keywords: | Operating System: Linux Architecture: x86_64 | Type of failure: Compile-time (amd64) | crash or panic Test Case: | Blocked By: Blocking: | Related Tickets: Differential Rev(s): | Wiki Page: -------------------------------------+------------------------------------- The following code will cause GHC to consume all memory/swap and eventually crash. {{{ #!div style="font-size: 80%" Code highlighting: {{{#!haskell module Test.Test where import Data.Text (Text) import Data.Monoid ((<>)) import Data.Vector as V import TextShow (showt) compileTest :: V.Vector (Text, V.Vector (Int, V.Vector a)) -> V.Vector (Text, V.Vector (Int, V.Vector a)) -> Either Text () compileTest vecA vecB = V.ifoldl' validateSym (Right ()) vecB where validateSym :: Either Text () -> Int -> (Text, V.Vector (Int, V.Vector a)) -> Either Text () validateSym res iSym (sym, freqs) | Just sym == (fst <$> (vecA V.!? iSym)) = V.ifoldl' validateFreq res freqs | otherwise = Left $ if iSym < V.length vecA then "Seed data" <> " not found at index [" <> showt iSym <> "]." else "No " <> sym <> " at index " <> showt iSym <> "." where validateFreq :: Either Text () -> Int -> (Int, V.Vector a) -> Either Text () validateFreq res2 iFreq (freq, _) | freq == fst (snd (vecA V.! iSym) V.! iFreq) = res2 | otherwise = Left $ "Seed data " <> (fst (vecA V.! iSym)) <> " at frequency " <> showt (fst (snd (vecA V.! iSym) V.! iFreq)) <> " not found at index [" <> showt iSym <> "][" <> showt iFreq -- <> "]." }}} }}} NOTE: The snippet is large (and messy) because there seems to be an exact sequence of evaluation to causing the out of memory. For example if you comment out line 26 (<> showt iFreq) it will allow the code to compile. Like wise if I comment out all of line 25 it will compile. I can't seem to figure out what exact combination of things causes the issue. Cabal file (used with stack 1.5.1, resolver: nightly-2017-10-21). {{{ #!div style="font-size: 80%" Code highlighting: {{{#!text name: some-test version: 0.2.1.0 build-type: Simple cabal-version: >= 1.10 library default-language: Haskell2010 ghc-options: -Wall -fwarn-tabs -funbox-strict-fields -fno-warn- unused-do-bind -O2 ghc-prof-options: -fprof-auto exposed-modules: Test.Test build-depends: base >= 4.9 && < 4.11, text >= 1.2, text-show >= 3.4 && < 3.7, vector >= 0.10 && < 0.13 default-extensions: OverloadedStrings }}} }}} -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/14379 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#14379: Regression - GHC 2.8.1 Consumes All Memory On Build -------------------------------------+------------------------------------- Reporter: jm4games | Owner: (none) Type: bug | Status: new Priority: high | Milestone: Component: Compiler | Version: 8.2.1 Resolution: | Keywords: Operating System: Linux | Architecture: x86_64 Type of failure: Compile-time | (amd64) crash or panic | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): 8.0.2 Wiki Page: | -------------------------------------+------------------------------------- Changes (by jm4games): * differential: => 8.0.2 Old description:
The following code will cause GHC to consume all memory/swap and eventually crash.
{{{ #!div style="font-size: 80%" Code highlighting: {{{#!haskell module Test.Test where
import Data.Text (Text)
import Data.Monoid ((<>)) import Data.Vector as V import TextShow (showt)
compileTest :: V.Vector (Text, V.Vector (Int, V.Vector a)) -> V.Vector (Text, V.Vector (Int, V.Vector a)) -> Either Text () compileTest vecA vecB = V.ifoldl' validateSym (Right ()) vecB where validateSym :: Either Text () -> Int -> (Text, V.Vector (Int, V.Vector a)) -> Either Text () validateSym res iSym (sym, freqs) | Just sym == (fst <$> (vecA V.!? iSym)) = V.ifoldl' validateFreq res freqs | otherwise = Left $ if iSym < V.length vecA then "Seed data" <> " not found at index [" <> showt iSym <> "]." else "No " <> sym <> " at index " <> showt iSym <> "." where validateFreq :: Either Text () -> Int -> (Int, V.Vector a) -> Either Text () validateFreq res2 iFreq (freq, _) | freq == fst (snd (vecA V.! iSym) V.! iFreq) = res2 | otherwise = Left $ "Seed data " <> (fst (vecA V.! iSym)) <> " at frequency " <> showt (fst (snd (vecA V.! iSym) V.! iFreq)) <> " not found at index [" <> showt iSym <> "][" <> showt iFreq -- <> "]." }}} }}}
NOTE: The snippet is large (and messy) because there seems to be an exact sequence of evaluation to causing the out of memory. For example if you comment out line 26 (<> showt iFreq) it will allow the code to compile. Like wise if I comment out all of line 25 it will compile. I can't seem to figure out what exact combination of things causes the issue.
Cabal file (used with stack 1.5.1, resolver: nightly-2017-10-21). {{{ #!div style="font-size: 80%" Code highlighting: {{{#!text name: some-test version: 0.2.1.0 build-type: Simple cabal-version: >= 1.10
library default-language: Haskell2010 ghc-options: -Wall -fwarn-tabs -funbox-strict-fields -fno-warn- unused-do-bind -O2 ghc-prof-options: -fprof-auto
exposed-modules: Test.Test
build-depends: base >= 4.9 && < 4.11, text >= 1.2, text-show >= 3.4 && < 3.7, vector >= 0.10 && < 0.13
default-extensions: OverloadedStrings }}} }}}
New description: The following code will cause GHC to consume all memory/swap and eventually crash (a regression from 8.0.2). {{{ #!div style="font-size: 80%" Code highlighting: {{{#!haskell module Test.Test where import Data.Text (Text) import Data.Monoid ((<>)) import Data.Vector as V import TextShow (showt) compileTest :: V.Vector (Text, V.Vector (Int, V.Vector a)) -> V.Vector (Text, V.Vector (Int, V.Vector a)) -> Either Text () compileTest vecA vecB = V.ifoldl' validateSym (Right ()) vecB where validateSym :: Either Text () -> Int -> (Text, V.Vector (Int, V.Vector a)) -> Either Text () validateSym res iSym (sym, freqs) | Just sym == (fst <$> (vecA V.!? iSym)) = V.ifoldl' validateFreq res freqs | otherwise = Left $ if iSym < V.length vecA then "Seed data" <> " not found at index [" <> showt iSym <> "]." else "No " <> sym <> " at index " <> showt iSym <> "." where validateFreq :: Either Text () -> Int -> (Int, V.Vector a) -> Either Text () validateFreq res2 iFreq (freq, _) | freq == fst (snd (vecA V.! iSym) V.! iFreq) = res2 | otherwise = Left $ "Seed data " <> (fst (vecA V.! iSym)) <> " at frequency " <> showt (fst (snd (vecA V.! iSym) V.! iFreq)) <> " not found at index [" <> showt iSym <> "][" <> showt iFreq -- <> "]." }}} }}} NOTE: The snippet is large (and messy) because there seems to be an exact sequence of evaluation to causing the out of memory. For example if you comment out line 26 (<> showt iFreq) it will allow the code to compile. Like wise if I comment out all of line 25 it will compile. I can't seem to figure out what exact combination of things causes the issue. Cabal file (used with stack 1.5.1, resolver: nightly-2017-10-21). {{{ #!div style="font-size: 80%" Code highlighting: {{{#!text name: some-test version: 0.2.1.0 build-type: Simple cabal-version: >= 1.10 library default-language: Haskell2010 ghc-options: -Wall -fwarn-tabs -funbox-strict-fields -fno-warn- unused-do-bind -O2 ghc-prof-options: -fprof-auto exposed-modules: Test.Test build-depends: base >= 4.9 && < 4.11, text >= 1.2, text-show >= 3.4 && < 3.7, vector >= 0.10 && < 0.13 default-extensions: OverloadedStrings }}} }}} -- -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/14379#comment:1 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#14379: Regression - GHC 2.8.1 Consumes All Memory On Build -------------------------------------+------------------------------------- Reporter: jm4games | Owner: (none) Type: bug | Status: new Priority: high | Milestone: Component: Compiler | Version: 8.2.1 Resolution: | Keywords: Operating System: Linux | Architecture: x86_64 Type of failure: Compile-time | (amd64) crash or panic | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): 8.0.2 Wiki Page: | -------------------------------------+------------------------------------- Comment (by simonpj): As so often, I failed to reproduce this with HEAD, at the first fence {{{ simonpj@cam-05-unx:/cam-01-srv/simonpj/tmp/T14379$ cabal install --with- ghc=/home/simonpj/5builds/HEAD/inplace/bin/ghc-stage2 --allow-newer Resolving dependencies... Configuring primitive-0.6.2.0... Building primitive-0.6.2.0... Failed to install primitive-0.6.2.0 Build log ( /home/simonpj/.cabal/logs/primitive-0.6.2.0.log ): cabal: Entering directory '/tmp/cabal-tmp-46331/primitive-0.6.2.0' Configuring primitive-0.6.2.0... Building primitive-0.6.2.0... Preprocessing library primitive-0.6.2.0... [ 1 of 12] Compiling Control.Monad.Primitive ( Control/Monad/Primitive.hs, dist/build/Control/Monad/Primitive.o ) Control/Monad/Primitive.hs:45:1: warning: [-Wdeprecations] Module ‘Control.Monad.Trans.List’ is deprecated: This transformer is invalid on most monads | 45 | import Control.Monad.Trans.List ( ListT ) | ^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^ ...plus many more similar deprecation warnings... [ 2 of 12] Compiling Data.Primitive.Internal.Compat ( Data/Primitive/Internal/Compat.hs, dist/build/Data/Primitive/Internal/Compat.o ) [ 3 of 12] Compiling Data.Primitive.Array ( Data/Primitive/Array.hs, dist/build/Data/Primitive/Array.o ) Data/Primitive/Array.hs:531:10: error: • No instance for (Semigroup (Array a)) arising from the superclasses of an instance declaration • In the instance declaration for ‘Monoid (Array a)’ | 531 | instance Monoid (Array a) where | ^^^^^^^^^^^^^^^^ cabal: Leaving directory '/tmp/cabal-tmp-46331/primitive-0.6.2.0' cabal: Error: some packages failed to install: primitive-0.6.2.0 failed during the building phase. The exception was: ExitFailure 1 some-test-0.2.1.0 depends on primitive-0.6.2.0 which failed to install. vector-0.12.0.1 depends on primitive-0.6.2.0 which failed to install. simonpj@cam-05-unx:/cam-01-srv/simonpj/tmp/T14379$ }}} Without `--allow-newer` it falls over much faster. Any ideas for how to fix? I will try again with 8.2. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/14379#comment:2 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#14379: Regression - GHC 2.8.1 Consumes All Memory On Build -------------------------------------+------------------------------------- Reporter: jm4games | Owner: (none) Type: bug | Status: new Priority: high | Milestone: Component: Compiler | Version: 8.2.1 Resolution: | Keywords: Operating System: Linux | Architecture: x86_64 Type of failure: Compile-time | (amd64) crash or panic | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): 8.0.2 Wiki Page: | -------------------------------------+------------------------------------- Comment (by mpickering): Since Herbert merged the commit which made Semigroup a superclass of Monoid it became much more difficult to build packages with HEAD. https://phabricator.haskell.org/rGHC8ae263ceb3566a7c82336400b09cb8f381217405 The most reliable way I found now was to use the package overlay he posted about but it is more fiddly to set up. https://mail.haskell.org/pipermail/ghc-devs/2017-September/014682.html -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/14379#comment:3 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#14379: Regression - GHC 2.8.1 Consumes All Memory On Build -------------------------------------+------------------------------------- Reporter: jm4games | Owner: (none) Type: bug | Status: new Priority: high | Milestone: Component: Compiler | Version: 8.2.1 Resolution: | Keywords: Operating System: Linux | Architecture: x86_64 Type of failure: Compile-time | (amd64) crash or panic | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): 8.0.2 Wiki Page: | -------------------------------------+------------------------------------- Comment (by simonpj): OK I have a fix for this. It was `SpecConstr` going wild. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/14379#comment:4 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#14379: Regression - GHC 2.8.1 Consumes All Memory On Build
-------------------------------------+-------------------------------------
Reporter: jm4games | Owner: (none)
Type: bug | Status: new
Priority: high | Milestone:
Component: Compiler | Version: 8.2.1
Resolution: | Keywords:
Operating System: Linux | Architecture: x86_64
Type of failure: Compile-time | (amd64)
crash or panic | Test Case:
Blocked By: | Blocking:
Related Tickets: | Differential Rev(s): 8.0.2
Wiki Page: |
-------------------------------------+-------------------------------------
Comment (by Simon Peyton Jones

#14379: Regression - GHC 2.8.1 Consumes All Memory On Build -------------------------------------+------------------------------------- Reporter: jm4games | Owner: (none) Type: bug | Status: new Priority: high | Milestone: Component: Compiler | Version: 8.2.1 Resolution: | Keywords: Operating System: Linux | Architecture: x86_64 Type of failure: Compile-time | (amd64) crash or panic | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): 8.0.2 Wiki Page: | -------------------------------------+------------------------------------- Comment (by simonpj): This would be worth merging to 8.2. I have not added a test because the repro case is tricky. My change deliberately reduces the amount of specialisation that `SpecConstr` does; but I suppose it's possible that some other important use-case will get worse. But I think it's unlikely. Worth a check on `perf.haskell.org`. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/14379#comment:6 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#14379: Regression - GHC 2.8.1 Consumes All Memory On Build -------------------------------------+------------------------------------- Reporter: jm4games | Owner: (none) Type: bug | Status: merge Priority: high | Milestone: Component: Compiler | Version: 8.2.1 Resolution: | Keywords: Operating System: Linux | Architecture: x86_64 Type of failure: Compile-time | (amd64) crash or panic | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): 8.0.2 Wiki Page: | -------------------------------------+------------------------------------- Changes (by simonpj): * status: new => merge -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/14379#comment:7 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#14379: Regression - GHC 2.8.1 Consumes All Memory On Build -------------------------------------+------------------------------------- Reporter: jm4games | Owner: (none) Type: bug | Status: merge Priority: high | Milestone: Component: Compiler | Version: 8.2.1 Resolution: | Keywords: Operating System: Linux | Architecture: x86_64 Type of failure: Compile-time | (amd64) crash or panic | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): 8.0.2 Wiki Page: | -------------------------------------+------------------------------------- Comment (by jm4games): Thanks alot simon! -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/14379#comment:8 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#14379: Regression - GHC 8.2.1 Consumes All Memory On Build -------------------------------------+------------------------------------- Reporter: jm4games | Owner: (none) Type: bug | Status: merge Priority: high | Milestone: Component: Compiler | Version: 8.2.1 Resolution: | Keywords: Operating System: Linux | Architecture: x86_64 Type of failure: Compile-time | (amd64) crash or panic | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): 8.0.2 Wiki Page: | -------------------------------------+------------------------------------- -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/14379#comment:9 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#14379: Regression - GHC 8.2.1 Consumes All Memory On Build -------------------------------------+------------------------------------- Reporter: jm4games | Owner: (none) Type: bug | Status: closed Priority: high | Milestone: 8.2.2 Component: Compiler | Version: 8.2.1 Resolution: fixed | Keywords: Operating System: Linux | Architecture: x86_64 Type of failure: Compile-time | (amd64) crash or panic | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): 8.0.2 Wiki Page: | -------------------------------------+------------------------------------- Changes (by bgamari): * status: merge => closed * resolution: => fixed * milestone: => 8.2.2 Comment: Merged to `ghc-8.2` as 58bb1a781982d26729efb4a3b72186257a637013. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/14379#comment:10 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler
participants (1)
-
GHC