[Git][ghc/ghc][master] Add missing gParPat in cvtp's ViewP case

Marge Bot (@marge-bot) gitlab at gitlab.haskell.org
Thu Jul 4 15:15:16 UTC 2024



Marge Bot pushed to branch master at Glasgow Haskell Compiler / GHC


Commits:
87cf4111 by Ryan Scott at 2024-07-04T11:11:47-04:00
Add missing gParPat in cvtp's ViewP case

When converting a `ViewP` using `cvtp`, we need to ensure that the view pattern
is parenthesized so that the resulting code will parse correctly when
roundtripped back through GHC's parser.

Fixes #24894.

- - - - -


4 changed files:

- compiler/GHC/ThToHs.hs
- + testsuite/tests/th/T24894.hs
- + testsuite/tests/th/T24894.stderr
- testsuite/tests/th/all.T


Changes:

=====================================
compiler/GHC/ThToHs.hs
=====================================
@@ -1488,7 +1488,7 @@ cvtp (SigP p t)        = do { p' <- cvtPat p; t' <- cvtType t
                             ; let pp = parenthesizePat sigPrec p'
                             ; return $ SigPat noAnn pp (mkHsPatSigType noAnn t') }
 cvtp (ViewP e p)       = do { e' <- cvtl e; p' <- cvtPat p
-                            ; return $ ViewPat noAnn e' p'}
+                            ; wrapParLA gParPat $ ViewPat noAnn e' p'}
 cvtp (TypeP t)         = do { t' <- cvtType t
                             ; return $ EmbTyPat noAnn (mkHsTyPat t') }
 cvtp (InvisP t)        = do { t' <- cvtType t


=====================================
testsuite/tests/th/T24894.hs
=====================================
@@ -0,0 +1,6 @@
+{-# LANGUAGE PatternSynonyms #-}
+{-# LANGUAGE TemplateHaskell #-}
+{-# LANGUAGE ViewPatterns #-}
+module T24894 where
+
+$([d| pattern P x <- (id -> x) |])


=====================================
testsuite/tests/th/T24894.stderr
=====================================
@@ -0,0 +1,2 @@
+T24894.hs:6:2-34: Splicing declarations
+    [d| pattern P x <- (id -> x) |] ======> pattern P x <- (id -> x)


=====================================
testsuite/tests/th/all.T
=====================================
@@ -615,5 +615,6 @@ test('T24557e', normal, compile, [''])
 test('T24702a', normal, compile, [''])
 test('T24702b', normal, compile, [''])
 test('T24837', normal, compile, ['-v0 -ddump-splices -dsuppress-uniques'])
+test('T24894', normal, compile, ['-v0 -ddump-splices -dsuppress-uniques'])
 test('T24911', normal, compile, ['-v0 -ddump-splices -dsuppress-uniques'])
 test('T24997', normal, compile_and_run, [''])



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

-- 
This project does not include diff previews in email notifications.
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/87cf41111ef6a650e360e4a9b9ac691feecc4973
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/20240704/5f8a4533/attachment-0001.html>


More information about the ghc-commits mailing list