[Git][ghc/ghc][master] 2 commits: Add regression test for #17574

Marge Bot (@marge-bot) gitlab at gitlab.haskell.org
Sat Mar 25 04:03:43 UTC 2023



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


Commits:
43bd7694 by Teo Camarasu at 2023-03-25T00:03:24-04:00
Add regression test for #17574

This test currently fails in the nonmoving way

- - - - -
f2d56bf7 by Teo Camarasu at 2023-03-25T00:03:24-04:00
fix: account for large and compact object stats with nonmoving gc

Make sure that we keep track of the size of large and compact objects that have been moved onto the nonmoving heap.
We keep track of their size and add it to the amount of live bytes in nonmoving segments to get the total size of the live nonmoving heap.

Resolves #17574

- - - - -


8 changed files:

- rts/sm/NonMoving.c
- rts/sm/NonMoving.h
- rts/sm/NonMovingMark.c
- rts/sm/NonMovingMark.h
- rts/sm/Storage.c
- + testsuite/tests/rts/T17574.hs
- + testsuite/tests/rts/T17574.stdout
- testsuite/tests/rts/all.T


Changes:

=====================================
rts/sm/NonMoving.c
=====================================
@@ -395,7 +395,8 @@ Mutex concurrent_coll_finished_lock;
  * ~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~
  * The nonmoving collector uses an approximate heuristic for reporting live
  * data quantity. Specifically, during mark we record how much live data we
- * find in nonmoving_live_words. At the end of mark we declare this amount to
+ * find in nonmoving_segment_live_words. At the end of mark this is combined with nonmoving_large_words
+ * and nonmoving_compact_words, and we declare this amount to
  * be how much live data we have on in the nonmoving heap (by setting
  * oldest_gen->live_estimate).
  *
@@ -540,7 +541,7 @@ Mutex concurrent_coll_finished_lock;
  *
  */
 
-memcount nonmoving_live_words = 0;
+memcount nonmoving_segment_live_words = 0;
 
 // See Note [Sync phase marking budget].
 MarkBudget sync_phase_marking_budget = 200000;
@@ -682,10 +683,11 @@ static void nonmovingPrepareMark(void)
         dbl_link_onto(bd, &nonmoving_large_objects);
     }
     n_nonmoving_large_blocks += oldest_gen->n_large_blocks;
+    nonmoving_large_words += oldest_gen->n_large_words;
     oldest_gen->large_objects = NULL;
     oldest_gen->n_large_words = 0;
     oldest_gen->n_large_blocks = 0;
-    nonmoving_live_words = 0;
+    nonmoving_segment_live_words = 0;
 
     // Clear compact object mark bits
     for (bdescr *bd = nonmoving_compact_objects; bd; bd = bd->link) {
@@ -700,6 +702,7 @@ static void nonmovingPrepareMark(void)
         dbl_link_onto(bd, &nonmoving_compact_objects);
     }
     n_nonmoving_compact_blocks += oldest_gen->n_compact_blocks;
+    nonmoving_compact_words += oldest_gen->n_compact_blocks * BLOCK_SIZE_W;
     oldest_gen->n_compact_blocks = 0;
     oldest_gen->compact_objects = NULL;
     // TODO (osa): what about "in import" stuff??
@@ -1053,7 +1056,9 @@ concurrent_marking:
     freeMarkQueue(mark_queue);
     stgFree(mark_queue);
 
-    oldest_gen->live_estimate = nonmoving_live_words;
+    nonmoving_large_words = countOccupied(nonmoving_marked_large_objects);
+    nonmoving_compact_words = n_nonmoving_marked_compact_blocks * BLOCK_SIZE_W;
+    oldest_gen->live_estimate = nonmoving_segment_live_words + nonmoving_large_words + nonmoving_compact_words;
     oldest_gen->n_old_blocks = 0;
     resizeGenerations();
 


=====================================
rts/sm/NonMoving.h
=====================================
@@ -122,7 +122,7 @@ struct NonmovingHeap {
 
 extern struct NonmovingHeap nonmovingHeap;
 
-extern memcount nonmoving_live_words;
+extern memcount nonmoving_segment_live_words;
 
 #if defined(THREADED_RTS)
 extern bool concurrent_coll_running;


=====================================
rts/sm/NonMovingMark.c
=====================================
@@ -76,6 +76,10 @@ static bool is_nonmoving_weak(StgWeak *weak);
  * consequently will trace the pointers of only one object per block. However,
  * this is okay since the only type of pinned object supported by GHC is the
  * pinned ByteArray#, which has no pointers.
+ *
+ * We need to take care that the stats department is made aware of the amount of
+ * live large (and compact) objects, since they no longer live on gen[i]->large_objects.
+ * Failing to do so caused #17574.
  */
 
 bdescr *nonmoving_large_objects = NULL;
@@ -83,6 +87,9 @@ bdescr *nonmoving_marked_large_objects = NULL;
 memcount n_nonmoving_large_blocks = 0;
 memcount n_nonmoving_marked_large_blocks = 0;
 
+memcount nonmoving_large_words = 0;
+memcount nonmoving_compact_words = 0;
+
 bdescr *nonmoving_compact_objects = NULL;
 bdescr *nonmoving_marked_compact_objects = NULL;
 memcount n_nonmoving_compact_blocks = 0;
@@ -1745,7 +1752,7 @@ mark_closure (MarkQueue *queue, const StgClosure *p0, StgClosure **origin)
         struct NonmovingSegment *seg = nonmovingGetSegment((StgPtr) p);
         nonmoving_block_idx block_idx = nonmovingGetBlockIdx((StgPtr) p);
         nonmovingSetMark(seg, block_idx);
-        nonmoving_live_words += nonmovingSegmentBlockSize(seg) / sizeof(W_);
+        nonmoving_segment_live_words += nonmovingSegmentBlockSize(seg) / sizeof(W_);
     }
 
     // If we found a indirection to shortcut keep going.


=====================================
rts/sm/NonMovingMark.h
=====================================
@@ -127,6 +127,11 @@ extern bdescr *nonmoving_large_objects, *nonmoving_marked_large_objects,
 extern memcount n_nonmoving_large_blocks, n_nonmoving_marked_large_blocks,
                 n_nonmoving_compact_blocks, n_nonmoving_marked_compact_blocks;
 
+// The size of live large/compact objects in words.
+// Only updated at the end of nonmoving GC.
+extern memcount nonmoving_large_words,
+                nonmoving_compact_words;
+
 extern StgTSO *nonmoving_old_threads;
 extern StgWeak *nonmoving_old_weak_ptr_list;
 extern StgTSO *nonmoving_threads;


=====================================
rts/sm/Storage.c
=====================================
@@ -42,6 +42,7 @@
 #include "GC.h"
 #include "Evac.h"
 #include "NonMovingAllocate.h"
+#include "sm/NonMovingMark.h"
 #if defined(ios_HOST_OS) || defined(darwin_HOST_OS)
 #include "Hash.h"
 #endif
@@ -1615,7 +1616,12 @@ W_ genLiveWords (generation *gen)
 
 W_ genLiveBlocks (generation *gen)
 {
-    return gen->n_blocks + gen->n_large_blocks + gen->n_compact_blocks;
+  W_ nonmoving_blocks = 0;
+  // The nonmoving heap contains some blocks that live outside the regular generation structure.
+  if (gen == oldest_gen && RtsFlags.GcFlags.useNonmoving){
+    nonmoving_blocks = n_nonmoving_large_blocks + n_nonmoving_marked_large_blocks + n_nonmoving_compact_blocks + n_nonmoving_marked_compact_blocks;
+  }
+  return gen->n_blocks + gen->n_large_blocks + gen->n_compact_blocks + nonmoving_blocks;
 }
 
 W_ gcThreadLiveWords (uint32_t i, uint32_t g)
@@ -1711,6 +1717,9 @@ StgWord calcTotalLargeObjectsW (void)
     for (g = 0; g < RtsFlags.GcFlags.generations; g++) {
         totalW += generations[g].n_large_words;
     }
+
+    totalW += nonmoving_large_words;
+
     return totalW;
 }
 
@@ -1722,6 +1731,9 @@ StgWord calcTotalCompactW (void)
     for (g = 0; g < RtsFlags.GcFlags.generations; g++) {
         totalW += generations[g].n_compact_blocks * BLOCK_SIZE_W;
     }
+
+    totalW += nonmoving_compact_words;
+
     return totalW;
 }
 


=====================================
testsuite/tests/rts/T17574.hs
=====================================
@@ -0,0 +1,40 @@
+-- | Check that large objects are properly accounted for by GHC.Stats
+module Main (main) where
+
+import Control.Monad
+import Control.Exception
+import Control.Concurrent
+import System.Mem
+import System.Exit
+import GHC.Stats
+import GHC.Compact
+import Data.List (replicate)
+
+import qualified Data.ByteString.Char8 as BS
+
+doGC :: IO ()
+doGC = do
+  performMajorGC
+  threadDelay 1000 -- small delay to allow GC to run when using concurrent gc
+
+main :: IO ()
+main = do
+  let size = 4096*2
+  largeString <- evaluate $ BS.replicate size 'A'
+  compactString <- compact $ replicate size 'A'
+  doGC
+  doGC -- run GC twice to make sure the objects end up in the oldest gen
+  stats <- getRTSStats
+  let large_obj_bytes = gcdetails_large_objects_bytes $ gc stats
+  let compact_obj_bytes = gcdetails_compact_bytes $ gc stats
+  -- assert that large_obj_bytes is at least as big as size
+  -- this indicates that `largeString` is being accounted for by the stats department
+  when (large_obj_bytes < fromIntegral size) $ do
+    putStrLn $ "large_obj_bytes is: " <> show large_obj_bytes <> " but expected at least: " <> show size
+    exitFailure
+  when (compact_obj_bytes < fromIntegral size) $ do
+    putStrLn $ "compact_obj_bytes is: " <> show large_obj_bytes <> " but expected at least: " <> show size
+    exitFailure
+  -- keep them alive
+  print $ BS.length largeString
+  print $ length $ getCompact compactString


=====================================
testsuite/tests/rts/T17574.stdout
=====================================
@@ -0,0 +1,2 @@
+8192
+8192


=====================================
testsuite/tests/rts/all.T
=====================================
@@ -573,3 +573,5 @@ test('decodeMyStack_emptyListForMissingFlag',
 test('T22795a', [only_ways(['normal']), js_skip], compile_and_run, ['-threaded'])
 test('T22795b', [only_ways(['normal']), js_skip], compile_and_run, ['-single-threaded'])
 test('T22795c', [only_ways(['normal']), js_skip], compile_and_run, ['-threaded -single-threaded'])
+
+test('T17574', [js_skip], compile_and_run, ['-with-rtsopts -T'])



View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/6a73655fd6d22f0fd7e1c24d0d07a573b6bdc042...f2d56bf735185a59d7ce916edcf6a97f1401b230

-- 
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/6a73655fd6d22f0fd7e1c24d0d07a573b6bdc042...f2d56bf735185a59d7ce916edcf6a97f1401b230
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/20230325/7cd5ee27/attachment-0001.html>


More information about the ghc-commits mailing list