[Git][ghc/ghc][wip/multiline-strings-th] Support multiline strings in TH
Brandon Chinn (@brandonchinn178)
gitlab at gitlab.haskell.org
Sun Aug 11 19:53:47 UTC 2024
Brandon Chinn pushed to branch wip/multiline-strings-th at Glasgow Haskell Compiler / GHC
Commits:
0b24dfbc by Brandon Chinn at 2024-08-11T12:53:35-07:00
Support multiline strings in TH
- - - - -
4 changed files:
- compiler/GHC/HsToCore/Quote.hs
- + testsuite/tests/th/TH_MultilineStrings.hs
- + testsuite/tests/th/TH_MultilineStrings.stdout
- testsuite/tests/th/all.T
Changes:
=====================================
compiler/GHC/HsToCore/Quote.hs
=====================================
@@ -3026,6 +3026,7 @@ repLiteral lit
HsChar _ _ -> Just charLName
HsCharPrim _ _ -> Just charPrimLName
HsString _ _ -> Just stringLName
+ HsMultilineString _ _ -> Just stringLName
HsRat _ _ _ -> Just rationalLName
_ -> Nothing
=====================================
testsuite/tests/th/TH_MultilineStrings.hs
=====================================
@@ -0,0 +1,18 @@
+{-# LANGUAGE MultilineStrings #-}
+{-# LANGUAGE TemplateHaskell #-}
+
+import Language.Haskell.TH (runQ)
+
+{-
+Test the MultilineStrings proposal
+https://github.com/ghc-proposals/ghc-proposals/blob/master/proposals/0569-multiline-strings.rst
+-}
+
+main :: IO ()
+main = do
+ print =<< runQ [|
+ """
+ hello
+ world
+ """
+ |]
=====================================
testsuite/tests/th/TH_MultilineStrings.stdout
=====================================
@@ -0,0 +1 @@
+LitE (StringL "hello\nworld")
=====================================
testsuite/tests/th/all.T
=====================================
@@ -622,3 +622,4 @@ test('T24572a', normal, compile, [''])
test('T24572b', normal, compile_fail, [''])
test('T24572c', normal, compile_fail, [''])
test('T24572d', normal, compile, [''])
+test('TH_MultilineStrings', normal, compile_and_run, [''])
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/0b24dfbca6c0c771ac1abccb2903df77e4ab76d5
--
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/0b24dfbca6c0c771ac1abccb2903df77e4ab76d5
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/20240811/df8b09b6/attachment-0001.html>
More information about the ghc-commits
mailing list