[GHC] #13059: High memory usage during compilation

GHC ghc-devs at haskell.org
Fri Feb 10 20:55:02 UTC 2017


#13059: High memory usage during compilation
-------------------------------------+-------------------------------------
        Reporter:  domenkozar        |                Owner:
            Type:  bug               |               Status:  new
        Priority:  highest           |            Milestone:  8.2.1
       Component:  Compiler          |              Version:  8.0.2-rc2
      Resolution:                    |             Keywords:
Operating System:  Unknown/Multiple  |         Architecture:  x86_64
 Type of failure:  Compile-time      |  (amd64)
  performance bug                    |            Test Case:
      Blocked By:                    |             Blocking:
 Related Tickets:                    |  Differential Rev(s):
       Wiki Page:                    |
-------------------------------------+-------------------------------------

Comment (by RyanGlScott):

 I've independently verified that 54b887b5abf6ee723c6ac6aaa2d2f4c14cf74060
 caused this regression (at least on `Store-Random.hs`, which I believe is
 representative of `store`'s compilation regression as a whole).

 Furthermore, I discovered something interesting. I tweaked `StoreImpl.hs`
 and `Store-Random.hs` a little such that:

 1. `StoreImpl.hs` no longer uses `DefaultSignatures`
 2. `Store-Random.hs` now explicitly defines all of its instance methods.
 That is, `Store-Random.hs` contains these lines:

    {{{#!hs
    instance Store ModName
    instance Store Name
    instance Store NameFlavour
    instance Store Type
    instance Store TyVarBndr
    instance Store NameSpace
    instance Store PkgName
    instance Store OccName
    instance Store TyLit
    }}}

    I tweaked it to be this instead:

    {{{#!hs
    instance Store ModName where
      size = genericSize
      peek = genericPeek
      poke = genericPoke

      {-# INLINE size #-}
      {-# INLINE peek #-}
      {-# INLINE poke #-}

    instance Store Name where
      size = genericSize
      peek = genericPeek
      poke = genericPoke

      {-# INLINE size #-}
      {-# INLINE peek #-}
      {-# INLINE poke #-}

    instance Store NameFlavour where
      size = genericSize
      peek = genericPeek
      poke = genericPoke

      {-# INLINE size #-}
      {-# INLINE peek #-}
      {-# INLINE poke #-}

    instance Store Type where
      size = genericSize
      peek = genericPeek
      poke = genericPoke

      {-# INLINE size #-}
      {-# INLINE peek #-}
      {-# INLINE poke #-}

    instance Store TyVarBndr where
      size = genericSize
      peek = genericPeek
      poke = genericPoke

      {-# INLINE size #-}
      {-# INLINE peek #-}
      {-# INLINE poke #-}

    instance Store NameSpace where
      size = genericSize
      peek = genericPeek
      poke = genericPoke

      {-# INLINE size #-}
      {-# INLINE peek #-}
      {-# INLINE poke #-}

    instance Store PkgName where
      size = genericSize
      peek = genericPeek
      poke = genericPoke

      {-# INLINE size #-}
      {-# INLINE peek #-}
      {-# INLINE poke #-}

    instance Store OccName where
      size = genericSize
      peek = genericPeek
      poke = genericPoke

      {-# INLINE size #-}
      {-# INLINE peek #-}
      {-# INLINE poke #-}

    instance Store TyLit where
      size = genericSize
      peek = genericPeek
      poke = genericPoke

      {-# INLINE size #-}
      {-# INLINE peek #-}
      {-# INLINE poke #-}
    }}}

 I then ran `-dshow-passes` on this program using a pre-
 54b887b5abf6ee723c6ac6aaa2d2f4c14cf74060 GHC and a post-
 54b887b5abf6ee723c6ac6aaa2d2f4c14cf74060 GHC.

 On the original `Store-Random.hs` program:

 * Pre-54b887b5abf6ee723c6ac6aaa2d2f4c14cf74060:

   {{{
   *** Float out(FOS {Lam = Just 0,
                      Consts = True,
                      OverSatApps = False}) [Store]:
   Result size of Float out(FOS {Lam = Just 0,
                                 Consts = True,
                                 OverSatApps = False})
     = {terms: 12,859, types: 119,332, coercions: 72,859}
   !!! Float out(FOS {Lam = Just 0,
                      Consts = True,
                      OverSatApps = False}) [Store]: finished in 236.00
 milliseconds, allocated 252.916 megabytes
   *** Simplifier [Store]:
   Result size of Simplifier iteration=1
     = {terms: 40,398, types: 205,815, coercions: 109,233}
   }}}

 * Post-54b887b5abf6ee723c6ac6aaa2d2f4c14cf74060:

   {{{
   *** Float out(FOS {Lam = Just 0,
                      Consts = True,
                      OverSatApps = False}) [Store]:
   Result size of Float out(FOS {Lam = Just 0,
                                 Consts = True,
                                 OverSatApps = False})
     = {terms: 12,859, types: 119,332, coercions: 72,859}
   !!! Float out(FOS {Lam = Just 0,
                      Consts = True,
                      OverSatApps = False}) [Store]: finished in 160.00
 milliseconds, allocated 252.680 megabytes
   *** Simplifier [Store]:
   Result size of Simplifier iteration=1
     = {terms: 59,073, types: 286,228, coercions: 152,155}
   }}}

 On the tweaked `Store-Random.hs` program:

 * Pre-54b887b5abf6ee723c6ac6aaa2d2f4c14cf74060:

   {{{
   *** Float out(FOS {Lam = Just 0,
                      Consts = True,
                      OverSatApps = False}) [Store2]:
   Result size of Float out(FOS {Lam = Just 0,
                                 Consts = True,
                                 OverSatApps = False})
     = {terms: 12,796, types: 119,305, coercions: 72,832}
   !!! Float out(FOS {Lam = Just 0,
                      Consts = True,
                      OverSatApps = False}) [Store2]: finished in 156.00
 milliseconds, allocated 252.064 megabytes
   *** Simplifier [Store2]:
   Result size of Simplifier iteration=1
     = {terms: 58,888, types: 283,015, coercions: 149,870}
   }}}

 * Post-54b887b5abf6ee723c6ac6aaa2d2f4c14cf74060:

   {{{
   *** Float out(FOS {Lam = Just 0,
                      Consts = True,
                      OverSatApps = False}) [Store2]:
   Result size of Float out(FOS {Lam = Just 0,
                                 Consts = True,
                                 OverSatApps = False})
     = {terms: 12,796, types: 119,305, coercions: 72,832}
   !!! Float out(FOS {Lam = Just 0,
                      Consts = True,
                      OverSatApps = False}) [Store2]: finished in 176.00
 milliseconds, al    located 252.076 megabytes
   *** Simplifier [Store2]:
   Result size of Simplifier iteration=1
     = {terms: 58,888, types: 283,015, coercions: 149,870}
   }}}

 Notice that in the tweaked `Store-Random.hs`, there is no difference
 before and after 54b887b5abf6ee723c6ac6aaa2d2f4c14cf74060. While this
 consistency is nice, the resulting program size is the same as the
 original program post-54b887b5abf6ee723c6ac6aaa2d2f4c14cf74060, so this
 certainly didn't fix the bug—it just made it easier to see in the source
 program.

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


More information about the ghc-tickets mailing list