[Git][ghc/ghc][wip/nonmoving-fixes] 7 commits: rts/Messages: Add missing write barrier in THROWTO message update

Ben Gamari gitlab at gitlab.haskell.org
Fri Nov 27 03:26:44 UTC 2020



Ben Gamari pushed to branch wip/nonmoving-fixes at Glasgow Haskell Compiler / GHC


Commits:
ced673a4 by GHC GitLab CI at 2020-11-27T03:26:18+00:00
rts/Messages: Add missing write barrier in THROWTO message update

After a THROWTO message has been handle the message closure is
overwritten by a NULL message. We must ensure that the original
closure's pointers continue to be visible to the nonmoving GC.

- - - - -
cf1792ec by GHC GitLab CI at 2020-11-27T03:26:18+00:00
nonmoving: Add missing write barrier in shrinkSmallByteArray

- - - - -
142e8844 by GHC GitLab CI at 2020-11-27T03:26:18+00:00
Updates: Don't zero slop until closure has been pushed

Ensure that the the free variables have been pushed to the update
remembered set before we zero the slop.

- - - - -
ec086bfa by GHC GitLab CI at 2020-11-27T03:26:18+00:00
OSThreads: Fix error code checking

pthread_join returns its error code and apparently doesn't set errno.

- - - - -
b62bd8f8 by GHC GitLab CI at 2020-11-27T03:26:18+00:00
nonmoving: Don't join to mark_thread on shutdown

The mark thread is not joinable as we detach from it on creation.

- - - - -
75578ed3 by Ben Gamari at 2020-11-27T03:26:18+00:00
nonmoving: Add reference to Ueno 2016

- - - - -
4f77bcc8 by GHC GitLab CI at 2020-11-27T03:26:18+00:00
nonmoving: Ensure that evacuated large objects are marked

See Note [Non-moving GC: Marking evacuated objects].

- - - - -


8 changed files:

- rts/Messages.c
- rts/Messages.h
- rts/PrimOps.cmm
- rts/RaiseAsync.c
- rts/Updates.h
- rts/posix/OSThreads.c
- rts/sm/Evac.c
- rts/sm/NonMoving.c


Changes:

=====================================
rts/Messages.c
=====================================
@@ -97,7 +97,7 @@ loop:
         case THROWTO_SUCCESS: {
             // this message is done
             StgTSO *source = t->source;
-            doneWithMsgThrowTo(t);
+            doneWithMsgThrowTo(cap, t);
             tryWakeupThread(cap, source);
             break;
         }


=====================================
rts/Messages.h
=====================================
@@ -23,8 +23,16 @@ void sendMessage    (Capability *from_cap, Capability *to_cap, Message *msg);
 #include "SMPClosureOps.h"
 
 INLINE_HEADER void
-doneWithMsgThrowTo (MessageThrowTo *m)
+doneWithMsgThrowTo (Capability *cap, MessageThrowTo *m)
 {
+    // The message better be locked
+    ASSERT(m->header.info == &stg_WHITEHOLE_info);
+    IF_NONMOVING_WRITE_BARRIER_ENABLED {
+      updateRemembSetPushClosure(cap, (StgClosure *) m->link);
+      updateRemembSetPushClosure(cap, (StgClosure *) m->source);
+      updateRemembSetPushClosure(cap, (StgClosure *) m->target);
+      updateRemembSetPushClosure(cap, (StgClosure *) m->exception);
+    }
     OVERWRITING_CLOSURE((StgClosure*)m);
     unlockClosure((StgClosure*)m, &stg_MSG_NULL_info);
     LDV_RECORD_CREATE(m);


=====================================
rts/PrimOps.cmm
=====================================
@@ -227,6 +227,21 @@ stg_shrinkSmallMutableArrayzh ( gcptr mba, W_ new_size )
 {
    ASSERT(new_size <= StgSmallMutArrPtrs_ptrs(mba));
 
+   IF_NONMOVING_WRITE_BARRIER_ENABLED {
+     // Ensure that the elements we are about to shrink out of existence
+     // remain visible to the non-moving collector.
+     W_ p, end;
+     p = mba + SIZEOF_StgSmallMutArrPtrs + WDS(new_size);
+     end = mba + SIZEOF_StgSmallMutArrPtrs + WDS(StgSmallMutArrPtrs_ptrs(mba));
+again:
+     ccall updateRemembSetPushClosure_(BaseReg "ptr",
+                                       W_[p] "ptr");
+     if (p < end) {
+       p = p + SIZEOF_W;
+       goto again;
+     }
+   }
+
    OVERWRITING_CLOSURE_MUTABLE(mba, (BYTES_TO_WDS(SIZEOF_StgSmallMutArrPtrs) +
                                      new_size));
    StgSmallMutArrPtrs_ptrs(mba) = new_size;


=====================================
rts/RaiseAsync.c
=====================================
@@ -336,7 +336,7 @@ check_target:
         }
 
         // nobody else can wake up this TSO after we claim the message
-        doneWithMsgThrowTo(m);
+        doneWithMsgThrowTo(cap, m);
 
         raiseAsync(cap, target, msg->exception, false, NULL);
         return THROWTO_SUCCESS;
@@ -580,7 +580,7 @@ maybePerformBlockedException (Capability *cap, StgTSO *tso)
 
         throwToSingleThreaded(cap, msg->target, msg->exception);
         source = msg->source;
-        doneWithMsgThrowTo(msg);
+        doneWithMsgThrowTo(cap, msg);
         tryWakeupThread(cap, source);
         return 1;
     }
@@ -602,7 +602,7 @@ awakenBlockedExceptionQueue (Capability *cap, StgTSO *tso)
         i = lockClosure((StgClosure *)msg);
         if (i != &stg_MSG_NULL_info) {
             source = msg->source;
-            doneWithMsgThrowTo(msg);
+            doneWithMsgThrowTo(cap, msg);
             tryWakeupThread(cap, source);
         } else {
             unlockClosure((StgClosure *)msg,i);
@@ -700,7 +700,7 @@ removeFromQueues(Capability *cap, StgTSO *tso)
       // ASSERT(m->header.info == &stg_WHITEHOLE_info);
 
       // unlock and revoke it at the same time
-      doneWithMsgThrowTo(m);
+      doneWithMsgThrowTo(cap, m);
       break;
   }
 


=====================================
rts/Updates.h
=====================================
@@ -49,7 +49,6 @@
     W_ bd;                                                      \
                                                                 \
     prim_write_barrier;                                         \
-    OVERWRITING_CLOSURE(p1);                                    \
     bd = Bdescr(p1);                                            \
     if (bdescr_gen_no(bd) != 0 :: bits16) {                     \
       IF_NONMOVING_WRITE_BARRIER_ENABLED {                      \
@@ -60,6 +59,7 @@
     } else {                                                    \
       TICK_UPD_NEW_IND();                                       \
     }                                                           \
+    OVERWRITING_CLOSURE(p1);                                    \
     StgInd_indirectee(p1) = p2;                                 \
     prim_write_barrier;                                         \
     SET_INFO(p1, stg_BLACKHOLE_info);                           \


=====================================
rts/posix/OSThreads.c
=====================================
@@ -401,8 +401,9 @@ interruptOSThread (OSThreadId id)
 void
 joinOSThread (OSThreadId id)
 {
-    if (pthread_join(id, NULL) != 0) {
-        sysErrorBelch("joinOSThread: error %d", errno);
+    int ret = pthread_join(id, NULL);
+    if (ret != 0) {
+        sysErrorBelch("joinOSThread: error %d", ret);
     }
 }
 


=====================================
rts/sm/Evac.c
=====================================
@@ -109,6 +109,8 @@ alloc_for_copy (uint32_t size, uint32_t gen_no)
             //
             // However, if we are in a deadlock detection GC then we disable aging
             // so there is no need.
+            //
+            // See Note [Non-moving GC: Marking evacuated objects].
             if (major_gc && !deadlock_detect_gc)
                 markQueuePushClosureGC(&gct->cap->upd_rem_set.queue, (StgClosure *) to);
             return to;
@@ -134,6 +136,52 @@ alloc_for_copy (uint32_t size, uint32_t gen_no)
    The evacuate() code
    -------------------------------------------------------------------------- */
 
+/*
+ * Note [Non-moving GC: Marking evacuated objects]
+ * ~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~
+ *
+ * When the non-moving collector is in use we must be careful to ensure that any
+ * references to objects in the non-moving generation from younger generations
+ * are pushed to the mark queue.
+ *
+ * In particular we need to ensure that we handle newly-promoted objects are
+ * correctly marked. For instance, consider this case:
+ *
+ *     generation 0                          generation 1
+ *    ──────────────                        ──────────────
+ *
+ *                                            ┌───────┐
+ *      ┌───────┐                             │   A   │
+ *      │   B   │ ◁────────────────────────── │       │
+ *      │       │ ──┬─────────────────┐       └───────┘
+ *      └───────┘   ┆        after GC │
+ *                  ┆                 │
+ *      ┌───────┐   ┆ before GC       │       ┌───────┐
+ *      │   C   │ ◁┄┘                 └─────▷ │   C'  │
+ *      │       │                             │       │
+ *      └───────┘                             └───────┘
+ *
+ *
+ * In this case object C started off in generation 0 and was evacuated into
+ * generation 1 during the preparatory GC. However, the only reference to C'
+ * is from B, which lives in the generation 0 (via aging); this reference will
+ * not be visible to the concurrent non-moving collector (which can only
+ * traverse the generation 1 heap). Consequently, upon evacuating C we need to
+ * ensure that C' is added to the update remembered set as we know that it will
+ * continue to be reachable via B (which is assumed to be reachable as it lives
+ * in a younger generation).
+ *
+ * Where this happens depends upon the type of the object (e.g. C'):
+ *
+ *  - In the case of "normal" small heap-allocated objects this happens in
+ *    alloc_for_copy.
+ *  - In the case of compact region this happens in evacuate_compact.
+ *  - In the case of large objects this happens in evacuate_large.
+ *
+ * See also Note [Aging under the non-moving collector] in NonMoving.c.
+ *
+ */
+
 /* size is in words */
 STATIC_INLINE GNUC_ATTR_HOT void
 copy_tag(StgClosure **p, const StgInfoTable *info,
@@ -351,6 +399,9 @@ evacuate_large(StgPtr p)
   __atomic_fetch_or(&bd->flags, BF_EVACUATED, __ATOMIC_ACQ_REL);
   if (RTS_UNLIKELY(RtsFlags.GcFlags.useNonmoving && new_gen == oldest_gen)) {
       __atomic_fetch_or(&bd->flags, BF_NONMOVING, __ATOMIC_ACQ_REL);
+
+      // See Note [Non-moving GC: Marking evacuated objects].
+      markQueuePushClosureGC(&gct->cap->upd_rem_set.queue, p);
   }
   initBdescr(bd, new_gen, new_gen->to);
 
@@ -505,6 +556,9 @@ evacuate_compact (StgPtr p)
     bd->flags |= BF_EVACUATED;
     if (RTS_UNLIKELY(RtsFlags.GcFlags.useNonmoving && new_gen == oldest_gen)) {
       __atomic_fetch_or(&bd->flags, BF_NONMOVING, __ATOMIC_RELAXED);
+
+      // See Note [Non-moving GC: Marking evacuated objects].
+      markQueuePushClosureGC(&gct->cap->upd_rem_set.queue, (StgClosure *) str);
     }
     initBdescr(bd, new_gen, new_gen->to);
 
@@ -690,13 +744,6 @@ loop:
        */
       if (flags & BF_LARGE) {
           evacuate_large((P_)q);
-
-          // We may have evacuated the block to the nonmoving generation. If so
-          // we need to make sure it is added to the mark queue since the only
-          // reference to it may be from the moving heap.
-          if (major_gc && flags & BF_NONMOVING && !deadlock_detect_gc) {
-              markQueuePushClosureGC(&gct->cap->upd_rem_set.queue, q);
-          }
           return;
       }
 


=====================================
rts/sm/NonMoving.c
=====================================
@@ -191,8 +191,8 @@ Mutex concurrent_coll_finished_lock;
  * === Other references ===
  *
  * Apart from the design document in docs/storage/nonmoving-gc and the Ueno
- * 2016 paper (TODO citation) from which it drew inspiration, there are a
- * variety of other relevant Notes scattered throughout the tree:
+ * 2016 paper [ueno 2016] from which it drew inspiration, there are a variety
+ * of other relevant Notes scattered throughout the tree:
  *
  *  - Note [Concurrent non-moving collection] (NonMoving.c) describes
  *    concurrency control of the nonmoving collector
@@ -204,6 +204,10 @@ Mutex concurrent_coll_finished_lock;
  *  - Note [Aging under the non-moving collector] (NonMoving.c) describes how
  *    we accommodate aging
  *
+ *  - Note [Non-moving GC: Marking evacuated objects] (Evac.c) describes how
+ *    non-moving objects reached by evacuate() are marked, which is necessary
+ *    due to aging.
+ *
  *  - Note [Large objects in the non-moving collector] (NonMovingMark.c)
  *    describes how we track large objects.
  *
@@ -232,6 +236,11 @@ Mutex concurrent_coll_finished_lock;
  *    how we use the DIRTY flags associated with MUT_VARs and TVARs to improve
  *    barrier efficiency.
  *
+ * [ueno 2016]:
+ *   Katsuhiro Ueno and Atsushi Ohori. 2016. A fully concurrent garbage
+ *   collector for functional programs on multicore processors. SIGPLAN Not. 51,
+ *   9 (September 2016), 421–433. DOI:https://doi.org/10.1145/3022670.2951944
+ *
  *
  * Note [Concurrent non-moving collection]
  * ~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~
@@ -312,6 +321,8 @@ Mutex concurrent_coll_finished_lock;
  *
  *     The non-moving collector will come to C in the mark queue and mark it.
  *
+ * The implementation details of this are described in Note [Non-moving GC:
+ * Marking evacuated objects] in Evac.c.
  *
  * Note [Deadlock detection under the non-moving collector]
  * ~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~
@@ -726,7 +737,6 @@ void nonmovingStop(void)
                    "waiting for nonmoving collector thread to terminate");
         ACQUIRE_LOCK(&concurrent_coll_finished_lock);
         waitCondition(&concurrent_coll_finished, &concurrent_coll_finished_lock);
-        joinOSThread(mark_thread);
     }
 #endif
 }



View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/d13e4c8f335ab8cac8b68790686f79f1c9c2b5b0...4f77bcc8276f9b81698aa7da3b2ae681ba76d800

-- 
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/d13e4c8f335ab8cac8b68790686f79f1c9c2b5b0...4f77bcc8276f9b81698aa7da3b2ae681ba76d800
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/20201126/516b25af/attachment-0001.html>


More information about the ghc-commits mailing list