[GHC] #12790: GHC 8.0.1 uses copious amounts of RAM and time when trying to compile lambdabot-haskell-plugins

GHC ghc-devs at haskell.org
Tue Dec 6 21:49:54 UTC 2016


#12790: GHC 8.0.1 uses copious amounts of RAM and time when trying to compile
lambdabot-haskell-plugins
-------------------------------------+-------------------------------------
        Reporter:  clint             |                Owner:
            Type:  bug               |               Status:  new
        Priority:  normal            |            Milestone:
       Component:  Compiler          |              Version:  8.0.1
      Resolution:                    |             Keywords:
Operating System:  Unknown/Multiple  |         Architecture:
 Type of failure:  Compile-time      |  Unknown/Multiple
  performance bug                    |            Test Case:
      Blocked By:                    |             Blocking:
 Related Tickets:                    |  Differential Rev(s):
       Wiki Page:                    |
-------------------------------------+-------------------------------------

Comment (by RyanGlScott):

 I've managed to reduce it down to something which just requires `parsec`:

 {{{#!hs
 module Lambdabot.Plugin.Haskell.Pl.Parser (list) where

 import Data.Foldable (asum)
 import Text.ParserCombinators.Parsec (Parser, (<?>), sepBy, try)

 data Expr
   = Var Fixity String
   | App Expr Expr

 data Fixity = Pref | Inf

 cons, nil :: Expr
 cons = Var Inf  ":"
 nil  = Var Pref "[]"

 brackets :: Parser a -> Parser a
 brackets = undefined

 symbol :: String -> Parser String
 symbol = undefined

 list :: Parser Expr
 list = asum (map (try . brackets) plist) <?> "list" where
   plist = [
     foldr (\e1 e2 -> cons `App` e1 `App` e2) nil `fmap`
       (myParser False `sepBy` symbol ","),
     do e <- myParser False
        _ <- symbol ".."
        return $ Var Pref "enumFrom" `App` e,
     do e  <- myParser False
        _  <- symbol ","
        e' <- myParser False
        _  <- symbol ".."
        return $ Var Pref "enumFromThen" `App` e `App` e',
     do e  <- myParser False
        _  <- symbol ".."
        e' <- myParser False
        return $ Var Pref "enumFromTo" `App` e `App` e',
     do e   <- myParser False
        _   <- symbol ","
        e'  <- myParser False
        _   <- symbol ".."
        e'' <- myParser False
        return $ Var Pref "enumFromThenTo" `App` e `App` e' `App` e''
     ]

 myParser :: Bool -> Parser Expr
 myParser = undefined
 }}}

 `plist` appears to be the culprit. It seems to have some sort of quadratic
 slowdown whenever new elements are added to `plist`. For example,
 commenting out the last element of `plist` makes it compile within a
 reasonable amount of time (but not instantly).

 I think the `Alternative` instance for `Parser` might have something to do
 with it, too. Notably, if I comment out the import of `asum` and redefine
 it locally as:

 {{{#!hs
 asum :: [Parser a] -> Parser a
 asum = undefined
 }}}

 Then it compiles instantly.

--
Ticket URL: <http://ghc.haskell.org/trac/ghc/ticket/12790#comment:7>
GHC <http://www.haskell.org/ghc/>
The Glasgow Haskell Compiler


More information about the ghc-tickets mailing list