[Git][ghc/ghc][wip/multiline-strings-th] Support multiline strings in TH

Brandon Chinn (@brandonchinn178) gitlab at gitlab.haskell.org
Sat Aug 10 01:33:07 UTC 2024



Brandon Chinn pushed to branch wip/multiline-strings-th at Glasgow Haskell Compiler / GHC


Commits:
a0f908ce by Brandon Chinn at 2024-08-09T18:06:44-07:00
Support multiline strings in TH

- - - - -


3 changed files:

- compiler/GHC/HsToCore/Quote.hs
- testsuite/tests/parser/should_run/MultilineStrings.hs
- testsuite/tests/parser/should_run/MultilineStrings.stdout


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/parser/should_run/MultilineStrings.hs
=====================================
@@ -1,6 +1,8 @@
 {-# LANGUAGE MultilineStrings #-}
+{-# LANGUAGE TemplateHaskell #-}
 {-# OPTIONS_GHC -Wno-tabs #-}
 
+import Language.Haskell.TH (runQ)
 import Text.Printf (printf)
 
 {-
@@ -65,6 +67,14 @@ main = do
         
       b
         """
+
+  putStrLn "\n-- TH"
+  print $ runQ [|
+      """
+      hello
+      world
+      """
+    |]
   where
     prints :: String -> IO ()
     prints = print


=====================================
testsuite/tests/parser/should_run/MultilineStrings.stdout
=====================================
@@ -45,4 +45,7 @@
 "a"
 "\n"
 "\\n"
-"a\n\n  b"
\ No newline at end of file
+"a\n\n  b"
+
+-- TH
+LitE (StringL "hello\nworld")
\ No newline at end of file



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

-- 
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/a0f908cef43c5562e8adda3a0ef14a5acc0ee651
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/20240809/f516b42f/attachment-0001.html>


More information about the ghc-commits mailing list