[Git][ghc/ghc][wip/andreask/deep_discounts] Remove one flag

Andreas Klebinger (@AndreasK) gitlab at gitlab.haskell.org
Sun Oct 2 14:27:16 UTC 2022



Andreas Klebinger pushed to branch wip/andreask/deep_discounts at Glasgow Haskell Compiler / GHC


Commits:
f0919c83 by Andreas Klebinger at 2022-10-02T16:26:21+02:00
Remove one flag

- - - - -


8 changed files:

- compiler/GHC/Core.hs
- compiler/GHC/Core/Opt/Simplify/Env.hs
- compiler/GHC/Core/Opt/Simplify/Inline.hs
- compiler/GHC/Core/Opt/Simplify/Iteration.hs
- compiler/GHC/Core/Unfold.hs
- compiler/GHC/Driver/Session.hs
- docs/users_guide/hints.rst
- docs/users_guide/using-optimisation.rst


Changes:

=====================================
compiler/GHC/Core.hs
=====================================
@@ -2022,10 +2022,6 @@ bindersOf (Rec pairs)       = [binder | (binder, _) <- pairs]
 bindersOfBinds :: [Bind b] -> [b]
 bindersOfBinds binds = foldr ((++) . bindersOf) [] binds
 
-{-# INLINE foldBindersOf #-}
-foldBindersOf :: (a -> b -> a) -> Bind b -> a -> a
-foldBindersOf f b r = foldl' f r (bindersOf b)
-
 rhssOfBind :: Bind b -> [Expr b]
 rhssOfBind (NonRec _ rhs) = [rhs]
 rhssOfBind (Rec pairs)    = [rhs | (_,rhs) <- pairs]


=====================================
compiler/GHC/Core/Opt/Simplify/Env.hs
=====================================
@@ -21,7 +21,8 @@ module GHC.Core.Opt.Simplify.Env (
         extendTvSubst, extendCvSubst,
         zapSubstEnv, setSubstEnv, bumpCaseDepth,
         getInScope, setInScopeFromE, setInScopeFromF,
-        setInScopeSet, modifyInScope, addNewInScopeIds, addNewInScopeId, addNewInScopeBndr,
+        setInScopeSet, modifyInScope, addNewInScopeIds,
+        addNewInScopeId, addNewInScopeBndr,
         getSimplRules, enterRecGroupRHSs,
 
         -- * Substitution results


=====================================
compiler/GHC/Core/Opt/Simplify/Inline.hs
=====================================
@@ -26,7 +26,6 @@ import GHC.Core.DataCon
 import GHC.Types.Var
 import GHC.Core.Opt.Simplify.Utils
 import GHC.Utils.Panic.Plain (assert)
-import GHC.Utils.Trace
 import GHC.Types.Tickish
 
 callSiteInline :: Logger
@@ -581,7 +580,7 @@ interestingArg :: SimplEnv -> CoreExpr -> ArgSummary
 interestingArg env e =
   go env depth_limit 0 e
     where
-    depth_limit = unfoldingMaxAppDepth . sm_uf_opts . seMode $ env
+    depth_limit = unfoldingMaxDiscountDepth . sm_uf_opts . seMode $ env
 
     -- n is # value args to which the expression is applied
     go :: SimplEnv -> Int -> Int -> CoreExpr -> ArgSummary


=====================================
compiler/GHC/Core/Opt/Simplify/Iteration.hs
=====================================
@@ -7,7 +7,6 @@
 
 {-# LANGUAGE TypeFamilies #-}
 {-# LANGUAGE MultiWayIf #-}
--- {-# OPTIONS_GHC -ddump-simpl -ddump-to-file -ddump-stg-final -dsuppress-coercions -dsuppress-coercion-types #-}
 
 {-# OPTIONS_GHC -Wno-incomplete-record-updates -Wno-incomplete-uni-patterns #-}
 module GHC.Core.Opt.Simplify.Iteration ( simplTopBinds, simplExpr, simplImpRules ) where


=====================================
compiler/GHC/Core/Unfold.hs
=====================================
@@ -26,7 +26,7 @@ module GHC.Core.Unfold (
         updateFunAppDiscount, updateDictDiscount,
         updateVeryAggressive, updateCaseScaling,
         updateCaseThreshold, updateReportPrefix,
-        updateMaxAppDepth, updateMaxGuideDepth,
+        updateMaxDiscountDepth,
 
         ArgSummary(..), nonTrivArg,
 
@@ -91,13 +91,9 @@ data UnfoldingOpts = UnfoldingOpts
    , unfoldingReportPrefix :: !(Maybe String)
       -- ^ Only report inlining decisions for names with this prefix
 
-   , unfoldingMaxAppDepth :: !Int
+   , unfoldingMaxDiscountDepth :: !Int
       -- ^ When considering unfolding a definition look this deep
-      -- into the applied argument.
-
-   , unfoldingMaxGuideDepth :: !Int
-      -- ^ When creating unfolding guidance look this deep into
-      -- nested argument use.
+      -- into the applied arguments and into nested argument use.
 
    }
 
@@ -134,8 +130,7 @@ defaultUnfoldingOpts = UnfoldingOpts
       -- Don't filter inlining decision reports
    , unfoldingReportPrefix = Nothing
 
-   , unfoldingMaxAppDepth = 20
-   , unfoldingMaxGuideDepth = 20
+   , unfoldingMaxDiscountDepth = 20
    }
 
 -- Helpers for "GHC.Driver.Session"
@@ -165,11 +160,9 @@ updateCaseScaling n opts = opts { unfoldingCaseScaling = n }
 updateReportPrefix :: Maybe String -> UnfoldingOpts -> UnfoldingOpts
 updateReportPrefix n opts = opts { unfoldingReportPrefix = n }
 
-updateMaxAppDepth :: Int -> UnfoldingOpts -> UnfoldingOpts
-updateMaxAppDepth n opts = opts { unfoldingMaxAppDepth = n }
+updateMaxDiscountDepth :: Int -> UnfoldingOpts -> UnfoldingOpts
+updateMaxDiscountDepth n opts = opts { unfoldingMaxDiscountDepth = n }
 
-updateMaxGuideDepth :: Int -> UnfoldingOpts -> UnfoldingOpts
-updateMaxGuideDepth n opts = opts { unfoldingMaxGuideDepth = n }
 
 {-
 Note [Occurrence analysis of unfoldings]
@@ -474,7 +467,7 @@ sizeExpr :: UnfoldingOpts
 sizeExpr opts !bOMB_OUT_SIZE top_args' expr
   = size_up depth_limit (mkUnVarSet top_args') expr
   where
-    depth_limit = unfoldingMaxGuideDepth opts
+    depth_limit = unfoldingMaxDiscountDepth opts
     size_up :: Int -> UnVarSet -> Expr Var -> ExprSize
     size_up !depth !arg_comps (Cast e _) = size_up depth arg_comps e
     size_up !depth arg_comps (Tick _ e) = size_up depth arg_comps e


=====================================
compiler/GHC/Driver/Session.hs
=====================================
@@ -2825,10 +2825,8 @@ dynamic_flags_deps = [
       (intSuffix   (\n d -> d { unfoldingOpts = updateCaseThreshold n (unfoldingOpts d)}))
   , make_ord_flag defFlag "funfolding-case-scaling"
       (intSuffix   (\n d -> d { unfoldingOpts = updateCaseScaling n (unfoldingOpts d)}))
-  , make_ord_flag defFlag "funfolding-max-arg-depth"
-      (intSuffix   (\n d -> d { unfoldingOpts = updateMaxAppDepth n (unfoldingOpts d)}))
-  , make_ord_flag defFlag "funfolding-max-guide-depth"
-      (intSuffix   (\n d -> d { unfoldingOpts = updateMaxGuideDepth n (unfoldingOpts d)}))
+  , make_ord_flag defFlag "funfolding-discount-depth"
+      (intSuffix   (\n d -> d { unfoldingOpts = updateMaxDiscountDepth n (unfoldingOpts d)}))
 
   , make_dep_flag defFlag "funfolding-keeness-factor"
       (floatSuffix (\_ d -> d))


=====================================
docs/users_guide/hints.rst
=====================================
@@ -405,7 +405,7 @@ decision about inlining a specific binding.
 * :ghc-flag:`-funfolding-dict-discount=⟨n⟩`
 * :ghc-flag:`-funfolding-fun-discount=⟨n⟩`
 * :ghc-flag:`-funfolding-max-guide-depth=⟨n⟩`
-* :ghc-flag:`-funfolding-max-arg-depth=⟨n⟩`
+* :ghc-flag:`-funfolding-discount-depth=⟨n⟩`
 
 Should the simplifier run out of ticks because of a inlining loop
 users are encouraged to try decreasing :ghc-flag:`-funfolding-case-threshold=⟨n⟩`


=====================================
docs/users_guide/using-optimisation.rst
=====================================
@@ -1651,8 +1651,8 @@ by saying ``-fno-wombat``.
     while still allowing GHC to compile modules containing such inlining loops.
 
 
-.. ghc-flag:: -funfolding-max-arg-depth=⟨n⟩
-    :shortdesc: *default: 20.* Don't look deepter than `n` levels into function arguments.
+.. ghc-flag:: -funfolding-discount-depth=⟨n⟩
+    :shortdesc: *default: 20.* Don't look deeper than `n` levels into function argument use.
     :type: dynamic
     :category:
 
@@ -1673,35 +1673,14 @@ by saying ``-fno-wombat``.
                         Zero -> 2
                         _ -> error "Large"
 
-    Then GHC can consider the nested use of the argument when making inlining decisions.
-    However inspecting deeply nested arguments can be costly in terms of compile time overhead.
-    So we restrict inspection of the argument to a certain depth.
+    Then GHC can consider the nested structure of the argument as well as how
+    deeply the function looks into the argument to make inlining decisions.
 
-.. ghc-flag:: -funfolding-max-guide-depth=⟨n⟩
-    :shortdesc: *default: 20.* Don't look deepter than `n` levels into a functions use of it's arguments.
-    :type: dynamic
-    :category:
-
-    :default: 20
-
-    .. index::
-       single: inlining, controlling
-       single: unfolding, controlling
-
-    If we have a function f::
-
-        f x =
-            case x of
-                Zero -> 0
-                Succ y -> case y of
-                    Zero -> 1
-                    Succ z -> case z of
-                        Zero -> 2
-                        _ -> error "Large"
+    This allows us to properly estimate the result code size from applying arguments
+    with complex structure to functions taking these arguments appart.
 
-    GHC can consider the nested use of the argument when making inlining decisions.
-    However looking deeply into nested argument use can be costly in terms of compile time overhead.
-    So we restrict inspection of nested argument use to a certain level of nesting.
+    However inspecting deeply nested arguments can be costly in terms of compile
+    time overhead. So we restrict these considerations to a certain depth.
 
 .. ghc-flag:: -fworker-wrapper
     :shortdesc: Enable the worker/wrapper transformation.



View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/f0919c83e3ef82ad63e44723631b672e4580fb29

-- 
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/f0919c83e3ef82ad63e44723631b672e4580fb29
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/20221002/0355f06e/attachment-0001.html>


More information about the ghc-commits mailing list