Cheng Shao pushed to branch wip/sm-no-sweep at Glasgow Haskell Compiler / GHC Commits: 871f7517 by Cheng Shao at 2026-01-20T09:03:08+01:00 rts: drop the legacy mark-region oldest generation collector This patch drops the legacy mark-region oldest generation collector from the RTS, which performs simple mark-and-sweep in the oldest generation's old blocks, checking their bitmap and freeing the blocks that contain no live closure; any old block that contains live closure is retained, and is suspectible to fragmentation. It was added as an experiment in 2008 (https://mail.haskell.org/pipermail/cvs-ghc/2008-June/043146.html), has not seen much changes over the years, does not work with heap census, is completely untested in CI, and doesn't seem to be really used by anyone in production. Keeping it in the RTS codebase also causes a slight confusion in terminology, since the term "sweep" can refer to both the legacy code path as well as the nonmoving sweep logic. This motivates the cleanup. Closes #26802. - - - - - 15 changed files: - docs/users_guide/runtime_control.rst - libraries/base/src/GHC/RTS/Flags.hs - libraries/ghc-internal/src/GHC/Internal/RTS/Flags.hsc - rts/RtsFlags.c - rts/include/rts/Flags.h - rts/include/rts/storage/Block.h - rts/rts.cabal - rts/sm/GC.c - rts/sm/Sanity.c - rts/sm/Storage.c - − rts/sm/Sweep.c - − rts/sm/Sweep.h - testsuite/tests/interface-stability/ghc-experimental-exports.stdout - testsuite/tests/interface-stability/ghc-experimental-exports.stdout-mingw32 - testsuite/tests/linters/Makefile Changes: ===================================== docs/users_guide/runtime_control.rst ===================================== @@ -449,18 +449,6 @@ performance. Large values are likely to lead to diminishing returns as , in practice, the Haskell heap tends to be dominated by small objects. - -.. rts-flag:: -w - - :default: off - :since: a long time ago - :reverse: none - - Uses a mark-region garbage collection strategy for the oldest-generation heap. - Note that this cannot be used in conjunction with heap profiling - (:rts-flag:`-hT`) unless linked against the profiling runtime system with - :ghc-flag:`-prof`. - .. rts-flag:: -A ⟨size⟩ :default: 4MB ===================================== libraries/base/src/GHC/RTS/Flags.hs ===================================== @@ -55,7 +55,7 @@ module GHC.RTS.Flags , getHpcFlags ) where -import Prelude (Show,IO,Bool,Maybe,String,Int,Enum,FilePath,Double,Eq,(<$>)) +import Prelude (Show,IO,Bool(..),Maybe,String,Int,Enum,FilePath,Double,Eq,(<$>)) import GHC.Generics (Generic) import qualified GHC.Internal.RTS.Flags as Internal @@ -107,7 +107,8 @@ data GCFlags = GCFlags , compact :: Bool -- ^ True <=> "compact all the time" , compactThreshold :: Double , sweep :: Bool - -- ^ use "mostly mark-sweep" instead of copying for the oldest generation + -- ^ Always 'False', refers to the legacy mark-and-sweep + -- collector (@+RTS -w@) that's now removed , ringBell :: Bool , idleGCDelayTime :: RtsTime , doIdleGC :: Bool @@ -362,7 +363,7 @@ internal_to_base_RTSFlags Internal.RTSFlags{..} = internal_to_base_GCFlags :: Internal.GCFlags -> GCFlags internal_to_base_GCFlags i@Internal.GCFlags{..} = let give_stats = internal_to_base_giveStats (Internal.giveStats i) - in GCFlags{ giveStats = give_stats, .. } + in GCFlags{ giveStats = give_stats, sweep = False, .. } where internal_to_base_giveStats :: Internal.GiveGCStats -> GiveGCStats internal_to_base_giveStats Internal.NoGCStats = NoGCStats ===================================== libraries/ghc-internal/src/GHC/Internal/RTS/Flags.hsc ===================================== @@ -126,8 +126,6 @@ data GCFlags = GCFlags , squeezeUpdFrames :: Bool , compact :: Bool -- ^ True <=> "compact all the time" , compactThreshold :: Double - , sweep :: Bool - -- ^ use "mostly mark-sweep" instead of copying for the oldest generation , ringBell :: Bool , idleGCDelayTime :: RtsTime , doIdleGC :: Bool @@ -472,8 +470,6 @@ getGCFlags = do <*> (toBool <$> (#{peek GC_FLAGS, compact} ptr :: IO CBool)) <*> #{peek GC_FLAGS, compactThreshold} ptr - <*> (toBool <$> - (#{peek GC_FLAGS, sweep} ptr :: IO CBool)) <*> (toBool <$> (#{peek GC_FLAGS, ringBell} ptr :: IO CBool)) <*> #{peek GC_FLAGS, idleGCDelayTime} ptr ===================================== rts/RtsFlags.c ===================================== @@ -170,7 +170,6 @@ void initRtsFlagsDefaults(void) RtsFlags.GcFlags.squeezeUpdFrames = true; RtsFlags.GcFlags.compact = false; RtsFlags.GcFlags.compactThreshold = 30.0; - RtsFlags.GcFlags.sweep = false; RtsFlags.GcFlags.idleGCDelayTime = USToTime(300000); // 300ms RtsFlags.GcFlags.interIdleGCWait = 0; #if defined(THREADED_RTS) @@ -361,7 +360,6 @@ usage_text[] = { " -M (default: 30%)", " -c Use in-place compaction for all oldest generation collections", " (the default is to use copying)", -" -w Use mark-region for the oldest generation (experimental)", #if defined(THREADED_RTS) " -I<sec> Perform full GC after <sec> idle time (default: 0.3, 0 == off)", " -Iw<sec> Minimum wait time between idle GC runs (default: 0, 0 == no min wait time)", @@ -1266,12 +1264,6 @@ error = true; } break; - case 'w': - OPTION_UNSAFE; - RtsFlags.GcFlags.sweep = true; - unchecked_arg_start++; - goto check_rest; - case 'F': OPTION_UNSAFE; switch(rts_argv[arg][2]) { @@ -2019,16 +2011,6 @@ static void normaliseRtsOpts (void) barf("The non-moving collector doesn't support -G1"); } -#if !defined(PROFILING) && !defined(DEBUG) - // The mark-region collector is incompatible with heap census unless - // we zero slop of blackhole'd thunks, which doesn't happen in the - // vanilla way. See #9666. - if (RtsFlags.ProfFlags.doHeapProfile && RtsFlags.GcFlags.sweep) { - barf("The mark-region collector can only be used with profiling\n" - "when linked against the profiled RTS."); - } -#endif - if (RtsFlags.GcFlags.compact && RtsFlags.GcFlags.useNonmoving) { errorBelch("The non-moving collector cannot be used in conjunction with\n" "the compacting collector."); ===================================== rts/include/rts/Flags.h ===================================== @@ -61,8 +61,6 @@ typedef struct _GC_FLAGS { bool compact; /* True <=> "compact all the time" */ double compactThreshold; - bool sweep; /* use "mostly mark-sweep" instead of copying - * for the oldest generation */ bool ringBell; Time idleGCDelayTime; /* units: TIME_RESOLUTION */ ===================================== rts/include/rts/storage/Block.h ===================================== @@ -168,8 +168,6 @@ typedef struct bdescr_ { #define BF_FRAGMENTED 64 /* we know about this block (for finding leaks) */ #define BF_KNOWN 128 -/* Block was swept in the last generation */ -#define BF_SWEPT 256 /* Block is part of a Compact */ #define BF_COMPACT 512 /* A non-moving allocator segment (see NonMoving.c) */ ===================================== rts/rts.cabal ===================================== @@ -528,7 +528,6 @@ library sm/Scav.c sm/Scav_thr.c sm/Storage.c - sm/Sweep.c fs.c prim/atomic.c prim/bitrev.c ===================================== rts/sm/GC.c ===================================== @@ -26,7 +26,6 @@ #include "MarkStack.h" #include "MarkWeak.h" #include "Sparks.h" -#include "Sweep.h" #include "Arena.h" #include "Storage.h" @@ -384,7 +383,7 @@ GarbageCollect (struct GcConfig config, #if defined(THREADED_RTS) /* How many threads will be participating in this GC? - * We don't always parallelise minor GCs, or mark/compact/sweep GC. + * We don't always parallelise minor GCs, or mark/compact GC. * The policy on when to do a parallel GC is controlled by RTS flags (see * below) @@ -602,14 +601,11 @@ GarbageCollect (struct GcConfig config, // NO MORE EVACUATION AFTER THIS POINT! - // Finally: compact or sweep the oldest generation. + // Finally: compact the oldest generation. if (major_gc && oldest_gen->mark) { - if (oldest_gen->compact) compact(gct->scavenged_static_objects, &dead_weak_ptr_list, &resurrected_threads); - else - sweep(oldest_gen); } copied = 0; @@ -1792,10 +1788,6 @@ prepare_collected_gen (generation *gen) if (!(bd->flags & BF_FRAGMENTED)) { bd->flags |= BF_MARKED; } - - // BF_SWEPT should be marked only for blocks that are being - // collected in sweep() - bd->flags &= ~BF_SWEPT; } } } @@ -2025,10 +2017,6 @@ resizeGenerations (void) // debugBelch("compaction: off\n", live); } - if (RtsFlags.GcFlags.sweep) { - oldest_gen->mark = 1; - } - // if we're going to go over the maximum heap size, reduce the // size of the generations accordingly. The calculation is // different if compaction is turned on, because we don't need ===================================== rts/sm/Sanity.c ===================================== @@ -597,7 +597,6 @@ checkClosure( const StgClosure* p ) void checkHeapChain (bdescr *bd) { for (; bd != NULL; bd = bd->link) { - if(!(bd->flags & BF_SWEPT)) { StgPtr p = bd->start; while (p < bd->free) { uint32_t size = checkClosure((StgClosure *)p); @@ -609,7 +608,6 @@ void checkHeapChain (bdescr *bd) while (p < bd->free && (*p < 0x1000 || !LOOKS_LIKE_INFO_PTR(*p))) { p++; } } - } } } ===================================== rts/sm/Storage.c ===================================== @@ -226,13 +226,12 @@ initStorage (void) nonmovingInit(); /* The oldest generation has one step. */ - if (RtsFlags.GcFlags.compact || RtsFlags.GcFlags.sweep) { + if (RtsFlags.GcFlags.compact) { if (RtsFlags.GcFlags.generations == 1) { errorBelch("WARNING: compact/sweep is incompatible with -G1; disabled"); } else { oldest_gen->mark = 1; - if (RtsFlags.GcFlags.compact) - oldest_gen->compact = 1; + oldest_gen->compact = 1; } } ===================================== rts/sm/Sweep.c deleted ===================================== @@ -1,86 +0,0 @@ -/* ----------------------------------------------------------------------------- - * - * (c) The GHC Team 2008 - * - * Simple mark/sweep, collecting whole blocks. - * - * Documentation on the architecture of the Garbage Collector can be - * found in the online commentary: - * - * https://gitlab.haskell.org/ghc/ghc/wikis/commentary/rts/storage/gc - * - * ---------------------------------------------------------------------------*/ - -#include "rts/PosixSource.h" -#include "Rts.h" - -#include "BlockAlloc.h" -#include "Sweep.h" -#include "Trace.h" - -void -sweep(generation *gen) -{ - bdescr *bd, *prev, *next; - uint32_t i; - W_ freed, resid, fragd, blocks, live; - - ASSERT(countBlocks(gen->old_blocks) == gen->n_old_blocks); - - live = 0; // estimate of live data in this gen - freed = 0; - fragd = 0; - blocks = 0; - prev = NULL; - for (bd = gen->old_blocks; bd != NULL; bd = next) - { - next = bd->link; - - if (!(bd->flags & BF_MARKED)) { - prev = bd; - continue; - } - - blocks++; - resid = 0; - for (i = 0; i < BLOCK_SIZE_W / BITS_IN(W_); i++) - { - if (bd->u.bitmap[i] != 0) resid++; - } - live += resid * BITS_IN(W_); - - if (resid == 0) - { - freed++; - gen->n_old_blocks--; - if (prev == NULL) { - gen->old_blocks = next; - } else { - prev->link = next; - } - freeGroup(bd); - } - else - { - prev = bd; - if (resid < (BLOCK_SIZE_W * 3) / (BITS_IN(W_) * 4)) { - fragd++; - bd->flags |= BF_FRAGMENTED; - } - - bd->flags |= BF_SWEPT; - } - } - - gen->live_estimate = live; - - debugTrace(DEBUG_gc, "sweeping: %d blocks, %d were copied, %d freed (%d%%), %d are fragmented, live estimate: %ld%%", - gen->n_old_blocks + freed, - gen->n_old_blocks - blocks + freed, - freed, - blocks == 0 ? 0 : (freed * 100) / blocks, - fragd, - (unsigned long)((blocks - freed) == 0 ? 0 : ((live / BLOCK_SIZE_W) * 100) / (blocks - freed))); - - ASSERT(countBlocks(gen->old_blocks) == gen->n_old_blocks); -} ===================================== rts/sm/Sweep.h deleted ===================================== @@ -1,16 +0,0 @@ -/* ----------------------------------------------------------------------------- - * - * (c) The GHC Team 2008 - * - * Simple mark/sweep, collecting whole blocks. - * - * Documentation on the architecture of the Garbage Collector can be - * found in the online commentary: - * - * https://gitlab.haskell.org/ghc/ghc/wikis/commentary/rts/storage/gc - * - * ---------------------------------------------------------------------------*/ - -#pragma once - -RTS_PRIVATE void sweep(generation *gen); ===================================== testsuite/tests/interface-stability/ghc-experimental-exports.stdout ===================================== @@ -6415,7 +6415,6 @@ module GHC.RTS.Flags.Experimental where squeezeUpdFrames :: GHC.Internal.Types.Bool, compact :: GHC.Internal.Types.Bool, compactThreshold :: GHC.Internal.Types.Double, - sweep :: GHC.Internal.Types.Bool, ringBell :: GHC.Internal.Types.Bool, idleGCDelayTime :: RtsTime, doIdleGC :: GHC.Internal.Types.Bool, ===================================== testsuite/tests/interface-stability/ghc-experimental-exports.stdout-mingw32 ===================================== @@ -6418,7 +6418,6 @@ module GHC.RTS.Flags.Experimental where squeezeUpdFrames :: GHC.Internal.Types.Bool, compact :: GHC.Internal.Types.Bool, compactThreshold :: GHC.Internal.Types.Double, - sweep :: GHC.Internal.Types.Bool, ringBell :: GHC.Internal.Types.Bool, idleGCDelayTime :: RtsTime, doIdleGC :: GHC.Internal.Types.Bool, ===================================== testsuite/tests/linters/Makefile ===================================== @@ -90,8 +90,6 @@ whitespace: rts/sm/MarkStack.h\ rts/sm/MarkWeak.h\ rts/sm/Scav.h\ - rts/sm/Sweep.c\ - rts/sm/Sweep.h\ rts/win32/veh_excn.h\ utils/genprimopcode/Parser.y\ utils/genprimopcode/Syntax.hs\ View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/871f7517477337398686168fc3f2319b... -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/871f7517477337398686168fc3f2319b... You're receiving this email because of your account on gitlab.haskell.org.
participants (1)
-
Cheng Shao (@TerrorJack)