[Git][ghc/ghc][master] JS: fix getpid (fix #23399)

Marge Bot (@marge-bot) gitlab at gitlab.haskell.org
Wed May 17 01:32:37 UTC 2023



Marge Bot pushed to branch master at Glasgow Haskell Compiler / GHC


Commits:
2972fd66 by Sylvain Henry at 2023-05-16T21:32:20-04:00
JS: fix getpid (fix #23399)

- - - - -


4 changed files:

- libraries/base/System/Posix/Internals.hs
- + libraries/base/tests/System/T23399.hs
- + libraries/base/tests/System/T23399.stdout
- libraries/base/tests/System/all.T


Changes:

=====================================
libraries/base/System/Posix/Internals.hs
=====================================
@@ -499,7 +499,7 @@ foreign import javascript interruptible "(($1,$2_1,$2_2,$c) => { return h$base_f
    c_ftruncate :: CInt -> FileOffset -> IO CInt
 foreign import javascript interruptible "(($1_1,$1_2,$c) => { return h$base_unlink($1_1,$1_2,$c); })"
    c_unlink :: CString -> IO CInt
-foreign import javascript unsafe "(() => { return h$base_getpid; })"
+foreign import javascript unsafe "h$base_getpid"
    c_getpid :: IO CPid
 -- foreign import ccall unsafe "HsBase.h fork"
 --   c_fork :: IO CPid


=====================================
libraries/base/tests/System/T23399.hs
=====================================
@@ -0,0 +1,9 @@
+module Main where
+
+import System.Posix.Internals
+
+main = do
+  r <- c_getpid
+  -- #23399: JS backend wasn't returning a valid JS number as a CPid hence
+  -- "read" would fail because the string was "0\0" (not a number, NUL byte)
+  print ((read (show r) :: Int) /= -1)


=====================================
libraries/base/tests/System/T23399.stdout
=====================================
@@ -0,0 +1 @@
+True


=====================================
libraries/base/tests/System/all.T
=====================================
@@ -8,3 +8,4 @@ test('system001', [js_broken(22349), when(opsys("mingw32"), skip), req_process],
 	compile_and_run, [''])
 test('Timeout001', js_broken(22261), compile_and_run, [''])
 test('T16466', normal, compile_and_run, [''])
+test('T23399', normal, compile_and_run, [''])



View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/2972fd66f91cb51426a1df86b8166a067015e231

-- 
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/2972fd66f91cb51426a1df86b8166a067015e231
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/20230516/591f4667/attachment-0001.html>


More information about the ghc-commits mailing list