[Git][ghc/ghc][master] DmdAnal: No need to attach a StrictSig to DataCon workers

Marge Bot gitlab at gitlab.haskell.org
Fri Apr 10 03:12:07 UTC 2020



 Marge Bot pushed to branch master at Glasgow Haskell Compiler / GHC


Commits:
f5212dfc by Sebastian Graf at 2020-04-09T23:11:57-04:00
DmdAnal: No need to attach a StrictSig to DataCon workers

In GHC.Types.Id.Make we were giving a strictness signature to every data
constructor wrapper Id that we weren't looking at in demand analysis
anyway. We used to use its CPR info, but that has its own CPR signature
now.

`Note [Data-con worker strictness]` then felt very out of place, so I
moved it to GHC.Core.DataCon.

- - - - -


5 changed files:

- compiler/GHC/Core/DataCon.hs
- compiler/GHC/Core/Op/DmdAnal.hs
- compiler/GHC/Core/Op/Simplify.hs
- compiler/GHC/Types/Demand.hs
- compiler/GHC/Types/Id/Make.hs


Changes:

=====================================
compiler/GHC/Core/DataCon.hs
=====================================
@@ -614,7 +614,7 @@ data DataConRep
                                  -- and *including* all evidence args
 
         , dcr_stricts :: [StrictnessMark]  -- 1-1 with dcr_arg_tys
-                -- See also Note [Data-con worker strictness] in GHC.Types.Id.Make
+                -- See also Note [Data-con worker strictness]
 
         , dcr_bangs :: [HsImplBang]  -- The actual decisions made (including failures)
                                      -- about the original arguments; 1-1 with orig_arg_tys
@@ -715,8 +715,26 @@ filterEqSpec eq_spec
 instance Outputable EqSpec where
   ppr (EqSpec tv ty) = ppr (tv, ty)
 
-{- Note [Bangs on data constructor arguments]
-~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~
+{- Note [Data-con worker strictness]
+~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~
+Notice that we do *not* say the worker Id is strict even if the data
+constructor is declared strict
+     e.g.    data T = MkT !(Int,Int)
+Why?  Because the *wrapper* $WMkT is strict (and its unfolding has case
+expressions that do the evals) but the *worker* MkT itself is not. If we
+pretend it is strict then when we see
+     case x of y -> MkT y
+the simplifier thinks that y is "sure to be evaluated" (because the worker MkT
+is strict) and drops the case.  No, the workerId MkT is not strict.
+
+However, the worker does have StrictnessMarks.  When the simplifier sees a
+pattern
+     case e of MkT x -> ...
+it uses the dataConRepStrictness of MkT to mark x as evaluated; but that's
+fine... dataConRepStrictness comes from the data con not from the worker Id.
+
+Note [Bangs on data constructor arguments]
+~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~
 Consider
   data T = MkT !Int {-# UNPACK #-} !Int Bool
 


=====================================
compiler/GHC/Core/Op/DmdAnal.hs
=====================================
@@ -454,7 +454,7 @@ dmdTransform :: AnalEnv         -- The strictness environment
 
 dmdTransform env var dmd
   | isDataConWorkId var                          -- Data constructor
-  = dmdTransformDataConSig (idArity var) (idStrictness var) dmd
+  = dmdTransformDataConSig (idArity var) dmd
 
   | gopt Opt_DmdTxDictSel (ae_dflags env),
     Just _ <- isClassOpId_maybe var -- Dictionary component selector


=====================================
compiler/GHC/Core/Op/Simplify.hs
=====================================
@@ -2758,7 +2758,7 @@ a case pattern.  This is *important*.  Consider
 
 We really must record that b is already evaluated so that we don't
 go and re-evaluate it when constructing the result.
-See Note [Data-con worker strictness] in GHC.Types.Id.Make
+See Note [Data-con worker strictness] in GHC.Core.DataCon
 
 NB: simplLamBndrs preserves this eval info
 


=====================================
compiler/GHC/Types/Demand.hs
=====================================
@@ -1666,17 +1666,15 @@ dmdTransformSig (StrictSig dmd_ty@(DmdType _ arg_ds _)) cd
   = postProcessUnsat (peelManyCalls (length arg_ds) cd) dmd_ty
     -- see Note [Demands from unsaturated function calls]
 
-dmdTransformDataConSig :: Arity -> StrictSig -> CleanDemand -> DmdType
+dmdTransformDataConSig :: Arity -> CleanDemand -> DmdType
 -- Same as dmdTransformSig but for a data constructor (worker),
 -- which has a special kind of demand transformer.
 -- If the constructor is saturated, we feed the demand on
 -- the result into the constructor arguments.
-dmdTransformDataConSig arity (StrictSig (DmdType _ _ con_res))
-                             (JD { sd = str, ud = abs })
+dmdTransformDataConSig arity (JD { sd = str, ud = abs })
   | Just str_dmds <- go_str arity str
   , Just abs_dmds <- go_abs arity abs
-  = DmdType emptyDmdEnv (mkJointDmds str_dmds abs_dmds) con_res
-                -- Must remember whether it's a product, hence con_res, not TopRes
+  = DmdType emptyDmdEnv (mkJointDmds str_dmds abs_dmds) topDiv
 
   | otherwise   -- Not saturated
   = nopDmdType


=====================================
compiler/GHC/Types/Id/Make.hs
=====================================
@@ -506,10 +506,9 @@ mkDataConWorkId wkr_name data_con
     tycon  = dataConTyCon data_con  -- The representation TyCon
     wkr_ty = dataConRepType data_con
 
-        ----------- Workers for data types --------------
+    ----------- Workers for data types --------------
     alg_wkr_info = noCafIdInfo
                    `setArityInfo`          wkr_arity
-                   `setStrictnessInfo`     wkr_sig
                    `setCprInfo`            mkCprSig wkr_arity (dataConCPR data_con)
                    `setUnfoldingInfo`      evaldUnfolding  -- Record that it's evaluated,
                                                            -- even if arity = 0
@@ -518,27 +517,7 @@ mkDataConWorkId wkr_name data_con
                      -- setNeverLevPoly
 
     wkr_arity = dataConRepArity data_con
-    wkr_sig   = mkClosedStrictSig (replicate wkr_arity topDmd) topDiv
-        --      Note [Data-con worker strictness]
-        -- Notice that we do *not* say the worker Id is strict
-        -- even if the data constructor is declared strict
-        --      e.g.    data T = MkT !(Int,Int)
-        -- Why?  Because the *wrapper* $WMkT is strict (and its unfolding has
-        -- case expressions that do the evals) but the *worker* MkT itself is
-        --  not. If we pretend it is strict then when we see
-        --      case x of y -> MkT y
-        -- the simplifier thinks that y is "sure to be evaluated" (because
-        -- the worker MkT is strict) and drops the case.  No, the workerId
-        -- MkT is not strict.
-        --
-        -- However, the worker does have StrictnessMarks.  When the simplifier
-        -- sees a pattern
-        --      case e of MkT x -> ...
-        -- it uses the dataConRepStrictness of MkT to mark x as evaluated;
-        -- but that's fine... dataConRepStrictness comes from the data con
-        -- not from the worker Id.
-
-        ----------- Workers for newtypes --------------
+    ----------- Workers for newtypes --------------
     univ_tvs = dataConUnivTyVars data_con
     arg_tys  = dataConRepArgTys  data_con  -- Should be same as dataConOrigArgTys
     nt_work_info = noCafIdInfo          -- The NoCaf-ness is set by noCafIdInfo



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

-- 
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/f5212dfc10414212e42247c2f2dcc45252f7e1d2
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/8687b5d6/attachment-0001.html>


More information about the ghc-commits mailing list