[commit: ghc] wip/T11770: Demand Analyzer: Do not set OneShot information (d140500)
git at git.haskell.org
git at git.haskell.org
Wed Mar 30 08:05:59 UTC 2016
Repository : ssh://git@git.haskell.org/ghc
On branch : wip/T11770
Link : http://ghc.haskell.org/trac/ghc/changeset/d14050006e3db1aa90d063884c4cd98f0fd5e859/ghc
>---------------------------------------------------------------
commit d14050006e3db1aa90d063884c4cd98f0fd5e859
Author: Joachim Breitner <mail at joachim-breitner.de>
Date: Wed Mar 30 10:05:28 2016 +0200
Demand Analyzer: Do not set OneShot information
as suggested in ticket:11770#comment:1. This naturally fixes
issue #117700; performance validation pending.
(Pushing this as a branch to get perf.haskell.org to measure it).
>---------------------------------------------------------------
d14050006e3db1aa90d063884c4cd98f0fd5e859
compiler/stranal/DmdAnal.hs | 27 +++------------------------
testsuite/tests/stranal/should_compile/all.T | 2 +-
2 files changed, 4 insertions(+), 25 deletions(-)
diff --git a/compiler/stranal/DmdAnal.hs b/compiler/stranal/DmdAnal.hs
index 6ef911f..aae0c74 100644
--- a/compiler/stranal/DmdAnal.hs
+++ b/compiler/stranal/DmdAnal.hs
@@ -260,17 +260,13 @@ dmdAnal' env dmd (Case scrut case_bndr ty alts)
(res_ty, Case scrut' case_bndr' ty alts')
dmdAnal' env dmd (Let (NonRec id rhs) body)
- = (body_ty2, Let (NonRec id2 annotated_rhs) body')
+ = (body_ty2, Let (NonRec id2 rhs') body')
where
(sig, lazy_fv, id1, rhs') = dmdAnalRhs NotTopLevel Nothing env id rhs
(body_ty, body') = dmdAnal (extendAnalEnv NotTopLevel env id sig) dmd body
(body_ty1, id2) = annotateBndr env body_ty id1
body_ty2 = addLazyFVs body_ty1 lazy_fv
- -- Annotate top-level lambdas at RHS basing on the aggregated demand info
- -- See Note [Annotating lambdas at right-hand side]
- annotated_rhs = annLamWithShotness (idDemandInfo id2) rhs'
-
-- If the actual demand is better than the vanilla call
-- demand, you might think that we might do better to re-analyse
-- the RHS with the stronger demand.
@@ -317,8 +313,8 @@ annLamWithShotness d e
| Just (c, u') <- peelUseCall u
, Lam bndr body <- e
= if isTyVar bndr
- then Lam bndr (go u body)
- else Lam (setOneShotness c bndr) (go u' body)
+ then Lam bndr (go u body)
+ else Lam bndr (go u' body)
| otherwise
= e
@@ -432,23 +428,6 @@ free variable |y|. Conversely, if the demand on |h| is unleashed right
on the spot, we will get the desired result, namely, that |f| is
strict in |y|.
-Note [Annotating lambdas at right-hand side]
-~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~
-Let us take a look at the following example:
-
-g f = let x = 100
- h = \y -> f x y
- in h 5
-
-One can see that |h| is called just once, therefore the RHS of h can
-be annotated as a one-shot lambda. This is done by the function
-annLamWithShotness *a posteriori*, i.e., basing on the aggregated
-usage demand on |h| from the body of |let|-expression, which is C1(U)
-in this case.
-
-In other words, for locally-bound lambdas we can infer
-one-shotness.
-
************************************************************************
* *
diff --git a/testsuite/tests/stranal/should_compile/all.T b/testsuite/tests/stranal/should_compile/all.T
index 3ac075b..dabc9fc 100644
--- a/testsuite/tests/stranal/should_compile/all.T
+++ b/testsuite/tests/stranal/should_compile/all.T
@@ -45,6 +45,6 @@ test('T9208', when(compiler_debugged(), expect_broken(9208)), compile, [''])
# Hence the above expect_broken. See comments in the Trac ticket
test('T10694', [ grepCoreString(r'Str=') ], compile, ['-dppr-cols=200 -ddump-simpl'])
-test('T11770', [ expect_broken(117700), checkCoreString("OneShot") ], compile, ['-ddump-simpl'])
+test('T11770', [ checkCoreString('OneShot') ], compile, ['-ddump-simpl'])
More information about the ghc-commits
mailing list