[Git][ghc/ghc][master] 3 commits: ghc-experimental: make JSVal abstract in GHC.Wasm.Prim

Marge Bot (@marge-bot) gitlab at gitlab.haskell.org
Wed Mar 5 09:51:07 UTC 2025



Marge Bot pushed to branch master at Glasgow Haskell Compiler / GHC


Commits:
8037f487 by Cheng Shao at 2025-03-05T04:49:54-05:00
ghc-experimental: make JSVal abstract in GHC.Wasm.Prim

This commit makes JSVal an abstract type in the export list of
GHC.Wasm.Prim. JSVal's internal representation is supposed to be a non
user facing implementation detail subject to change at any time. We
should only expose things that are newtypes of JSVal, not JSVal
itself.

- - - - -
4f342431 by Cheng Shao at 2025-03-05T04:49:54-05:00
wasm: make JSVal internal Weak# point to lifted JSVal

JSVal has an internal Weak# with the unlifted JSVal# object as key to
arrange its builtin finalization logic. The Weak# used to designate
Unit_closure as a dummy value; now this commit designates the lifted
JSVal closure as the Weak# value. This allows the implementation of
mkWeakJSVal which can be used to observe the liveliness of a JSVal and
attach a user-specified finalizer.

- - - - -
55af20e6 by Cheng Shao at 2025-03-05T04:49:54-05:00
ghc-experimental: add mkWeakJSVal

This commit adds a mkWeakJSVal function that can be used to set up a
Weak pointer with a JSVal key to observe the key's lifetime and
optionally attach a finalizer.

- - - - -


5 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
- rts/wasm/JSFFI.c
- testsuite/tests/jsffi/jsffigc.hs


Changes:

=====================================
libraries/ghc-experimental/src/GHC/Wasm/Prim.hs
=====================================
@@ -2,8 +2,9 @@
 
 module GHC.Wasm.Prim (
   -- User-facing JSVal type and freeJSVal
-  JSVal (..),
+  JSVal,
   freeJSVal,
+  mkWeakJSVal,
 
   -- The JSString type and conversion from/to Haskell String
   JSString (..),
@@ -20,4 +21,3 @@ module GHC.Wasm.Prim (
 ) where
 
 import GHC.Internal.Wasm.Prim
-


=====================================
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
 
 {-
 
@@ -82,7 +84,7 @@ newtype JSVal#
   = JSVal# (Any :: UnliftedType)
 
 data JSVal
-  = forall a . JSVal JSVal# (Weak# JSVal#) (StablePtr# a)
+  = forall a . JSVal JSVal# (Weak# JSVal) (StablePtr# a)
 
 freeJSVal :: JSVal -> IO ()
 freeJSVal v@(JSVal _ w sp) = do
@@ -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 ()
 


=====================================
rts/wasm/JSFFI.c
=====================================
@@ -107,7 +107,6 @@ HaskellObj rts_mkJSVal(Capability *cap, HsJSVal v) {
   SET_HDR(w, &stg_WEAK_info, CCS_SYSTEM);
   w->cfinalizers = (StgClosure *)cfin;
   w->key = p;
-  w->value = Unit_closure;
   w->finalizer = &stg_NO_FINALIZER_closure;
   w->link = cap->weak_ptr_list_hd;
   cap->weak_ptr_list_hd = w;
@@ -120,7 +119,9 @@ HaskellObj rts_mkJSVal(Capability *cap, HsJSVal v) {
   box->payload[0] = p;
   box->payload[1] = (HaskellObj)w;
   box->payload[2] = NULL;
-  return TAG_CLOSURE(1, box);
+
+  w->value = TAG_CLOSURE(1, box);
+  return w->value;
 }
 
 __attribute__((import_module("ghc_wasm_jsffi"), import_name("getJSVal")))


=====================================
testsuite/tests/jsffi/jsffigc.hs
=====================================
@@ -22,13 +22,6 @@ foreign import javascript "wrapper"
 foreign export javascript "testDynExportFree sync"
   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 $ unsafeCoerce# Weak w
-
 probeWeak :: Weak v -> IO ()
 probeWeak wk = print =<< isJust <$> deRefWeak wk
 
@@ -42,7 +35,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.
@@ -60,7 +53,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/-/compare/eb9fe1ec0a1b35e4a9ceeafd7943dc95b3180fc3...55af20e6ed5c72a46a09b88e8590b6b2309eb41b

-- 
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/eb9fe1ec0a1b35e4a9ceeafd7943dc95b3180fc3...55af20e6ed5c72a46a09b88e8590b6b2309eb41b
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/20250305/af3cbb93/attachment-0001.html>


More information about the ghc-commits mailing list