[Git][ghc/ghc][wip/andreask/strict_dicts] Make WorkWrap.Lib.isWorkerSmallEnough aware of the old arity
Sebastian Graf
gitlab at gitlab.haskell.org
Thu Apr 9 11:27:58 UTC 2020
Sebastian Graf pushed to branch wip/andreask/strict_dicts at Glasgow Haskell Compiler / GHC
Commits:
b9ff82fe by Sebastian Graf at 2020-04-09T13:25:17+02:00
Make WorkWrap.Lib.isWorkerSmallEnough aware of the old arity
We should allow a wrapper with up to 82 parameters when the original
function had 82 parameters to begin with.
- - - - -
2 changed files:
- compiler/GHC/Core/Op/SpecConstr.hs
- compiler/GHC/Core/Op/WorkWrap/Lib.hs
Changes:
=====================================
compiler/GHC/Core/Op/SpecConstr.hs
=====================================
@@ -1995,7 +1995,7 @@ callsToNewPats env fn spec_info@(SI { si_specs = done_specs }) bndr_occs calls
-- Remove ones that have too many worker variables
small_pats = filterOut too_big non_dups
- too_big (vars,_) = not (isWorkerSmallEnough (sc_dflags env) vars)
+ too_big (vars,args) = not (isWorkerSmallEnough (sc_dflags env) (length args) vars)
-- We are about to construct w/w pair in 'spec_one'.
-- Omit specialisation leading to high arity workers.
-- See Note [Limit w/w arity] in GHC.Core.Op.WorkWrap.Lib
=====================================
compiler/GHC/Core/Op/WorkWrap/Lib.hs
=====================================
@@ -162,7 +162,7 @@ mkWwBodies dflags fam_envs rhs_fvs fun_id demands cpr_info
wrapper_body = wrap_fn_args . wrap_fn_cpr . wrap_fn_str . applyToVars work_call_args . Var
worker_body = mkLams work_lam_args. work_fn_str . work_fn_cpr . work_fn_args
- ; if isWorkerSmallEnough dflags work_args
+ ; if isWorkerSmallEnough dflags (length demands) work_args
&& not (too_many_args_for_join_point wrap_args)
&& ((useful1 && not only_one_void_argument) || useful2)
then return (Just (worker_args_dmds, length work_call_args,
@@ -203,10 +203,13 @@ mkWwBodies dflags fam_envs rhs_fvs fun_id demands cpr_info
= False
-- See Note [Limit w/w arity]
-isWorkerSmallEnough :: DynFlags -> [Var] -> Bool
-isWorkerSmallEnough dflags vars = count isId vars <= maxWorkerArgs dflags
+isWorkerSmallEnough :: DynFlags -> Int -> [Var] -> Bool
+isWorkerSmallEnough dflags old_n_args vars
+ = count isId vars <= max old_n_args (maxWorkerArgs dflags)
-- We count only Free variables (isId) to skip Type, Kind
-- variables which have no runtime representation.
+ -- Also if the function took 82 arguments before (old_n_args), it's fine if
+ -- it takes <= 82 arguments afterwards.
{-
Note [Always do CPR w/w]
@@ -227,7 +230,8 @@ Guard against high worker arity as it generates a lot of stack traffic.
A simplified example is #11565#comment:6
Current strategy is very simple: don't perform w/w transformation at all
-if the result produces a wrapper with arity higher than -fmax-worker-args=.
+if the result produces a wrapper with arity higher than -fmax-worker-args
+and the number arguments before w/w.
It is a bit all or nothing, consider
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/b9ff82fee1e600ca2c183725c97d2b6e1d59a668
--
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/b9ff82fee1e600ca2c183725c97d2b6e1d59a668
You're receiving this email because of your account on gitlab.haskell.org.
-------------- next part --------------
An HTML attachment was scrubbed...
URL: <http://mail.haskell.org/pipermail/ghc-commits/attachments/20200409/8ba41e49/attachment-0001.html>
More information about the ghc-commits
mailing list