... |
... |
@@ -147,6 +147,7 @@ data JSVal |
147
|
147
|
-- the same 'JSVal', subsequent invocations are no-ops. You are
|
148
|
148
|
-- strongly recommended to call 'freeJSVal' on short-lived
|
149
|
149
|
-- intermediate 'JSVal' values for timely release of resources!
|
|
150
|
+{-# INLINE freeJSVal #-}
|
150
|
151
|
freeJSVal :: JSVal -> IO ()
|
151
|
152
|
freeJSVal v@(JSVal p) = do
|
152
|
153
|
js_callback_unregister v
|
... |
... |
@@ -183,15 +184,16 @@ newtype JSString |
183
|
184
|
-- eagerly once the resulting 'String' is forced, and the argument
|
184
|
185
|
-- 'JSString' may be explicitly freed if no longer used.
|
185
|
186
|
fromJSString :: JSString -> String
|
186
|
|
-fromJSString s = unsafeDupablePerformIO $ do
|
187
|
|
- l <- js_stringLength s
|
188
|
|
- fp <- mallocPlainForeignPtrBytes $ l * 3
|
189
|
|
- withForeignPtr fp $ \buf -> do
|
190
|
|
- l' <- js_encodeInto s buf $ l * 3
|
191
|
|
- peekCStringLen utf8 (buf, l')
|
|
187
|
+fromJSString s = case js_stringLength s * 3 of
|
|
188
|
+ 0 -> ""
|
|
189
|
+ max_len -> unsafePerformIO $ do
|
|
190
|
+ fptr <- mallocPlainForeignPtrBytes max_len
|
|
191
|
+ withForeignPtr fptr $ \ptr -> do
|
|
192
|
+ len <- js_encodeInto s ptr max_len
|
|
193
|
+ peekCStringLen utf8 (ptr, len)
|
192
|
194
|
|
193
|
195
|
foreign import javascript unsafe "$1.length"
|
194
|
|
- js_stringLength :: JSString -> IO Int
|
|
196
|
+ js_stringLength :: JSString -> Int
|
195
|
197
|
|
196
|
198
|
foreign import javascript unsafe "(new TextEncoder()).encodeInto($1, new Uint8Array(__exports.memory.buffer, $2, $3)).written"
|
197
|
199
|
js_encodeInto :: JSString -> Ptr a -> Int -> IO Int
|