[Git][ghc/ghc][master] 3 commits: Cleanup OVERWRITING_CLOSURE logic

Marge Bot gitlab at gitlab.haskell.org
Mon Jun 1 10:33:07 UTC 2020



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


Commits:
2ee4f36c by Daniel Gröber at 2020-06-01T06:32:56-04:00
Cleanup OVERWRITING_CLOSURE logic

The code is just more confusing than it needs to be. We don't need to mix
the threaded check with the ldv profiling check since ldv's init already
checks for this. Hence they can be two separate checks. Taking the sanity
checking into account is also cleaner via DebugFlags.sanity. No need for
checking the DEBUG define.

The ZERO_SLOP_FOR_LDV_PROF and ZERO_SLOP_FOR_SANITY_CHECK definitions the
old code had also make things a lot more opaque IMO so I removed those.

- - - - -
6159559b by Daniel Gröber at 2020-06-01T06:32:56-04:00
Fix OVERWRITING_CLOSURE assuming closures are not inherently used

The new ASSERT in LDV_recordDead() was being tripped up by MVars when
removeFromMVarBlockedQueue() calls OVERWRITING_CLOSURE() via
OVERWRITE_INFO().

- - - - -
38992085 by Daniel Gröber at 2020-06-01T06:32:56-04:00
Always zero shrunk mutable array slop when profiling

When shrinking arrays in the profiling way we currently don't always zero
the leftover slop. This means we can't traverse such closures in the heap
profiler. The old Note [zeroing slop] and #8402 have some rationale for why
this is so but I belive the reasoning doesn't apply to mutable
closures. There users already have to ensure multiple threads don't step on
each other's toes so zeroing should be safe.

- - - - -


5 changed files:

- includes/Cmm.h
- includes/Rts.h
- includes/rts/storage/ClosureMacros.h
- rts/PrimOps.cmm
- rts/sm/Storage.c


Changes:

=====================================
includes/Cmm.h
=====================================
@@ -623,14 +623,14 @@
 #define mutArrPtrCardUp(i)   (((i) + mutArrCardMask) >> MUT_ARR_PTRS_CARD_BITS)
 #define mutArrPtrsCardWords(n) ROUNDUP_BYTES_TO_WDS(mutArrPtrCardUp(n))
 
-#if defined(PROFILING) || (!defined(THREADED_RTS) && defined(DEBUG))
+#if defined(PROFILING) || defined(DEBUG)
 #define OVERWRITING_CLOSURE_SIZE(c, size) foreign "C" overwritingClosureSize(c "ptr", size)
 #define OVERWRITING_CLOSURE(c) foreign "C" overwritingClosure(c "ptr")
-#define OVERWRITING_CLOSURE_OFS(c,n) foreign "C" overwritingClosureOfs(c "ptr", n)
+#define OVERWRITING_CLOSURE_MUTABLE(c, off) foreign "C" overwritingMutableClosureOfs(c "ptr", off)
 #else
 #define OVERWRITING_CLOSURE_SIZE(c, size) /* nothing */
 #define OVERWRITING_CLOSURE(c) /* nothing */
-#define OVERWRITING_CLOSURE_OFS(c,n) /* nothing */
+#define OVERWRITING_CLOSURE_MUTABLE(c, off) /* nothing */
 #endif
 
 // Memory barriers.


=====================================
includes/Rts.h
=====================================
@@ -184,6 +184,9 @@ void _assertFail(const char *filename, unsigned int linenum)
 /* Global constraints */
 #include "rts/Constants.h"
 
+/* Runtime flags */
+#include "rts/Flags.h"
+
 /* Profiling information */
 #include "rts/prof/CCS.h"
 #include "rts/prof/LDV.h"
@@ -214,7 +217,6 @@ void _assertFail(const char *filename, unsigned int linenum)
 #include "rts/Signals.h"
 #include "rts/BlockSignals.h"
 #include "rts/Hpc.h"
-#include "rts/Flags.h"
 #include "rts/Adjustor.h"
 #include "rts/FileLock.h"
 #include "rts/GetTime.h"


=====================================
includes/rts/storage/ClosureMacros.h
=====================================
@@ -510,24 +510,16 @@ INLINE_HEADER StgWord8 *mutArrPtrsCard (StgMutArrPtrs *a, W_ n)
 
    -------------------------------------------------------------------------- */
 
-#if defined(PROFILING)
-#define ZERO_SLOP_FOR_LDV_PROF 1
+#if defined(PROFILING) || defined(DEBUG)
+#define OVERWRITING_CLOSURE(c) \
+    overwritingClosure(c)
+#define OVERWRITING_CLOSURE_MUTABLE(c, off) \
+    overwritingMutableClosureOfs(c, off)
 #else
-#define ZERO_SLOP_FOR_LDV_PROF 0
-#endif
-
-#if defined(DEBUG) && !defined(THREADED_RTS)
-#define ZERO_SLOP_FOR_SANITY_CHECK 1
-#else
-#define ZERO_SLOP_FOR_SANITY_CHECK 0
-#endif
-
-#if ZERO_SLOP_FOR_LDV_PROF || ZERO_SLOP_FOR_SANITY_CHECK
-#define OVERWRITING_CLOSURE(c) overwritingClosure(c)
-#define OVERWRITING_CLOSURE_OFS(c,n) overwritingClosureOfs(c,n)
-#else
-#define OVERWRITING_CLOSURE(c) /* nothing */
-#define OVERWRITING_CLOSURE_OFS(c,n) /* nothing */
+#define OVERWRITING_CLOSURE(c) \
+    do { (void) sizeof(c); } while(0)
+#define OVERWRITING_CLOSURE_MUTABLE(c, off) \
+    do { (void) sizeof(c); (void) sizeof(off); } while(0)
 #endif
 
 #if defined(PROFILING)
@@ -535,22 +527,57 @@ void LDV_recordDead (const StgClosure *c, uint32_t size);
 RTS_PRIVATE bool isInherentlyUsed ( StgHalfWord closure_type );
 #endif
 
-EXTERN_INLINE void overwritingClosure_ (StgClosure *p,
-                                        uint32_t offset /* in words */,
-                                        uint32_t size /* closure size, in words */,
-                                        bool inherently_used USED_IF_PROFILING
-                                        );
-EXTERN_INLINE void overwritingClosure_ (StgClosure *p, uint32_t offset, uint32_t size, bool inherently_used USED_IF_PROFILING)
+EXTERN_INLINE void
+zeroSlop (
+    StgClosure *p,
+    uint32_t offset, /*< offset to start zeroing at, in words */
+    uint32_t size,   /*< total closure size, in words */
+    bool known_mutable /*< is this a closure who's slop we can always zero? */
+    );
+
+EXTERN_INLINE void
+zeroSlop (StgClosure *p, uint32_t offset, uint32_t size, bool known_mutable)
 {
-#if ZERO_SLOP_FOR_LDV_PROF && !ZERO_SLOP_FOR_SANITY_CHECK
     // see Note [zeroing slop when overwriting closures], also #8402
-    if (era <= 0) return;
+
+    const bool want_to_zero_immutable_slop = false
+        // Sanity checking (-DS) is enabled
+        || RTS_DEREF(RtsFlags).DebugFlags.sanity
+#if defined(PROFILING)
+        // LDV profiler is enabled
+        || era > 0
 #endif
+        ;
+
+    const bool can_zero_immutable_slop =
+        // Only if we're running single threaded.
+        RTS_DEREF(RtsFlags).ParFlags.nCapabilities <= 1;
+
+    const bool zero_slop_immutable =
+        want_to_zero_immutable_slop && can_zero_immutable_slop;
 
-    // For LDV profiling, we need to record the closure as dead
+    const bool zero_slop_mutable =
 #if defined(PROFILING)
-    if (!inherently_used) { LDV_recordDead(p, size); };
+        // Always zero mutable closure slop when profiling. We do this to cover
+        // the case of shrinking mutable arrays in pinned blocks for the heap
+        // profiler, see Note [skipping slop in the heap profiler]
+        //
+        // TODO: We could make this check more specific and only zero if the
+        // object is in a BF_PINNED bdescr here. Update Note [slop on the heap]
+        // and [zeroing slop when overwriting closures] if you change this.
+        true
+#else
+        zero_slop_immutable
 #endif
+        ;
+
+    const bool zero_slop =
+        // If we're not sure this is a mutable closure treat it like an
+        // immutable one.
+        known_mutable ? zero_slop_mutable : zero_slop_immutable;
+
+    if(!zero_slop)
+        return;
 
     for (uint32_t i = offset; i < size; i++) {
         ((StgWord *)p)[i] = 0;
@@ -560,22 +587,23 @@ EXTERN_INLINE void overwritingClosure_ (StgClosure *p, uint32_t offset, uint32_t
 EXTERN_INLINE void overwritingClosure (StgClosure *p);
 EXTERN_INLINE void overwritingClosure (StgClosure *p)
 {
+    W_ size = closure_sizeW(p);
 #if defined(PROFILING)
-    ASSERT(!isInherentlyUsed(get_itbl(p)->type));
+    if(era > 0 && !isInherentlyUsed(get_itbl(p)->type))
+        LDV_recordDead(p, size);
 #endif
-    overwritingClosure_(p, sizeofW(StgThunkHeader), closure_sizeW(p),
-                        /*inherently_used=*/false);
+    zeroSlop(p, sizeofW(StgThunkHeader), size, /*known_mutable=*/false);
 }
 
 // Version of 'overwritingClosure' which overwrites only a suffix of a
 // closure.  The offset is expressed in words relative to 'p' and shall
 // be less than or equal to closure_sizeW(p), and usually at least as
 // large as the respective thunk header.
-//
-// Note: As this calls LDV_recordDead() you have to call LDV_RECORD_CREATE()
-//       on the final state of the closure at the call-site
-EXTERN_INLINE void overwritingClosureOfs (StgClosure *p, uint32_t offset);
-EXTERN_INLINE void overwritingClosureOfs (StgClosure *p, uint32_t offset)
+EXTERN_INLINE void
+overwritingMutableClosureOfs (StgClosure *p, uint32_t offset);
+
+EXTERN_INLINE void
+overwritingMutableClosureOfs (StgClosure *p, uint32_t offset)
 {
     // Since overwritingClosureOfs is only ever called by:
     //
@@ -583,18 +611,24 @@ EXTERN_INLINE void overwritingClosureOfs (StgClosure *p, uint32_t offset)
     //
     //   - shrinkSmallMutableArray# (SMALL_MUT_ARR_PTRS)
     //
-    // we can safely set inherently_used = true, which means LDV_recordDead
-    // won't be invoked below. Since these closures are inherenlty used we don't
-    // need to track their destruction.
-    overwritingClosure_(p, offset, closure_sizeW(p), /*inherently_used=*/true);
+    // we can safely omit the Ldv_recordDead call. Since these closures are
+    // considered inherenlty used we don't need to track their destruction.
+#if defined(PROFILING)
+    ASSERT(isInherentlyUsed(get_itbl(p)->type) == true);
+#endif
+    zeroSlop(p, offset, closure_sizeW(p), /*known_mutable=*/true);
 }
 
 // Version of 'overwritingClosure' which takes closure size as argument.
 EXTERN_INLINE void overwritingClosureSize (StgClosure *p, uint32_t size /* in words */);
 EXTERN_INLINE void overwritingClosureSize (StgClosure *p, uint32_t size)
 {
+    // This function is only called from stg_AP_STACK so we can assume it's not
+    // inherently used.
 #if defined(PROFILING)
-    ASSERT(!isInherentlyUsed(get_itbl(p)->type));
+    ASSERT(isInherentlyUsed(get_itbl(p)->type) == false);
+    if(era > 0)
+        LDV_recordDead(p, size);
 #endif
-    overwritingClosure_(p, sizeofW(StgThunkHeader), size, /*inherently_used=*/false);
+    zeroSlop(p, sizeofW(StgThunkHeader), size, /*known_mutable=*/false);
 }


=====================================
rts/PrimOps.cmm
=====================================
@@ -175,8 +175,8 @@ stg_shrinkMutableByteArrayzh ( gcptr mba, W_ new_size )
 {
    ASSERT(new_size <= StgArrBytes_bytes(mba));
 
-   OVERWRITING_CLOSURE_OFS(mba, (BYTES_TO_WDS(SIZEOF_StgArrBytes) +
-                                 ROUNDUP_BYTES_TO_WDS(new_size)));
+   OVERWRITING_CLOSURE_MUTABLE(mba, (BYTES_TO_WDS(SIZEOF_StgArrBytes) +
+                                     ROUNDUP_BYTES_TO_WDS(new_size)));
    StgArrBytes_bytes(mba) = new_size;
    // No need to call LDV_RECORD_CREATE. See Note [LDV profiling and resizing arrays]
 
@@ -199,8 +199,8 @@ stg_resizzeMutableByteArrayzh ( gcptr mba, W_ new_size )
    new_size_wds = ROUNDUP_BYTES_TO_WDS(new_size);
 
    if (new_size_wds <= BYTE_ARR_WDS(mba)) {
-      OVERWRITING_CLOSURE_OFS(mba, (BYTES_TO_WDS(SIZEOF_StgArrBytes) +
-                                    new_size_wds));
+      OVERWRITING_CLOSURE_MUTABLE(mba, (BYTES_TO_WDS(SIZEOF_StgArrBytes) +
+                                        new_size_wds));
       StgArrBytes_bytes(mba) = new_size;
       // No need to call LDV_RECORD_CREATE. See Note [LDV profiling and resizing arrays]
 
@@ -228,8 +228,8 @@ stg_shrinkSmallMutableArrayzh ( gcptr mba, W_ new_size )
 {
    ASSERT(new_size <= StgSmallMutArrPtrs_ptrs(mba));
 
-   OVERWRITING_CLOSURE_OFS(mba, (BYTES_TO_WDS(SIZEOF_StgSmallMutArrPtrs) +
-                                 new_size));
+   OVERWRITING_CLOSURE_MUTABLE(mba, (BYTES_TO_WDS(SIZEOF_StgSmallMutArrPtrs) +
+                                     new_size));
    StgSmallMutArrPtrs_ptrs(mba) = new_size;
    // No need to call LDV_RECORD_CREATE. See Note [LDV profiling and resizing arrays]
 


=====================================
rts/sm/Storage.c
=====================================
@@ -948,7 +948,7 @@ accountAllocation(Capability *cap, W_ n)
  *
  * When profiling we zero:
  *  - Pinned object alignment slop, see MEMSET_IF_PROFILING_W in allocatePinned.
- *  - Shrunk array slop, see OVERWRITING_MUTABLE_CLOSURE.
+ *  - Shrunk array slop, see OVERWRITING_CLOSURE_MUTABLE.
  *
  * When performing LDV profiling or using a (single threaded) debug RTS we zero
  * slop even when overwriting immutable closures, see Note [zeroing slop when



View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/6947231abd8c33840860ad51699b76efd4725f0e...389920858e0b9efe5234cb7dac55d06e955768f7

-- 
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/6947231abd8c33840860ad51699b76efd4725f0e...389920858e0b9efe5234cb7dac55d06e955768f7
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/20200601/afcbf623/attachment-0001.html>


More information about the ghc-commits mailing list