Cheng Shao pushed to branch wip/sm-no-sweep at Glasgow Haskell Compiler / GHC

Commits:

15 changed files:

Changes:

  • docs/users_guide/runtime_control.rst
    ... ... @@ -449,18 +449,6 @@ performance.
    449 449
         Large values are likely to lead to diminishing returns as
    
    450 450
         , in practice, the Haskell heap tends to be dominated by small objects.
    
    451 451
     
    
    452
    -
    
    453
    -.. rts-flag:: -w
    
    454
    -
    
    455
    -    :default: off
    
    456
    -    :since: a long time ago
    
    457
    -    :reverse: none
    
    458
    -
    
    459
    -    Uses a mark-region garbage collection strategy for the oldest-generation heap.
    
    460
    -    Note that this cannot be used in conjunction with heap profiling
    
    461
    -    (:rts-flag:`-hT`) unless linked against the profiling runtime system with
    
    462
    -    :ghc-flag:`-prof`.
    
    463
    -
    
    464 452
     .. rts-flag:: -A ⟨size⟩
    
    465 453
     
    
    466 454
         :default: 4MB
    

  • libraries/base/src/GHC/RTS/Flags.hs
    ... ... @@ -55,7 +55,7 @@ module GHC.RTS.Flags
    55 55
       , getHpcFlags
    
    56 56
       ) where
    
    57 57
     
    
    58
    -import Prelude (Show,IO,Bool,Maybe,String,Int,Enum,FilePath,Double,Eq,(<$>))
    
    58
    +import Prelude (Show,IO,Bool(..),Maybe,String,Int,Enum,FilePath,Double,Eq,(<$>))
    
    59 59
     
    
    60 60
     import GHC.Generics (Generic)
    
    61 61
     import qualified GHC.Internal.RTS.Flags as Internal
    
    ... ... @@ -107,7 +107,8 @@ data GCFlags = GCFlags
    107 107
         , compact               :: Bool -- ^ True <=> "compact all the time"
    
    108 108
         , compactThreshold      :: Double
    
    109 109
         , sweep                 :: Bool
    
    110
    -      -- ^ use "mostly mark-sweep" instead of copying for the oldest generation
    
    110
    +      -- ^ Always 'False', refers to the legacy mark-and-sweep
    
    111
    +      -- collector (@+RTS -w@) that's now removed
    
    111 112
         , ringBell              :: Bool
    
    112 113
         , idleGCDelayTime       :: RtsTime
    
    113 114
         , doIdleGC              :: Bool
    
    ... ... @@ -362,7 +363,7 @@ internal_to_base_RTSFlags Internal.RTSFlags{..} =
    362 363
     internal_to_base_GCFlags :: Internal.GCFlags -> GCFlags
    
    363 364
     internal_to_base_GCFlags i@Internal.GCFlags{..} =
    
    364 365
       let give_stats = internal_to_base_giveStats (Internal.giveStats i)
    
    365
    -  in GCFlags{ giveStats = give_stats, .. }
    
    366
    +  in GCFlags{ giveStats = give_stats, sweep = False, .. }
    
    366 367
       where
    
    367 368
         internal_to_base_giveStats :: Internal.GiveGCStats -> GiveGCStats
    
    368 369
         internal_to_base_giveStats Internal.NoGCStats      = NoGCStats
    

  • libraries/ghc-internal/src/GHC/Internal/RTS/Flags.hsc
    ... ... @@ -126,8 +126,6 @@ data GCFlags = GCFlags
    126 126
         , squeezeUpdFrames      :: Bool
    
    127 127
         , compact               :: Bool -- ^ True <=> "compact all the time"
    
    128 128
         , compactThreshold      :: Double
    
    129
    -    , sweep                 :: Bool
    
    130
    -      -- ^ use "mostly mark-sweep" instead of copying for the oldest generation
    
    131 129
         , ringBell              :: Bool
    
    132 130
         , idleGCDelayTime       :: RtsTime
    
    133 131
         , doIdleGC              :: Bool
    
    ... ... @@ -472,8 +470,6 @@ getGCFlags = do
    472 470
               <*> (toBool <$>
    
    473 471
                     (#{peek GC_FLAGS, compact} ptr :: IO CBool))
    
    474 472
               <*> #{peek GC_FLAGS, compactThreshold} ptr
    
    475
    -          <*> (toBool <$>
    
    476
    -                (#{peek GC_FLAGS, sweep} ptr :: IO CBool))
    
    477 473
               <*> (toBool <$>
    
    478 474
                     (#{peek GC_FLAGS, ringBell} ptr :: IO CBool))
    
    479 475
               <*> #{peek GC_FLAGS, idleGCDelayTime} ptr
    

  • rts/RtsFlags.c
    ... ... @@ -170,7 +170,6 @@ void initRtsFlagsDefaults(void)
    170 170
         RtsFlags.GcFlags.squeezeUpdFrames   = true;
    
    171 171
         RtsFlags.GcFlags.compact            = false;
    
    172 172
         RtsFlags.GcFlags.compactThreshold   = 30.0;
    
    173
    -    RtsFlags.GcFlags.sweep              = false;
    
    174 173
         RtsFlags.GcFlags.idleGCDelayTime    = USToTime(300000); // 300ms
    
    175 174
         RtsFlags.GcFlags.interIdleGCWait    = 0;
    
    176 175
     #if defined(THREADED_RTS)
    
    ... ... @@ -361,7 +360,6 @@ usage_text[] = {
    361 360
     "            -M (default: 30%)",
    
    362 361
     "  -c        Use in-place compaction for all oldest generation collections",
    
    363 362
     "            (the default is to use copying)",
    
    364
    -"  -w        Use mark-region for the oldest generation (experimental)",
    
    365 363
     #if defined(THREADED_RTS)
    
    366 364
     "  -I<sec>   Perform full GC after <sec> idle time (default: 0.3, 0 == off)",
    
    367 365
     "  -Iw<sec>  Minimum wait time between idle GC runs (default: 0, 0 == no min wait time)",
    
    ... ... @@ -1266,12 +1264,6 @@ error = true;
    1266 1264
                       }
    
    1267 1265
                       break;
    
    1268 1266
     
    
    1269
    -              case 'w':
    
    1270
    -                OPTION_UNSAFE;
    
    1271
    -                RtsFlags.GcFlags.sweep = true;
    
    1272
    -                unchecked_arg_start++;
    
    1273
    -                goto check_rest;
    
    1274
    -
    
    1275 1267
                   case 'F':
    
    1276 1268
                     OPTION_UNSAFE;
    
    1277 1269
                     switch(rts_argv[arg][2]) {
    
    ... ... @@ -2019,16 +2011,6 @@ static void normaliseRtsOpts (void)
    2019 2011
             barf("The non-moving collector doesn't support -G1");
    
    2020 2012
         }
    
    2021 2013
     
    
    2022
    -#if !defined(PROFILING) && !defined(DEBUG)
    
    2023
    -    // The mark-region collector is incompatible with heap census unless
    
    2024
    -    // we zero slop of blackhole'd thunks, which doesn't happen in the
    
    2025
    -    // vanilla way. See #9666.
    
    2026
    -    if (RtsFlags.ProfFlags.doHeapProfile && RtsFlags.GcFlags.sweep) {
    
    2027
    -        barf("The mark-region collector can only be used with profiling\n"
    
    2028
    -             "when linked against the profiled RTS.");
    
    2029
    -    }
    
    2030
    -#endif
    
    2031
    -
    
    2032 2014
         if (RtsFlags.GcFlags.compact && RtsFlags.GcFlags.useNonmoving) {
    
    2033 2015
             errorBelch("The non-moving collector cannot be used in conjunction with\n"
    
    2034 2016
                        "the compacting collector.");
    

  • rts/include/rts/Flags.h
    ... ... @@ -61,8 +61,6 @@ typedef struct _GC_FLAGS {
    61 61
         bool compact;               /* True <=> "compact all the time" */
    
    62 62
         double  compactThreshold;
    
    63 63
     
    
    64
    -    bool sweep;                 /* use "mostly mark-sweep" instead of copying
    
    65
    -                                 * for the oldest generation */
    
    66 64
         bool ringBell;
    
    67 65
     
    
    68 66
         Time    idleGCDelayTime;    /* units: TIME_RESOLUTION */
    

  • rts/include/rts/storage/Block.h
    ... ... @@ -168,8 +168,6 @@ typedef struct bdescr_ {
    168 168
     #define BF_FRAGMENTED 64
    
    169 169
     /* we know about this block (for finding leaks) */
    
    170 170
     #define BF_KNOWN     128
    
    171
    -/* Block was swept in the last generation */
    
    172
    -#define BF_SWEPT     256
    
    173 171
     /* Block is part of a Compact */
    
    174 172
     #define BF_COMPACT   512
    
    175 173
     /* A non-moving allocator segment (see NonMoving.c) */
    

  • rts/rts.cabal
    ... ... @@ -528,7 +528,6 @@ library
    528 528
                      sm/Scav.c
    
    529 529
                      sm/Scav_thr.c
    
    530 530
                      sm/Storage.c
    
    531
    -                 sm/Sweep.c
    
    532 531
                      fs.c
    
    533 532
                      prim/atomic.c
    
    534 533
                      prim/bitrev.c
    

  • rts/sm/GC.c
    ... ... @@ -26,7 +26,6 @@
    26 26
     #include "MarkStack.h"
    
    27 27
     #include "MarkWeak.h"
    
    28 28
     #include "Sparks.h"
    
    29
    -#include "Sweep.h"
    
    30 29
     
    
    31 30
     #include "Arena.h"
    
    32 31
     #include "Storage.h"
    
    ... ... @@ -384,7 +383,7 @@ GarbageCollect (struct GcConfig config,
    384 383
     
    
    385 384
     #if defined(THREADED_RTS)
    
    386 385
       /* How many threads will be participating in this GC?
    
    387
    -   * We don't always parallelise minor GCs, or mark/compact/sweep GC.
    
    386
    +   * We don't always parallelise minor GCs, or mark/compact GC.
    
    388 387
        * The policy on when to do a parallel GC is controlled by RTS flags (see
    
    389 388
        * below)
    
    390 389
     
    
    ... ... @@ -602,14 +601,11 @@ GarbageCollect (struct GcConfig config,
    602 601
     
    
    603 602
       // NO MORE EVACUATION AFTER THIS POINT!
    
    604 603
     
    
    605
    -  // Finally: compact or sweep the oldest generation.
    
    604
    +  // Finally: compact the oldest generation.
    
    606 605
       if (major_gc && oldest_gen->mark) {
    
    607
    -      if (oldest_gen->compact)
    
    608 606
               compact(gct->scavenged_static_objects,
    
    609 607
                       &dead_weak_ptr_list,
    
    610 608
                       &resurrected_threads);
    
    611
    -      else
    
    612
    -          sweep(oldest_gen);
    
    613 609
       }
    
    614 610
     
    
    615 611
       copied = 0;
    
    ... ... @@ -1792,10 +1788,6 @@ prepare_collected_gen (generation *gen)
    1792 1788
                     if (!(bd->flags & BF_FRAGMENTED)) {
    
    1793 1789
                         bd->flags |= BF_MARKED;
    
    1794 1790
                     }
    
    1795
    -
    
    1796
    -                // BF_SWEPT should be marked only for blocks that are being
    
    1797
    -                // collected in sweep()
    
    1798
    -                bd->flags &= ~BF_SWEPT;
    
    1799 1791
                 }
    
    1800 1792
             }
    
    1801 1793
         }
    
    ... ... @@ -2025,10 +2017,6 @@ resizeGenerations (void)
    2025 2017
     //        debugBelch("compaction: off\n", live);
    
    2026 2018
         }
    
    2027 2019
     
    
    2028
    -    if (RtsFlags.GcFlags.sweep) {
    
    2029
    -        oldest_gen->mark = 1;
    
    2030
    -    }
    
    2031
    -
    
    2032 2020
         // if we're going to go over the maximum heap size, reduce the
    
    2033 2021
         // size of the generations accordingly.  The calculation is
    
    2034 2022
         // different if compaction is turned on, because we don't need
    

  • rts/sm/Sanity.c
    ... ... @@ -597,7 +597,6 @@ checkClosure( const StgClosure* p )
    597 597
     void checkHeapChain (bdescr *bd)
    
    598 598
     {
    
    599 599
         for (; bd != NULL; bd = bd->link) {
    
    600
    -        if(!(bd->flags & BF_SWEPT)) {
    
    601 600
                 StgPtr p = bd->start;
    
    602 601
                 while (p < bd->free) {
    
    603 602
                     uint32_t size = checkClosure((StgClosure *)p);
    
    ... ... @@ -609,7 +608,6 @@ void checkHeapChain (bdescr *bd)
    609 608
                     while (p < bd->free &&
    
    610 609
                            (*p < 0x1000 || !LOOKS_LIKE_INFO_PTR(*p))) { p++; }
    
    611 610
                 }
    
    612
    -        }
    
    613 611
         }
    
    614 612
     }
    
    615 613
     
    

  • rts/sm/Storage.c
    ... ... @@ -226,13 +226,12 @@ initStorage (void)
    226 226
       nonmovingInit();
    
    227 227
     
    
    228 228
       /* The oldest generation has one step. */
    
    229
    -  if (RtsFlags.GcFlags.compact || RtsFlags.GcFlags.sweep) {
    
    229
    +  if (RtsFlags.GcFlags.compact) {
    
    230 230
           if (RtsFlags.GcFlags.generations == 1) {
    
    231 231
               errorBelch("WARNING: compact/sweep is incompatible with -G1; disabled");
    
    232 232
           } else {
    
    233 233
               oldest_gen->mark = 1;
    
    234
    -          if (RtsFlags.GcFlags.compact)
    
    235
    -              oldest_gen->compact = 1;
    
    234
    +          oldest_gen->compact = 1;
    
    236 235
           }
    
    237 236
       }
    
    238 237
     
    

  • rts/sm/Sweep.c deleted
    1
    -/* -----------------------------------------------------------------------------
    
    2
    - *
    
    3
    - * (c) The GHC Team 2008 
    
    4
    - *
    
    5
    - * Simple mark/sweep, collecting whole blocks.
    
    6
    - *
    
    7
    - * Documentation on the architecture of the Garbage Collector can be
    
    8
    - * found in the online commentary:
    
    9
    - * 
    
    10
    - *   https://gitlab.haskell.org/ghc/ghc/wikis/commentary/rts/storage/gc
    
    11
    - *
    
    12
    - * ---------------------------------------------------------------------------*/
    
    13
    -
    
    14
    -#include "rts/PosixSource.h"
    
    15
    -#include "Rts.h"
    
    16
    -
    
    17
    -#include "BlockAlloc.h"
    
    18
    -#include "Sweep.h"
    
    19
    -#include "Trace.h"
    
    20
    -
    
    21
    -void
    
    22
    -sweep(generation *gen)
    
    23
    -{
    
    24
    -    bdescr *bd, *prev, *next;
    
    25
    -    uint32_t i;
    
    26
    -    W_ freed, resid, fragd, blocks, live;
    
    27
    -    
    
    28
    -    ASSERT(countBlocks(gen->old_blocks) == gen->n_old_blocks);
    
    29
    -
    
    30
    -    live = 0; // estimate of live data in this gen
    
    31
    -    freed = 0;
    
    32
    -    fragd = 0;
    
    33
    -    blocks = 0;
    
    34
    -    prev = NULL;
    
    35
    -    for (bd = gen->old_blocks; bd != NULL; bd = next)
    
    36
    -    {
    
    37
    -        next = bd->link;
    
    38
    -
    
    39
    -        if (!(bd->flags & BF_MARKED)) { 
    
    40
    -            prev = bd;
    
    41
    -            continue;
    
    42
    -        }
    
    43
    -
    
    44
    -        blocks++;
    
    45
    -        resid = 0;
    
    46
    -        for (i = 0; i < BLOCK_SIZE_W / BITS_IN(W_); i++)
    
    47
    -        {
    
    48
    -            if (bd->u.bitmap[i] != 0) resid++;
    
    49
    -        }
    
    50
    -        live += resid * BITS_IN(W_);
    
    51
    -
    
    52
    -        if (resid == 0)
    
    53
    -        {
    
    54
    -            freed++;
    
    55
    -            gen->n_old_blocks--;
    
    56
    -            if (prev == NULL) {
    
    57
    -                gen->old_blocks = next;
    
    58
    -            } else {
    
    59
    -                prev->link = next;
    
    60
    -            }
    
    61
    -            freeGroup(bd);
    
    62
    -        }
    
    63
    -        else
    
    64
    -        {
    
    65
    -            prev = bd;
    
    66
    -            if (resid < (BLOCK_SIZE_W * 3) / (BITS_IN(W_) * 4)) {
    
    67
    -                fragd++;
    
    68
    -                bd->flags |= BF_FRAGMENTED;
    
    69
    -            }
    
    70
    -
    
    71
    -            bd->flags |= BF_SWEPT;
    
    72
    -        }
    
    73
    -    }
    
    74
    -
    
    75
    -    gen->live_estimate = live;
    
    76
    -
    
    77
    -    debugTrace(DEBUG_gc, "sweeping: %d blocks, %d were copied, %d freed (%d%%), %d are fragmented, live estimate: %ld%%",
    
    78
    -          gen->n_old_blocks + freed,
    
    79
    -          gen->n_old_blocks - blocks + freed,
    
    80
    -          freed,
    
    81
    -          blocks == 0 ? 0 : (freed * 100) / blocks,
    
    82
    -          fragd, 
    
    83
    -          (unsigned long)((blocks - freed) == 0 ? 0 : ((live / BLOCK_SIZE_W) * 100) / (blocks - freed)));
    
    84
    -
    
    85
    -    ASSERT(countBlocks(gen->old_blocks) == gen->n_old_blocks);
    
    86
    -}

  • rts/sm/Sweep.h deleted
    1
    -/* -----------------------------------------------------------------------------
    
    2
    - *
    
    3
    - * (c) The GHC Team 2008
    
    4
    - *
    
    5
    - * Simple mark/sweep, collecting whole blocks.
    
    6
    - *
    
    7
    - * Documentation on the architecture of the Garbage Collector can be
    
    8
    - * found in the online commentary:
    
    9
    - * 
    
    10
    - *   https://gitlab.haskell.org/ghc/ghc/wikis/commentary/rts/storage/gc
    
    11
    - *
    
    12
    - * ---------------------------------------------------------------------------*/
    
    13
    -
    
    14
    -#pragma once
    
    15
    -
    
    16
    -RTS_PRIVATE void sweep(generation *gen);

  • testsuite/tests/interface-stability/ghc-experimental-exports.stdout
    ... ... @@ -6415,7 +6415,6 @@ module GHC.RTS.Flags.Experimental where
    6415 6415
                    squeezeUpdFrames :: GHC.Internal.Types.Bool,
    
    6416 6416
                    compact :: GHC.Internal.Types.Bool,
    
    6417 6417
                    compactThreshold :: GHC.Internal.Types.Double,
    
    6418
    -               sweep :: GHC.Internal.Types.Bool,
    
    6419 6418
                    ringBell :: GHC.Internal.Types.Bool,
    
    6420 6419
                    idleGCDelayTime :: RtsTime,
    
    6421 6420
                    doIdleGC :: GHC.Internal.Types.Bool,
    

  • testsuite/tests/interface-stability/ghc-experimental-exports.stdout-mingw32
    ... ... @@ -6418,7 +6418,6 @@ module GHC.RTS.Flags.Experimental where
    6418 6418
                    squeezeUpdFrames :: GHC.Internal.Types.Bool,
    
    6419 6419
                    compact :: GHC.Internal.Types.Bool,
    
    6420 6420
                    compactThreshold :: GHC.Internal.Types.Double,
    
    6421
    -               sweep :: GHC.Internal.Types.Bool,
    
    6422 6421
                    ringBell :: GHC.Internal.Types.Bool,
    
    6423 6422
                    idleGCDelayTime :: RtsTime,
    
    6424 6423
                    doIdleGC :: GHC.Internal.Types.Bool,
    

  • testsuite/tests/linters/Makefile
    ... ... @@ -90,8 +90,6 @@ whitespace:
    90 90
     				rts/sm/MarkStack.h\
    
    91 91
     				rts/sm/MarkWeak.h\
    
    92 92
     				rts/sm/Scav.h\
    
    93
    -				rts/sm/Sweep.c\
    
    94
    -				rts/sm/Sweep.h\
    
    95 93
     				rts/win32/veh_excn.h\
    
    96 94
     				utils/genprimopcode/Parser.y\
    
    97 95
     				utils/genprimopcode/Syntax.hs\