[Git][ghc/ghc][wip/swordlash/allow_multiline_strings_in_js_ffi] Add test for multiline imports
Mateusz Goślinowski (@Swordlash)
gitlab at gitlab.haskell.org
Sun Jan 12 00:29:30 UTC 2025
Mateusz Goślinowski pushed to branch wip/swordlash/allow_multiline_strings_in_js_ffi at Glasgow Haskell Compiler / GHC
Commits:
148a1e5c by Mateusz Goślinowski at 2025-01-12T01:29:20+01:00
Add test for multiline imports
- - - - -
4 changed files:
- docs/users_guide/9.14.1-notes.rst
- + testsuite/tests/javascript/T25633.hs
- + testsuite/tests/javascript/T25633.stdout
- testsuite/tests/javascript/all.T
Changes:
=====================================
docs/users_guide/9.14.1-notes.rst
=====================================
@@ -38,6 +38,8 @@ Language
That will break the combination of :extension:`OverloadedRecordUpdate` with :extension:`RebindableSyntax`.
+* Multiline strings are now accepted in foreign imports. (#25157)
+
Compiler
~~~~~~~~
=====================================
testsuite/tests/javascript/T25633.hs
=====================================
@@ -0,0 +1,41 @@
+{-# LANGUAGE MultilineStrings #-}
+module Main where
+
+import GHC.Prim
+import GHC.JS.Prim
+import Foreign.C
+import System.IO
+
+foreign import javascript
+ """
+ ((x) => x)
+ """
+ toJSDouble :: Double -> JSVal
+
+foreign import javascript
+ """
+ (function (x) { console.log(x); })
+ """
+ multiLog :: JSVal -> IO ()
+
+foreign import javascript
+ """
+ ((x) => x + "")
+ """
+ jsToString :: JSVal -> JSVal
+
+foreign import ccall
+ """
+ cos
+ """ mycos :: CDouble -> CDouble
+
+main :: IO ()
+main = do
+ -- avoid C and Haskell prints to stdout to be intermingled due to buffering on the Haskell side
+ hSetBuffering stdout NoBuffering
+
+ multiLog $ toJSInt 5
+ multiLog $ toJSString "Hello"
+ putStrLn $ fromJSString $ jsToString $ toJSInt (- 5)
+ multiLog $ jsToString $ toJSDouble 3.0
+ print $ mycos 0 == 1
\ No newline at end of file
=====================================
testsuite/tests/javascript/T25633.stdout
=====================================
@@ -0,0 +1,5 @@
+5
+Hello
+-5
+3
+True
\ No newline at end of file
=====================================
testsuite/tests/javascript/all.T
=====================================
@@ -25,3 +25,5 @@ test('T24495', normal, makefile_test, ['T24495'])
test('T23479', normal, makefile_test, ['T23479'])
test('T24744', normal, makefile_test, ['T24744'])
+
+test('T25633', normal, compile_and_run, [''])
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/148a1e5c9e0dc606ef682edd43a62c011e02cc7f
--
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/148a1e5c9e0dc606ef682edd43a62c011e02cc7f
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/20250111/a5232e1a/attachment-0001.html>
More information about the ghc-commits
mailing list