[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
Mon Dec 12 17:33:39 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):

 There's quite a difference between the generated Core for `list` depending
 on whether `-fprof-auto` is on or not. With `-fprof-auto`, we have:

 {{{#!hs
 -- RHS size: {terms: 2, types: 0, coercions: 0}
 list :: Parser Expr
 list =
   Lambdabot.Plugin.Haskell.Pl.Parser.list_go1
     Lambdabot.Plugin.Haskell.Pl.Parser.list1

 -- RHS size: {terms: 3, types: 11, coercions: 10}
 Lambdabot.Plugin.Haskell.Pl.Parser.list1
   :: [Text.Parsec.Prim.ParsecT
         [Char] () Data.Functor.Identity.Identity Expr]
 }}}

 But without `-fprof-auto`, we have:

 {{{#!hs
 -- RHS size: {terms: 1, types: 0, coercions: 7}
 list :: Parser Expr
 list =
   Lambdabot.Plugin.Haskell.Pl.Parser.list1
   `cast` (Sym
             (Text.Parsec.Prim.N:ParsecT[0]
                <[Char]>_R <()>_R <Data.Functor.Identity.Identity>_R
 <Expr>_R)
           :: ((forall b.
                Text.Parsec.Prim.State [Char] ()
                -> (Expr
                    -> Text.Parsec.Prim.State [Char] ()
                    -> Text.Parsec.Error.ParseError
                    -> Data.Functor.Identity.Identity b)
                -> (Text.Parsec.Error.ParseError
                    -> Data.Functor.Identity.Identity b)
                -> (Expr
                    -> Text.Parsec.Prim.State [Char] ()
                    -> Text.Parsec.Error.ParseError
                    -> Data.Functor.Identity.Identity b)
                -> (Text.Parsec.Error.ParseError
                    -> Data.Functor.Identity.Identity b)
                -> Data.Functor.Identity.Identity b) :: *)
              ~R#
              (Text.Parsec.Prim.ParsecT
                 [Char] () Data.Functor.Identity.Identity Expr :: *))

 -- RHS size: {terms: 910,139, types: 246,618, coercions: 0}
 Lambdabot.Plugin.Haskell.Pl.Parser.list1
   :: forall b.
      Text.Parsec.Prim.State [Char] ()
      -> (Expr
          -> Text.Parsec.Prim.State [Char] ()
          -> Text.Parsec.Error.ParseError
          -> Data.Functor.Identity.Identity b)
      -> (Text.Parsec.Error.ParseError
          -> Data.Functor.Identity.Identity b)
      -> (Expr
          -> Text.Parsec.Prim.State [Char] ()
          -> Text.Parsec.Error.ParseError
          -> Data.Functor.Identity.Identity b)
      -> (Text.Parsec.Error.ParseError
          -> Data.Functor.Identity.Identity b)
      -> Data.Functor.Identity.Identity b
 }}}

 That's quite the code explosion!

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


More information about the ghc-tickets mailing list