[Git][ghc/ghc][master] 2 commits: wasm: mark freeJSVal as INLINE

Marge Bot pushed to branch master at Glasgow Haskell Compiler / GHC Commits: eaa8093b by Cheng Shao at 2025-05-11T03:25:28-04:00 wasm: mark freeJSVal as INLINE This patch marks `freeJSVal` as `INLINE` for the wasm backend. I noticed that the `freeJSVal` invocations are not inlined when inspecting STG/Cmm dumps of downstream libraries that use release build of the wasm backend. The performance benefit of inlining here is very modest, but so is the cost anyway; if you are using `freeJSVal` at all then you care about every potential chance to improve performance :) - - - - - eac196df by Cheng Shao at 2025-05-11T03:25:28-04:00 wasm: add zero length fast path for fromJSString This patch adds a zero length fast path for `fromJSString`; when marshaling a zero-length `JSString` we don't need to allocate an empty `ByteArray#` at all. - - - - - 1 changed file: - libraries/ghc-internal/src/GHC/Internal/Wasm/Prim/Types.hs Changes: ===================================== libraries/ghc-internal/src/GHC/Internal/Wasm/Prim/Types.hs ===================================== @@ -147,6 +147,7 @@ data JSVal -- the same 'JSVal', subsequent invocations are no-ops. You are -- strongly recommended to call 'freeJSVal' on short-lived -- intermediate 'JSVal' values for timely release of resources! +{-# INLINE freeJSVal #-} freeJSVal :: JSVal -> IO () freeJSVal v@(JSVal p) = do js_callback_unregister v @@ -183,15 +184,16 @@ newtype JSString -- eagerly once the resulting 'String' is forced, and the argument -- 'JSString' may be explicitly freed if no longer used. fromJSString :: JSString -> String -fromJSString s = unsafeDupablePerformIO $ do - l <- js_stringLength s - fp <- mallocPlainForeignPtrBytes $ l * 3 - withForeignPtr fp $ \buf -> do - l' <- js_encodeInto s buf $ l * 3 - peekCStringLen utf8 (buf, l') +fromJSString s = case js_stringLength s * 3 of + 0 -> "" + max_len -> unsafePerformIO $ do + fptr <- mallocPlainForeignPtrBytes max_len + withForeignPtr fptr $ \ptr -> do + len <- js_encodeInto s ptr max_len + peekCStringLen utf8 (ptr, len) foreign import javascript unsafe "$1.length" - js_stringLength :: JSString -> IO Int + js_stringLength :: JSString -> Int foreign import javascript unsafe "(new TextEncoder()).encodeInto($1, new Uint8Array(__exports.memory.buffer, $2, $3)).written" js_encodeInto :: JSString -> Ptr a -> Int -> IO Int View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/7b2d1e6d0319dabe5a19b130744f6b5... -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/7b2d1e6d0319dabe5a19b130744f6b5... You're receiving this email because of your account on gitlab.haskell.org.
participants (1)
-
Marge Bot (@marge-bot)