Skip to content
Snippets Groups Projects
Commit 2788a597 authored by Cheng Shao's avatar Cheng Shao :beach:
Browse files

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.

(cherry picked from commit 55af20e6)
parent 4941e126
No related branches found
No related tags found
No related merge requests found
......@@ -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 (..),
......
......@@ -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 (..),
......
......@@ -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 ()
......
......@@ -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
......@@ -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 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
......
0% Loading or .
You are about to add 0 people to the discussion. Proceed with caution.
Finish editing this message first!
Please register or to comment