[Git][ghc/ghc][wip/T23096] codeGen/tsan: Disable instrumentation of unaligned stores

Ben Gamari (@bgamari) gitlab at gitlab.haskell.org
Thu Mar 9 14:59:39 UTC 2023



Ben Gamari pushed to branch wip/T23096 at Glasgow Haskell Compiler / GHC


Commits:
b5bbc334 by Ben Gamari at 2023-03-09T09:59:35-05:00
codeGen/tsan: Disable instrumentation of unaligned stores

There is some disagreement regarding the prototype of
`__tsan_unaligned_write` (specifically whether it takes just the written
address, or the address and the value as an argument). Moreover, I have
observed crashes which appear to be due to it. Disable instrumentation
of unaligned stores as a temporary mitigation.

Fixes #23096.

- - - - -


1 changed file:

- compiler/GHC/Cmm/ThreadSanitizer.hs


Changes:

=====================================
compiler/GHC/Cmm/ThreadSanitizer.hs
=====================================
@@ -54,11 +54,13 @@ annotateNode env node =
       CmmTick{}               -> BMiddle node
       CmmUnwind{}             -> BMiddle node
       CmmAssign{}             -> annotateNodeOO env node
-      CmmStore lhs rhs align  ->
+      -- TODO: Track unaligned stores
+      CmmStore lhs rhs Unaligned  -> annotateNodeOO env node
+      CmmStore lhs rhs NaturallyAligned  ->
           let ty = cmmExprType (platform env) rhs
               rhs_nodes = annotateLoads env (collectExprLoads rhs)
               lhs_nodes = annotateLoads env (collectExprLoads lhs)
-              st        = tsanStore env align ty lhs
+              st        = tsanStore env ty lhs
           in rhs_nodes `blockAppend` lhs_nodes `blockAppend` st `blockSnoc` node
       CmmUnsafeForeignCall (PrimTarget op) formals args ->
           let node' = fromMaybe (BMiddle node) (annotatePrim env op formals args)
@@ -197,17 +199,14 @@ tsanTarget fn formals args =
     lbl = mkForeignLabel fn Nothing ForeignLabelInExternalPackage IsFunction
 
 tsanStore :: Env
-          -> AlignmentSpec -> CmmType -> CmmExpr
+          -> CmmType -> CmmExpr
           -> Block CmmNode O O
-tsanStore env align ty addr =
+tsanStore env ty addr =
     mkUnsafeCall env ftarget [] [addr]
   where
     ftarget = tsanTarget fn [] [AddrHint]
     w = widthInBytes (typeWidth ty)
-    fn = case align of
-           Unaligned
-             | w > 1    -> fsLit $ "__tsan_unaligned_write" ++ show w
-           _            -> fsLit $ "__tsan_write" ++ show w
+    fn = fsLit $ "__tsan_write" ++ show w
 
 tsanLoad :: Env
          -> AlignmentSpec -> CmmType -> CmmExpr



View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/b5bbc3349764f8fcbca49ee83370cfdff2a69460

-- 
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/b5bbc3349764f8fcbca49ee83370cfdff2a69460
You're receiving this email because of your account on gitlab.haskell.org.


-------------- next part --------------
An HTML attachment was scrubbed...
URL: <http://mail.haskell.org/pipermail/ghc-commits/attachments/20230309/519ba706/attachment-0001.html>


More information about the ghc-commits mailing list