[commit: ghc] wip/T13227: Improve the Occurrence Analyzer’s handling of one-shot functions (52fc503)
git at git.haskell.org
git at git.haskell.org
Tue Feb 7 02:39:10 UTC 2017
Repository : ssh://git@git.haskell.org/ghc
On branch : wip/T13227
Link : http://ghc.haskell.org/trac/ghc/changeset/52fc50301279da2e8672f57d5505c94a6d9b9217/ghc
>---------------------------------------------------------------
commit 52fc50301279da2e8672f57d5505c94a6d9b9217
Author: Joachim Breitner <mail at joachim-breitner.de>
Date: Sun Feb 5 10:52:12 2017 -0500
Improve the Occurrence Analyzer’s handling of one-shot functions
when determining whether an expression is used saturatedly, count the
number of value arguments that the occurrence analyser sees, and add
the number of one-shot arguments that we know (from the strictness
analyser) are passed from the context. This was suggested by Simon PJ in
ticket #13227.
perf results suggest no noticable change in allocations, reduction of
code sizes, and performance regression possibliy due to loss of join
points.
Differential Revision: https://phabricator.haskell.org/D3089
>---------------------------------------------------------------
52fc50301279da2e8672f57d5505c94a6d9b9217
compiler/simplCore/OccurAnal.hs | 42 +++++++++++++++++++++++++++++------------
1 file changed, 30 insertions(+), 12 deletions(-)
diff --git a/compiler/simplCore/OccurAnal.hs b/compiler/simplCore/OccurAnal.hs
index 80eca71..6d0e321 100644
--- a/compiler/simplCore/OccurAnal.hs
+++ b/compiler/simplCore/OccurAnal.hs
@@ -1547,7 +1547,7 @@ occAnalNonRecRhs env bndr bndrs body
env1 | certainly_inline = env
| otherwise = rhsCtxt env
- -- See Note [Use one-shot info]
+ -- See Note [Sources of one-shot info]
rhs_env = env1 { occ_one_shots = argOneShots dmd }
@@ -1867,7 +1867,13 @@ occAnalApp env (Var fun, args, ticks)
-- This is the *whole point* of the isRhsEnv predicate
-- See Note [Arguments of let-bound constructors]
- n_val_args = valArgCount args
+ n_val_args = valArgCount args + length (takeWhile isOneShotInfo (occ_one_shots env))
+ -- n_val_args is used to determine if this call is saturated. We want to consider
+ -- the lambda expression in 'build (\x y -> …)' to be considered
+ -- saturated, so we count one-shot arguments from the context.
+ -- But 'map (\x -> …)' is not saturated, so we only count the one-shot
+ -- arguments.
+
n_args = length args
fun_uds = mkOneOcc env fun (n_val_args > 0) n_args
is_exp = isExpandableApp fun n_val_args
@@ -1876,7 +1882,7 @@ occAnalApp env (Var fun, args, ticks)
-- Simplify.prepareRhs
one_shots = argsOneShots (idStrictness fun) n_val_args
- -- See Note [Use one-shot info]
+ -- See Note [Sources of one-shot information]
occAnalApp env (fun, args, ticks)
= (markAllNonTailCalled (fun_uds +++ args_uds),
@@ -1898,10 +1904,9 @@ zapDetailsIf True uds = zapDetails uds
zapDetailsIf False uds = uds
{-
-Note [Use one-shot information]
-~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~
-The occurrrence analyser propagates one-shot-lambda information in two
-situations:
+Note [Sources of one-shot information]
+~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~
+The occurrence analyser obtains one-shot-lambda information from two sources:
* Applications: eg build (\c n -> blah)
@@ -1924,6 +1929,22 @@ Previously, the demand analyser would *also* set the one-shot information, but
that code was buggy (see #11770), so doing it only in on place, namely here, is
saner.
+Note [OneShots]
+~~~~~~~~~~~~~~~
+When analysing an expression, the occ_one_shots argument contains information
+about how the function is being used. The length of the list indicates
+how many arguments will eventually be passed to the analysed expression,
+and the OneShotInfo indicates whether this application is once or multiple times.
+
+Example:
+
+ Context of f occ_one_shots when analysing f
+
+ f 1 2 [OneShot, OneShot]
+ map (f 1) [OneShot, NoOneShotInfo]
+ build f [OneShot, OneShot]
+ f 1 2 `seq` f 2 1 [NoOneShotInfo, OneShot]
+
Note [Binders in case alternatives]
~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~
Consider
@@ -2008,7 +2029,7 @@ wrapAltRHS _ _ alt_usg _ alt_rhs
data OccEnv
= OccEnv { occ_encl :: !OccEncl -- Enclosing context information
- , occ_one_shots :: !OneShots -- Tells about linearity
+ , occ_one_shots :: !OneShots -- See Note [OneShots]
, occ_gbl_scrut :: GlobalScruts
, occ_rule_act :: Activation -> Bool -- Which rules are active
-- See Note [Finding rule RHS free vars]
@@ -2037,11 +2058,8 @@ instance Outputable OccEncl where
ppr OccRhs = text "occRhs"
ppr OccVanilla = text "occVanilla"
+-- See note [OneShots]
type OneShots = [OneShotInfo]
- -- [] No info
- --
- -- one_shot_info:ctxt Analysing a function-valued expression that
- -- will be applied as described by one_shot_info
initOccEnv :: (Activation -> Bool) -> OccEnv
initOccEnv active_rule
More information about the ghc-commits
mailing list