[Git][ghc/ghc][wip/T23083] CorePrep: Eta expand arguments (#23083)
Sebastian Graf (@sgraf812)
gitlab at gitlab.haskell.org
Wed Apr 5 14:35:31 UTC 2023
Sebastian Graf pushed to branch wip/T23083 at Glasgow Haskell Compiler / GHC
Commits:
4f0eb801 by Sebastian Graf at 2023-04-05T16:34:17+02:00
CorePrep: Eta expand arguments (#23083)
Previously, we'd only eta expand let bindings and lambdas,
now we'll also eta expand arguments such as in T23083:
```hs
g f h = f (h `seq` (h $))
```
Unless `-fpedantic-bottoms` is set, we'll now transform to
```hs
g f h = f (\eta -> h eta)
```
in CorePrep.
See the new `Note [Eta expansion of arguments in CorePrep]` for the details.
We only do this optimisation with -O2 because we saw 2-3% ghc/alloc regressions
in T4801 and T5321FD.
Fixes #23083.
- - - - -
8 changed files:
- compiler/GHC/CoreToStg/Prep.hs
- compiler/GHC/Driver/Config/CoreToStg/Prep.hs
- compiler/GHC/Driver/Flags.hs
- compiler/GHC/Driver/Session.hs
- docs/users_guide/using-optimisation.rst
- + testsuite/tests/simplCore/should_compile/T23083.hs
- + testsuite/tests/simplCore/should_compile/T23083.stderr
- testsuite/tests/simplCore/should_compile/all.T
Changes:
=====================================
compiler/GHC/CoreToStg/Prep.hs
=====================================
@@ -1445,12 +1445,31 @@ cpeArg env dmd arg
; if okCpeArg arg2
then do { v <- newVar arg_ty
- ; let arg3 = cpeEtaExpand (exprArity arg2) arg2
+ -- See Note [Eta expansion of arguments in CorePrep]
+ ; let arg3 | Just ao <- cp_arityOpts (cpe_config env)
+ , not (is_join_head arg2)
+ , Just at <- exprEtaExpandArity ao arg2
+ -- See Note [Eta expansion for join points]
+ -- Eta expanding the join point would
+ -- introduce crap that we can't generate
+ -- code for
+ = cpeEtaExpand (arityTypeArity at) arg2
+ | otherwise
+ = arg2
arg_float = mkFloat env dmd is_unlifted v arg3
; return (addFloat floats2 arg_float, varToCoreExpr v) }
else return (floats2, arg2)
}
+is_join_head :: CoreExpr -> Bool
+-- ^ Identify the cases where our mishandling described in
+-- Note [Eta expansion for join points] would generate crap
+is_join_head (Let bs e) = isJoinBind bs || is_join_head e
+is_join_head (Cast e _) = is_join_head e
+is_join_head (Tick _ e) = is_join_head e
+is_join_head (Case _ _ _ alts) = any is_join_head (rhssOfAlts alts)
+is_join_head _ = False
+
{-
Note [Floating unlifted arguments]
~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~
@@ -1568,6 +1587,36 @@ and now we do NOT want eta expansion to give
Instead GHC.Core.Opt.Arity.etaExpand gives
f = /\a -> \y -> let s = h 3 in g s y
+Note [Eta expansion of arguments in CorePrep]
+~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~
+We eta expand arguments in here, in CorePrep, rather than in the Simplifier, and
+do so based on 'exprEtaExpandArity' rather than the cheaper 'exprArity' analysis
+we do on let RHSs and lambdas. The reason for the latter is that the Simplifier
+has already run the more costly analysis on lambdas and let RHSs and eta
+expanded accordingly, while it does not try to eta expand arguments at all.
+
+So why eta expand arguments in CorePrep rather than in the Simplifier?
+There are two reasons why eta expansion of arguments is useful
+
+ 1. In expressions like @f (h `seq` (g $))@ (from T23083) eta expanding the
+ argument to @f (\x -> h `seq` (g $ x))@ allows us to save allocation of a
+ closure and have a faster call sequence; a code-gen matter.
+
+ 2. The eta expansion to @f (\x -> h `seq` (g $ x))@ gives rise to another
+ opportunity: We could inline ($), saving call overhead and perhaps turning
+ an unknown call into a known call. In general, there could be further
+ simplification based on the structure of the concrete argument `x`.
+ Whether we should inline in the PAP `(g $)` (thus solving this problem
+ independently of (1)) is discussed in #22886.
+
+To profit from (1), it is enough to eta expand in CorePrep, while (2) shows
+that in some rare cases as above, eta expansion of arguments may enable
+further simplification. CorePrep would not allow to exploit (2), while eta
+expansion in the Simplifier would.
+
+Alas, trying to eta expand arguments in every round of the Simplifier is costly
+(!10088 measured a geom. mean of +2.0% regression in ghc/alloc perf, regressing
+as much as 27.2%), so we only exploit (1) for now.
-}
cpeEtaExpand :: Arity -> CpeRhs -> CpeRhs
@@ -1931,6 +1980,10 @@ data CorePrepConfig = CorePrepConfig
, cp_convertNumLit :: !(LitNumType -> Integer -> Maybe CoreExpr)
-- ^ Convert some numeric literals (Integer, Natural) into their final
-- Core form.
+
+ , cp_arityOpts :: !(Maybe ArityOpts)
+ -- ^ Configuration for arity analysis ('exprEtaExpandArity').
+ -- When 'Nothing' (e.g., -O0, -O1), use the cheaper 'exprArity' instead
}
data CorePrepEnv
@@ -1941,6 +1994,7 @@ data CorePrepEnv
-- enabled we instead produce an 'error' expression to catch
-- the case where a function we think should bottom
-- unexpectedly returns.
+
, cpe_env :: IdEnv CoreExpr -- Clone local Ids
-- ^ This environment is used for three operations:
--
=====================================
compiler/GHC/Driver/Config/CoreToStg/Prep.hs
=====================================
@@ -9,6 +9,7 @@ import GHC.Core.Opt.Pipeline.Types ( CoreToDo(..) )
import GHC.Driver.Env
import GHC.Driver.Session
import GHC.Driver.Config.Core.Lint
+import GHC.Driver.Config.Core.Opt.Arity
import GHC.Tc.Utils.Env
import GHC.Types.Var
import GHC.Utils.Outputable ( alwaysQualify )
@@ -17,14 +18,18 @@ import GHC.CoreToStg.Prep
initCorePrepConfig :: HscEnv -> IO CorePrepConfig
initCorePrepConfig hsc_env = do
+ let dflags = hsc_dflags hsc_env
convertNumLit <- do
- let platform = targetPlatform $ hsc_dflags hsc_env
+ let platform = targetPlatform dflags
home_unit = hsc_home_unit hsc_env
lookup_global = lookupGlobal hsc_env
mkConvertNumLiteral platform home_unit lookup_global
return $ CorePrepConfig
- { cp_catchNonexhaustiveCases = gopt Opt_CatchNonexhaustiveCases $ hsc_dflags hsc_env
+ { cp_catchNonexhaustiveCases = gopt Opt_CatchNonexhaustiveCases dflags
, cp_convertNumLit = convertNumLit
+ , cp_arityOpts = if gopt Opt_DoArgEtaExpansion dflags
+ then Just (initArityOpts dflags)
+ else Nothing
}
initCorePrepPgmConfig :: DynFlags -> [Var] -> CorePrepPgmConfig
=====================================
compiler/GHC/Driver/Flags.hs
=====================================
@@ -259,6 +259,7 @@ data GeneralFlag
| Opt_SpecConstr
| Opt_SpecConstrKeen
| Opt_DoLambdaEtaExpansion
+ | Opt_DoArgEtaExpansion -- Eta expansion of arguments in CorePrep
| Opt_IgnoreAsserts
| Opt_DoEtaReduction
| Opt_CaseMerge
=====================================
compiler/GHC/Driver/Session.hs
=====================================
@@ -3398,6 +3398,7 @@ fFlagsDeps = [
Opt_DmdTxDictSel "effect is now unconditionally enabled",
flagSpec "do-eta-reduction" Opt_DoEtaReduction,
flagSpec "do-lambda-eta-expansion" Opt_DoLambdaEtaExpansion,
+ flagSpec "do-arg-eta-expansion" Opt_DoArgEtaExpansion,
flagSpec "eager-blackholing" Opt_EagerBlackHoling,
flagSpec "embed-manifest" Opt_EmbedManifest,
flagSpec "enable-rewrite-rules" Opt_EnableRewriteRules,
@@ -3990,6 +3991,7 @@ optLevelFlags :: [([Int], GeneralFlag)]
-- Default settings of flags, before any command-line overrides
optLevelFlags -- see Note [Documenting optimisation flags]
= [ ([0,1,2], Opt_DoLambdaEtaExpansion)
+ , ([2], Opt_DoArgEtaExpansion)
, ([0,1,2], Opt_DoEtaReduction) -- See Note [Eta-reduction in -O0]
, ([0,1,2], Opt_LlvmTBAA)
, ([0,1,2], Opt_ProfManualCcs )
=====================================
docs/users_guide/using-optimisation.rst
=====================================
@@ -467,6 +467,16 @@ by saying ``-fno-wombat``.
Eta-expand let-bindings to increase their arity.
+.. ghc-flag:: -fdo-arg-eta-expansion
+ :shortdesc: Enable argument eta-expansion. Implied by :ghc-flag:`-O2`.
+ :type: dynamic
+ :reverse: -fno-do-arg-eta-expansion
+ :category:
+
+ :default: off
+
+ Eta-expand arguments to increase their arity.
+
.. ghc-flag:: -feager-blackholing
:shortdesc: Turn on :ref:`eager blackholing <parallel-compile-options>`
:type: dynamic
=====================================
testsuite/tests/simplCore/should_compile/T23083.hs
=====================================
@@ -0,0 +1,6 @@
+{-# OPTIONS_GHC -O2 -fforce-recomp #-}
+
+module T23083 where
+
+g :: ((Integer -> Integer) -> Integer) -> (Integer -> Integer) -> Integer
+g f h = f (h `seq` (h $))
=====================================
testsuite/tests/simplCore/should_compile/T23083.stderr
=====================================
@@ -0,0 +1,42 @@
+
+==================== CorePrep ====================
+Result size of CorePrep = {terms: 27, types: 24, coercions: 0, joins: 0/1}
+
+-- RHS size: {terms: 12, types: 13, coercions: 0, joins: 0/1}
+T23083.g :: ((GHC.Num.Integer.Integer -> GHC.Num.Integer.Integer) -> GHC.Num.Integer.Integer) -> (GHC.Num.Integer.Integer -> GHC.Num.Integer.Integer) -> GHC.Num.Integer.Integer
+[GblId, Arity=2, Str=<1C(1,L)><ML>, Unf=OtherCon []]
+T23083.g
+ = \ (f [Occ=Once1!] :: (GHC.Num.Integer.Integer -> GHC.Num.Integer.Integer) -> GHC.Num.Integer.Integer) (h [Occ=OnceL1] :: GHC.Num.Integer.Integer -> GHC.Num.Integer.Integer) ->
+ let {
+ sat [Occ=Once1] :: GHC.Num.Integer.Integer -> GHC.Num.Integer.Integer
+ [LclId]
+ sat = \ (eta [Occ=Once1] :: GHC.Num.Integer.Integer) -> case h of h1 [Occ=Once1] { __DEFAULT -> GHC.Base.$ @GHC.Types.LiftedRep @GHC.Num.Integer.Integer @GHC.Num.Integer.Integer h1 eta } } in
+ f sat
+
+-- RHS size: {terms: 1, types: 0, coercions: 0, joins: 0/0}
+T23083.$trModule4 :: GHC.Prim.Addr#
+[GblId, Unf=OtherCon []]
+T23083.$trModule4 = "main"#
+
+-- RHS size: {terms: 2, types: 0, coercions: 0, joins: 0/0}
+T23083.$trModule3 :: GHC.Types.TrName
+[GblId, Unf=OtherCon []]
+T23083.$trModule3 = GHC.Types.TrNameS T23083.$trModule4
+
+-- RHS size: {terms: 1, types: 0, coercions: 0, joins: 0/0}
+T23083.$trModule2 :: GHC.Prim.Addr#
+[GblId, Unf=OtherCon []]
+T23083.$trModule2 = "T23083"#
+
+-- RHS size: {terms: 2, types: 0, coercions: 0, joins: 0/0}
+T23083.$trModule1 :: GHC.Types.TrName
+[GblId, Unf=OtherCon []]
+T23083.$trModule1 = GHC.Types.TrNameS T23083.$trModule2
+
+-- RHS size: {terms: 3, types: 0, coercions: 0, joins: 0/0}
+T23083.$trModule :: GHC.Types.Module
+[GblId, Unf=OtherCon []]
+T23083.$trModule = GHC.Types.Module T23083.$trModule3 T23083.$trModule1
+
+
+
=====================================
testsuite/tests/simplCore/should_compile/all.T
=====================================
@@ -477,3 +477,4 @@ test('T23012', normal, compile, ['-O'])
test('RewriteHigherOrderPatterns', normal, compile, ['-O -ddump-rule-rewrites -dsuppress-all -dsuppress-uniques'])
test('T23024', normal, multimod_compile, ['T23024', '-O -v0'])
test('T23026', normal, compile, ['-O'])
+test('T23083', [ grep_errmsg(r'eta.+::.+Integer') ], compile, ['-O -ddump-prep -dsuppress-uniques -dppr-cols=99999'])
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/4f0eb801500744770cc6bfef401229113c28a8c4
--
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/4f0eb801500744770cc6bfef401229113c28a8c4
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/20230405/883406b7/attachment-0001.html>
More information about the ghc-commits
mailing list