Marge Bot pushed to branch master at Glasgow Haskell Compiler / GHC
Commits:
f69c5f14 by Cheng Shao at 2025-12-19T03:19:45-05:00
wasm: fix handling of ByteArray#/MutableByteArray# arguments in JSFFI imports
This patch fixes the handling of ByteArray#/MutableByteArray#
arguments in JSFFI imports, see the amended note and manual for
explanation. Also adds a test to witness the fix.
Co-authored-by: Codex
- - - - -
7 changed files:
- compiler/GHC/HsToCore/Foreign/Wasm.hs
- docs/users_guide/wasm.rst
- testsuite/tests/jsffi/all.T
- + testsuite/tests/jsffi/bytearrayarg.hs
- + testsuite/tests/jsffi/bytearrayarg.mjs
- + testsuite/tests/jsffi/bytearrayarg.stdout
- testsuite/tests/perf/should_run/all.T
Changes:
=====================================
compiler/GHC/HsToCore/Foreign/Wasm.hs
=====================================
@@ -224,6 +224,25 @@ especially since leaving all the boxing/unboxing business to C unifies
the implementation of JSFFI imports and exports
(rts_mkJSVal/rts_getJSVal).
+We don't support unboxed FFI types like Int# etc. But we do support
+one kind of unlifted FFI type for JSFFI import arguments:
+ByteArray#/MutableByteArray#. The semantics is the same in C: the
+pointer to the ByteArray# payload is passed instead of the ByteArray#
+closure itself. This allows efficient zero-copy data exchange between
+Haskell and JavaScript using unpinned ByteArray#, and the following
+conditions must be met:
+
+- The JSFFI import itself must be a sync import marked as unsafe
+- The JavaScript code must not re-enter Haskell when a ByteArray# is
+ passed as argument
+
+There's no magic in the handling of ByteArray#/MutableByteArray#
+arguments. When generating C stub, we treat them like Ptr that points
+to the payload, just without the rts_getPtr() unboxing call. After
+lowering to C import, the backend takes care of adding the offset, see
+add_shim in GHC.StgToCmm.Foreign and
+Note [Unlifted boxed arguments to foreign calls].
+
Now, each sync import calls a generated C function with a unique
symbol. The C function uses rts_get* to unbox the arguments, call into
JavaScript, then boxes the result with rts_mk* and returns it to
@@ -517,8 +536,9 @@ importCStub sync cfun_name arg_tys res_ty js_src = CStub c_doc [] []
cfun_ret
| res_ty `eqType` unitTy = cfun_call_import <> semi
| otherwise = text "return" <+> cfun_call_import <> semi
- cfun_make_arg arg_ty arg_val =
- text ("rts_get" ++ ffiType arg_ty) <> parens arg_val
+ cfun_make_arg arg_ty arg_val
+ | isByteArrayPrimTy arg_ty = arg_val
+ | otherwise = text ("rts_get" ++ ffiType arg_ty) <> parens arg_val
cfun_make_ret ret_val
| res_ty `eqType` unitTy = ret_val
| otherwise =
@@ -543,7 +563,11 @@ importCStub sync cfun_name arg_tys res_ty js_src = CStub c_doc [] []
| res_ty `eqType` unitTy = text "void"
| otherwise = text "HaskellObj"
cfun_arg_list =
- [text "HaskellObj" <+> char 'a' <> int n | n <- [1 .. length arg_tys]]
+ [ text (if isByteArrayPrimTy arg_ty then "HsPtr" else "HaskellObj")
+ <+> char 'a'
+ <> int n
+ | (arg_ty, n) <- zip arg_tys [1 ..]
+ ]
cfun_args = case cfun_arg_list of
[] -> text "void"
_ -> hsep $ punctuate comma cfun_arg_list
@@ -746,8 +770,18 @@ lookupGhcInternalTyCon m t = do
n <- lookupOrig (mkGhcInternalModule m) (mkTcOcc t)
dsLookupTyCon n
+isByteArrayPrimTy :: Type -> Bool
+isByteArrayPrimTy ty
+ | Just tc <- tyConAppTyCon_maybe ty,
+ tc == byteArrayPrimTyCon || tc == mutableByteArrayPrimTyCon =
+ True
+ | otherwise =
+ False
+
ffiType :: Type -> String
-ffiType = occNameString . getOccName . fst . splitTyConApp
+ffiType ty
+ | isByteArrayPrimTy ty = "Ptr"
+ | otherwise = occNameString $ getOccName $ tyConAppTyCon ty
commonCDecls :: SDoc
commonCDecls =
=====================================
docs/users_guide/wasm.rst
=====================================
@@ -265,7 +265,7 @@ backend’s JavaScript FFI, which we’ll now abbreviate as JSFFI.
Marshalable types and ``JSVal``
~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~
-JSFFI supports all boxed marshalable foreign types in C FFI:
+JSFFI supports all lifted marshalable foreign types in C FFI:
- ``Bool``
- ``Char``
@@ -298,8 +298,14 @@ types in JSFFI. Some caveats to keep in mind:
results in type errors, so keep this in mind. As for ``Int`` /
``Word``, they are 32-bit since the GHC wasm backend is based on
``wasm32`` .
-- JSFFI doesn’t support unboxed foreign types like ``Int#``,
- ``ByteArray#``, etc, even when ``UnliftedFFITypes`` is enabled.
+- JSFFI doesn’t support unboxed foreign types like ``Int#``, even
+ when ``UnliftedFFITypes`` is enabled. The only supported unlifted
+ types are ``ByteArray#`` and ``MutableByteArray#``, they may only
+ be used as JSFFI import argument types, with the same semantics in
+ C FFI: the pointer to the payload is passed to JavaScript. Be
+ careful and avoid calling back into Haskell in such cases,
+ otherwise GC may occur and the pointer may be invalidated if it's
+ unpinned!
In addition to the above types, JSFFI supports the ``JSVal`` type and
its ``newtype``\ s as argument/result types. ``JSVal`` is defined in
=====================================
testsuite/tests/jsffi/all.T
=====================================
@@ -25,4 +25,6 @@ test('jsffion', [], compile_and_run, ['-optl-Wl,--export=main'])
test('jsffisleep', [], compile_and_run, ['-optl-Wl,--export=testWouldBlock,--export=testLazySleep,--export=testThreadDelay,--export=testInterruptingSleep'])
+test('bytearrayarg', [], compile_and_run, ['-optl-Wl,--export=main'])
+
test('textconv', [], compile_and_run, ['-optl-Wl,--export=main'])
=====================================
testsuite/tests/jsffi/bytearrayarg.hs
=====================================
@@ -0,0 +1,39 @@
+{-# LANGUAGE MagicHash #-}
+{-# LANGUAGE UnboxedTuples #-}
+{-# LANGUAGE UnliftedFFITypes #-}
+
+module Test where
+
+import GHC.Exts
+import GHC.IO
+import GHC.Word (Word8(W8#))
+
+foreign import javascript unsafe "(() => { const u8 = new Uint8Array(__exports.memory.buffer, $1, 4); return (u8[0] === 0x12 && u8[1] === 0x34 && u8[2] === 0x56 && u8[3] === 0x78) ? 1 : 0; })()"
+ js_check_mba :: MutableByteArray# RealWorld -> IO Int
+
+foreign import javascript unsafe "(() => { const u8 = new Uint8Array(__exports.memory.buffer, $1, 4); return (u8[0] === 0x12 && u8[1] === 0x34 && u8[2] === 0x56 && u8[3] === 0x78) ? 1 : 0; })()"
+ js_check_ba :: ByteArray# -> IO Int
+
+foreign export javascript "main"
+ main :: IO ()
+
+main :: IO ()
+main =
+ IO $ \s0 ->
+ case newPinnedByteArray# 4# s0 of
+ (# s1, mba# #) ->
+ case (0x12 :: Word8) of { W8# b0# ->
+ case (0x34 :: Word8) of { W8# b1# ->
+ case (0x56 :: Word8) of { W8# b2# ->
+ case (0x78 :: Word8) of { W8# b3# ->
+ let s2 = writeWord8Array# mba# 0# b0# s1
+ s3 = writeWord8Array# mba# 1# b1# s2
+ s4 = writeWord8Array# mba# 2# b2# s3
+ s5 = writeWord8Array# mba# 3# b3# s4
+ in case unIO (js_check_mba mba#) s5 of
+ (# s6, ok_mba #) -> case unsafeFreezeByteArray# mba# s6 of
+ (# s7, ba# #) -> case unIO (js_check_ba ba#) s7 of
+ (# s8, ok_ba #) -> case unIO (print ok_mba) s8 of
+ (# s9, _ #) -> case unIO (print ok_ba) s9 of
+ (# s10, _ #) -> (# s10, () #)
+ }}}}
=====================================
testsuite/tests/jsffi/bytearrayarg.mjs
=====================================
@@ -0,0 +1,4 @@
+export default async (__exports) => {
+ await __exports.main();
+ process.exit();
+}
=====================================
testsuite/tests/jsffi/bytearrayarg.stdout
=====================================
@@ -0,0 +1,2 @@
+1
+1
=====================================
testsuite/tests/perf/should_run/all.T
=====================================
@@ -420,6 +420,7 @@ test('T17949', [collect_stats('bytes allocated', 1), only_ways(['normal'])], com
test('ByteCodeAsm',
[ extra_run_opts('"' + config.libdir + '"')
, js_broken(22261)
+ , when(arch('wasm32'), run_timeout_multiplier(10))
, collect_stats('bytes allocated', 10),
],
compile_and_run,
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/f69c5f1492b275da7d2947612574d5c5...
--
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/f69c5f1492b275da7d2947612574d5c5...
You're receiving this email because of your account on gitlab.haskell.org.