[Git][ghc/ghc][master] 2 commits: testsuite: add regression test T25473
Marge Bot (@marge-bot)
gitlab at gitlab.haskell.org
Fri Nov 15 00:09:50 UTC 2024
Marge Bot pushed to branch master at Glasgow Haskell Compiler / GHC
Commits:
ed2ed6c5 by Cheng Shao at 2024-11-14T19:08:37-05:00
testsuite: add regression test T25473
This commit adds regression test T25473 marked as broken due to #25473.
It will be fixed in the subsequent commit.
- - - - -
bd0a8b7e by Cheng Shao at 2024-11-14T19:08:37-05:00
wasm: fix foreign import javascript "wrapper" in TH/ghci
This patch fixes foreign import javascript "wrapper" in wasm backend's
TH/ghci by fixing the handling of dyld/finalization_registry magic
variables. Fixes T25473 and closes #25473.
- - - - -
5 changed files:
- libraries/ghci/GHCi/ObjLink.hs
- + testsuite/tests/th/wasm/T25473A.hs
- + testsuite/tests/th/wasm/T25473B.hs
- + testsuite/tests/th/wasm/all.T
- utils/jsffi/dyld.mjs
Changes:
=====================================
libraries/ghci/GHCi/ObjLink.hs
=====================================
@@ -76,7 +76,7 @@ loadDLL f =
evaluate =<< js_loadDLL (toJSString f)
pure $ Right nullPtr
-foreign import javascript safe "__exports.__dyld.loadDLL($1)"
+foreign import javascript safe "__ghc_wasm_jsffi_dyld.loadDLL($1)"
js_loadDLL :: JSString -> IO ()
loadArchive :: String -> IO ()
@@ -96,7 +96,7 @@ lookupSymbol sym = do
r <- js_lookupSymbol $ toJSString sym
evaluate $ if r == nullPtr then Nothing else Just r
-foreign import javascript unsafe "__exports.__dyld.lookupSymbol($1)"
+foreign import javascript unsafe "__ghc_wasm_jsffi_dyld.lookupSymbol($1)"
js_lookupSymbol :: JSString -> IO (Ptr a)
lookupSymbolInDLL :: Ptr LoadedDLL -> String -> IO (Maybe (Ptr a))
@@ -114,7 +114,7 @@ addLibrarySearchPath p = do
evaluate =<< js_addLibrarySearchPath (toJSString p)
pure nullPtr
-foreign import javascript safe "__exports.__dyld.addLibrarySearchPath($1)"
+foreign import javascript safe "__ghc_wasm_jsffi_dyld.addLibrarySearchPath($1)"
js_addLibrarySearchPath :: JSString -> IO ()
removeLibrarySearchPath :: Ptr () -> IO Bool
@@ -128,7 +128,7 @@ findSystemLibrary f = m `catch` \(_ :: JSException) -> pure Nothing
p <- evaluate $ fromJSString p'
pure $ Just p
-foreign import javascript safe "__exports.__dyld.findSystemLibrary($1)"
+foreign import javascript safe "__ghc_wasm_jsffi_dyld.findSystemLibrary($1)"
js_findSystemLibrary :: JSString -> IO JSString
#else
=====================================
testsuite/tests/th/wasm/T25473A.hs
=====================================
@@ -0,0 +1,8 @@
+module T25473A where
+
+import GHC.Wasm.Prim
+
+type BinOp a = a -> a -> a
+
+foreign import javascript "wrapper"
+ mkJSBinOp :: BinOp Int -> IO JSVal
=====================================
testsuite/tests/th/wasm/T25473B.hs
=====================================
@@ -0,0 +1,10 @@
+{-# LANGUAGE TemplateHaskell #-}
+
+module T25473B where
+
+import Language.Haskell.TH
+import T25473A
+
+$(runIO $ do
+ _ <- mkJSBinOp (+)
+ pure [])
=====================================
testsuite/tests/th/wasm/all.T
=====================================
@@ -0,0 +1,5 @@
+setTestOpts([
+ unless(arch('wasm32'), skip)
+])
+
+test('T25473', [], multimod_compile, ['T25473B', '-v0'])
=====================================
utils/jsffi/dyld.mjs
=====================================
@@ -293,9 +293,13 @@ class DyLD {
#loadedSos = new Set();
// Mapping from export names to export funcs. It's also passed as
- // __exports in JSFFI code, hence the "memory" special field. __dyld
- // is used by ghci to call into here.
- exportFuncs = { memory: this.#memory, __dyld: this };
+ // __exports in JSFFI code, hence the "memory" special field.
+ exportFuncs = { memory: this.#memory };
+
+ // The FinalizationRegistry used by JSFFI.
+ #finalizationRegistry = new FinalizationRegistry((sp) =>
+ this.exportFuncs.rts_freeStablePtr(sp)
+ );
// The GOT.func table.
#gotFunc = {};
@@ -623,17 +627,22 @@ class DyLD {
const mod = await modp;
- // Fulfill the ghc_wasm_jsffi imports
+ // Fulfill the ghc_wasm_jsffi imports. Use new Function()
+ // instead of eval() to prevent bindings in this local scope to
+ // be accessed by JSFFI code snippets.
Object.assign(
import_obj.ghc_wasm_jsffi,
new Function(
- "return (__exports) => ({".concat(
+ "__exports",
+ "__ghc_wasm_jsffi_dyld",
+ "__ghc_wasm_jsffi_finalization_registry",
+ "return {".concat(
...parseSections(mod).map(
(rec) => `${rec[0]}: ${parseRecord(rec)}, `
),
- "});"
+ "};"
)
- )()(this.exportFuncs)
+ )(this.exportFuncs, this, this.#finalizationRegistry)
);
// Fulfill the rest of the imports
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/c2c562e04b44079f622cf7748b0e21af443b6a49...bd0a8b7e7537499f7dc703f78ac96f34e4c40554
--
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/c2c562e04b44079f622cf7748b0e21af443b6a49...bd0a8b7e7537499f7dc703f78ac96f34e4c40554
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/20241114/c2ed2731/attachment-0001.html>
More information about the ghc-commits
mailing list