[Git][ghc/ghc][wip/T25132] Support multiline strings in type literals (#25132)
Brandon Chinn (@brandonchinn178)
gitlab at gitlab.haskell.org
Wed Aug 7 00:58:14 UTC 2024
Brandon Chinn pushed to branch wip/T25132 at Glasgow Haskell Compiler / GHC
Commits:
01dbbf2d by Brandon Chinn at 2024-08-06T17:57:57-07:00
Support multiline strings in type literals (#25132)
- - - - -
7 changed files:
- compiler/GHC/Parser.y
- compiler/GHC/Tc/Gen/HsType.hs
- + testsuite/tests/parser/should_compile/T25132.hs
- testsuite/tests/parser/should_compile/all.T
- testsuite/tests/printer/Makefile
- + testsuite/tests/printer/Test25132.hs
- testsuite/tests/printer/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.
=====================================
compiler/GHC/Tc/Gen/HsType.hs
=====================================
@@ -4705,6 +4705,7 @@ addTyConFlavCtxt name flav
tyLitFromLit :: HsLit GhcRn -> Maybe (HsTyLit GhcRn)
tyLitFromLit (HsString x str) = Just (HsStrTy x str)
+tyLitFromLit (HsMultilineString x str) = Just (HsStrTy x str)
tyLitFromLit (HsChar x char) = Just (HsCharTy x char)
tyLitFromLit _ = Nothing
=====================================
testsuite/tests/parser/should_compile/T25132.hs
=====================================
@@ -0,0 +1,56 @@
+{-# LANGUAGE DataKinds #-}
+{-# LANGUAGE MultilineStrings #-}
+{-# LANGUAGE RequiredTypeArguments #-}
+
+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"""
+
+k5 :: ()
+k5 = test """string""" where
+ test :: forall a -> ()
+ test _ = ()
=====================================
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, [''])
=====================================
testsuite/tests/printer/Makefile
=====================================
@@ -881,3 +881,8 @@ Test24771:
Test24159:
$(CHECK_PPR) $(LIBDIR) Test24159.hs
$(CHECK_EXACT) $(LIBDIR) Test24159.hs
+
+.PHONY: Test25132
+Test25132:
+ $(CHECK_PPR) $(LIBDIR) Test25132.hs
+ $(CHECK_EXACT) $(LIBDIR) Test25132.hs
=====================================
testsuite/tests/printer/Test25132.hs
=====================================
@@ -0,0 +1,16 @@
+{-# LANGUAGE MultilineStrings #-}
+
+module Test25132 where
+
+import Data.Proxy
+
+v :: Proxy """
+ this is a
+ multiline
+ string
+ """
+v = Proxy @"""
+ this is a
+ multiline
+ string
+ """
=====================================
testsuite/tests/printer/all.T
=====================================
@@ -209,3 +209,4 @@ test('Test24755', [ignore_stderr, req_ppr_deps], makefile_test, ['Test24755'])
test('Test24753', [ignore_stderr, req_ppr_deps], makefile_test, ['Test24753'])
test('Test24771', [ignore_stderr, req_ppr_deps], makefile_test, ['Test24771'])
test('Test24159', [ignore_stderr, req_ppr_deps], makefile_test, ['Test24159'])
+test('Test25132', [ignore_stderr, req_ppr_deps], makefile_test, ['Test25132'])
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/01dbbf2dfd3f016a4d6f420ead8f061e09af23ee
--
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/01dbbf2dfd3f016a4d6f420ead8f061e09af23ee
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/670693de/attachment-0001.html>
More information about the ghc-commits
mailing list