
Simon Peyton Jones pushed to branch wip/T23109a at Glasgow Haskell Compiler / GHC Commits: bc27b6c9 by Simon Peyton Jones at 2025-04-17T13:12:48+01:00 More eperiments * Don't inline toplevel things so much * Don't float constants so vigorously in the first float-out - - - - - 3 changed files: - compiler/GHC/Core/Opt/OccurAnal.hs - compiler/GHC/Core/Opt/Pipeline.hs - compiler/GHC/Core/Opt/Simplify/Utils.hs Changes: ===================================== compiler/GHC/Core/Opt/OccurAnal.hs ===================================== @@ -1096,14 +1096,14 @@ mkNonRecRhsCtxt lvl bndr unf certainly_inline -- See Note [Cascading inlines] = -- mkNonRecRhsCtxt is only used for non-join points, so occAnalBind -- has set the OccInfo for this binder before calling occAnalNonRecRhs + -- Distressing delicacy ... has to line up with preInlineUnconditionally case idOccInfo bndr of OneOcc { occ_in_lam = NotInsideLam, occ_n_br = 1 } - -> active && not stable_unf && not top_bottoming + -> active && not (isTopLevel lvl) && not stable_unf _ -> False active = isAlwaysActive (idInlineActivation bndr) stable_unf = isStableUnfolding unf - top_bottoming = isTopLevel lvl && isDeadEndId bndr ----------------- occAnalRecBind :: OccEnv -> TopLevelFlag -> ImpRuleEdges -> [(Var,CoreExpr)] ===================================== compiler/GHC/Core/Opt/Pipeline.hs ===================================== @@ -217,7 +217,7 @@ getCoreToDo dflags hpt_rule_base extra_vars if full_laziness then CoreDoFloatOutwards $ FloatOutSwitches { floatOutLambdas = Just 0 - , floatOutConstants = True + , floatOutConstants = False -- Initially , floatOutOverSatApps = False , floatToTopLevelOnly = False , floatJoinsToTop = False -- Initially, don't float join points at all @@ -284,7 +284,7 @@ getCoreToDo dflags hpt_rule_base extra_vars -- f_el22 (f_el21 r_midblock) runWhen full_laziness $ CoreDoFloatOutwards $ FloatOutSwitches { floatOutLambdas = floatLamArgs dflags - , floatOutConstants = True + , floatOutConstants = True -- For SpecConstr and CSE , floatOutOverSatApps = True , floatToTopLevelOnly = False , floatJoinsToTop = True }, ===================================== compiler/GHC/Core/Opt/Simplify/Utils.hs ===================================== @@ -1461,12 +1461,18 @@ preInlineUnconditionally env top_lvl bndr rhs rhs_env extend_subst_with inl_rhs = extendIdSubst env bndr $! (mkContEx rhs_env inl_rhs) one_occ IAmDead = True -- Happens in ((\x.1) v) - one_occ OneOcc{ occ_n_br = 1 - , occ_in_lam = NotInsideLam } = isNotTopLevel top_lvl || early_phase + one_occ OneOcc{ occ_n_br = 1 + , occ_in_lam = NotInsideLam + , occ_int_cxt = int_cxt } + = isNotTopLevel top_lvl -- Get rid of allocation + || (int_cxt==IsInteresting) -- Function is applied + || (early_phase && not (isConLikeUnfolding unf)) -- See early_phase one_occ OneOcc{ occ_n_br = 1 , occ_in_lam = IsInsideLam - , occ_int_cxt = IsInteresting } = canInlineInLam rhs - one_occ _ = False + , occ_int_cxt = IsInteresting } + = canInlineInLam rhs + one_occ _ + = False pre_inline_unconditionally = sePreInline env active = isActive (sePhase env) (inlinePragmaActivation inline_prag) @@ -1641,9 +1647,10 @@ postInlineUnconditionally env bind_cxt old_bndr bndr rhs | otherwise = smallEnoughToInline uf_opts unfolding -- See Note [Post-inline for single-use things] - check_one_occ NotInsideLam _ n_br = code_dup_ok n_br - check_one_occ IsInsideLam NotInteresting _ = False - check_one_occ IsInsideLam IsInteresting n_br = is_cheap && code_dup_ok n_br + check_one_occ NotInsideLam NotInteresting n_br = not is_top_lvl && code_dup_ok n_br + check_one_occ NotInsideLam IsInteresting n_br = code_dup_ok n_br + check_one_occ IsInsideLam NotInteresting _ = False + check_one_occ IsInsideLam IsInteresting n_br = is_cheap && code_dup_ok n_br -- IsInteresting: inlining inside a lambda only with good reason -- See the notes on int_cxt in preInlineUnconditionally -- is_cheap: check for acceptable work duplication, using isCheapUnfolding View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/bc27b6c9b536a8200cd2b8750e4744fc... -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/bc27b6c9b536a8200cd2b8750e4744fc... You're receiving this email because of your account on gitlab.haskell.org.
participants (1)
-
Simon Peyton Jones (@simonpj)