[Git][ghc/ghc][wip/wasm-no-tmp-callee] 2 commits: compiler: avoid saving foreign call target to local when there are no caller-save GlobalRegs

Cheng Shao (@TerrorJack) gitlab at gitlab.haskell.org
Thu May 23 18:38:09 UTC 2024



Cheng Shao pushed to branch wip/wasm-no-tmp-callee at Glasgow Haskell Compiler / GHC


Commits:
0c7651a1 by Cheng Shao at 2024-05-23T18:37:44+00:00
compiler: avoid saving foreign call target to local when there are no caller-save GlobalRegs

This patch makes the STG->Cmm backend avoid saving foreign call target
to local when there are no caller-save GlobalRegs.

Since 321941a8ebe25192cdeece723e1058f2f47809ea, when we lower a
foreign call, we unconditionally save the foreign call target to a
temporary local first, then rely on cmmSink to clean it up later,
which only happens with -fcmm-sink (implied by -O) and not in
unoptimized code.

And this is troublesome for the wasm backend NCG, which needs to infer
a foreign call target symbol's type signature from the Cmm call site.
Previously, the NCG has been emitting incorrect type signatures for
unoptimized code, which happens to work with `wasm-ld` most of the
time, but this is never future-proof against upstream toolchain
updates, and it causes horrible breakages when LTO objects are
included in linker input. Hence this patch.

- - - - -
09d6d0e4 by Cheng Shao at 2024-05-23T18:37:57+00:00
testsuite: add callee-no-local regression test

- - - - -


6 changed files:

- compiler/GHC/Driver/Config/StgToCmm.hs
- compiler/GHC/StgToCmm/Config.hs
- compiler/GHC/StgToCmm/Foreign.hs
- testsuite/tests/codeGen/should_compile/all.T
- + testsuite/tests/codeGen/should_compile/callee-no-local.hs
- + testsuite/tests/codeGen/should_compile/callee-no-local.stderr


Changes:

=====================================
compiler/GHC/Driver/Config/StgToCmm.hs
=====================================
@@ -14,6 +14,7 @@ import GHC.Driver.Backend
 import GHC.Driver.Session
 import GHC.Platform
 import GHC.Platform.Profile
+import GHC.Platform.Regs
 import GHC.Utils.Error
 import GHC.Unit.Module
 import GHC.Utils.Outputable
@@ -84,6 +85,8 @@ initStgToCmmConfig dflags mod = StgToCmmConfig
   , stgToCmmAvx2          = isAvx2Enabled                  dflags
   , stgToCmmAvx512f       = isAvx512fEnabled               dflags
   , stgToCmmTickyAP       = gopt Opt_Ticky_AP dflags
+  -- See Note [Saving foreign call target to local]
+  , stgToCmmSaveFCallTargetToLocal = any (callerSaves platform) $ activeStgRegs platform
   } where profile  = targetProfile dflags
           platform = profilePlatform profile
           bk_end  = backend dflags


=====================================
compiler/GHC/StgToCmm/Config.hs
=====================================
@@ -73,6 +73,8 @@ data StgToCmmConfig = StgToCmmConfig
   , stgToCmmAllowWordMul2Instr        :: !Bool   -- ^ Allowed to generate WordMul2 instruction
   , stgToCmmAllowFMAInstr             :: FMASign -> Bool -- ^ Allowed to generate FMA instruction
   , stgToCmmTickyAP                   :: !Bool   -- ^ Disable use of precomputed standard thunks.
+  , stgToCmmSaveFCallTargetToLocal    :: !Bool   -- ^ Save a foreign call target to a Cmm local, see
+                                                 -- Note [Saving foreign call target to local] for details
   ------------------------------ SIMD flags ------------------------------------
   -- Each of these flags checks vector compatibility with the backend requested
   -- during compilation. In essence, this means checking for @-fllvm@ which is


=====================================
compiler/GHC/StgToCmm/Foreign.hs
=====================================
@@ -277,23 +277,83 @@ load_target_into_temp (ForeignTarget expr conv) = do
 load_target_into_temp other_target@(PrimTarget _) =
   return other_target
 
+-- Note [Saving foreign call target to local]
+-- ~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~
+--
 -- What we want to do here is create a new temporary for the foreign
 -- call argument if it is not safe to use the expression directly,
 -- because the expression mentions caller-saves GlobalRegs (see
 -- Note [Register parameter passing]).
 --
 -- However, we can't pattern-match on the expression here, because
--- this is used in a loop by GHC.Cmm.Parser, and testing the expression
--- results in a black hole.  So we always create a temporary, and rely
--- on GHC.Cmm.Sink to clean it up later.  (Yuck, ToDo).  The generated code
--- ends up being the same, at least for the RTS .cmm code.
+-- this is used in a loop by GHC.Cmm.Parser, and testing the
+-- expression results in a black hole.  So when there exist
+-- caller-saves GlobalRegs, we create a temporary, and rely on
+-- GHC.Cmm.Sink to clean it up later. The generated code ends up being
+-- the same if -fcmm-sink is enabled (implied by -O).
+--
+-- When there doesn't exist caller-save GlobalRegs, keep the original
+-- target in place. This matters for the wasm backend, otherwise it
+-- cannot infer the target symbol's correct foreign function type in
+-- unoptimized Cmm. For instance:
+--
+-- foreign import ccall unsafe "foo" c_foo :: IO ()
+--
+-- Without optimization, previously this would lower to something like:
+--
+-- [Test.c_foo_entry() { //  []
+--          { []
+--          }
+--      {offset
+--        cDk:
+--            goto cDm;
+--        cDm:
+--            _cDj::I32 = foo;
+--            call "ccall" arg hints:  []  result hints:  [] (_cDj::I32)();
+--            R1 = GHC.Tuple.()_closure+1;
+--            call (I32[P32[Sp]])(R1) args: 4, res: 0, upd: 4;
+--      }
+--  },
 --
+-- The wasm backend only sees "foo" being assigned to a local, but
+-- there's no type signature associated with a CLabel! So it has to
+-- emit a dummy .functype directive and fingers crossed that wasm-ld
+-- tolerates function type mismatch. THis is horrible, not future
+-- proof against upstream toolchain upgrades, and already known to
+-- break in certain cases (e.g. when LTO objects are involved).
+--
+-- Therefore, on wasm as well as other targets that don't risk
+-- mentioning caller-saved GlobalRegs in a foreign call target, just
+-- keep the original call target in place and don't assign it to a
+-- local. So this would now lower to something like:
+--
+-- [Test.c_foo_entry() { //  []
+--          { []
+--          }
+--      {offset
+--        cDo:
+--            goto cDq;
+--        cDq:
+--            call "ccall" arg hints:  []  result hints:  [] foo();
+--            R1 = GHC.Tuple.()_closure+1;
+--            call (I32[P32[Sp]])(R1) args: 4, res: 0, upd: 4;
+--      }
+--  },
+--
+-- Since "foo" appears at call site directly, the wasm backend would
+-- now be able to infer its type signature correctly.
+
 maybe_assign_temp :: CmmExpr -> FCode CmmExpr
 maybe_assign_temp e = do
-  platform <- getPlatform
-  reg <- newTemp (cmmExprType platform e)
-  emitAssign (CmmLocal reg) e
-  return (CmmReg (CmmLocal reg))
+  do_save <- stgToCmmSaveFCallTargetToLocal <$> getStgToCmmConfig
+  if do_save
+    then do
+      platform <- getPlatform
+      reg <- newTemp (cmmExprType platform e)
+      emitAssign (CmmLocal reg) e
+      return (CmmReg (CmmLocal reg))
+    else
+      pure e
 
 -- -----------------------------------------------------------------------------
 -- Save/restore the thread state in the TSO


=====================================
testsuite/tests/codeGen/should_compile/all.T
=====================================
@@ -130,3 +130,11 @@ test('T21710a', [ unless(tables_next_to_code(), skip) , when(wordsize(32), skip)
 test('T23002', normal, compile, ['-fregs-graph'])
 test('T24264', [req_cmm, grep_errmsg(r'(.*\().*(\) returns to)', [1,2])],
      compile, ['-O -ddump-cmm-from-stg -dno-typeable-binds'])
+
+test('callee-no-local', [
+    req_cmm, unless(arch('wasm32') or unregisterised(), skip),
+    grep_errmsg('ccall')
+  ],
+  compile,
+  ['-ddump-cmm-raw']
+)


=====================================
testsuite/tests/codeGen/should_compile/callee-no-local.hs
=====================================
@@ -0,0 +1,3 @@
+module Test where
+
+foreign import ccall unsafe "foo" c_foo :: IO ()


=====================================
testsuite/tests/codeGen/should_compile/callee-no-local.stderr
=====================================
@@ -0,0 +1 @@
+           call "ccall" arg hints:  []  result hints:  [] foo();



View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/40b4b1019036208f5278ffef9e135ed1446a7248...09d6d0e45b953d4534e07ad14c6bf93c964d3d5b

-- 
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/40b4b1019036208f5278ffef9e135ed1446a7248...09d6d0e45b953d4534e07ad14c6bf93c964d3d5b
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/20240523/55edbfe9/attachment-0001.html>


More information about the ghc-commits mailing list