diff --git a/docs/users_guide/wasm.rst b/docs/users_guide/wasm.rst index ce572759f1a0660466286cd1c680d62ca6a07aec..40335bb322eeb713f31b96fda1ac69ade30cdac7 100644 --- a/docs/users_guide/wasm.rst +++ b/docs/users_guide/wasm.rst @@ -582,18 +582,11 @@ caveats: registered on that ``Promise`` will no longer be invoked. For simplicity of implementation, we aren’t using those for the time being. -- Normally, ``throwTo`` would block until the async exception has been - delivered. In the case of JSFFI, ``throwTo`` would always return - successfully immediately, while the target thread is still left in a - suspended state. The target thread will only be waken up when the - ``Promise`` actually resolves or rejects, though the ``Promise`` - result will be discarded at that point. - -The current way async exceptions are handled in JSFFI is subject to -change though. Ideally, once the exception is delivered, the target -thread can be waken up immediately and continue execution, and the -pending ``Promise`` will drop reference to that thread and no longer -invoke any continuations. +- When a thread blocks for a ``Promise`` to settle while masking + async exceptions, ``throwTo`` would block the caller until the + ``Promise`` is settled. If the target thread isn't masking async + exceptions, ``throwTo`` would cancel its blocking on the + ``Promise`` and resume its execution. .. _wasm-jsffi-cffi: diff --git a/libraries/ghc-internal/src/GHC/Internal/Wasm/Prim/Imports.hs b/libraries/ghc-internal/src/GHC/Internal/Wasm/Prim/Imports.hs index 8fd6e6875d9dfb653c858612cca0e26d895bc87c..b5b8a66688e6bad0182e982371b3568be10ad196 100644 --- a/libraries/ghc-internal/src/GHC/Internal/Wasm/Prim/Imports.hs +++ b/libraries/ghc-internal/src/GHC/Internal/Wasm/Prim/Imports.hs @@ -67,23 +67,19 @@ function. At this point, the Promise fulfill logic that resumes the thread in the future has been set up, we can drop the Promise eagerly, then arrange the current thread to block. -Blocking is done by calling stg_jsffi_block: it pushes a -stg_jsffi_block frame and suspends the thread. The payload of -stg_jsffi_block frame is a single pointer field that holds the return -value. When the Promise is resolved with the result, the RTS fetches -the TSO indexed by the stable pointer passed earlier, checks for the -top stack frame to see if it's still a stg_jsffi_block frame (could be -stripped by an async exception), fills in the boxed result and -restarts execution. In case of a Promise rejection, the closure being -filled is generated via raiseJSException. +Blocking is done by readMVar. stg_blockPromise allocates an empty MVar +and pins it under a stable pointer, then finally blocks by readMVar. +The stable pointer is captured in the promise.then callback. When the +Promise is settled in the future, the promise.then callback writes the +result (or exception) to the MVar and then resumes Haskell execution. -} stg_blockPromise :: String -> JSVal -> (JSVal -> StablePtr Any -> IO ()) -> r stg_blockPromise err_msg p msg_p = unsafeDupablePerformIO $ IO $ \s0 -> case stg_jsffi_check (unsafeCoerce# $ toException $ WouldBlockException err_msg) s0 of - (# s1 #) -> case myThreadId# s1 of - (# s2, tso #) -> case makeStablePtr# tso s2 of + (# s1 #) -> case newMVar# s1 of + (# s2, mv# #) -> case makeStablePtr# mv# s2 of (# s3, sp #) -> case unIO (msg_p p $ StablePtr $ unsafeCoerce# sp) s3 of -- Since we eagerly free the Promise here, we must return @@ -104,15 +100,11 @@ stg_blockPromise err_msg p msg_p = unsafeDupablePerformIO $ IO $ \s0 -> -- the Promise to resolve or reject, and also mark it -- as OPAQUE just to be sure. keepAlive# raiseJSException s5 $ - stg_jsffi_block $ - throw PromisePendingException + readMVar# mv# foreign import prim "stg_jsffi_check" stg_jsffi_check :: Any -> State# RealWorld -> (# State# RealWorld #) -foreign import prim "stg_jsffi_block" - stg_jsffi_block :: Any -> State# RealWorld -> (# State# RealWorld, r #) - foreign import javascript unsafe "$1.then(() => __exports.rts_promiseResolveUnit($2), err => __exports.rts_promiseReject($2, err))" stg_messagePromiseUnit :: JSVal -> StablePtr Any -> IO () diff --git a/libraries/ghc-internal/src/GHC/Internal/Wasm/Prim/Types.hs b/libraries/ghc-internal/src/GHC/Internal/Wasm/Prim/Types.hs index d5e8348b6e69a4b60a680e1b4da9d31c9c4773c2..a2b30f26de991f878384967926509fe2c353a50f 100644 --- a/libraries/ghc-internal/src/GHC/Internal/Wasm/Prim/Types.hs +++ b/libraries/ghc-internal/src/GHC/Internal/Wasm/Prim/Types.hs @@ -15,8 +15,7 @@ module GHC.Internal.Wasm.Prim.Types ( fromJSString, toJSString, JSException (..), - WouldBlockException (..), - PromisePendingException (..) + WouldBlockException (..) ) where import GHC.Internal.Base @@ -255,9 +254,3 @@ newtype WouldBlockException deriving (Show) instance Exception WouldBlockException - -data PromisePendingException - = PromisePendingException - deriving (Show) - -instance Exception PromisePendingException diff --git a/rts/wasm/JSFFI.c b/rts/wasm/JSFFI.c index 4129591dcf8fe0385678a2375132ac3ab10ddfee..cbc90ce554b6defe5f11f6fb29d869a428d86778 100644 --- a/rts/wasm/JSFFI.c +++ b/rts/wasm/JSFFI.c @@ -144,7 +144,6 @@ INLINE_HEADER void pushClosure (StgTSO *tso, StgWord c) { tso->stackobj->sp[0] = (W_) c; } -extern const StgInfoTable stg_jsffi_block_info; extern const StgInfoTable stg_scheduler_loop_info; extern StgClosure ghczminternal_GHCziInternalziWasmziPrimziImports_raiseJSException_closure; @@ -173,19 +172,7 @@ void rts_schedulerLoop(void) { #define mk_rtsPromiseCallback(obj) \ { \ Capability *cap = &MainCapability; \ - StgTSO *tso = (StgTSO*)deRefStablePtr(sp); \ - IF_DEBUG(sanity, checkTSO(tso)); \ - hs_free_stable_ptr(sp); \ - \ - StgStack *stack = tso->stackobj; \ - IF_DEBUG(sanity, checkSTACK(stack)); \ - \ - if (stack->sp[0] == (StgWord)&stg_jsffi_block_info) { \ - dirty_TSO(cap, tso); \ - dirty_STACK(cap, stack); \ - stack->sp[1] = (StgWord)(obj); \ - } \ - scheduleThreadNow(cap, tso); \ + hs_try_putmvar_with_value(cap->no, sp, obj); \ rts_schedulerLoop(); \ } diff --git a/rts/wasm/blocker.cmm b/rts/wasm/blocker.cmm index b449b5fa2264eedf1a347c93a448886b808f6170..64a71398ce6a4d9bb6155630cc86ede30974156c 100644 --- a/rts/wasm/blocker.cmm +++ b/rts/wasm/blocker.cmm @@ -1,35 +1,5 @@ #include "Cmm.h" -#if !defined(UnregisterisedCompiler) -import CLOSURE STK_CHK_ctr; -import CLOSURE stg_jsffi_block_info; -#endif - -// The ret field will be the boxed result that the JSFFI async import -// actually returns. Or a bottom closure that throws JSException in -// case of Promise rejection. -INFO_TABLE_RET ( stg_jsffi_block, RET_SMALL, W_ info_ptr, P_ ret ) - return () -{ - jump %ENTRY_CODE(Sp(0)) (ret); -} - -// Push a stg_jsffi_block frame and suspend the current thread. bottom -// is a placeholder that throws PromisePendingException, though in -// theory the user should never see PromisePendingException since that -// indicates a thread blocked for async JSFFI is mistakenly resumed -// somehow. -stg_jsffi_block (P_ bottom) -{ - Sp_adj(-2); - Sp(0) = stg_jsffi_block_info; - Sp(1) = bottom; - - ASSERT(SpLim - WDS(RESERVED_STACK_WORDS) <= Sp); - - jump stg_block_noregs (); -} - // Check that we're in a forked thread at the moment, since main // threads that are bound to an InCall frame cannot block waiting for // a Promise to fulfill. err is the SomeException closure of diff --git a/rts/wasm/scheduler.cmm b/rts/wasm/scheduler.cmm index c9424744c4d305142a692c1716206547d81774d5..ecf59543cadd735fb8d25f599403f26ac5b07348 100644 --- a/rts/wasm/scheduler.cmm +++ b/rts/wasm/scheduler.cmm @@ -61,13 +61,13 @@ // 3. The main thread "scheduler loop" does one simple thing: check if // the thread run queue is non-empty and if so, yield to other // threads for execution, otherwise exit the loop. -// 4. When a thread blocks for a JSFFI async import result, it pins -// the current TSO via a stable pointer, and calls Promise.then() -// on the particular Promise it's blocked on. When that Promise is -// fulfilled in the future, it will call back into the RTS, fetches -// the TSO indexed by that stable pointer, passes the result and -// wakes up the TSO, then finally does another round of scheduler -// loop. This is handled by stg_blockPromise. +// 4. When a thread blocks for a JSFFI async import result, it pins an +// MVar to a stable pointer, calls Promise.then() on the particular +// Promise it's blocked on, then finally blocks by readMVar. When +// that Promise is fulfilled in the future, the Promise.then() +// callback writes the result to MVar and wakes up the TSO, then +// finally does another round of scheduler loop. This is handled by +// stg_blockPromise. // // The async JSFFI scheduler is idempotent, it's safe to run it // multiple times, now or later, though it's not safe to forget to run