[Git][ghc/ghc][wip/dmdanal-split-fvs] DmdAnal: Kill `is_thunk` case in `splitFV`

Sebastian Graf gitlab at gitlab.haskell.org
Sat Oct 24 15:19:26 UTC 2020



Sebastian Graf pushed to branch wip/dmdanal-split-fvs at Glasgow Haskell Compiler / GHC


Commits:
01cf781b by Sebastian Graf at 2020-10-24T17:18:17+02:00
DmdAnal: Kill `is_thunk` case in `splitFV`

The `splitFV` function implements the highly dubious hack
described in `Note [Lazy und unleashable free variables]` in
GHC.Core.Opt.DmdAnal. It arranges it so that demand signatures only
carry strictness info on free variables. Usage info is released through
other means, see the Note. It's purely for analysis performance reasons.

TODO: Update commit message

But in case of a strict FV demand, we still add the FV to the demand
signature *and* the lazy_fv DmdEnv. It would be far simpler (and more
precise) not having to split the demand over both places, if analysis
performance doesn't degrade too much.

- - - - -


2 changed files:

- compiler/GHC/Core/Opt/DmdAnal.hs
- compiler/GHC/Types/Demand.hs


Changes:

=====================================
compiler/GHC/Core/Opt/DmdAnal.hs
=====================================
@@ -574,7 +574,7 @@ dmdAnalRhsLetDown rec_flag env let_dmd id rhs
     rhs_fv2 = rhs_fv1 `keepAliveDmdEnv` extra_fvs
 
     -- See Note [Lazy and unleashable free variables]
-    (lazy_fv, sig_fv) = splitFVs is_thunk rhs_fv2
+    (lazy_fv, sig_fv) = partitionVarEnv isWeakDmd rhs_fv2
     is_thunk = not (exprIsHNF rhs) && not (isJoinId id)
 
     -- Find the RHS free vars of the unfoldings and RULES


=====================================
compiler/GHC/Types/Demand.hs
=====================================
@@ -42,7 +42,7 @@ module GHC.Types.Demand (
         seqDemand, seqDemandList, seqDmdType, seqStrictSig,
 
         evalDmd, cleanEvalDmd, cleanEvalProdDmd, isStrictDmd,
-        splitDmdTy, splitFVs, deferAfterPreciseException,
+        splitDmdTy, isWeakDmd, deferAfterPreciseException,
         postProcessUnsat, postProcessDmdType,
 
         splitProdDmd_maybe, peelCallDmd, peelManyCalls, mkCallDmd, mkCallDmds,
@@ -796,22 +796,6 @@ cleanUseDmd_maybe :: Demand -> Maybe UseDmd
 cleanUseDmd_maybe (JD { ud = Use _ u }) = Just u
 cleanUseDmd_maybe _                     = Nothing
 
-splitFVs :: Bool   -- Thunk
-         -> DmdEnv -> (DmdEnv, DmdEnv)
-splitFVs is_thunk rhs_fvs
-  | is_thunk  = strictPairToTuple $
-                nonDetStrictFoldUFM_Directly add (emptyVarEnv :*: emptyVarEnv) rhs_fvs
-                -- It's OK to use a non-deterministic fold because we
-                -- immediately forget the ordering by putting the elements
-                -- in the envs again
-  | otherwise = partitionVarEnv isWeakDmd rhs_fvs
-  where
-    add uniq dmd@(JD { sd = s, ud = u }) (lazy_fv :*: sig_fv)
-      | Lazy <- s = addToUFM_Directly lazy_fv uniq dmd :*: sig_fv
-      | otherwise = addToUFM_Directly lazy_fv uniq (JD { sd = Lazy, ud = u })
-                    :*:
-                    addToUFM_Directly sig_fv  uniq (JD { sd = s,    ud = Abs })
-
 keepAliveDmdEnv :: DmdEnv -> IdSet -> DmdEnv
 -- (keepAliveDmdType dt vs) makes sure that the Ids in vs have
 -- /some/ usage in the returned demand types -- they are not Absent
@@ -842,11 +826,6 @@ splitProdDmd_maybe (JD { sd = s, ud = u })
       (Lazy,  Use _ (UProd ux)) -> Just (mkJointDmds (replicate (length ux) Lazy) ux)
       _ -> Nothing
 
-data StrictPair a b = !a :*: !b
-
-strictPairToTuple :: StrictPair a b -> (a, b)
-strictPairToTuple (x :*: y) = (x, y)
-
 {- *********************************************************************
 *                                                                      *
                TypeShape and demand trimming



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

-- 
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/01cf781b4ef8210f4270a31dffd66558a05268a8
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/20201024/b74c465d/attachment-0001.html>


More information about the ghc-commits mailing list