[Git][ghc/ghc][wip/T25132] Support multiline strings in type literals (#25132)

Brandon Chinn (@brandonchinn178) gitlab at gitlab.haskell.org
Tue Aug 6 04:33:15 UTC 2024



Brandon Chinn pushed to branch wip/T25132 at Glasgow Haskell Compiler / GHC


Commits:
ac3d8fa7 by Brandon Chinn at 2024-08-05T21:30:55-07:00
Support multiline strings in type literals (#25132)

- - - - -


3 changed files:

- compiler/GHC/Parser.y
- + testsuite/tests/parser/should_compile/T25132.hs
- testsuite/tests/parser/should_compile/all.T


Changes:

=====================================
compiler/GHC/Parser.y
=====================================
@@ -2341,6 +2341,8 @@ atype :: { LHsType GhcPs }
                                                                         (getCHAR $1) }
         | STRING               { sLLa $1 $> $ HsTyLit noExtField $ HsStrTy (getSTRINGs $1)
                                                                      (getSTRING  $1) }
+        | MULTILINESTRING      { sLLa $1 $> $ HsTyLit noExtField $ HsStrTy (getMULTILINESTRINGs $1)
+                                                                     (getMULTILINESTRING  $1) }
         | '_'                  { sL1a $1 $ mkAnonWildCardTy }
         -- Type variables are never exported, so `M.tyvar` will be rejected by the renamer.
         -- We let it pass the parser because the renamer can generate a better error message.


=====================================
testsuite/tests/parser/should_compile/T25132.hs
=====================================
@@ -0,0 +1,51 @@
+{-# LANGUAGE DataKinds #-}
+{-# LANGUAGE MultilineStrings #-}
+
+module T25132 where
+
+import Data.Proxy
+import GHC.TypeLits
+
+singleTypeMultiVal :: Proxy "this is a\nmultiline\nstring"
+singleTypeMultiVal = Proxy @"""
+                            this is a
+                            multiline
+                            string
+                            """
+
+multiTypeSingleVal :: Proxy """
+                            this is a
+                            multiline
+                            string
+                            """
+multiTypeSingleVal = Proxy @"this is a\nmultiline\nstring"
+
+multiTypeMultiVal :: Proxy """
+                           this is a
+                           multiline
+                           string
+                           """
+multiTypeMultiVal = Proxy @"""
+                           this is a
+                           multiline
+                           string
+                           """
+
+k1 :: ()
+k1 = test where
+  test :: "string" ~ """string""" => ()
+  test = ()
+
+k2 :: ()
+k2 = test where
+  test :: ConsSymbol 's' "tring" ~ """string""" => ()
+  test = ()
+
+k3 :: UnconsSymbol "string" ~ Just '( 's', x) => Proxy x
+k3 = test where
+  test :: Proxy """tring"""
+  test = Proxy
+
+k4 :: Proxy "string"
+k4 = Proxy @"""string"""
+


=====================================
testsuite/tests/parser/should_compile/all.T
=====================================
@@ -202,3 +202,5 @@ test('ListTuplePunsFamilies', [expect_broken(23135), extra_files(['ListTuplePuns
 
 
 test('T22155', normal, compile, ['-dsuppress-uniques -ddump-simpl -dsuppress-all -dno-typeable-binds'])
+
+test('T25132', normal, compile, [''])



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

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


More information about the ghc-commits mailing list