[Git][ghc/ghc][master] Allow multiline strings in JS FFI (#25633)
Marge Bot (@marge-bot)
gitlab at gitlab.haskell.org
Sat Jan 18 07:53:56 UTC 2025
Marge Bot pushed to branch master at Glasgow Haskell Compiler / GHC
Commits:
14f8a7ec by Mateusz Goślinowski at 2025-01-17T22:49:09+00:00
Allow multiline strings in JS FFI (#25633)
- - - - -
5 changed files:
- compiler/GHC/Parser.y
- docs/users_guide/9.14.1-notes.rst
- + testsuite/tests/javascript/T25633.hs
- + testsuite/tests/javascript/T25633.stdout
- testsuite/tests/javascript/all.T
Changes:
=====================================
compiler/GHC/Parser.y
=====================================
@@ -2148,6 +2148,9 @@ fspec :: { Located (TokDcolon
: STRING var '::' sigtype { sLL $1 $> (epUniTok $3
,(L (getLoc $1)
(getStringLiteral $1), $2, $4)) }
+ | STRING_MULTI var '::' sigtype { sLL $1 $> (epUniTok $3
+ ,(L (getLoc $1)
+ (getStringMultiLiteral $1), $2, $4)) }
| var '::' sigtype { sLL $1 $> (epUniTok $2
,(noLoc (StringLiteral NoSourceText nilFS Nothing), $1, $3)) }
-- if the entity string is missing, it defaults to the empty string;
@@ -4247,6 +4250,7 @@ getINCOHERENT_PRAGs (L _ (ITincoherent_prag src)) = src
getCTYPEs (L _ (ITctype src)) = src
getStringLiteral l = StringLiteral (getSTRINGs l) (getSTRING l) Nothing
+getStringMultiLiteral l = StringLiteral (getSTRINGMULTIs l) (getSTRINGMULTI l) Nothing
isUnicode :: Located Token -> Bool
isUnicode (L _ (ITforall iu)) = iu == UnicodeSyntax
=====================================
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,44 @@
+{-# 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
+ 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/14f8a7ec7ffd4368de84b6cc415a9a36ad396260
--
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/14f8a7ec7ffd4368de84b6cc415a9a36ad396260
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/20250118/034cd21b/attachment-0001.html>
More information about the ghc-commits
mailing list