[commit: ghc] master: Avoid excessive space usage from unfoldings in CoreTidy (5c602d2)

git at git.haskell.org git at git.haskell.org
Mon May 1 16:29:43 UTC 2017


Repository : ssh://git@git.haskell.org/ghc

On branch  : master
Link       : http://ghc.haskell.org/trac/ghc/changeset/5c602d2228d28530621cc6c94fbb736b13f474fb/ghc

>---------------------------------------------------------------

commit 5c602d2228d28530621cc6c94fbb736b13f474fb
Author: Reid Barton <rwbarton at gmail.com>
Date:   Mon May 1 11:17:47 2017 -0400

    Avoid excessive space usage from unfoldings in CoreTidy
    
    Test Plan: validate
    
    Reviewers: austin, bgamari
    
    Reviewed By: bgamari
    
    Subscribers: thomie
    
    GHC Trac Issues: #13564
    
    Differential Revision: https://phabricator.haskell.org/D3516


>---------------------------------------------------------------

5c602d2228d28530621cc6c94fbb736b13f474fb
 compiler/coreSyn/CoreTidy.hs        |  8 +++++++-
 compiler/main/TidyPgm.hs            |  5 ++++-
 testsuite/tests/perf/compiler/all.T | 12 ++++++++----
 3 files changed, 19 insertions(+), 6 deletions(-)

diff --git a/compiler/coreSyn/CoreTidy.hs b/compiler/coreSyn/CoreTidy.hs
index 7f82bec..89ce692 100644
--- a/compiler/coreSyn/CoreTidy.hs
+++ b/compiler/coreSyn/CoreTidy.hs
@@ -15,6 +15,7 @@ module CoreTidy (
 #include "HsVersions.h"
 
 import CoreSyn
+import CoreSeq ( seqUnfolding )
 import CoreArity
 import Id
 import IdInfo
@@ -223,9 +224,14 @@ tidyUnfolding tidy_env
               unf@(CoreUnfolding { uf_tmpl = unf_rhs, uf_src = src })
               unf_from_rhs
   | isStableSource src
-  = unf { uf_tmpl = tidyExpr tidy_env unf_rhs }    -- Preserves OccInfo
+  = seqIt $ unf { uf_tmpl = tidyExpr tidy_env unf_rhs }    -- Preserves OccInfo
+    -- This seqIt avoids a space leak: otherwise the uf_is_value,
+    -- uf_is_conlike, ... fields may retain a reference to the
+    -- pre-tidied expression forever (ToIface doesn't look at them)
+
   | otherwise
   = unf_from_rhs
+  where seqIt unf = seqUnfolding unf `seq` unf
 tidyUnfolding _ unf _ = unf     -- NoUnfolding or OtherCon
 
 {-
diff --git a/compiler/main/TidyPgm.hs b/compiler/main/TidyPgm.hs
index 21d0208..4b9fbae 100644
--- a/compiler/main/TidyPgm.hs
+++ b/compiler/main/TidyPgm.hs
@@ -22,6 +22,7 @@ import CoreMonad
 import CorePrep
 import CoreUtils        (rhsIsStatic)
 import CoreStats        (coreBindsStats, CoreStats(..))
+import CoreSeq          (seqBinds)
 import CoreLint
 import Literal
 import Rules
@@ -1134,7 +1135,9 @@ tidyTopBinds hsc_env this_mod unfold_env init_occ_env binds
   = do mkIntegerId <- lookupMkIntegerName dflags hsc_env
        integerSDataCon <- lookupIntegerSDataConName dflags hsc_env
        let cvt_integer = cvtLitInteger dflags mkIntegerId integerSDataCon
-       return $ tidy cvt_integer init_env binds
+           result      = tidy cvt_integer init_env binds
+       seqBinds (snd result) `seq` return result
+       -- This seqBinds avoids a spike in space usage (see #13564)
   where
     dflags = hsc_dflags hsc_env
 
diff --git a/testsuite/tests/perf/compiler/all.T b/testsuite/tests/perf/compiler/all.T
index 3acc511..733e3ba 100644
--- a/testsuite/tests/perf/compiler/all.T
+++ b/testsuite/tests/perf/compiler/all.T
@@ -742,7 +742,7 @@ test('T9020',
 test('T9675',
      [ only_ways(['optasm']),
        compiler_stats_num_field('max_bytes_used', # Note [residency]
-          [(wordsize(64), 29871032, 15),
+          [(wordsize(64), 17675240, 15),
           # 2014-10-13    29596552
           # 2014-10-13    26570896   seq the DmdEnv in seqDmdType as well
           # 2014-10-13    18582472   different machines giving different results..
@@ -752,12 +752,13 @@ test('T9675',
           # 2015-12-11    30837312   TypeInType (see #11196)
           # 2016-03-14    38776008   Final demand analyzer run
           # 2016-04-01    29871032   Fix leaks in demand analysis
+          # 2016-04-30    17675240   Fix leaks in tidy unfoldings
            (wordsize(32), 18043224, 15)
           # 2015-07-11    15341228   (x86/Linux, 64-bit machine) use +RTS -G1
           # 2016-04-06    18043224   (x86/Linux, 64-bit machine)
           ]),
        compiler_stats_num_field('peak_megabytes_allocated', # Note [residency]
-          [(wordsize(64), 121, 15),
+          [(wordsize(64), 63, 15),
           # 2014-10-13    66
           # 2014-10-13    58         seq the DmdEnv in seqDmdType as well
           # 2014-10-13    49         different machines giving different results...
@@ -768,6 +769,7 @@ test('T9675',
           # 2015-12-11    113        TypeInType (see #11196)
           # 2016-04-14    144        Final demand analyzer run
           # 2016-07-26    121        Unboxed sums?
+          # 2017-04-30    63         Fix leaks in tidy unfoldings
             (wordsize(32), 56, 15)
           # 2015-07-11    56         (x86/Linux, 64-bit machine) use +RTS -G1
           ]),
@@ -933,7 +935,7 @@ test('T9233',
 test('T10370',
      [ only_ways(['optasm']),
        compiler_stats_num_field('max_bytes_used', # Note [residency]
-          [(wordsize(64), 41291976, 15),
+          [(wordsize(64), 31524048, 15),
           # 2015-10-22    19548720
           # 2016-02-24    22823976   Changing Levity to RuntimeRep; not sure why this regresses though, even after some analysis
           # 2016-04-14    28256896   final demand analyzer run
@@ -949,19 +951,21 @@ test('T10370',
           # 2017-02-17    51126304   Type-indexed Typeable
           # 2017-02-27    43455848   Likely drift from recent simplifier improvements
           # 2017-02-25    41291976   Early inline patch
+          # 2017-04-30    31524048   Fix leaks in tidy unfoldings
 
            (wordsize(32), 19276304, 15),
           # 2015-10-22    11371496
           # 2017-03-24    19276304 (x86/Linux, 64-bit machine)
           ]),
        compiler_stats_num_field('peak_megabytes_allocated', # Note [residency]
-          [(wordsize(64), 154, 15),
+          [(wordsize(64), 117, 15),
           # 2015-10-22     76
           # 2016-04-14    101 final demand analyzer run
           # 2016-08-08    121 see above
           # 2017-01-18    146 Allow top-level string literals in Core
           # 2017-02-17    187 Type-indexed Typeable
           # 2017-02-25    154 Early inline patch
+          # 2017-04-30    117 Fix leaks in tidy unfoldings
            (wordsize(32),  69, 15),
           # 2015-10-22     39
           # 2017-03-24     69



More information about the ghc-commits mailing list