[GHC] #8852: 7.8.1 uses a lot of memory when compiling attoparsec programs using <|>
GHC
ghc-devs at haskell.org
Thu Mar 6 17:46:00 UTC 2014
#8852: 7.8.1 uses a lot of memory when compiling attoparsec programs using <|>
-------------------------+-------------------------------------------------
Reporter: | Owner:
joelteon | Status: new
Type: bug | Milestone:
Priority: | Version: 7.8.1-rc2
normal | Operating System: Unknown/Multiple
Component: | Type of failure: Compile-time performance bug
Compiler | Test Case:
Keywords: | Blocking:
Architecture: |
Unknown/Multiple |
Difficulty: |
Unknown |
Blocked By: |
Related Tickets: |
-------------------------+-------------------------------------------------
To reproduce, install a pre-`0.11.2.1` version of attoparsec. This bug was
worked around in 0.11.2.1 by removing the `INLINE` on `plus` in
attoparsec.
With this test program:
{{{#!haskell
{-# LANGUAGE OverloadedStrings #-}
import Control.Applicative
import Data.Attoparsec.Text
import Data.Text (Text)
parser :: Parser Text
parser = string "a" <|> string "a"
<|> string "a" <|> string "a"
<|> string "a" <|> string "a"
<|> string "a" <|> string "a"
<|> string "a" <|> string "a"
<|> string "a" <|> string "a"
<|> string "a" <|> string "a"
<|> string "a" <|> string "a"
<|> string "a" <|> string "a"
<|> string "a" <|> string "a"
<|> string "a" <|> string "a"
<|> string "a" <|> string "a"
<|> string "a" <|> string "a"
<|> string "a" <|> string "a"
<|> string "a" <|> string "a"
<|> string "a" <|> string "a"
<|> string "a" <|> string "a"
main :: IO ()
main = parseTest parser "a"
}}}
and using GHC 7.8.1.rc2:
Compiling using `-O2`, GHC tops out at ~1GB of RAM and takes 25s.
Using `-O0`, GHC takes 0.47s and uses <150MB of RAM.
Compare this with GHC 7.6.3:
Compiling using `-O2`, GHC uses <150MB and takes 3.7s. Memory usage is
similar with `-O0` although compile time goes down to 0.36s.
An extreme version of this bug can be found in the `thyme` package here:
https://github.com/liyang/thyme/blob/master/src/Data/Thyme/Format.hs#L589-L693.
Compiling that module with an unfixed attoparsec makes GHC use all
available memory and stall out, forcing kill -9. Replacing the function
body with `undefined` makes the package compile as expected.
--
Ticket URL: <http://ghc.haskell.org/trac/ghc/ticket/8852>
GHC <http://www.haskell.org/ghc/>
The Glasgow Haskell Compiler
More information about the ghc-tickets
mailing list