[Git][ghc/ghc][master] Check for platform support for JavaScript foreign imports

Marge Bot (@marge-bot) gitlab at gitlab.haskell.org
Fri Mar 3 03:43:04 UTC 2023



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


Commits:
8919f341 by Luite Stegeman at 2023-03-02T22:42:45-05:00
Check for platform support for JavaScript foreign imports

GHC was accepting `foreign import javascript` declarations
on non-JavaScript platforms. This adds a check so that these
are only supported on an platform that supports the JavaScript
calling convention.

Fixes #22774

- - - - -


3 changed files:

- compiler/GHC/Tc/Gen/Foreign.hs
- + testsuite/tests/ffi/should_compile/T22774.hs
- testsuite/tests/ffi/should_compile/all.T


Changes:

=====================================
compiler/GHC/Tc/Gen/Foreign.hs
=====================================
@@ -341,9 +341,10 @@ tcCheckFIType arg_tys res_ty idecl@(CImport src (L lc cconv) (L ls safety) mh
       checkForeignRes nonIOok checkSafe (isFFIPrimResultTy dflags) res_ty
       return (CImport src (L lc cconv) (L ls safety) mh (CFunction target))
   | cconv == JavaScriptCallConv = do
+      cconv' <- checkCConv (Right idecl) cconv
       checkCg (Right idecl) backendValidityOfCImport
       -- leave the rest to the JS backend (at least for now)
-      return (CImport src (L lc cconv) (L ls safety) mh (CFunction target))
+      return (CImport src (L lc cconv') (L ls safety) mh (CFunction target))
   | otherwise = do              -- Normal foreign import
       checkCg (Right idecl) backendValidityOfCImport
       cconv' <- checkCConv (Right idecl) cconv


=====================================
testsuite/tests/ffi/should_compile/T22774.hs
=====================================
@@ -0,0 +1,4 @@
+module T22774 where
+
+foreign import javascript foo :: IO ()
+


=====================================
testsuite/tests/ffi/should_compile/all.T
=====================================
@@ -44,3 +44,6 @@ test(
 )
 test('T15531', normal, compile, ['-Wall'])
 test('T22043', [omit_ways(['ghci'])], compile, [''])
+
+test('T22774', when(not js_arch(), expect_fail), compile, [''])
+



View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/8919f34102cae1ff3bae95b7f53e5d93dbad7ecf

-- 
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/8919f34102cae1ff3bae95b7f53e5d93dbad7ecf
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/20230302/035cf368/attachment-0001.html>


More information about the ghc-commits mailing list