[commit: ghc] wip/T13227: Get rid of ProbOneShot (9985779)

git at git.haskell.org git at git.haskell.org
Thu Feb 2 17:54:13 UTC 2017


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

On branch  : wip/T13227
Link       : http://ghc.haskell.org/trac/ghc/changeset/99857796bdac0845e62ed7d134b9696bbdf884c5/ghc

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

commit 99857796bdac0845e62ed7d134b9696bbdf884c5
Author: Joachim Breitner <mail at joachim-breitner.de>
Date:   Thu Feb 2 12:52:57 2017 -0500

    Get rid of ProbOneShot
    
    This fixes #13227. It remains to be seen what the performance impacts
    are. Pushing as a branch to get perf.haskell.org answer that for us.


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

99857796bdac0845e62ed7d134b9696bbdf884c5
 compiler/basicTypes/BasicTypes.hs          |  7 -------
 compiler/basicTypes/Demand.hs              | 22 ++++------------------
 compiler/basicTypes/Id.hs                  |  3 +--
 testsuite/tests/simplCore/should_run/all.T |  2 +-
 4 files changed, 6 insertions(+), 28 deletions(-)

diff --git a/compiler/basicTypes/BasicTypes.hs b/compiler/basicTypes/BasicTypes.hs
index ff4d2c7..49ecc72 100644
--- a/compiler/basicTypes/BasicTypes.hs
+++ b/compiler/basicTypes/BasicTypes.hs
@@ -211,8 +211,6 @@ type Alignment = Int -- align to next N-byte boundary (N must be a power of 2).
 -- work.
 data OneShotInfo
   = NoOneShotInfo -- ^ No information
-  | ProbOneShot   -- ^ The lambda is probably applied at most once
-                  -- See Note [Computing one-shot info, and ProbOneShot] in Demand
   | OneShotLam    -- ^ The lambda is applied at most once.
   deriving (Eq)
 
@@ -229,18 +227,13 @@ hasNoOneShotInfo _             = False
 
 worstOneShot, bestOneShot :: OneShotInfo -> OneShotInfo -> OneShotInfo
 worstOneShot NoOneShotInfo _             = NoOneShotInfo
-worstOneShot ProbOneShot   NoOneShotInfo = NoOneShotInfo
-worstOneShot ProbOneShot   _             = ProbOneShot
 worstOneShot OneShotLam    os            = os
 
 bestOneShot NoOneShotInfo os         = os
-bestOneShot ProbOneShot   OneShotLam = OneShotLam
-bestOneShot ProbOneShot   _          = ProbOneShot
 bestOneShot OneShotLam    _          = OneShotLam
 
 pprOneShotInfo :: OneShotInfo -> SDoc
 pprOneShotInfo NoOneShotInfo = empty
-pprOneShotInfo ProbOneShot   = text "ProbOneShot"
 pprOneShotInfo OneShotLam    = text "OneShot"
 
 instance Outputable OneShotInfo where
diff --git a/compiler/basicTypes/Demand.hs b/compiler/basicTypes/Demand.hs
index 8cacf22..d7fa57c 100644
--- a/compiler/basicTypes/Demand.hs
+++ b/compiler/basicTypes/Demand.hs
@@ -1783,13 +1783,13 @@ it should not fall over.
 -}
 
 argsOneShots :: StrictSig -> Arity -> [[OneShotInfo]]
--- See Note [Computing one-shot info, and ProbOneShot]
+-- See Note [Computing one-shot info]
 argsOneShots (StrictSig (DmdType _ arg_ds _)) n_val_args
   = go arg_ds
   where
     unsaturated_call = arg_ds `lengthExceeds` n_val_args
     good_one_shot
-      | unsaturated_call = ProbOneShot
+      | unsaturated_call = NoOneShotInfo
       | otherwise        = OneShotLam
 
     go []               = []
@@ -1813,7 +1813,7 @@ saturatedByOneShots n (JD { ud = usg })
     go n (UCall One u) = go (n-1) u
     go _ _             = False
 
-argOneShots :: OneShotInfo     -- OneShotLam or ProbOneShot,
+argOneShots :: OneShotInfo     -- OneShotLam or NoOneShotInfo,
             -> Demand          -- depending on saturation
             -> [OneShotInfo]
 argOneShots one_shot_info (JD { ud = usg })
@@ -1825,7 +1825,7 @@ argOneShots one_shot_info (JD { ud = usg })
     go (UCall Many u) = NoOneShotInfo : go u
     go _              = []
 
-{- Note [Computing one-shot info, and ProbOneShot]
+{- Note [Computing one-shot info]
 ~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~
 Consider a call
     f (\pqr. e1) (\xyz. e2) e3
@@ -1835,20 +1835,6 @@ Then argsOneShots returns a [[OneShotInfo]] of
     [[OneShot,NoOneShotInfo,OneShot],  [OneShot]]
 The occurrence analyser propagates this one-shot infor to the
 binders \pqr and \xyz; see Note [Use one-shot information] in OccurAnal.
-
-But suppose f was not saturated, so the call looks like
-    f (\pqr. e1) (\xyz. e2)
-The in principle this partial application might be shared, and
-the (\prq.e1) abstraction might be called more than once.  So
-we can't mark them OneShot. But instead we return
-    [[ProbOneShot,NoOneShotInfo,ProbOneShot],  [ProbOneShot]]
-The occurrence analyser propagates this to the \pqr and \xyz
-binders.
-
-How is it used?  Well, it's quite likely that the partial application
-of f is not shared, so the float-out pass (in SetLevels.lvlLamBndrs)
-does not float MFEs out of a ProbOneShot lambda.  That currently is
-the only way that ProbOneShot is used.
 -}
 
 -- appIsBottom returns true if an application to n args
diff --git a/compiler/basicTypes/Id.hs b/compiler/basicTypes/Id.hs
index acb22e8..09e018c 100644
--- a/compiler/basicTypes/Id.hs
+++ b/compiler/basicTypes/Id.hs
@@ -762,7 +762,7 @@ isOneShotBndr var
 
 -- | Should we apply the state hack to values of this 'Type'?
 stateHackOneShot :: OneShotInfo
-stateHackOneShot = OneShotLam         -- Or maybe ProbOneShot?
+stateHackOneShot = OneShotLam
 
 typeOneShot :: Type -> OneShotInfo
 typeOneShot ty
@@ -798,7 +798,6 @@ isStateHackType ty
 isProbablyOneShotLambda :: Id -> Bool
 isProbablyOneShotLambda id = case idStateHackOneShotInfo id of
                                OneShotLam    -> True
-                               ProbOneShot   -> True
                                NoOneShotInfo -> False
 
 setOneShotLambda :: Id -> Id
diff --git a/testsuite/tests/simplCore/should_run/all.T b/testsuite/tests/simplCore/should_run/all.T
index 6fe17e1..702d83c 100644
--- a/testsuite/tests/simplCore/should_run/all.T
+++ b/testsuite/tests/simplCore/should_run/all.T
@@ -73,4 +73,4 @@ test('T12689broken', expect_broken(12689), compile_and_run, [''])
 test('T12689a', normal, compile_and_run, [''])
 
 test('T13172', only_ways(['optasm']), compile_and_run, ['-dcore-lint'])
-test('T13227', expect_broken(13227), compile_and_run, [''])
+test('T13227', normal, compile_and_run, [''])



More information about the ghc-commits mailing list