[Git][ghc/ghc][master] Don't override proc CafInfos in ticky builds

Marge Bot gitlab at gitlab.haskell.org
Mon Apr 6 17:16:18 UTC 2020



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


Commits:
dcfe29c8 by Ömer Sinan Ağacan at 2020-04-06T13:16:08-04:00
Don't override proc CafInfos in ticky builds

Fixes #17947

When we have a ticky label for a proc, IdLabels for the ticky counter
and proc entry share the same Name. This caused overriding proc CafInfos
with the ticky CafInfos (i.e. NoCafRefs) during SRT analysis.

We now ignore the ticky labels when building SRTMaps. This makes sense
because:

- When building the current module they don't need to be in SRTMaps as
  they're initialized as non-CAFFY (see mkRednCountsLabel), so they
  don't take part in the dependency analysis and they're never added to
  SRTs.

  (Reminder: a "dependency" in the SRT analysis is a CAFFY dependency,
  non-CAFFY uses are not considered as dependencies for the algorithm)

- They don't appear in the interfaces as they're not exported, so it
  doesn't matter for cross-module concerns whether they're in the SRTMap
  or not.

See also the new Note [Ticky labels in SRT analysis].

- - - - -


2 changed files:

- compiler/GHC/Cmm/CLabel.hs
- compiler/GHC/Cmm/Info/Build.hs


Changes:

=====================================
compiler/GHC/Cmm/CLabel.hs
=====================================
@@ -108,7 +108,7 @@ module GHC.Cmm.CLabel (
         pprCLabel,
         isInfoTableLabel,
         isConInfoTableLabel,
-        isIdLabel
+        isIdLabel, isTickyLabel
     ) where
 
 #include "HsVersions.h"
@@ -268,6 +268,12 @@ isIdLabel :: CLabel -> Bool
 isIdLabel IdLabel{} = True
 isIdLabel _ = False
 
+-- Used in SRT analysis. See Note [Ticky labels in SRT analysis] in
+-- GHC.Cmm.Info.Build.
+isTickyLabel :: CLabel -> Bool
+isTickyLabel (IdLabel _ _ RednCounts) = True
+isTickyLabel _ = False
+
 -- This is laborious, but necessary. We can't derive Ord because
 -- Unique doesn't have an Ord instance. Note nonDetCmpUnique in the
 -- implementation. See Note [No Ord for Unique]
@@ -462,8 +468,7 @@ mkSRTLabel     :: Unique -> CLabel
 mkSRTLabel u = SRTLabel u
 
 mkRednCountsLabel :: Name -> CLabel
-mkRednCountsLabel       name    =
-  IdLabel name NoCafRefs RednCounts  -- Note [ticky for LNE]
+mkRednCountsLabel name = IdLabel name NoCafRefs RednCounts  -- Note [ticky for LNE]
 
 -- These have local & (possibly) external variants:
 mkLocalClosureLabel      :: Name -> CafInfo -> CLabel


=====================================
compiler/GHC/Cmm/Info/Build.hs
=====================================
@@ -409,6 +409,30 @@ Maybe, but could you prove that RET_FUN is the only way that
 resurrection can occur?
 
 So, no shortcutting.
+
+Note [Ticky labels in SRT analysis]
+~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~
+
+Raw Cmm data (CmmStaticsRaw) can't contain pointers so they're considered
+non-CAFFY in SRT analysis and we update the SRTMap mapping them to `Nothing`
+(meaning they're not CAFFY).
+
+However when building with -ticky we generate ticky CLabels using the function's
+`Name`. For example, if we have a top-level function `sat_s1rQ`, in a ticky
+build we get two IdLabels using the name `sat_s1rQ`:
+
+- For the function itself: IdLabel sat_s1rQ ... Entry
+- For the ticky counter: IdLabel sat_s1rQ ... RednCounts
+
+In these cases we really want to use the function definition for the SRT
+analysis of this Name, because that's what we export for this Name -- ticky
+counters are not exported. So we ignore ticky counters in SRT analysis (which
+are never CAFFY and never exported).
+
+Not doing this caused #17947 where we analysed the function first mapped the
+name to CAFFY. We then saw the ticky constructor, and becuase it has the same
+Name as the function and is not CAFFY we overrode the CafInfo of the name as
+non-CAFFY.
 -}
 
 -- ---------------------------------------------------------------------
@@ -818,8 +842,11 @@ doSRTs dflags moduleSRTInfo procs data_ = do
                       -- already updated by oneSRT
                       srtMap
                     CmmData _ (CmmStaticsRaw lbl _)
-                      | isIdLabel lbl ->
-                          -- not analysed by oneSRT, declare it non-CAFFY here
+                      | isIdLabel lbl && not (isTickyLabel lbl) ->
+                          -- Raw data are not analysed by oneSRT and they can't
+                          -- be CAFFY.
+                          -- See Note [Ticky labels in SRT analysis] above for
+                          -- why we exclude ticky labels here.
                           Map.insert (mkCAFLabel lbl) Nothing srtMap
                       | otherwise ->
                           -- Not an IdLabel, ignore



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

-- 
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/dcfe29c8520244764146c7a5f336be1f9700db6c
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/20200406/8d7b0628/attachment-0001.html>


More information about the ghc-commits mailing list