[Git][ghc/ghc][wip/wasm-prim-improve] ghc-experimental: add mkWeakJSVal
Cheng Shao (@TerrorJack)
gitlab at gitlab.haskell.org
Mon Feb 24 14:34:34 UTC 2025
Cheng Shao pushed to branch wip/wasm-prim-improve at Glasgow Haskell Compiler / GHC
Commits:
91cf4fce by Cheng Shao at 2025-02-24T14:34:22+00:00
ghc-experimental: add mkWeakJSVal
- - - - -
4 changed files:
- libraries/ghc-experimental/src/GHC/Wasm/Prim.hs
- libraries/ghc-internal/src/GHC/Internal/Wasm/Prim.hs
- libraries/ghc-internal/src/GHC/Internal/Wasm/Prim/Types.hs
- testsuite/tests/jsffi/jsffigc.hs
Changes:
=====================================
libraries/ghc-experimental/src/GHC/Wasm/Prim.hs
=====================================
@@ -4,6 +4,7 @@ module GHC.Wasm.Prim (
-- User-facing JSVal type and freeJSVal
JSVal,
freeJSVal,
+ mkWeakJSVal,
-- The JSString type and conversion from/to Haskell String
JSString (..),
=====================================
libraries/ghc-internal/src/GHC/Internal/Wasm/Prim.hs
=====================================
@@ -4,6 +4,7 @@ module GHC.Internal.Wasm.Prim (
-- User-facing JSVal type and freeJSVal
JSVal (..),
freeJSVal,
+ mkWeakJSVal,
-- The JSString type and conversion from/to Haskell String
JSString (..),
=====================================
libraries/ghc-internal/src/GHC/Internal/Wasm/Prim/Types.hs
=====================================
@@ -8,6 +8,7 @@ module GHC.Internal.Wasm.Prim.Types (
JSVal# (..),
JSVal (..),
freeJSVal,
+ mkWeakJSVal,
JSString (..),
fromJSString,
toJSString,
@@ -26,6 +27,7 @@ import GHC.Internal.IO.Encoding
import GHC.Internal.Num
import GHC.Internal.Show
import GHC.Internal.Stable
+import GHC.Internal.Weak
{-
@@ -94,6 +96,12 @@ freeJSVal v@(JSVal _ w sp) = do
IO $ \s0 -> case finalizeWeak# w s0 of
(# s1, _, _ #) -> (# s1, () #)
+mkWeakJSVal :: JSVal -> Maybe (IO ()) -> IO (Weak JSVal)
+mkWeakJSVal v@(JSVal k _ _) (Just (IO fin)) = IO $ \s0 ->
+ case mkWeak# k v fin s0 of
+ (# s1, w #) -> (# s1, Weak w #)
+mkWeakJSVal (JSVal _ w _) Nothing = pure $ Weak w
+
foreign import javascript unsafe "if (!__ghc_wasm_jsffi_finalization_registry.unregister($1)) { throw new WebAssembly.RuntimeError('js_callback_unregister'); }"
js_callback_unregister :: JSVal -> IO ()
=====================================
testsuite/tests/jsffi/jsffigc.hs
=====================================
@@ -4,7 +4,7 @@ module Test where
import Data.Maybe
import GHC.Exts
-import GHC.Internal.Wasm.Prim
+import GHC.Wasm.Prim
import GHC.Weak
import System.Mem
@@ -23,13 +23,6 @@ foreign import javascript "wrapper"
foreign export javascript "testDynExportFree"
testDynExportFree :: Int -> Int -> Int -> IO ()
--- JSVal uses Weak# under the hood for garbage collection support,
--- this exposes the internal Weak# to observe the liveliness of
--- JSVal#. Do not use this in your own codebase since this is purely
--- an implementation detail of JSVal and subject to change!
-jsvalWeak :: JSVal -> Weak JSVal
-jsvalWeak (JSVal _ w _) = Weak w
-
probeWeak :: Weak v -> IO ()
probeWeak wk = print =<< isJust <$> deRefWeak wk
@@ -43,7 +36,7 @@ testDynExportFree x y z = do
-- wk_js observe the liveliness of the JavaScript callback on the
-- Haskell heap. Make sure it's eagerly evaluated and isn't a thunk
-- that retains cb.
- let !wk_js = jsvalWeak cb
+ !wk_js <- mkWeakJSVal cb Nothing
print $ js_to_hs cb x y
-- Eagerly drop references to both the JavaScript callback and the
-- Haskell function closure.
@@ -61,7 +54,7 @@ testDynExportGC x y z = do
let fn a b = a * b + z
wk_fn <- mkWeak fn () Nothing
cb <- js_from_hs fn
- let !wk_js = jsvalWeak cb
+ !wk_js <- mkWeakJSVal cb Nothing
print $ js_to_hs cb x y
-- Why performGC twice? The first run gathers some C finalizers
-- which will be invoked in the second run to free the JSVal
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/91cf4fce96249a967cab1d709dc5a499c68da35f
--
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/91cf4fce96249a967cab1d709dc5a499c68da35f
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/20250224/98e1785e/attachment-0001.html>
More information about the ghc-commits
mailing list