| ... |
... |
@@ -7,6 +7,7 @@ module Flavour |
|
7
|
7
|
, addArgs
|
|
8
|
8
|
, splitSections
|
|
9
|
9
|
, enableThreadSanitizer
|
|
|
10
|
+ , enableUBSan
|
|
10
|
11
|
, enableLateCCS
|
|
11
|
12
|
, enableHashUnitIds
|
|
12
|
13
|
, enableDebugInfo, enableTickyGhc
|
| ... |
... |
@@ -33,6 +34,9 @@ import Data.Either |
|
33
|
34
|
import Data.Map (Map)
|
|
34
|
35
|
import qualified Data.Map as M
|
|
35
|
36
|
import qualified Data.Set as Set
|
|
|
37
|
+import GHC.Platform.ArchOS
|
|
|
38
|
+import Oracles.Flag
|
|
|
39
|
+import Oracles.Setting
|
|
36
|
40
|
import Packages
|
|
37
|
41
|
import Flavour.Type
|
|
38
|
42
|
import Settings.Parser
|
| ... |
... |
@@ -53,6 +57,7 @@ flavourTransformers = M.fromList |
|
53
|
57
|
, "no_split_sections" =: noSplitSections
|
|
54
|
58
|
, "thread_sanitizer" =: enableThreadSanitizer False
|
|
55
|
59
|
, "thread_sanitizer_cmm" =: enableThreadSanitizer True
|
|
|
60
|
+ , "ubsan" =: enableUBSan
|
|
56
|
61
|
, "llvm" =: viaLlvmBackend
|
|
57
|
62
|
, "profiled_ghc" =: enableProfiledGhc
|
|
58
|
63
|
, "no_dynamic_ghc" =: disableDynamicGhcPrograms
|
| ... |
... |
@@ -258,6 +263,66 @@ enableThreadSanitizer instrumentCmm = addArgs $ notStage0 ? mconcat |
|
258
|
263
|
]
|
|
259
|
264
|
]
|
|
260
|
265
|
|
|
|
266
|
+-- | Whether or not -shared-libsan should be passed to clang at
|
|
|
267
|
+-- link-time.
|
|
|
268
|
+--
|
|
|
269
|
+-- See
|
|
|
270
|
+-- https://github.com/llvm/llvm-project/blob/llvmorg-21.1.5/clang/lib/Driver/SanitizerArgs.cpp#L1008,
|
|
|
271
|
+-- clang defaults to -shared-libsan on darwin/windows and
|
|
|
272
|
+-- -static-libsan on linux. In general, -static-libsan is incredibly
|
|
|
273
|
+-- problematic when multiple copies of the sanitizer runtimes coexist
|
|
|
274
|
+-- in the same address space due to being linked into multiple Haskell
|
|
|
275
|
+-- libraries. So we should explicitly specify `-shared-libsan` if
|
|
|
276
|
+-- needed.
|
|
|
277
|
+--
|
|
|
278
|
+-- A small downside of -shared-libsan is the clang-specific sanitizer
|
|
|
279
|
+-- runtime shared library path needs to be manually specified via
|
|
|
280
|
+-- @export LD_LIBRARY_PATH=$(dirname $(clang -print-libgcc-file-name
|
|
|
281
|
+-- -rtlib=compiler-rt))@ for ld.so to find it at runtime.
|
|
|
282
|
+needSharedLibSAN :: Action Bool
|
|
|
283
|
+needSharedLibSAN = do
|
|
|
284
|
+ is_clang <- flag CcLlvmBackend
|
|
|
285
|
+ is_default_shared_libsan <- anyTargetOs [OSDarwin, OSMinGW32]
|
|
|
286
|
+ pure $ is_clang && not is_default_shared_libsan
|
|
|
287
|
+
|
|
|
288
|
+-- | Build all stage1+ C/C++ code with UndefinedBehaviorSanitizer
|
|
|
289
|
+-- support:
|
|
|
290
|
+-- https://clang.llvm.org/docs/UndefinedBehaviorSanitizer.html.
|
|
|
291
|
+--
|
|
|
292
|
+-- Note that we also pass -fno-sanitize=function to clang, since
|
|
|
293
|
+-- "runtime call to function foo through pointer to incorrect function
|
|
|
294
|
+-- type" is unfortunately pretty common (e.g. evac_fn in rts) and
|
|
|
295
|
+-- impact the signal to noise ratio of UBSAN warnings. gcc doesn't
|
|
|
296
|
+-- implement this instrumentation though.
|
|
|
297
|
+enableUBSan :: Flavour -> Flavour
|
|
|
298
|
+enableUBSan =
|
|
|
299
|
+ addArgs $
|
|
|
300
|
+ notStage0
|
|
|
301
|
+ ? mconcat
|
|
|
302
|
+ [ package rts
|
|
|
303
|
+ ? builder (Cabal Flags)
|
|
|
304
|
+ ? arg "+ubsan"
|
|
|
305
|
+ <> (needSharedLibSAN ? arg "+shared-libsan"),
|
|
|
306
|
+ builder (Ghc CompileHs)
|
|
|
307
|
+ ? arg "-optc-fsanitize=undefined"
|
|
|
308
|
+ <> (flag CcLlvmBackend ? arg "-optc-fno-sanitize=function"),
|
|
|
309
|
+ builder (Ghc CompileCWithGhc)
|
|
|
310
|
+ ? arg "-optc-fsanitize=undefined"
|
|
|
311
|
+ <> (flag CcLlvmBackend ? arg "-optc-fno-sanitize=function"),
|
|
|
312
|
+ builder (Ghc CompileCppWithGhc)
|
|
|
313
|
+ ? arg "optcxx-fsanitize=undefined"
|
|
|
314
|
+ <> (flag CcLlvmBackend ? arg "-optcxx-fno-sanitize=function"),
|
|
|
315
|
+ builder (Ghc LinkHs)
|
|
|
316
|
+ ? arg "-optc-fsanitize=undefined"
|
|
|
317
|
+ <> arg "-optl-fsanitize=undefined"
|
|
|
318
|
+ <> (needSharedLibSAN ? arg "-optl-shared-libsan")
|
|
|
319
|
+ <> (flag CcLlvmBackend ? arg "-optc-fno-sanitize=function"),
|
|
|
320
|
+ builder (Cc CompileC)
|
|
|
321
|
+ ? arg "-fsanitize=undefined"
|
|
|
322
|
+ <> (flag CcLlvmBackend ? arg "-fno-sanitize=function"),
|
|
|
323
|
+ builder Testsuite ? arg "--config=have_ubsan=True"
|
|
|
324
|
+ ]
|
|
|
325
|
+
|
|
261
|
326
|
-- | Use the LLVM backend in stages 1 and later.
|
|
262
|
327
|
viaLlvmBackend :: Flavour -> Flavour
|
|
263
|
328
|
viaLlvmBackend = addArgs $ notStage0 ? builder Ghc ? arg "-fllvm"
|