[Git][ghc/ghc][wip/T21694a] Documentation

Simon Peyton Jones (@simonpj) gitlab at gitlab.haskell.org
Fri Aug 19 23:33:32 UTC 2022



Simon Peyton Jones pushed to branch wip/T21694a at Glasgow Haskell Compiler / GHC


Commits:
aa3ea6af by Simon Peyton Jones at 2022-08-20T00:33:45+01:00
Documentation

- - - - -


3 changed files:

- compiler/GHC/Core/Opt/Arity.hs
- compiler/GHC/Core/Opt/DmdAnal.hs
- compiler/GHC/Core/Opt/Simplify/Utils.hs


Changes:

=====================================
compiler/GHC/Core/Opt/Arity.hs
=====================================
@@ -1582,8 +1582,8 @@ function, via idArityType.
 
 But see Note [Arity type for recursive join bindings] for dark corners.
 
-See Note [Arity type for recursive join bindings]
-~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~
+Note [Arity type for recursive join bindings]
+~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~
 Consider
   f x = joinrec j 0 = \ a b c -> (a,x,b)
                 j n = j (n-1)


=====================================
compiler/GHC/Core/Opt/DmdAnal.hs
=====================================
@@ -1005,8 +1005,7 @@ dmdAnalRhsSig top_lvl rec_flag env let_dmd id rhs
     !(!lazy_fv, !sig_fv) = partitionVarEnv isWeakDmd rhs_fv2
 
 thresholdArity :: Id -> CoreExpr -> Arity
--- **** TODO ***
--- See Note [Demand signatures are computed for a threshold demand based on idArity]
+-- See Note [Demand signatures are computed for a threshold arity based on idArity]
 thresholdArity fn rhs
   = case isJoinId_maybe fn of
       Just join_arity -> count isId $ fst $ collectNBinders join_arity rhs
@@ -1144,28 +1143,40 @@ meaning one absent argument, returns bottom.  That seems odd because
 there's a \y inside.  But it's right because when consumed in a C1(L)
 context the RHS of the join point is indeed bottom.
 
-Note [Demand signatures are computed for a threshold demand based on idArity]
-~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~
-We compute demand signatures assuming idArity incoming arguments to approximate
-behavior for when we have a call site with at least that many arguments. idArity
-is /at least/ the number of manifest lambdas, but might be higher for PAPs and
-trivial RHS (see Note [Demand analysis for trivial right-hand sides]).
+Note [Demand signatures are computed for a threshold arity based on idArity]
+~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~
+Given a binding { f = rhs }, we compute a "theshold arity", and do demand
+analysis based on a call with that many value arguments.
 
-Because idArity of a function varies independently of its cardinality
-properties (cf. Note [idArity varies independently of dmdTypeDepth]), we
-implicitly encode the arity for when a demand signature is sound to unleash
-in its 'dmdTypeDepth' (cf. Note [Understanding DmdType and DmdSig] in
-GHC.Types.Demand). It is unsound to unleash a demand signature when the
-incoming number of arguments is less than that.
-See Note [What are demand signatures?] in GHC.Types.Demand for more details
-on soundness.
+The threshold we use is
+
+* Ordinary bindings: idArity f.
+  Why idArity arguments? Because that's a conservative estimate of how many
+  arguments we must feed a function before it does anything interesting with
+  them.  Also it elegantly subsumes the trivial RHS and PAP case.
+
+  idArity is /at least/ the number of manifest lambdas, but might be higher for
+  PAPs and trivial RHS (see Note [Demand analysis for trivial right-hand sides]).
 
-Why idArity arguments? Because that's a conservative estimate of how many
-arguments we must feed a function before it does anything interesting with them.
-Also it elegantly subsumes the trivial RHS and PAP case.
+* Join points: the value-binder subset of the JoinArity.  This can
+  be less than the number of visible lambdas; e.g.
+     join j x = \y. blah
+     in ...(jump j 2)....(jump j 3)....
+  We know that j will never be applied to more than 1 arg (its join
+  arity, and we don't eta-expand join points, so here a threshold
+  of 1 is the best we can do.
 
-There might be functions for which we might want to analyse for more incoming
-arguments than idArity. Example:
+Note that the idArity of a function varies independently of its cardinality
+properties (cf. Note [idArity varies independently of dmdTypeDepth]), so we
+implicitly encode the arity for when a demand signature is sound to unleash
+in its 'dmdTypeDepth', not in its idArity (cf. Note [Understanding DmdType
+and DmdSig] in GHC.Types.Demand). It is unsound to unleash a demand
+signature when the incoming number of arguments is less than that. See
+GHC.Types.Demand Note [What are demand signatures?]  for more details on
+soundness.
+
+Note that there might, in principle, be functions for which we might want to
+analyse for more incoming arguments than idArity. Example:
 
   f x =
     if expensive
@@ -1182,6 +1193,7 @@ strictness info for `y` (and more precise info on `x`) and possibly CPR
 information, but
 
   * We would no longer be able to unleash the signature at unary call sites
+
   * Performing the worker/wrapper split based on this information would be
     implicitly eta-expanding `f`, playing fast and loose with divergence and
     even being unsound in the presence of newtypes, so we refrain from doing so.


=====================================
compiler/GHC/Core/Opt/Simplify/Utils.hs
=====================================
@@ -1787,6 +1787,7 @@ tryEtaExpandRhs env (BC_Join is_rec _) bndr rhs
     -- these are used to set the bndr's IdInfo (#15517)
     -- Note [Invariants on join points] invariant 2b, in GHC.Core
   where
+    -- See Note [Arity computation for join points]
     arity_type = case is_rec of
                    NonRecursive -> cheapArityType rhs
                    Recursive    -> findRhsArity (seArityOpts env) Recursive
@@ -1931,6 +1932,24 @@ CorePrep comes around, the code is very likely to look more like this:
              $j2 = if n > 0 then $j1
                             else (...) eta
 
+Note [Arity computation for join points]
+~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~
+For /recursive/ join points we want the full glory of findRhsArity,
+with its fixpont computation.  Why?  See GHC.Core.Opt.Arity
+Note [Arity type for recursive join bindings].
+
+But for /non-recursive/ join points, findRhsArity will call arityType.
+And that can be expensive when we have deeply nested join points:
+   join j1 x1 = join j2 x2 = join j3 x3 = blah3
+                             in blah2
+                in blah1
+(e.g. test T18698b).
+
+So we call cheapArityType instead.  It's good enough for practical
+purposes.
+
+(Side note: maybe we should use cheapArity for the RHS of let bindings
+in the main arityType function.)
 
 ************************************************************************
 *                                                                      *



View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/aa3ea6af2a48994875d0dd2d7b5933475dc5f455

-- 
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/aa3ea6af2a48994875d0dd2d7b5933475dc5f455
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/20220819/6a23401d/attachment-0001.html>


More information about the ghc-commits mailing list