[Git][ghc/ghc][wip/js-exports] JS Prims: fix some implementations

Josh Meredith (@JoshMeredith) gitlab at gitlab.haskell.org
Wed Mar 8 17:11:12 UTC 2023



Josh Meredith pushed to branch wip/js-exports at Glasgow Haskell Compiler / GHC


Commits:
88cd4bba by Josh Meredith at 2023-03-08T17:10:37+00:00
JS Prims: fix some implementations

- - - - -


4 changed files:

- compiler/GHC/HsToCore/Foreign/JavaScript.hs
- libraries/base/GHC/JS/Foreign/Callback.hs
- libraries/base/GHC/JS/Prim.hs
- libraries/base/base.cabal


Changes:

=====================================
compiler/GHC/HsToCore/Foreign/JavaScript.hs
=====================================
@@ -639,7 +639,7 @@ jsResultWrapper result_ty
   | Just (tc,_) <- maybe_tc_app, tc `hasKey` boolTyConKey = do
 --    result_id <- newSysLocalDs boolTy
     ccall_uniq <- newUnique
-    let forceBool e = mkJsCall ccall_uniq (fsLit "$r = !(!$1)") [e] boolTy
+    let forceBool e = mkJsCall ccall_uniq (fsLit "(($1) => { return !(!$1); })") [e] boolTy
     return
      (Just intPrimTy, \e -> forceBool e)
 


=====================================
libraries/base/GHC/JS/Foreign/Callback.hs
=====================================
@@ -1,5 +1,3 @@
-{-# LANGUAGE MagicHash #-}
-
 module GHC.JS.Foreign.Callback
     ( Callback
     , OnBlocked(..)
@@ -31,7 +29,7 @@ import           Unsafe.Coerce
 
 data OnBlocked = ContinueAsync | ThrowWouldBlock deriving (Eq)
 
-data Callback a = Callback JSVal# deriving Typeable
+newtype Callback a = Callback JSVal deriving Typeable
 
 {- |
      When you create a callback, the Haskell runtime stores a reference to


=====================================
libraries/base/GHC/JS/Prim.hs
=====================================
@@ -280,10 +280,10 @@ foreign import javascript unsafe "(($1) => { return ($1 === undefined); })"
 foreign import javascript unsafe "(($1) => { return ($r = typeof($1) === 'number' ? ($1|0) : 0;); })"
   js_fromJSInt :: JSVal -> Int
 
-foreign import javascript unsafe "(($1) => { return ($r = $1;); })"
+foreign import javascript unsafe "(($1) => { return $1; })"
   js_toJSInt :: Int -> JSVal
 
-foreign import javascript unsafe "$r = null;"
+foreign import javascript unsafe "(() => { return null; })"
   js_null :: JSVal
 
 foreign import javascript unsafe "(($1,$2) => { return $1[h$fromHsString($2)]; })"
@@ -307,7 +307,6 @@ foreign import javascript unsafe "(($1,$2_1,$2_2) => { return $1[h$decodeUtf8z($
 foreign import javascript unsafe "(($1_1,$1_2) => { return h$decodeUtf8z($1_1, $1_2); })"
   js_unpackJSStringUtf8## :: Addr# -> State# s -> (# State# s, JSVal# #)
 
-
 foreign import javascript unsafe "(($1_1, $1_2) => { return h$decodeUtf8z($1_1,$1_2); })"
   js_unsafeUnpackJSStringUtf8## :: Addr# -> JSVal#
 


=====================================
libraries/base/base.cabal
=====================================
@@ -475,6 +475,7 @@ Library
             GHC.JS.Prim
             GHC.JS.Prim.Internal
             GHC.JS.Prim.Internal.Build
+            GHC.JS.Foreign.Callback
 
     -- We need to set the unit id to base (without a version number)
     -- as it's magic.



View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/88cd4bba5bd839025f00cdd2a0a574cd52dadb2e

-- 
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/88cd4bba5bd839025f00cdd2a0a574cd52dadb2e
You're receiving this email because of your account on gitlab.haskell.org.


-------------- next part --------------
An HTML attachment was scrubbed...
URL: <http://mail.haskell.org/pipermail/ghc-commits/attachments/20230308/ec210547/attachment-0001.html>


More information about the ghc-commits mailing list