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

Commits:

23 changed files:

Changes:

  • .gitlab/ci.sh
    ... ... @@ -259,6 +259,12 @@ function setup() {
    259 259
       git config user.email "ghc-ci@gitlab-haskell.org"
    
    260 260
       git config user.name "GHC GitLab CI"
    
    261 261
     
    
    262
    +  # Disable auto gc. Useless in a temporary checkout, and
    
    263
    +  # non-deterministic "Auto packing the repository in background for
    
    264
    +  # optimum performance." message could pop up that confuses the
    
    265
    +  # testsuite driver!
    
    266
    +  git config gc.auto 0
    
    267
    +
    
    262 268
       info "====================================================="
    
    263 269
       info "Toolchain versions"
    
    264 270
       info "====================================================="
    

  • .gitlab/test-metrics.sh
    ... ... @@ -17,12 +17,14 @@ fail() {
    17 17
     
    
    18 18
     function pull() {
    
    19 19
       local ref="refs/notes/$REF"
    
    20
    -  # 2023-10-04: `git fetch` started failing, first on Darwin in CI and then on
    
    21
    -  # Linux locally, both using git version 2.40.1. See #24055. One workaround is
    
    22
    -  # to set a larger http.postBuffer, although this is definitely a workaround.
    
    23
    -  # The default should work just fine. The error could be in git, GitLab, or
    
    24
    -  # perhaps the networking tube (including all proxies etc) between the two.
    
    25
    -  run git -c http.postBuffer=2097152 fetch -f "$NOTES_ORIGIN" "$ref:$ref"
    
    20
    +
    
    21
    +  # Fetch performance notes from a dedicated promisor remote using a
    
    22
    +  # treeless filter, so that individual note blobs are fetched lazily
    
    23
    +  # as needed.
    
    24
    +  git remote add perf-notes "$NOTES_ORIGIN" || true
    
    25
    +  git config fetch.recurseSubmodules false
    
    26
    +  git config remote.perf-notes.partialclonefilter tree:0
    
    27
    +  run git fetch --force perf-notes "$ref:$ref"
    
    26 28
       echo "perf notes ref $ref is $(git rev-parse $ref)"
    
    27 29
     }
    
    28 30
     
    
    ... ... @@ -81,4 +83,3 @@ case $1 in
    81 83
       pull) pull ;;
    
    82 84
       *) fail "Invalid mode $1" ;;
    
    83 85
     esac
    84
    -

  • compiler/GHC/Cmm/Opt.hs
    ... ... @@ -290,9 +290,7 @@ cmmMachOpFoldM _ (MO_Sub _) [CmmLit lit, CmmLit (CmmInt i rep)]
    290 290
     -- the same comparison at the larger size.
    
    291 291
     
    
    292 292
     cmmMachOpFoldM platform cmp [CmmMachOp conv [x], CmmLit (CmmInt i _)]
    
    293
    -  |     -- powerPC NCG has a TODO for I8/I16 comparisons, so don't try
    
    294
    -    platformArch platform `elem` [ArchX86, ArchX86_64],
    
    295
    -        -- if the operand is widened:
    
    293
    +  |     -- if the operand is widened:
    
    296 294
         Just (rep, signed, narrow_fn) <- maybe_conversion conv,
    
    297 295
             -- and this is a comparison operation:
    
    298 296
         Just narrow_cmp <- maybe_comparison cmp rep signed,
    

  • hadrian/doc/flavours.md
    ... ... @@ -242,6 +242,10 @@ The supported transformers are listed below:
    242 242
             <td><code>ubsan</code></td>
    
    243 243
             <td>Build all stage1+ C/C++ code with UndefinedBehaviorSanitizer support</td>
    
    244 244
         </tr>
    
    245
    +    <tr>
    
    246
    +        <td><code>asan</code></td>
    
    247
    +        <td>Build all stage1+ C/C++ code with AddressSanitizer support</td>
    
    248
    +    </tr>
    
    245 249
         <tr>
    
    246 250
             <td><code>llvm</code></td>
    
    247 251
             <td>Use GHC's LLVM backend (`-fllvm`) for all stage1+ compilation.</td>
    

  • hadrian/src/Flavour.hs
    ... ... @@ -8,6 +8,7 @@ module Flavour
    8 8
       , splitSections
    
    9 9
       , enableThreadSanitizer
    
    10 10
       , enableUBSan
    
    11
    +  , enableASan
    
    11 12
       , enableLateCCS
    
    12 13
       , enableHashUnitIds
    
    13 14
       , enableDebugInfo, enableTickyGhc
    
    ... ... @@ -56,6 +57,7 @@ flavourTransformers = M.fromList
    56 57
         , "thread_sanitizer" =: enableThreadSanitizer False
    
    57 58
         , "thread_sanitizer_cmm" =: enableThreadSanitizer True
    
    58 59
         , "ubsan"            =: enableUBSan
    
    60
    +    , "asan"             =: enableASan
    
    59 61
         , "llvm"             =: viaLlvmBackend
    
    60 62
         , "profiled_ghc"     =: enableProfiledGhc
    
    61 63
         , "no_dynamic_ghc"   =: disableDynamicGhcPrograms
    
    ... ... @@ -303,6 +305,28 @@ enableUBSan =
    303 305
               builder Testsuite ? arg "--config=have_ubsan=True"
    
    304 306
             ]
    
    305 307
     
    
    308
    +-- | Build all stage1+ C/C++ code with AddressSanitizer support:
    
    309
    +-- https://clang.llvm.org/docs/AddressSanitizer.html
    
    310
    +enableASan :: Flavour -> Flavour
    
    311
    +enableASan =
    
    312
    +  addArgs $
    
    313
    +    notStage0
    
    314
    +      ? mconcat
    
    315
    +        [ package rts
    
    316
    +            ? builder (Cabal Flags)
    
    317
    +            ? arg "+asan"
    
    318
    +            <> (needSharedLibSAN ? arg "+shared-libsan"),
    
    319
    +          builder (Ghc CompileHs) ? arg "-optc-fsanitize=address",
    
    320
    +          builder (Ghc CompileCWithGhc) ? arg "-optc-fsanitize=address",
    
    321
    +          builder (Ghc CompileCppWithGhc) ? arg "-optcxx-fsanitize=address",
    
    322
    +          builder (Ghc LinkHs)
    
    323
    +            ? arg "-optc-fsanitize=address"
    
    324
    +            <> arg "-optl-fsanitize=address"
    
    325
    +            <> (needSharedLibSAN ? arg "-optl-shared-libsan"),
    
    326
    +          builder (Cc CompileC) ? arg "-fsanitize=address",
    
    327
    +          builder Testsuite ? arg "--config=have_asan=True"
    
    328
    +        ]
    
    329
    +
    
    306 330
     -- | Use the LLVM backend in stages 1 and later.
    
    307 331
     viaLlvmBackend :: Flavour -> Flavour
    
    308 332
     viaLlvmBackend = addArgs $ notStage0 ? builder Ghc ? arg "-fllvm"
    

  • hadrian/src/Hadrian/Haskell/Cabal/Type.hs
    ... ... @@ -31,7 +31,7 @@ data PackageData = PackageData
    31 31
         , description               :: String
    
    32 32
         , packageDependencies       :: [Package]
    
    33 33
         , genericPackageDescription :: GenericPackageDescription
    
    34
    -    } deriving (Eq, Generic, Show, Typeable)
    
    34
    +    } deriving (Eq, Generic, Show)
    
    35 35
     
    
    36 36
     -- | Haskell package metadata obtained after resolving package configuration
    
    37 37
     -- flags and associated conditionals according to the current build context.
    
    ... ... @@ -75,7 +75,7 @@ data ContextData = ContextData
    75 75
         , contextLibdir    :: FilePath
    
    76 76
         -- The location where dynamic libraries go
    
    77 77
         , contextDynLibdir :: FilePath
    
    78
    -    } deriving (Eq, Generic, Show, Typeable)
    
    78
    +    } deriving (Eq, Generic, Show)
    
    79 79
     
    
    80 80
     instance Binary   PackageData
    
    81 81
     instance Hashable PackageData where hashWithSalt salt = hashWithSalt salt . show
    

  • hadrian/src/Hadrian/Haskell/Hash.hs
    ... ... @@ -108,7 +108,7 @@ data PackageHashConfigInputs = PackageHashConfigInputs {
    108 108
       deriving Show
    
    109 109
     
    
    110 110
     newtype PkgHashKey = PkgHashKey (Stage, Package)
    
    111
    -  deriving (Binary, Eq, Hashable, NFData, Show, Typeable)
    
    111
    +  deriving (Binary, Eq, Hashable, NFData, Show)
    
    112 112
     type instance RuleResult PkgHashKey = String
    
    113 113
     
    
    114 114
     pkgHash :: Stage -> Package -> Action String
    

  • hadrian/src/Hadrian/Oracles/ArgsHash.hs
    ... ... @@ -38,7 +38,7 @@ trackArgsHash t = do
    38 38
         void (askOracle $ ArgsHash hashedTarget :: Action Int)
    
    39 39
     
    
    40 40
     newtype ArgsHash c b = ArgsHash (Target c b)
    
    41
    -    deriving (Binary, Eq, Hashable, NFData, Show, Typeable)
    
    41
    +    deriving (Binary, Eq, Hashable, NFData, Show)
    
    42 42
     type instance RuleResult (ArgsHash c b) = Int
    
    43 43
     
    
    44 44
     -- | This oracle stores per-target argument list hashes in the Shake database,
    

  • hadrian/src/Hadrian/Oracles/Cabal/Type.hs
    ... ... @@ -26,13 +26,13 @@ import Stage
    26 26
     -- | This type of oracle key is used by 'Hadrian.Oracles.Cabal.readPackageData'
    
    27 27
     -- to cache reading and parsing of 'Hadrian.Haskell.Cabal.Type.PackageData'.
    
    28 28
     newtype PackageDataKey = PackageDataKey Package
    
    29
    -    deriving (Binary, Eq, Hashable, NFData, Show, Typeable)
    
    29
    +    deriving (Binary, Eq, Hashable, NFData, Show)
    
    30 30
     type instance RuleResult PackageDataKey = PackageData
    
    31 31
     
    
    32 32
     -- | This type of oracle key is used by 'Hadrian.Oracles.Cabal.readContextData'
    
    33 33
     -- to cache reading and parsing of 'Hadrian.Haskell.Cabal.Type.ContextData'.
    
    34 34
     newtype ContextDataKey = ContextDataKey Context
    
    35
    -    deriving (Binary, Eq, Hashable, NFData, Show, Typeable)
    
    35
    +    deriving (Binary, Eq, Hashable, NFData, Show)
    
    36 36
     type instance RuleResult ContextDataKey = ContextData
    
    37 37
     
    
    38 38
     -- TODO: Should @PackageConfiguration@ be simply @()@? Presumably the pair
    
    ... ... @@ -40,7 +40,7 @@ type instance RuleResult ContextDataKey = ContextData
    40 40
     -- | The result of Cabal package configuration produced by the oracle
    
    41 41
     -- 'Hadrian.Oracles.Cabal.configurePackageGHC'.
    
    42 42
     newtype PackageConfiguration = PackageConfiguration (C.Compiler, C.Platform)
    
    43
    -    deriving (Binary, Eq, Show, Typeable)
    
    43
    +    deriving (Binary, Eq, Show)
    
    44 44
     
    
    45 45
     instance NFData PackageConfiguration where
    
    46 46
         rnf (PackageConfiguration (c, p)) =
    
    ... ... @@ -58,5 +58,5 @@ instance Hashable PackageConfiguration where
    58 58
     -- | This type of oracle key is used by 'Hadrian.Oracles.Cabal.configurePackageGHC'
    
    59 59
     -- to cache configuration of a Cabal package.
    
    60 60
     newtype PackageConfigurationKey = PackageConfigurationKey (Package, Stage)
    
    61
    -    deriving (Binary, Eq, Hashable, NFData, Show, Typeable)
    
    61
    +    deriving (Binary, Eq, Hashable, NFData, Show)
    
    62 62
     type instance RuleResult PackageConfigurationKey = PackageConfiguration

  • hadrian/src/Hadrian/Oracles/DirectoryContents.hs
    ... ... @@ -15,7 +15,7 @@ import Hadrian.Utilities
    15 15
     import qualified System.Directory.Extra as IO
    
    16 16
     
    
    17 17
     data Match = Test FilePattern | Not Match | And [Match] | Or [Match]
    
    18
    -    deriving (Generic, Eq, Show, Typeable)
    
    18
    +    deriving (Generic, Eq, Show)
    
    19 19
     
    
    20 20
     instance Binary   Match
    
    21 21
     instance Hashable Match
    
    ... ... @@ -54,7 +54,7 @@ copyDirectoryContentsUntracked expr source target = do
    54 54
         mapM_ cp =<< directoryContents expr source
    
    55 55
     
    
    56 56
     newtype DirectoryContents = DirectoryContents (Match, FilePath)
    
    57
    -    deriving (Binary, Eq, Hashable, NFData, Show, Typeable)
    
    57
    +    deriving (Binary, Eq, Hashable, NFData, Show)
    
    58 58
     type instance RuleResult DirectoryContents = [FilePath]
    
    59 59
     
    
    60 60
     -- | This oracle answers 'directoryContents' queries and tracks the results.
    

  • hadrian/src/Hadrian/Oracles/Path.hs
    ... ... @@ -34,11 +34,11 @@ fixAbsolutePathOnWindows path =
    34 34
             return path
    
    35 35
     
    
    36 36
     newtype LookupInPath = LookupInPath String
    
    37
    -    deriving (Binary, Eq, Hashable, NFData, Show, Typeable)
    
    37
    +    deriving (Binary, Eq, Hashable, NFData, Show)
    
    38 38
     type instance RuleResult LookupInPath = String
    
    39 39
     
    
    40 40
     newtype WindowsPath = WindowsPath FilePath
    
    41
    -    deriving (Binary, Eq, Hashable, NFData, Show, Typeable)
    
    41
    +    deriving (Binary, Eq, Hashable, NFData, Show)
    
    42 42
     type instance RuleResult WindowsPath = String
    
    43 43
     
    
    44 44
     -- | Oracles for looking up paths. These are slow and require caching.
    

  • hadrian/src/Hadrian/Oracles/TextFile.hs
    ... ... @@ -118,15 +118,15 @@ queryTargetTarget :: (Toolchain.Target -> a) -> Action a
    118 118
     queryTargetTarget f = f <$> getTargetTarget
    
    119 119
     
    
    120 120
     newtype KeyValue = KeyValue (FilePath, String)
    
    121
    -    deriving (Binary, Eq, Hashable, NFData, Show, Typeable)
    
    121
    +    deriving (Binary, Eq, Hashable, NFData, Show)
    
    122 122
     type instance RuleResult KeyValue = Maybe String
    
    123 123
     
    
    124 124
     newtype KeyValues = KeyValues (FilePath, String)
    
    125
    -    deriving (Binary, Eq, Hashable, NFData, Show, Typeable)
    
    125
    +    deriving (Binary, Eq, Hashable, NFData, Show)
    
    126 126
     type instance RuleResult KeyValues = Maybe [String]
    
    127 127
     
    
    128 128
     newtype TargetFile = TargetFile FilePath
    
    129
    -    deriving (Binary, Eq, Hashable, NFData, Show, Typeable)
    
    129
    +    deriving (Binary, Eq, Hashable, NFData, Show)
    
    130 130
     type instance RuleResult TargetFile = Toolchain.Target
    
    131 131
     
    
    132 132
     -- | These oracle rules are used to cache and track answers to the following
    

  • hadrian/src/Hadrian/Utilities.hs
    ... ... @@ -298,7 +298,7 @@ userSettingRules defaultValue = do
    298 298
         extra <- shakeExtra <$> getShakeOptionsRules
    
    299 299
         return $ lookupExtra defaultValue extra
    
    300 300
     
    
    301
    -newtype BuildRoot = BuildRoot FilePath deriving (Typeable, Eq, Show)
    
    301
    +newtype BuildRoot = BuildRoot FilePath deriving (Eq, Show)
    
    302 302
     
    
    303 303
     -- | All build results are put into the 'buildRoot' directory.
    
    304 304
     buildRoot :: Action FilePath
    
    ... ... @@ -484,7 +484,6 @@ putColoured code msg = do
    484 484
             else putInfo msg
    
    485 485
     
    
    486 486
     newtype BuildProgressColour = BuildProgressColour String
    
    487
    -    deriving Typeable
    
    488 487
     
    
    489 488
     -- | By default, Hadrian tries to figure out if the current terminal
    
    490 489
     --   supports colors using this function. The default can be overridden
    
    ... ... @@ -511,7 +510,6 @@ putBuild msg = do
    511 510
         putColoured code msg
    
    512 511
     
    
    513 512
     newtype SuccessColour = SuccessColour String
    
    514
    -    deriving Typeable
    
    515 513
     
    
    516 514
     -- | Generate an encoded colour for successful output from names
    
    517 515
     mkSuccessColour :: Colour -> SuccessColour
    
    ... ... @@ -528,7 +526,6 @@ putSuccess msg = do
    528 526
         putColoured code msg
    
    529 527
     
    
    530 528
     newtype FailureColour = FailureColour String
    
    531
    -    deriving Typeable
    
    532 529
     
    
    533 530
     -- | Generate an encoded colour for failure output messages
    
    534 531
     mkFailureColour :: Colour -> FailureColour
    
    ... ... @@ -544,7 +541,7 @@ putFailure msg = do
    544 541
       FailureColour code <- userSetting red
    
    545 542
       putColoured code msg
    
    546 543
     
    
    547
    -data ProgressInfo = None | Brief | Normal | Unicorn deriving (Eq, Show, Typeable)
    
    544
    +data ProgressInfo = None | Brief | Normal | Unicorn deriving (Eq, Show)
    
    548 545
     
    
    549 546
     -- | Version of 'putBuild' controlled by @--progress-info@ command line argument.
    
    550 547
     putProgressInfo :: String -> Action ()
    

  • hadrian/src/Oracles/Flavour.hs
    ... ... @@ -14,11 +14,11 @@ import Flavour
    14 14
     import Settings (flavour)
    
    15 15
     
    
    16 16
     newtype DynGhcPrograms =
    
    17
    -  DynGhcPrograms () deriving (Show, Typeable, Eq, Hashable, Binary, NFData)
    
    17
    +  DynGhcPrograms () deriving (Show, Eq, Hashable, Binary, NFData)
    
    18 18
     type instance RuleResult DynGhcPrograms = Bool
    
    19 19
     
    
    20 20
     newtype GhcProfiled =
    
    21
    -  GhcProfiled Stage deriving (Show, Typeable, Eq, Hashable, Binary, NFData)
    
    21
    +  GhcProfiled Stage deriving (Show, Eq, Hashable, Binary, NFData)
    
    22 22
     type instance RuleResult GhcProfiled = Bool
    
    23 23
     
    
    24 24
     oracles :: Rules ()
    

  • hadrian/src/Oracles/ModuleFiles.hs
    ... ... @@ -16,11 +16,11 @@ import Expression
    16 16
     type ModuleName = String
    
    17 17
     
    
    18 18
     newtype ModuleFiles = ModuleFiles (Stage, Package)
    
    19
    -    deriving (Binary, Eq, Hashable, NFData, Show, Typeable)
    
    19
    +    deriving (Binary, Eq, Hashable, NFData, Show)
    
    20 20
     type instance RuleResult ModuleFiles = [Maybe FilePath]
    
    21 21
     
    
    22 22
     newtype Generator = Generator (Stage, Package, FilePath)
    
    23
    -    deriving (Binary, Eq, Hashable, NFData, Show, Typeable)
    
    23
    +    deriving (Binary, Eq, Hashable, NFData, Show)
    
    24 24
     type instance RuleResult Generator = Maybe FilePath
    
    25 25
     
    
    26 26
     -- | We scan for the following Haskell source extensions when looking for module
    

  • rts/.ubsan-suppressions
    1
    +# libraries/bytestring/cbits/is-valid-utf8.c:66:14: runtime load of misaligned address 0x7ae45206f112 for type 'const uint64_t *' (aka 'const unsigned long *'), which requires 8 byte alignment
    
    2
    +alignment:libraries/bytestring/cbits/is-valid-utf8.c
    
    3
    +
    
    1 4
     # libraries/text/cbits/measure_off.c:50:39: runtime left shift of 1 by 31 places cannot be represented in type 'int'
    
    2 5
     shift-base:libraries/text/cbits/measure_off.c
    
    3 6
     
    

  • rts/include/Stg.h
    ... ... @@ -335,6 +335,7 @@ external prototype return neither of these types to workaround #11395.
    335 335
     #include "stg/MachRegsForHost.h"
    
    336 336
     #include "stg/Regs.h"
    
    337 337
     #include "stg/Ticky.h"
    
    338
    +#include "rts/ASANUtils.h"
    
    338 339
     #include "rts/TSANUtils.h"
    
    339 340
     
    
    340 341
     #if IN_STG_CODE
    

  • rts/include/rts/ASANUtils.h
    1
    +#pragma once
    
    2
    +
    
    3
    +#if defined(__SANITIZE_ADDRESS__)
    
    4
    +#define ASAN_ENABLED
    
    5
    +#elif defined(__has_feature)
    
    6
    +#if __has_feature(address_sanitizer)
    
    7
    +#define ASAN_ENABLED
    
    8
    +#endif
    
    9
    +#endif
    
    10
    +
    
    11
    +#if defined(ASAN_ENABLED)
    
    12
    +#include <sanitizer/asan_interface.h>
    
    13
    +#define USED_IF_ASAN
    
    14
    +#else
    
    15
    +#include <stdlib.h>
    
    16
    +#define USED_IF_ASAN __attribute__((unused))
    
    17
    +#endif
    
    18
    +
    
    19
    +static inline void
    
    20
    +__ghc_asan_poison_memory_region(void const volatile *addr USED_IF_ASAN,
    
    21
    +                                size_t size USED_IF_ASAN) {
    
    22
    +#if defined(ASAN_ENABLED)
    
    23
    +  __asan_poison_memory_region(addr, size);
    
    24
    +#endif
    
    25
    +}
    
    26
    +
    
    27
    +static inline void
    
    28
    +__ghc_asan_unpoison_memory_region(void const volatile *addr USED_IF_ASAN,
    
    29
    +                                  size_t size USED_IF_ASAN) {
    
    30
    +#if defined(ASAN_ENABLED)
    
    31
    +  __asan_unpoison_memory_region(addr, size);
    
    32
    +#endif
    
    33
    +}

  • rts/rts.cabal
    ... ... @@ -97,6 +97,12 @@ flag ubsan
    97 97
         UndefinedBehaviorSanitizer.
    
    98 98
       default: False
    
    99 99
       manual: True
    
    100
    +flag asan
    
    101
    +  description:
    
    102
    +    Link with -fsanitize=address, to be enabled when building with
    
    103
    +    AddressSanitizer.
    
    104
    +  default: False
    
    105
    +  manual: True
    
    100 106
     flag shared-libsan
    
    101 107
       description:
    
    102 108
         Link with -shared-libsan, to guarantee only one copy of the
    
    ... ... @@ -216,6 +222,9 @@ library
    216 222
           if flag(ubsan)
    
    217 223
             ld-options: -fsanitize=undefined
    
    218 224
     
    
    225
    +      if flag(asan)
    
    226
    +        ld-options: -fsanitize=address
    
    227
    +
    
    219 228
           if flag(shared-libsan)
    
    220 229
             ld-options: -shared-libsan
    
    221 230
     
    
    ... ... @@ -280,6 +289,7 @@ library
    280 289
                             -- ^ generated
    
    281 290
                             rts/ghc_ffi.h
    
    282 291
                             rts/Adjustor.h
    
    292
    +                        rts/ASANUtils.h
    
    283 293
                             rts/ExecPage.h
    
    284 294
                             rts/BlockSignals.h
    
    285 295
                             rts/Bytecodes.h
    

  • rts/sm/MBlock.c
    ... ... @@ -579,6 +579,8 @@ getMBlocks(uint32_t n)
    579 579
     
    
    580 580
         ret = getCommittedMBlocks(n);
    
    581 581
     
    
    582
    +    __ghc_asan_unpoison_memory_region(ret, (W_)n * MBLOCK_SIZE);
    
    583
    +
    
    582 584
         debugTrace(DEBUG_gc, "allocated %d megablock(s) at %p",n,ret);
    
    583 585
     
    
    584 586
         mblocks_allocated += n;
    
    ... ... @@ -611,6 +613,8 @@ freeMBlocks(void *addr, uint32_t n)
    611 613
     
    
    612 614
         mblocks_allocated -= n;
    
    613 615
     
    
    616
    +    __ghc_asan_poison_memory_region(addr, (W_)n * MBLOCK_SIZE);
    
    617
    +
    
    614 618
         decommitMBlocks(addr, n);
    
    615 619
     }
    
    616 620
     
    

  • testsuite/driver/testglobals.py
    ... ... @@ -189,6 +189,9 @@ class TestConfig:
    189 189
             # Are we running with UndefinedBehaviorSanitizer enabled?
    
    190 190
             self.have_ubsan = False
    
    191 191
     
    
    192
    +        # Are we running with AddressSanitizer enabled?
    
    193
    +        self.have_asan = False
    
    194
    +
    
    192 195
             # Do symbols use leading underscores?
    
    193 196
             self.leading_underscore = False
    
    194 197
     
    

  • testsuite/driver/testlib.py
    ... ... @@ -1093,6 +1093,9 @@ def have_thread_sanitizer( ) -> bool:
    1093 1093
     def have_ubsan( ) -> bool:
    
    1094 1094
         return config.have_ubsan
    
    1095 1095
     
    
    1096
    +def have_asan( ) -> bool:
    
    1097
    +    return config.have_asan
    
    1098
    +
    
    1096 1099
     def gcc_as_cmmp() -> bool:
    
    1097 1100
         return config.cmm_cpp_is_gcc
    
    1098 1101
     
    

  • testsuite/tests/rts/T18623/all.T
    ... ... @@ -8,6 +8,8 @@ test('T18623',
    8 8
          # Recent versions of osx report an error when running `ulimit -v`
    
    9 9
          when(opsys('darwin'), skip),
    
    10 10
          when(arch('powerpc64le'), skip),
    
    11
    +     # ASan can't allocate shadow memory
    
    12
    +     when(have_asan(), skip),
    
    11 13
          cmd_prefix('ulimit -v ' + str(8 * 1024 ** 2) + ' && '),
    
    12 14
          ignore_stdout],
    
    13 15
         run_command,