Cheng Shao pushed to branch wip/T24052 at Glasgow Haskell Compiler / GHC

Commits:

21 changed files:

Changes:

  • compile_flags.txt
    1
    +-fPIC
    
    2
    +-U__PIC__
    
    3
    +-D__PIC__
    
    1 4
     -Wimplicit
    
    2 5
     -include
    
    3 6
     rts/include/ghcversion.h
    
    ... ... @@ -27,3 +30,4 @@ rts/include/ghcversion.h
    27 30
     -DDEBUG
    
    28 31
     -DDYNAMIC
    
    29 32
     -DPROFILING
    
    33
    +-DRtsWay="rts_thr_debug_p_dyn"

  • compiler/GHC/CmmToAsm/AArch64/RegInfo.hs
    ... ... @@ -8,7 +8,7 @@ import GHC.Cmm
    8 8
     
    
    9 9
     import GHC.Utils.Outputable
    
    10 10
     
    
    11
    -data JumpDest = DestBlockId BlockId
    
    11
    +newtype JumpDest = DestBlockId BlockId
    
    12 12
     
    
    13 13
     -- Debug Instance
    
    14 14
     instance Outputable JumpDest where
    

  • compiler/GHC/CmmToAsm/PPC/RegInfo.hs
    ... ... @@ -27,7 +27,7 @@ import GHC.Cmm.CLabel
    27 27
     import GHC.Types.Unique
    
    28 28
     import GHC.Utils.Outputable (ppr, text, Outputable, (<>))
    
    29 29
     
    
    30
    -data JumpDest = DestBlockId BlockId
    
    30
    +newtype JumpDest = DestBlockId BlockId
    
    31 31
     
    
    32 32
     -- Debug Instance
    
    33 33
     instance Outputable JumpDest where
    

  • compiler/GHC/Core/Map/Type.hs
    ... ... @@ -554,7 +554,7 @@ instance Eq (DeBruijn a) => Eq (DeBruijn (Maybe a)) where
    554 554
     -- We also need to do the same for multiplicity! Which, since multiplicities are
    
    555 555
     -- encoded simply as a 'Type', amounts to have a Trie for a pair of types. Tries
    
    556 556
     -- of pairs are composition.
    
    557
    -data BndrMap a = BndrMap (TypeMapG (MaybeMap TypeMapG a))
    
    557
    +newtype BndrMap a = BndrMap (TypeMapG (MaybeMap TypeMapG a))
    
    558 558
     
    
    559 559
     -- TODO(22292): derive
    
    560 560
     instance Functor BndrMap where
    

  • compiler/GHC/Driver/LlvmConfigCache.hs
    ... ... @@ -18,6 +18,8 @@ import System.IO.Unsafe
    18 18
     -- Currently implemented with unsafe lazy IO. But it could be implemented with
    
    19 19
     -- an IORef as the exposed interface is in IO.
    
    20 20
     data LlvmConfigCache = LlvmConfigCache LlvmConfig
    
    21
    +-- NB: It is crucial for this to be a datatype, not a newtype.
    
    22
    +-- Allocations can increase across the board over 20% otherwise (see the discussion on !10708 and non-final pipelines)
    
    21 23
     
    
    22 24
     initLlvmConfigCache :: FilePath -> IO LlvmConfigCache
    
    23 25
     initLlvmConfigCache top_dir = pure $ LlvmConfigCache (unsafePerformIO $ initLlvmConfig top_dir)
    

  • compiler/GHC/Driver/Pipeline/Phases.hs
    ... ... @@ -52,4 +52,4 @@ data TPhase res where
    52 52
       T_MergeForeign :: PipeEnv -> HscEnv -> FilePath -> [FilePath] -> TPhase FilePath
    
    53 53
     
    
    54 54
     -- | A wrapper around the interpretation function for phases.
    
    55
    -data PhaseHook = PhaseHook (forall a . TPhase a -> IO a)
    55
    +newtype PhaseHook = PhaseHook (forall a . TPhase a -> IO a)

  • compiler/GHC/Tc/Utils/Env.hs
    ... ... @@ -8,6 +8,7 @@
    8 8
                                           -- in module Language.Haskell.Syntax.Extension
    
    9 9
     {-# LANGUAGE TypeFamilies #-}
    
    10 10
     {-# LANGUAGE LambdaCase #-}
    
    11
    +{-# LANGUAGE MultiWayIf #-}
    
    11 12
     
    
    12 13
     module GHC.Tc.Utils.Env(
    
    13 14
             TyThing(..), TcTyThing(..), TcId,
    
    ... ... @@ -1213,6 +1214,20 @@ pprBinders bndrs = pprWithCommas ppr bndrs
    1213 1214
     notFound :: Name -> TcM TyThing
    
    1214 1215
     notFound name
    
    1215 1216
       = do { lcl_env <- getLclEnv
    
    1217
    +       ; lvls <- getCurrentAndBindLevel name
    
    1218
    +       ; if    -- See Note [Out of scope might be a staging error]
    
    1219
    +           | isUnboundName name -> failM  -- If the name really isn't in scope
    
    1220
    +                                          -- don't report it again (#11941)
    
    1221
    +                                          -- the
    
    1222
    +                                          -- the 'Nothing' case of 'getCurrentAndBindLevel'
    
    1223
    +                                          -- currently means 'isUnboundName' but to avoid
    
    1224
    +                                          -- introducing bugs after a refactoring of that
    
    1225
    +                                          -- function, we check this completely independently
    
    1226
    +                                          -- before scrutinizing lvls
    
    1227
    +           | Just (_top_lvl_flag, bind_lvls, lvl@Splice {}) <- lvls
    
    1228
    +               -> failWithTc (TcRnBadlyLevelled (LevelCheckSplice name Nothing) bind_lvls (thLevelIndex lvl) Nothing ErrorWithoutFlag)
    
    1229
    +           | otherwise  -> pure ()
    
    1230
    +
    
    1216 1231
            ; if isTermVarOrFieldNameSpace (nameNameSpace name)
    
    1217 1232
                then
    
    1218 1233
                    -- This code path is only reachable with RequiredTypeArguments enabled
    
    ... ... @@ -1243,14 +1258,23 @@ wrongThingErr expected thing name =
    1243 1258
     {- Note [Out of scope might be a staging error]
    
    1244 1259
     ~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~
    
    1245 1260
     Consider
    
    1246
    -  x = 3
    
    1247
    -  data T = MkT $(foo x)
    
    1261
    +  type T = Int
    
    1262
    +  foo = $(1 :: T)
    
    1263
    +
    
    1264
    +GHC currently leaves the user some liberty when it comes to using
    
    1265
    +types in a manner that is theoretically not well-staged.
    
    1266
    +E.g. if `T` here were to be a value, we would reject the program with
    
    1267
    +a staging error. Since it is a type though, we allow it for backwards
    
    1268
    +compatibility reasons.
    
    1269
    +
    
    1270
    +However, in this case, we're just in the process of renaming a splice
    
    1271
    +when trying to type check an expression involving a type, that hasn't
    
    1272
    +even been added to the (type checking) environment yet. That is, why
    
    1273
    +it is out of scope.
    
    1248 1274
     
    
    1249
    -where 'foo' is imported from somewhere.
    
    1275
    +The reason why we cannot recognise this issue earlier is, that if we
    
    1276
    +are not actually type checking the splice, i.e. if we're only using the
    
    1277
    +name of the type (e.g. ''T), the program should be accepted.
    
    1250 1278
     
    
    1251
    -This is really a staging error, because we can't run code involving 'x'.
    
    1252
    -But in fact the type checker processes types first, so 'x' won't even be
    
    1253
    -in the type envt when we look for it in $(foo x).  So inside splices we
    
    1254
    -report something missing from the type env as a staging error.
    
    1255
    -See #5752 and #5795.
    
    1279
    +We stop and report a staging error.
    
    1256 1280
     -}

  • rts/sm/NonMoving.c
    ... ... @@ -151,9 +151,9 @@ static void nonmovingBumpEpoch(void) {
    151 151
      *  3. [STW] Root collection: Here we walk over a variety of root sources
    
    152 152
      *     and add them to the mark queue (see nonmovingCollect).
    
    153 153
      *
    
    154
    - *  4. [CONC] Concurrent marking: Here we do the majority of marking concurrently
    
    155
    - *     with mutator execution (but with the write barrier enabled; see
    
    156
    - *     Note [Update remembered set]).
    
    154
    + *  4. [CONC] Concurrent marking: Here we do the majority of marking
    
    155
    + *     concurrently with mutator execution (but with the write barrier enabled;
    
    156
    + *     see Note [Update remembered set]).
    
    157 157
      *
    
    158 158
      *  5. [STW] Final sync: Here we interrupt the mutators, ask them to
    
    159 159
      *     flush their final update remembered sets, and mark any new references
    
    ... ... @@ -218,9 +218,9 @@ static void nonmovingBumpEpoch(void) {
    218 218
      *  - Note [Concurrent read barrier on deRefWeak#] (NonMovingMark.c) describes
    
    219 219
      *    the read barrier on Weak# objects.
    
    220 220
      *
    
    221
    - *  - Note [Unintentional marking in resurrectThreads] (NonMovingMark.c) describes
    
    222
    - *    a tricky interaction between the update remembered set flush and weak
    
    223
    - *    finalization.
    
    221
    + *  - Note [Unintentional marking in resurrectThreads] (NonMovingMark.c)
    
    222
    + *    describes a tricky interaction between the update remembered set flush and
    
    223
    + *    weak finalization.
    
    224 224
      *
    
    225 225
      *  - Note [Origin references in the nonmoving collector] (NonMovingMark.h)
    
    226 226
      *    describes how we implement indirection short-cutting and the selector
    
    ... ... @@ -229,8 +229,8 @@ static void nonmovingBumpEpoch(void) {
    229 229
      *  - Note [StgStack dirtiness flags and concurrent marking] (TSO.h) describes
    
    230 230
      *    the protocol for concurrent marking of stacks.
    
    231 231
      *
    
    232
    - *  - Note [Nonmoving write barrier in Perform{Put,Take}] (PrimOps.cmm) describes
    
    233
    - *    a tricky barrier necessary when resuming threads blocked on MVar
    
    232
    + *  - Note [Nonmoving write barrier in Perform{Put,Take}] (PrimOps.cmm)
    
    233
    + *    describes a tricky barrier necessary when resuming threads blocked on MVar
    
    234 234
      *    operations.
    
    235 235
      *
    
    236 236
      *  - Note [Static objects under the nonmoving collector] (Storage.c) describes
    
    ... ... @@ -240,13 +240,17 @@ static void nonmovingBumpEpoch(void) {
    240 240
      *    how we use the DIRTY flags associated with MUT_VARs and TVARs to improve
    
    241 241
      *    barrier efficiency.
    
    242 242
      *
    
    243
    - *  - Note [Weak pointer processing and the non-moving GC] (MarkWeak.c) describes
    
    244
    - *    how weak pointers are handled when the non-moving GC is in use.
    
    243
    + *  - Note [Weak pointer processing and the non-moving GC] (MarkWeak.c)
    
    244
    + *    describes how weak pointers are handled when the non-moving GC is in use.
    
    245 245
      *
    
    246 246
      *  - Note [Sync phase marking budget] describes how we avoid long mutator
    
    247 247
      *    pauses during the sync phase
    
    248 248
      *
    
    249
    - *  - Note [Allocator sizes] goes into detail about our choice of allocator sizes.
    
    249
    + *  - Note [Allocator sizes] goes into detail about our choice of allocator
    
    250
    + *    sizes.
    
    251
    + *
    
    252
    + *  - Note [Testing the nonmoving collector] describes how we test the
    
    253
    + *    collector.
    
    250 254
      *
    
    251 255
      *  - Note [Segment allocation strategy] explains our segment allocation strategy.
    
    252 256
      *
    
    ... ... @@ -261,15 +265,15 @@ static void nonmovingBumpEpoch(void) {
    261 265
      * Concurrency-control of non-moving garbage collection is a bit tricky. There
    
    262 266
      * are a few things to keep in mind:
    
    263 267
      *
    
    264
    - *  - Only one non-moving collection may be active at a time. This is enforced by the
    
    265
    - *    concurrent_coll_running flag, which is set when a collection is on-going. If
    
    266
    - *    we attempt to initiate a new collection while this is set we wait on the
    
    267
    - *    concurrent_coll_finished condition variable, which signals when the
    
    268
    - *    active collection finishes.
    
    268
    + *  - Only one non-moving collection may be active at a time. This is enforced
    
    269
    + *    by the concurrent_coll_running flag, which is set when a collection is
    
    270
    + *    on-going. If we attempt to initiate a new collection while this is set we
    
    271
    + *    wait on the concurrent_coll_finished condition variable, which signals
    
    272
    + *    when the active collection finishes.
    
    269 273
      *
    
    270
    - *  - In between the mark and sweep phases the non-moving collector must synchronize
    
    271
    - *    with mutator threads to collect and mark their final update remembered
    
    272
    - *    sets. This is accomplished using
    
    274
    + *  - In between the mark and sweep phases the non-moving collector must
    
    275
    + *    synchronize with mutator threads to collect and mark their final update
    
    276
    + *    remembered sets. This is accomplished using
    
    273 277
      *    stopAllCapabilitiesWith(SYNC_FLUSH_UPD_REM_SET). Capabilities are held
    
    274 278
      *    the final mark has concluded.
    
    275 279
      *
    
    ... ... @@ -363,9 +367,9 @@ static void nonmovingBumpEpoch(void) {
    363 367
      *        ╰─────────────────╯
    
    364 368
      *                    ┆
    
    365 369
      *
    
    366
    - * In this case we have a TSO blocked on a dead MVar. Because the MVAR_TSO_QUEUE on
    
    367
    - * which it is blocked lives in the moving heap, the TSO is necessarily on the
    
    368
    - * oldest generation's mut_list. As in Note [Aging under the non-moving
    
    370
    + * In this case we have a TSO blocked on a dead MVar. Because the MVAR_TSO_QUEUE
    
    371
    + * on which it is blocked lives in the moving heap, the TSO is necessarily on
    
    372
    + * the oldest generation's mut_list. As in Note [Aging under the non-moving
    
    369 373
      * collector], the MVAR_TSO_QUEUE will be evacuated. If MVAR_TSO_QUEUE is aged
    
    370 374
      * (e.g. evacuated to the young generation) then the MVAR will be added to the
    
    371 375
      * mark queue. Consequently, we will falsely conclude that the MVAR is still
    
    ... ... @@ -389,9 +393,9 @@ static void nonmovingBumpEpoch(void) {
    389 393
      * ~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~
    
    390 394
      * The nonmoving collector uses an approximate heuristic for reporting live
    
    391 395
      * data quantity. Specifically, during mark we record how much live data we
    
    392
    - * find in nonmoving_segment_live_words. At the end of mark this is combined with nonmoving_large_words
    
    393
    - * and nonmoving_compact_words, and we declare this amount to
    
    394
    - * be how much live data we have on in the nonmoving heap (by setting
    
    396
    + * find in nonmoving_segment_live_words. At the end of mark this is combined
    
    397
    + * with nonmoving_large_words and nonmoving_compact_words, and we declare this
    
    398
    + * amount to be how much live data we have on in the nonmoving heap (by setting
    
    395 399
      * oldest_gen->live_estimate).
    
    396 400
      *
    
    397 401
      * In addition, we update oldest_gen->live_estimate every time we fill a
    
    ... ... @@ -415,10 +419,10 @@ static void nonmovingBumpEpoch(void) {
    415 419
      *  - Minor collections assume that all sparks living in the non-moving heap
    
    416 420
      *    are reachable.
    
    417 421
      *
    
    418
    - *  - Major collections prune the spark queue during the final sync. This pruning
    
    419
    - *    assumes that all sparks in the young generations are reachable (since the
    
    420
    - *    BF_EVACUATED flag won't be set on the nursery blocks) and will consequently
    
    421
    - *    only prune dead sparks living in the non-moving heap.
    
    422
    + *  - Major collections prune the spark queue during the final sync. This
    
    423
    + * pruning assumes that all sparks in the young generations are reachable (since
    
    424
    + * the BF_EVACUATED flag won't be set on the nursery blocks) and will
    
    425
    + * consequently only prune dead sparks living in the non-moving heap.
    
    422 426
      *
    
    423 427
      *
    
    424 428
      * Note [Dirty flags in the non-moving collector]
    
    ... ... @@ -441,8 +445,8 @@ static void nonmovingBumpEpoch(void) {
    441 445
      * In the non-moving collector we use the same dirty flag to implement a
    
    442 446
      * related optimisation on the non-moving write barrier: Specifically, the
    
    443 447
      * snapshot invariant only requires that the non-moving write barrier applies
    
    444
    - * to the *first* mutation to an object after collection begins. To achieve this,
    
    445
    - * we impose the following invariant:
    
    448
    + * to the *first* mutation to an object after collection begins. To achieve
    
    449
    + * this, we impose the following invariant:
    
    446 450
      *
    
    447 451
      *     An object being marked as dirty implies that all of its fields are on
    
    448 452
      *     the mark queue (or, equivalently, update remembered set).
    
    ... ... @@ -494,8 +498,8 @@ static void nonmovingBumpEpoch(void) {
    494 498
      *                        ┊
    
    495 499
      *
    
    496 500
      * This is bad. When we resume mutation a mutator may mutate MVAR A; since it's
    
    497
    - * already dirty we would fail to add Y to the update remembered set, breaking the
    
    498
    - * snapshot invariant and potentially losing track of the liveness of Z.
    
    501
    + * already dirty we would fail to add Y to the update remembered set, breaking
    
    502
    + * the snapshot invariant and potentially losing track of the liveness of Z.
    
    499 503
      *
    
    500 504
      * To avoid this nonmovingScavengeOne we eagerly pushes the values of the
    
    501 505
      * fields of all objects which it fails to evacuate (e.g. MVAR A) to the update
    
    ... ... @@ -537,8 +541,9 @@ static void nonmovingBumpEpoch(void) {
    537 541
      * Note [Allocator sizes]
    
    538 542
      * ~~~~~~~~~~~~~~~~~~~~~~
    
    539 543
      * Our choice of allocator sizes has to balance several considerations:
    
    540
    - * - Allocator sizes should be available for the most commonly request block sizes,
    
    541
    - *   in order to avoid excessive waste from rounding up to the next size (internal fragmentation).
    
    544
    + * - Allocator sizes should be available for the most commonly request block
    
    545
    + *   sizes, in order to avoid excessive waste from rounding up to the next size
    
    546
    + *   (internal fragmentation).
    
    542 547
      * - It should be possible to efficiently determine which allocator services
    
    543 548
      *   a certain block size.
    
    544 549
      * - The amount of allocators should be kept down to avoid overheads
    
    ... ... @@ -550,15 +555,15 @@ static void nonmovingBumpEpoch(void) {
    550 555
      *   arbitrary allocator sizes, we need to do some precomputation and make
    
    551 556
      *   use of the integer division by constants optimisation.
    
    552 557
      *
    
    553
    - * We currently try to balance these considerations by adopting the following scheme.
    
    554
    - * We have nonmoving_alloca_dense_cnt "dense" allocators starting with size
    
    555
    - * NONMOVING_ALLOCA0, and incrementing by NONMOVING_ALLOCA_DENSE_INCREMENT.
    
    558
    + * We currently try to balance these considerations by adopting the following
    
    559
    + * scheme. We have nonmoving_alloca_dense_cnt "dense" allocators starting with
    
    560
    + * size NONMOVING_ALLOCA0, and incrementing by NONMOVING_ALLOCA_DENSE_INCREMENT.
    
    556 561
      * These service the vast majority of allocations.
    
    557 562
      * In practice, Haskell programs tend to allocate a lot of small objects.
    
    558 563
      *
    
    559
    - * Other allocations are handled by a family of "sparse" allocators, each providing
    
    560
    - * blocks up to a power of 2. This places an upper bound on the waste at half the
    
    561
    - * required block size.
    
    564
    + * Other allocations are handled by a family of "sparse" allocators, each
    
    565
    + * providing blocks up to a power of 2. This places an upper bound on the waste
    
    566
    + * at half the required block size.
    
    562 567
      *
    
    563 568
      * See #23340
    
    564 569
      *
    
    ... ... @@ -578,6 +583,25 @@ static void nonmovingBumpEpoch(void) {
    578 583
      * quick.
    
    579 584
      *
    
    580 585
      * See #24150
    
    586
    + *
    
    587
    + * Note [Testing the nonmoving collector]
    
    588
    + * ~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~
    
    589
    + * The testsuite has four "ways" which test the nonmoving collector:
    
    590
    + *
    
    591
    + *  - nonmoving: runs tests under the nonmoving collector running in
    
    592
    + *    non-concurrent mode (i.e. using the non-threaded runtime)
    
    593
    + *  - nonmoving_thr: runs tests under the collector running in concurrent
    
    594
    + *    mode (with the threaded runtime)
    
    595
    + *  - nonmoving_thr_sanity: runs tests with concurrent collection and
    
    596
    + *    sanity checking (i.e. `+RTS -DS`)
    
    597
    + *  - nonmoving_thr_ghc: compiles tests with `ghc +RTS --nonmoving-gc -RTS`
    
    598
    + *    as GHC itself tends to be a good smoke test of the collector.
    
    599
    + *
    
    600
    + * To avoid blowing up validation times, we do not run any of these ways in the
    
    601
    + * default "normal" test speed. To ensure that we catch regressions in during
    
    602
    + * normal validation we do run a small number of tests in these ways. These
    
    603
    + * tests are identified by the `nonmoving_test` test modifier.
    
    604
    + *
    
    581 605
      */
    
    582 606
     
    
    583 607
     memcount nonmoving_segment_live_words = 0;
    

  • testsuite/driver/testlib.py
    ... ... @@ -174,6 +174,18 @@ def js_fragile( bug: IssueNumber ):
    174 174
         else:
    
    175 175
             return normal;
    
    176 176
     
    
    177
    +def nonmoving_test( name, opts ):
    
    178
    +    """
    
    179
    +    Always run the given test with the nonmoving collector, in addition to
    
    180
    +    the usual ways.
    
    181
    +
    
    182
    +    See Note [Testing the nonmoving collector] in rts/sm/NonMoving.c.
    
    183
    +    """
    
    184
    +    ways = ['nonmoving']
    
    185
    +    if config.ghc_with_threaded_rts and config.target_has_smp:
    
    186
    +        ways += ['nonmoving_thr_sanity', 'nonmoving_thr_ghc']
    
    187
    +    return extra_ways(ways)(name, opts)
    
    188
    +
    
    177 189
     def expect_fail( name, opts ):
    
    178 190
         # The compiler, testdriver, OS or platform is missing a certain
    
    179 191
         # feature, and we don't plan to or can't fix it now or in the
    
    ... ... @@ -1382,7 +1394,7 @@ def normalise_win32_io_errors(name, opts):
    1382 1394
     def normalise_version_( *pkgs ):
    
    1383 1395
         def normalise_version__( str ):
    
    1384 1396
             # (name)(-version)(-hash)(-components)
    
    1385
    -        return re.sub('(' + '|'.join(map(re.escape,pkgs)) + r')-[0-9.]+(-[0-9a-zA-Z+]+)?(-[0-9a-zA-Z]+)?',
    
    1397
    +        return re.sub('(' + '|'.join(map(re.escape,pkgs)) + r')-[0-9.]+(-[0-9a-zA-Z\+]+)?(-[0-9a-zA-Z]+)?',
    
    1386 1398
                           r'\1-<VERSION>-<HASH>', str)
    
    1387 1399
         return normalise_version__
    
    1388 1400
     
    
    ... ... @@ -1971,7 +1983,7 @@ async def do_compile(name: TestName,
    1971 1983
         # of whether we expected the compilation to fail or not (successful
    
    1972 1984
         # compilations may generate warnings).
    
    1973 1985
     
    
    1974
    -    expected_stderr_file = find_expected_file(name, 'stderr')
    
    1986
    +    expected_stderr_file = find_expected_file(name, 'stderr', way)
    
    1975 1987
         actual_stderr_file = add_suffix(name, 'comp.stderr')
    
    1976 1988
         diff_file_name = in_testdir(add_suffix(name, 'comp.diff'))
    
    1977 1989
     
    
    ... ... @@ -2012,7 +2024,7 @@ async def compile_cmp_asm(name: TestName,
    2012 2024
         # of whether we expected the compilation to fail or not (successful
    
    2013 2025
         # compilations may generate warnings).
    
    2014 2026
     
    
    2015
    -    expected_asm_file = find_expected_file(name, 'asm')
    
    2027
    +    expected_asm_file = find_expected_file(name, 'asm', way)
    
    2016 2028
         actual_asm_file = add_suffix(name, 's')
    
    2017 2029
     
    
    2018 2030
         if not await compare_outputs(way, 'asm',
    
    ... ... @@ -2036,7 +2048,7 @@ async def compile_grep_asm(name: TestName,
    2036 2048
         if badResult(result):
    
    2037 2049
             return result
    
    2038 2050
     
    
    2039
    -    expected_pat_file = find_expected_file(name, 'asm')
    
    2051
    +    expected_pat_file = find_expected_file(name, 'asm', way)
    
    2040 2052
         actual_asm_file = add_suffix(name, 's')
    
    2041 2053
     
    
    2042 2054
         if not grep_output(join_normalisers(normalise_errmsg),
    
    ... ... @@ -2058,7 +2070,7 @@ async def compile_grep_core(name: TestName,
    2058 2070
         if badResult(result):
    
    2059 2071
             return result
    
    2060 2072
     
    
    2061
    -    expected_pat_file = find_expected_file(name, 'substr-simpl')
    
    2073
    +    expected_pat_file = find_expected_file(name, 'substr-simpl', way)
    
    2062 2074
         actual_core_file = add_suffix(name, 'dump-simpl')
    
    2063 2075
     
    
    2064 2076
         if not grep_output(join_normalisers(normalise_errmsg),
    
    ... ... @@ -2097,7 +2109,7 @@ async def compile_and_run__(name: TestName,
    2097 2109
                 return result
    
    2098 2110
     
    
    2099 2111
             if compile_stderr:
    
    2100
    -            expected_stderr_file = find_expected_file(name, 'ghc.stderr')
    
    2112
    +            expected_stderr_file = find_expected_file(name, 'ghc.stderr', way)
    
    2101 2113
                 actual_stderr_file = add_suffix(name, 'comp.stderr')
    
    2102 2114
                 diff_file_name = in_testdir(add_suffix(name, 'comp.diff'))
    
    2103 2115
     
    
    ... ... @@ -2556,7 +2568,7 @@ def get_compiler_flags() -> List[str]:
    2556 2568
     
    
    2557 2569
     async def stdout_ok(name: TestName, way: WayName) -> bool:
    
    2558 2570
        actual_stdout_file = add_suffix(name, 'run.stdout')
    
    2559
    -   expected_stdout_file = find_expected_file(name, 'stdout')
    
    2571
    +   expected_stdout_file = find_expected_file(name, 'stdout', way)
    
    2560 2572
     
    
    2561 2573
        extra_norm = join_normalisers(normalise_output, getTestOpts().extra_normaliser)
    
    2562 2574
     
    
    ... ... @@ -2583,7 +2595,7 @@ def dump_stdout( name: TestName ) -> None:
    2583 2595
     
    
    2584 2596
     async def stderr_ok(name: TestName, way: WayName) -> bool:
    
    2585 2597
        actual_stderr_file = add_suffix(name, 'run.stderr')
    
    2586
    -   expected_stderr_file = find_expected_file(name, 'stderr')
    
    2598
    +   expected_stderr_file = find_expected_file(name, 'stderr', way)
    
    2587 2599
     
    
    2588 2600
        return await compare_outputs(way, 'stderr',
    
    2589 2601
                               join_normalisers(normalise_errmsg, getTestOpts().extra_errmsg_normaliser), \
    
    ... ... @@ -2688,7 +2700,7 @@ async def check_hp_ok(name: TestName) -> bool:
    2688 2700
             return False
    
    2689 2701
     
    
    2690 2702
     async def check_prof_ok(name: TestName, way: WayName) -> bool:
    
    2691
    -    expected_prof_file = find_expected_file(name, 'prof.sample')
    
    2703
    +    expected_prof_file = find_expected_file(name, 'prof.sample', way)
    
    2692 2704
         expected_prof_path = in_testdir(expected_prof_file)
    
    2693 2705
     
    
    2694 2706
         # Check actual prof file only if we have an expected prof file to
    
    ... ... @@ -3368,18 +3380,19 @@ def in_statsdir(name: Union[Path, str], suffix: str='') -> Path:
    3368 3380
     
    
    3369 3381
     # Finding the sample output.  The filename is of the form
    
    3370 3382
     #
    
    3371
    -#   <test>.stdout[-ws-<wordsize>][-<platform>|-<os>]
    
    3383
    +#   <test>.stdout[-ws-<wordsize>][-<platform>|-<os>][-<way>]
    
    3372 3384
     #
    
    3373
    -def find_expected_file(name: TestName, suff: str) -> Path:
    
    3385
    +def find_expected_file(name: TestName, suff: str, way: WayName) -> Path:
    
    3374 3386
         basename = add_suffix(name, suff)
    
    3375 3387
         # Override the basename if the user has specified one, this will then be
    
    3376 3388
         # subjected to the same name mangling scheme as normal to allow platform
    
    3377 3389
         # specific overrides to work.
    
    3378 3390
         basename = getTestOpts().use_specs.get(suff, basename)
    
    3379 3391
     
    
    3380
    -    files = [str(basename) + ws + plat
    
    3392
    +    files = [str(basename) + ws + plat + way_ext
    
    3381 3393
                  for plat in ['-' + config.platform, '-' + config.os, '']
    
    3382
    -             for ws in ['-ws-' + config.wordsize, '']]
    
    3394
    +             for ws in ['-ws-' + config.wordsize, '']
    
    3395
    +             for way_ext in ['-' + way, '']]
    
    3383 3396
     
    
    3384 3397
         for f in files:
    
    3385 3398
             if in_srcdir(f).exists():
    

  • testsuite/tests/array/should_run/all.T
    ... ... @@ -21,6 +21,6 @@ test('arr014', when(fast(), skip), compile_and_run, [''])
    21 21
     test('arr015', when(fast(), skip), compile_and_run, [''])
    
    22 22
     test('arr017', when(fast(), skip), compile_and_run, [''])
    
    23 23
     test('arr018', when(fast(), skip), compile_and_run, [''])
    
    24
    -test('arr019', normal, compile_and_run, [''])
    
    25
    -test('arr020', normal, compile_and_run, [''])
    
    24
    +test('arr019', nonmoving_test, compile_and_run, [''])
    
    25
    +test('arr020', nonmoving_test, compile_and_run, [''])
    
    26 26
     test('T21962', normal, compile_and_run, [''])

  • testsuite/tests/concurrent/should_run/all.T
    1 1
     # -----------------------------------------------------------------------------
    
    2 2
     # These tests we do even for 'make fast'
    
    3 3
     
    
    4
    -test('conc003', normal, compile_and_run, [''])
    
    5
    -test('conc006', normal, compile_and_run, [''])
    
    6
    -test('conc027', normal, compile_and_run, [''])
    
    7
    -test('conc051', normal, compile_and_run, [''])
    
    4
    +test('conc003', nonmoving_test, compile_and_run, [''])
    
    5
    +test('conc006', nonmoving_test, compile_and_run, [''])
    
    6
    +test('conc027', nonmoving_test, compile_and_run, [''])
    
    7
    +test('conc051', nonmoving_test, compile_and_run, [''])
    
    8 8
     
    
    9 9
     if ('threaded1' in config.run_ways):
    
    10 10
        only_threaded_ways = only_ways(['ghci','threaded1','threaded2', 'nonmoving_thr'])
    
    11 11
     else:
    
    12 12
        only_threaded_ways = skip
    
    13 13
     
    
    14
    -test('conc069', only_threaded_ways, compile_and_run, [''])
    
    15
    -test('conc069a', only_threaded_ways, compile_and_run, [''])
    
    14
    +test('conc069', [nonmoving_test, only_threaded_ways], compile_and_run, [''])
    
    15
    +test('conc069a', [nonmoving_test, only_threaded_ways], compile_and_run, [''])
    
    16 16
     # this test gives slightly different results for non-threaded ways, so omit
    
    17 17
     # those for now.
    
    18 18
     test('conc070', only_threaded_ways, compile_and_run, [''])
    
    ... ... @@ -47,8 +47,8 @@ test('T3429', [ extra_run_opts('+RTS -C0.001 -RTS'),
    47 47
     # times out with ghci
    
    48 48
     test('T4030', omit_ghci, compile_and_run, ['-O'])
    
    49 49
     
    
    50
    -test('throwto002', js_fragile(24259), compile_and_run, [''])
    
    51
    -test('throwto003', normal, compile_and_run, [''])
    
    50
    +test('throwto002', [nonmoving_test, js_fragile(24259)], compile_and_run, [''])
    
    51
    +test('throwto003', nonmoving_test, compile_and_run, [''])
    
    52 52
     
    
    53 53
     test('mask001', normal, compile_and_run, [''])
    
    54 54
     test('mask002', js_broken(22261), compile_and_run, [''])
    
    ... ... @@ -81,9 +81,9 @@ test('T5611a', fragile(12751), compile_and_run, [''])
    81 81
     test('T5238', normal, compile_and_run, [''])
    
    82 82
     test('T5866', exit_code(1), compile_and_run, [''])
    
    83 83
     
    
    84
    -test('readMVar1', normal, compile_and_run, [''])
    
    85
    -test('readMVar2', normal, compile_and_run, [''])
    
    86
    -test('readMVar3', normal, compile_and_run, [''])
    
    84
    +test('readMVar1', nonmoving_test, compile_and_run, [''])
    
    85
    +test('readMVar2', nonmoving_test, compile_and_run, [''])
    
    86
    +test('readMVar3', nonmoving_test, compile_and_run, [''])
    
    87 87
     test('tryReadMVar1', normal, compile_and_run, [''])
    
    88 88
     test('tryReadMVar2', normal, compile_and_run, [''])
    
    89 89
     
    
    ... ... @@ -121,9 +121,9 @@ test('allocLimit4', [ extra_run_opts('+RTS -xq300k -RTS'),
    121 121
     
    
    122 122
     setTestOpts(when(fast(), skip))
    
    123 123
     
    
    124
    -test('conc001', normal, compile_and_run, [''])
    
    125
    -test('conc002', normal, compile_and_run, [''])
    
    126
    -test('conc004', normal, compile_and_run, [''])
    
    124
    +test('conc001', nonmoving_test, compile_and_run, [''])
    
    125
    +test('conc002', nonmoving_test, compile_and_run, [''])
    
    126
    +test('conc004', nonmoving_test, compile_and_run, [''])
    
    127 127
     test('conc007', extra_run_opts('+RTS -H128M -RTS'), compile_and_run, [''])
    
    128 128
     test('conc008', normal, compile_and_run, [''])
    
    129 129
     test('conc009', exit_code(1), compile_and_run, [''])
    
    ... ... @@ -218,16 +218,17 @@ test('conc039', [omit_ways(ghci_ways + threaded_ways), js_skip], compile_and_run
    218 218
     test('conc040', [exit_code(1), omit_ghci, js_skip], compile_and_run, [''])
    
    219 219
     
    
    220 220
     # STM-related tests.
    
    221
    -test('conc041', normal, compile_and_run, [''])
    
    222
    -test('conc042', normal, compile_and_run, [''])
    
    223
    -test('conc043', normal, compile_and_run, [''])
    
    224
    -test('conc044', normal, compile_and_run, [''])
    
    225
    -test('conc045', normal, compile_and_run, [''])
    
    221
    +test('conc041', nonmoving_test, compile_and_run, [''])
    
    222
    +test('conc042', nonmoving_test, compile_and_run, [''])
    
    223
    +test('conc043', nonmoving_test, compile_and_run, [''])
    
    224
    +test('conc044', nonmoving_test, compile_and_run, [''])
    
    225
    +test('conc045', nonmoving_test, compile_and_run, [''])
    
    226 226
     
    
    227
    -test('conc058', normal, compile_and_run, [''])
    
    227
    +test('conc058', nonmoving_test, compile_and_run, [''])
    
    228 228
     
    
    229 229
     test('conc059',
    
    230 230
          [only_ways(['threaded1', 'threaded2', 'nonmoving_thr']),
    
    231
    +      nonmoving_test,
    
    231 232
           pre_cmd('$MAKE -s --no-print-directory conc059_setup')],
    
    232 233
          compile_and_run, ['conc059_c.c -no-hs-main'])
    
    233 234
     
    

  • testsuite/tests/driver/T20696/T20696.stderr-ext-interp
    1
    +[1 of 3] Compiling C                ( C.hs, C.o )
    
    2
    +[2 of 3] Compiling B                ( B.hs, B.o )
    
    3
    +[3 of 3] Compiling A                ( A.hs, A.o )

  • testsuite/tests/driver/T20696/all.T
    1 1
     test('T20696', [extra_files(['A.hs', 'B.hs', 'C.hs'])
    
    2
    -               , expect_broken_for(26552, ['ext-interp'])
    
    3 2
                    , unless(ghc_dynamic(), skip)], multimod_compile, ['A', ''])
    
    4 3
     test('T20696-static', [extra_files(['A.hs', 'B.hs', 'C.hs'])
    
    5 4
                    , when(ghc_dynamic(), skip)], multimod_compile, ['A', ''])

  • testsuite/tests/driver/fat-iface/all.T
    ... ... @@ -9,12 +9,12 @@ test('fat010', [req_th,extra_files(['THA.hs', 'THB.hs', 'THC.hs']), copy_files],
    9 9
     # Check linking works when using -fbyte-code-and-object-code
    
    10 10
     test('fat011', [req_th, extra_files(['FatMain.hs', 'FatTH.hs', 'FatQuote.hs'])], multimod_compile, ['FatMain', '-fbyte-code-and-object-code -fprefer-byte-code'])
    
    11 11
     # Check that we use interpreter rather than enable dynamic-too if needed for TH
    
    12
    -test('fat012', [req_th, expect_broken_for(26552, ['ext-interp']), unless(ghc_dynamic(), skip), extra_files(['FatTH.hs', 'FatQuote.hs'])], multimod_compile, ['FatTH', '-fprefer-byte-code'])
    
    12
    +test('fat012', [req_th, unless(ghc_dynamic(), skip), extra_files(['FatTH.hs', 'FatQuote.hs'])], multimod_compile, ['FatTH', '-fprefer-byte-code'])
    
    13 13
     # Check that no objects are generated if using -fno-code and -fprefer-byte-code
    
    14 14
     test('fat013', [req_th, req_bco, extra_files(['FatTH.hs', 'FatQuote.hs'])], multimod_compile, ['FatTH', '-fno-code -fprefer-byte-code'])
    
    15 15
     # When using interpreter should not produce objects
    
    16 16
     test('fat014', [req_th, extra_files(['FatTH.hs', 'FatQuote.hs']), extra_run_opts('-fno-code')], ghci_script, ['fat014.script'])
    
    17
    -test('fat015', [req_th, expect_broken_for(26552, ['ext-interp']), unless(ghc_dynamic(), skip), extra_files(['FatQuote.hs', 'FatQuote1.hs', 'FatQuote2.hs', 'FatTH1.hs', 'FatTH2.hs', 'FatTHTop.hs'])], multimod_compile, ['FatTHTop', '-fno-code -fwrite-interface'])
    
    17
    +test('fat015', [req_th, unless(ghc_dynamic(), skip), extra_files(['FatQuote.hs', 'FatQuote1.hs', 'FatQuote2.hs', 'FatTH1.hs', 'FatTH2.hs', 'FatTHTop.hs'])], multimod_compile, ['FatTHTop', '-fno-code -fwrite-interface'])
    
    18 18
     test('T22807', [req_th, unless(ghc_dynamic(), skip), extra_files(['T22807A.hs', 'T22807B.hs'])]
    
    19 19
                  , makefile_test, ['T22807'])
    
    20 20
     test('T22807_ghci', [req_th, unless(ghc_dynamic(), skip), extra_files(['T22807_ghci.hs'])]
    

  • testsuite/tests/driver/fat-iface/fat012.stderr-ext-interp
    1
    +[1 of 2] Compiling FatQuote         ( FatQuote.hs, FatQuote.o )
    
    2
    +[2 of 2] Compiling FatTH            ( FatTH.hs, FatTH.o )

  • testsuite/tests/driver/fat-iface/fat015.stderr-ext-interp
    1
    +[1 of 6] Compiling FatQuote         ( FatQuote.hs, FatQuote.o, interpreted )
    
    2
    +[2 of 6] Compiling FatQuote1        ( FatQuote1.hs, interpreted )
    
    3
    +[3 of 6] Compiling FatQuote2        ( FatQuote2.hs, FatQuote2.o )
    
    4
    +[4 of 6] Compiling FatTH1           ( FatTH1.hs, nothing )
    
    5
    +[5 of 6] Compiling FatTH2           ( FatTH2.hs, nothing )
    
    6
    +[6 of 6] Compiling FatTHTop         ( FatTHTop.hs, nothing )

  • testsuite/tests/splice-imports/SI07.stderr-ext-interp
    1
    +[1 of 3] Compiling SI05A            ( SI05A.hs, SI05A.o )
    
    2
    +[2 of 3] Compiling SI07A            ( SI07A.hs, nothing )
    
    3
    +[3 of 3] Compiling SI07             ( SI07.hs, nothing )

  • testsuite/tests/splice-imports/all.T
    ... ... @@ -9,7 +9,7 @@ test('SI03', [extra_files(["SI01A.hs"])], multimod_compile_fail, ['SI03', '-v0']
    9 9
     test('SI04', [extra_files(["SI01A.hs"])], multimod_compile, ['SI04', '-v0'])
    
    10 10
     test('SI05', [extra_files(["SI01A.hs"])], multimod_compile_fail, ['SI05', '-v0'])
    
    11 11
     test('SI06', [extra_files(["SI01A.hs"])], multimod_compile, ['SI06', '-v0'])
    
    12
    -test('SI07', [expect_broken_for(26552, ['ext-interp']), unless(ghc_dynamic(), skip), extra_files(["SI05A.hs"])], multimod_compile, ['SI07', '-fwrite-interface -fno-code'])
    
    12
    +test('SI07', [unless(ghc_dynamic(), skip), extra_files(["SI05A.hs"])], multimod_compile, ['SI07', '-fwrite-interface -fno-code'])
    
    13 13
     # Instance tests
    
    14 14
     test('SI08', [extra_files(["ClassA.hs", "InstanceA.hs"])], multimod_compile_fail, ['SI08', '-v0'])
    
    15 15
     test('SI09', [extra_files(["ClassA.hs", "InstanceA.hs"])], multimod_compile, ['SI09', '-v0'])
    

  • testsuite/tests/th/T26099.hs
    1
    +{-# LANGUAGE TemplateHaskell #-}
    
    2
    +module M where
    
    3
    +
    
    4
    +type T = Int
    
    5
    +
    
    6
    +a = $(3 :: T)

  • testsuite/tests/th/T26099.stderr
    1
    +T26099.hs:6:12: error: [GHC-28914]
    
    2
    +    • Level error: ‘T’ is bound at level 0 but used at level -1
    
    3
    +    • In an expression type signature: T
    
    4
    +      In the expression: 3 :: T
    
    5
    +      In the untyped splice: $(3 :: T)
    
    6
    +

  • testsuite/tests/th/all.T
    ... ... @@ -642,3 +642,4 @@ test('QQInQuote', normal, compile, [''])
    642 642
     test('QQTopError', normal, compile_fail, ['-fdiagnostics-show-caret'])
    
    643 643
     test('GadtConSigs_th_pprint1', normal, compile, [''])
    
    644 644
     test('GadtConSigs_th_dump1', normal, compile, ['-v0 -ddump-splices -dsuppress-uniques'])
    
    645
    +test('T26099', normal, compile_fail, [''])