[commit: ghc] wip/T11770: Demand Analyzer: Do not set OneShot information (cc6e1e5)

git at git.haskell.org git at git.haskell.org
Wed Mar 30 09:18:13 UTC 2016


Repository : ssh://git@git.haskell.org/ghc

On branch  : wip/T11770
Link       : http://ghc.haskell.org/trac/ghc/changeset/cc6e1e5226253311ec9d9bda5c6df8211d65cf44/ghc

>---------------------------------------------------------------

commit cc6e1e5226253311ec9d9bda5c6df8211d65cf44
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 code was buggy (#11770),
    and the occurrence analyzer does the same job anyways.
    
    This also elaborates the notes in the occurrence analyzer accordingly.


>---------------------------------------------------------------

cc6e1e5226253311ec9d9bda5c6df8211d65cf44
 compiler/simplCore/OccurAnal.hs              | 33 ++++++++++++++++++++--------
 compiler/stranal/DmdAnal.hs                  | 27 +++--------------------
 testsuite/tests/stranal/should_compile/all.T |  2 +-
 3 files changed, 28 insertions(+), 34 deletions(-)

diff --git a/compiler/simplCore/OccurAnal.hs b/compiler/simplCore/OccurAnal.hs
index 3eb20d0..36d6e7a 100644
--- a/compiler/simplCore/OccurAnal.hs
+++ b/compiler/simplCore/OccurAnal.hs
@@ -1395,19 +1395,29 @@ markManyIf False uds = uds
 {-
 Note [Use one-shot information]
 ~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~
-The occurrrence analyser propagates one-shot-lambda information in two situation
-  * Applications:  eg   build (\cn -> blah)
+The occurrrence analyser propagates one-shot-lambda information in two
+situations:
+
+  * Applications:  eg   build (\c n -> blah)
+
     Propagate one-shot info from the strictness signature of 'build' to
-    the \cn
+    the \c n.
+
+    This strictness signature can come from a module interface, in the case of
+    an imported function, or from a previous run of the demand analyser.
 
   * Let-bindings:  eg   let f = \c. let ... in \n -> blah
                         in (build f, build f)
+
     Propagate one-shot info from the demanand-info on 'f' to the
     lambdas in its RHS (which may not be syntactically at the top)
 
-Some of this is done by the demand analyser, but this way it happens
-much earlier, taking advantage of the strictness signature of
-imported functions.
+    This information must have come from a previous run of the demanand
+    analyser.
+
+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 [Binders in case alternatives]
 ~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~
@@ -1534,7 +1544,7 @@ oneShotGroup :: OccEnv -> [CoreBndr]
              -> ( OccEnv
                 , [CoreBndr] )
         -- The result binders have one-shot-ness set that they might not have had originally.
-        -- This happens in (build (\cn -> e)).  Here the occurrence analyser
+        -- This happens in (build (\c n -> e)).  Here the occurrence analyser
         -- linearity context knows that c,n are one-shot, and it records that fact in
         -- the binder. This is useful to guide subsequent float-in/float-out tranformations
 
@@ -1555,8 +1565,13 @@ oneShotGroup env@(OccEnv { occ_one_shots = ctxt }) bndrs
       = case ctxt of
           []                -> go []   bndrs (bndr : rev_bndrs)
           (one_shot : ctxt) -> go ctxt bndrs (bndr': rev_bndrs)
-                            where
-                               bndr' = updOneShotInfo bndr one_shot
+            where
+               bndr' = updOneShotInfo bndr one_shot
+               -- Use updOneShotInfo, not setOneShotInfo, as pre-existing
+               -- one-shot info might be better than what we can infer, e.g.
+               -- due to explicit use of the magic 'oneShot' function.
+               -- See Note [The oneShot function]
+
        | otherwise
       = go ctxt bndrs (bndr:rev_bndrs)
 
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