
#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