[Git][ghc/ghc][master] 3 commits: Make ru_fn field strict to avoid retaining Ids

Marge Bot (@marge-bot) gitlab at gitlab.haskell.org
Fri Aug 19 04:09:28 UTC 2022



Marge Bot pushed to branch master at Glasgow Haskell Compiler / GHC


Commits:
519c712e by Matthew Pickering at 2022-08-19T00:09:11-04:00
Make ru_fn field strict to avoid retaining Ids

It's better to perform this projection from Id to Name strictly so we
don't retain an old Id (hence IdInfo, hence Unfolding, hence everything
etc)

- - - - -
7dda04b0 by Matthew Pickering at 2022-08-19T00:09:11-04:00
Force `getOccFS bndr` to avoid retaining reference to Bndr.

This is another symptom of #19619

- - - - -
4303acba by Matthew Pickering at 2022-08-19T00:09:11-04:00
Force unfoldings when they are cleaned-up in Tidy and CorePrep

If these thunks are not forced then the entire unfolding for the binding
is live throughout the whole of CodeGen despite the fact it should have
been discarded.

Fixes #22071

- - - - -


4 changed files:

- compiler/GHC/Core.hs
- compiler/GHC/Core/Opt/Simplify/Iteration.hs
- compiler/GHC/CoreToStg/Prep.hs
- compiler/GHC/Iface/Tidy.hs


Changes:

=====================================
compiler/GHC/Core.hs
=====================================
@@ -1151,7 +1151,7 @@ data CoreRule
 
         -- Rough-matching stuff
         -- see comments with InstEnv.ClsInst( is_cls, is_rough )
-        ru_fn    :: Name,               -- ^ Name of the 'GHC.Types.Id.Id' at the head of this rule
+        ru_fn    :: !Name,               -- ^ Name of the 'GHC.Types.Id.Id' at the head of this rule
         ru_rough :: [Maybe Name],       -- ^ Name at the head of each argument to the left hand side
 
         -- Proper-matching stuff


=====================================
compiler/GHC/Core/Opt/Simplify/Iteration.hs
=====================================
@@ -634,7 +634,8 @@ tryCastWorkerWrapper env bind_cxt old_bndr occ_info bndr (Cast rhs co)
                         floats' = floats `extendFloats` NonRec bndr' triv_rhs
                   ; return ( floats', setInScopeFromF env floats' ) } }
   where
-    occ_fs = getOccFS bndr
+    -- Force the occ_fs so that the old Id is not retained in the new Id.
+    !occ_fs = getOccFS bndr
     uf_opts = seUnfoldingOpts env
     work_ty = coercionLKind co
     info   = idInfo bndr
@@ -711,9 +712,11 @@ prepareBinding env top_lvl is_rec strict_bind bndr rhs_floats rhs
          -- rhs_env: add to in-scope set the binders from rhs_floats
          -- so that prepareRhs knows what is in scope in rhs
        ; let rhs_env = env `setInScopeFromF` rhs_floats1
+             -- Force the occ_fs so that the old Id is not retained in the new Id.
+             !occ_fs = getOccFS bndr
 
        -- Now ANF-ise the remaining rhs
-       ; (anf_floats, rhs2) <- prepareRhs rhs_env top_lvl (getOccFS bndr) rhs1
+       ; (anf_floats, rhs2) <- prepareRhs rhs_env top_lvl occ_fs rhs1
 
        -- Finally, decide whether or not to float
        ; let all_floats = rhs_floats1 `addLetFloats` anf_floats
@@ -4294,7 +4297,8 @@ simplRules env mb_new_id rules bind_cxt
                  lhs_env = updMode updModeForRules env'
                  rhs_env = updMode (updModeForStableUnfoldings act) env'
                            -- See Note [Simplifying the RHS of a RULE]
-                 fn_name' = case mb_new_id of
+                 -- Force this to avoid retaining reference to old Id
+                 !fn_name' = case mb_new_id of
                               Just id -> idName id
                               Nothing -> fn_name
 


=====================================
compiler/GHC/CoreToStg/Prep.hs
=====================================
@@ -2153,7 +2153,9 @@ cpCloneBndr env bndr
        -- Drop (now-useless) rules/unfoldings
        -- See Note [Drop unfoldings and rules]
        -- and Note [Preserve evaluatedness] in GHC.Core.Tidy
-       ; let unfolding' = trimUnfolding (realIdUnfolding bndr)
+       -- And force it.. otherwise the old unfolding is just retained.
+       -- See #22071
+       ; let !unfolding' = trimUnfolding (realIdUnfolding bndr)
                           -- Simplifier will set the Id's unfolding
 
              bndr'' = bndr' `setIdUnfolding`      unfolding'


=====================================
compiler/GHC/Iface/Tidy.hs
=====================================
@@ -1292,12 +1292,14 @@ tidyTopIdInfo uf_opts rhs_tidy_env name rhs_ty orig_rhs tidy_rhs idinfo show_unf
 
     --------- Unfolding ------------
     unf_info = realUnfoldingInfo idinfo
-    unfold_info
+    -- Force this, otherwise the old unfolding is retained over code generation
+    -- See #22071
+    !unfold_info
       | isCompulsoryUnfolding unf_info || show_unfold
       = tidyUnfolding rhs_tidy_env unf_info unf_from_rhs
       | otherwise
       = minimal_unfold_info
-    minimal_unfold_info = trimUnfolding unf_info
+    !minimal_unfold_info = trimUnfolding unf_info
     unf_from_rhs = mkFinalUnfolding uf_opts InlineRhs final_sig tidy_rhs
     -- NB: do *not* expose the worker if show_unfold is off,
     --     because that means this thing is a loop breaker or



View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/989b844d7598fd71ffd76e00d8d1f5207d58fd61...4303acba89b26cc3ae05527d701cba7d84edafcb

-- 
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/989b844d7598fd71ffd76e00d8d1f5207d58fd61...4303acba89b26cc3ae05527d701cba7d84edafcb
You're receiving this email because of your account on gitlab.haskell.org.


-------------- next part --------------
An HTML attachment was scrubbed...
URL: <http://mail.haskell.org/pipermail/ghc-commits/attachments/20220819/dde7e6f7/attachment-0001.html>


More information about the ghc-commits mailing list