[commit: ghc] master: Make worker-wrapper optional (31704ad)

git at git.haskell.org git at git.haskell.org
Tue Oct 27 17:25:16 UTC 2015


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

On branch  : master
Link       : http://ghc.haskell.org/trac/ghc/changeset/31704adc82c3a1e48ac05c51f02933fd996b642a/ghc

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

commit 31704adc82c3a1e48ac05c51f02933fd996b642a
Author: Christiaan Baaij <christiaan.baaij at gmail.com>
Date:   Tue Oct 27 10:21:27 2015 -0500

    Make worker-wrapper optional
    
    Add -fworker-wrapper flag which enables the worker-wrapper transformation. It
    is implied by -O.
    
    The expected users of this flag, which includes myself, are GHC API users.  In
    my Haskell-to-Hardware compiler, which uses the GHC API, I have seen no
    benifits of the worker-wrapper transformation. It does however induce longer
    compilation times.
    
    Further discussion can be seen here:
    https://mail.haskell.org/pipermail/ghc-devs/2015-October/010096.html
    
    Reviewed By: austin
    
    Differential Revision: https://phabricator.haskell.org/D1372
    
    GHC Trac Issues: #11020


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

31704adc82c3a1e48ac05c51f02933fd996b642a
 compiler/main/DynFlags.hs                      | 29 ++++++++++++++++++++++----
 compiler/simplCore/SimplCore.hs                | 24 ++++++++++++---------
 docs/users_guide/7.12.1-notes.rst              |  6 ++++++
 utils/mkUserGuidePart/Options/Optimizations.hs | 13 +++++++++++-
 4 files changed, 57 insertions(+), 15 deletions(-)

diff --git a/compiler/main/DynFlags.hs b/compiler/main/DynFlags.hs
index 6f5fa6a..320a11e 100644
--- a/compiler/main/DynFlags.hs
+++ b/compiler/main/DynFlags.hs
@@ -374,6 +374,7 @@ data GeneralFlag
    | Opt_DmdTxDictSel              -- use a special demand transformer for dictionary selectors
    | Opt_Loopification                  -- See Note [Self-recursive tail calls]
    | Opt_CprAnal
+   | Opt_WorkerWrapper
 
    -- Interface files
    | Opt_IgnoreInterfacePragmas
@@ -3011,7 +3012,8 @@ fFlags = [
   flagSpec "unbox-small-strict-fields"        Opt_UnboxSmallStrictFields,
   flagSpec "unbox-strict-fields"              Opt_UnboxStrictFields,
   flagSpec "vectorisation-avoidance"          Opt_VectorisationAvoidance,
-  flagSpec "vectorise"                        Opt_Vectorise
+  flagSpec "vectorise"                        Opt_Vectorise,
+  flagSpec "worker-wrapper"                   Opt_WorkerWrapper
   ]
 
 -- | These @-f\<blah\>@ flags can all be reversed with @-fno-\<blah\>@
@@ -3251,8 +3253,17 @@ default_PIC platform =
                                          -- information.
     _                      -> []
 
+-- General flags that are switched on/off when other general flags are switched
+-- on
 impliedGFlags :: [(GeneralFlag, TurnOnFlag, GeneralFlag)]
-impliedGFlags = [(Opt_DeferTypeErrors, turnOn, Opt_DeferTypedHoles)]
+impliedGFlags = [(Opt_DeferTypeErrors, turnOn, Opt_DeferTypedHoles)
+                ,(Opt_Strictness, turnOn, Opt_WorkerWrapper)
+                ]
+
+-- General flags that are switched on/off when other general flags are switched
+-- off
+impliedOffGFlags :: [(GeneralFlag, TurnOnFlag, GeneralFlag)]
+impliedOffGFlags = [(Opt_Strictness, turnOff, Opt_WorkerWrapper)]
 
 impliedXFlags :: [(ExtensionFlag, TurnOnFlag, ExtensionFlag)]
 impliedXFlags
@@ -3346,6 +3357,7 @@ optLevelFlags -- see Note [Documenting optimisation flags]
     , ([1,2],   Opt_Strictness)
     , ([1,2],   Opt_UnboxSmallStrictFields)
     , ([1,2],   Opt_CprAnal)
+    , ([1,2],   Opt_WorkerWrapper)
 
     , ([2],     Opt_LiberateCase)
     , ([2],     Opt_SpecConstr)
@@ -3613,8 +3625,17 @@ setGeneralFlag' f dflags = foldr ($) (gopt_set dflags f) deps
         --     implies further flags
 
 unSetGeneralFlag' :: GeneralFlag -> DynFlags -> DynFlags
-unSetGeneralFlag' f dflags = gopt_unset dflags f
-   -- When you un-set f, however, we don't un-set the things it implies
+unSetGeneralFlag' f dflags = foldr ($) (gopt_unset dflags f) deps
+  where
+    deps = [ if turn_on then setGeneralFlag' d
+                        else unSetGeneralFlag' d
+           | (f', turn_on, d) <- impliedOffGFlags, f' == f ]
+   -- In general, when you un-set f, we don't un-set the things it implies.
+   -- There are however some exceptions, e.g., -fno-strictness implies
+   -- -fno-worker-wrapper.
+   --
+   -- NB: use unSetGeneralFlag' recursively, in case the implied off flags
+   --     imply further flags.
 
 --------------------------
 setWarningFlag, unSetWarningFlag :: WarningFlag -> DynP ()
diff --git a/compiler/simplCore/SimplCore.hs b/compiler/simplCore/SimplCore.hs
index dddb24d..9207cf4 100644
--- a/compiler/simplCore/SimplCore.hs
+++ b/compiler/simplCore/SimplCore.hs
@@ -127,6 +127,7 @@ getCoreToDo dflags
     static_args   = gopt Opt_StaticArgumentTransformation dflags
     rules_on      = gopt Opt_EnableRewriteRules           dflags
     eta_expand_on = gopt Opt_DoLambdaEtaExpansion         dflags
+    ww_on         = gopt Opt_WorkerWrapper                dflags
 
     maybe_rule_check phase = runMaybe rule_check (CoreDoRuleCheck phase)
 
@@ -187,12 +188,16 @@ getCoreToDo dflags
                           -- Don't do case-of-case transformations.
                           -- This makes full laziness work better
 
+    strictness_pass = if ww_on
+                       then [CoreDoStrictness,CoreDoWorkerWrapper]
+                       else [CoreDoStrictness]
+
+
     -- New demand analyser
-    demand_analyser = (CoreDoPasses ([
-                           CoreDoStrictness,
-                           CoreDoWorkerWrapper,
-                           simpl_phase 0 ["post-worker-wrapper"] max_iter
-                           ]))
+    demand_analyser = (CoreDoPasses (
+                           strictness_pass ++
+                           [simpl_phase 0 ["post-worker-wrapper"] max_iter]
+                           ))
 
     core_todo =
      if opt_level == 0 then
@@ -309,11 +314,10 @@ getCoreToDo dflags
         -- Final clean-up simplification:
         simpl_phase 0 ["final"] max_iter,
 
-        runWhen late_dmd_anal $ CoreDoPasses [
-            CoreDoStrictness,
-            CoreDoWorkerWrapper,
-            simpl_phase 0 ["post-late-ww"] max_iter
-          ],
+        runWhen late_dmd_anal $ CoreDoPasses (
+            strictness_pass ++
+            [simpl_phase 0 ["post-late-ww"] max_iter]
+          ),
 
         maybe_rule_check (Phase 0)
      ]
diff --git a/docs/users_guide/7.12.1-notes.rst b/docs/users_guide/7.12.1-notes.rst
index e05366c..5cc02ad 100644
--- a/docs/users_guide/7.12.1-notes.rst
+++ b/docs/users_guide/7.12.1-notes.rst
@@ -102,6 +102,12 @@ Compiler
    ``-fcpr-off`` is now removed, run with ``-fno-cpr-anal`` to get the
    old ``-fcpr-off`` behaviour.
 
+-  Added the option ``-fworker-wrapper``. When enabled, the worker-wrapper
+   transformation is performed after a strictness analysis pass. It is implied
+   by ``-O`` and by ``-fstrictness``. It is disabled by ``-fno-strictness``.
+   Enabling ``-fworker-wrapper`` while strictness analysis is disabled (by
+   ``-fno-strictness``) has no effect.
+
 GHCi
 ~~~~
 
diff --git a/utils/mkUserGuidePart/Options/Optimizations.hs b/utils/mkUserGuidePart/Options/Optimizations.hs
index 0082a21..6e0a2ff 100644
--- a/utils/mkUserGuidePart/Options/Optimizations.hs
+++ b/utils/mkUserGuidePart/Options/Optimizations.hs
@@ -289,7 +289,8 @@ optimizationsOptions =
          , flagReverse = "-fno-static-argument-transformation"
          }
   , flag { flagName = "-fstrictness"
-         , flagDescription = "Turn on strictness analysis. Implied by ``-O``."
+         , flagDescription = "Turn on strictness analysis." ++
+           " Implied by ``-O``. Implies ``-fworker-wrapper``"
          , flagType = DynamicFlag
          , flagReverse = "-fno-strictness"
          }
@@ -341,4 +342,14 @@ optimizationsOptions =
          , flagType = DynamicFlag
          , flagReverse = "-fno-vectorise"
          }
+  , flag { flagName = "-fworker-wrapper"
+         , flagDescription =
+           "Enable the worker-wrapper transformation after a strictness" ++
+           " analysis pass. Implied by ``-O``, and by ``-fstrictness``." ++
+           " Disabled by ``-fno-strictness``. Enabling ``-fworker-wrapper``" ++
+           " while strictness analysis is disabled (by ``-fno-strictness``)" ++
+           " has no effect."
+         , flagType = DynamicFlag
+         , flagReverse = "-fno-worker-wrapper"
+         }
   ]



More information about the ghc-commits mailing list