[Git][ghc/ghc][master] Add missing parenthesizePat in cvtp
Marge Bot (@marge-bot)
gitlab at gitlab.haskell.org
Thu May 23 01:56:55 UTC 2024
Marge Bot pushed to branch master at Glasgow Haskell Compiler / GHC
Commits:
a3cd3a1d by Ryan Scott at 2024-05-22T21:55:19-04:00
Add missing parenthesizePat in cvtp
We need to ensure that the output of `cvtp` is parenthesized (at precedence
`sigPrec`) so that any pattern signatures with a surrounding pattern signature
can parse correctly.
Fixes #24837.
- - - - -
4 changed files:
- compiler/GHC/ThToHs.hs
- + testsuite/tests/th/T24837.hs
- + testsuite/tests/th/T24837.stderr
- testsuite/tests/th/all.T
Changes:
=====================================
compiler/GHC/ThToHs.hs
=====================================
@@ -1485,7 +1485,8 @@ cvtp (ListP ps) = do { ps' <- cvtPats ps
; return
$ ListPat noAnn ps'}
cvtp (SigP p t) = do { p' <- cvtPat p; t' <- cvtType t
- ; return $ SigPat noAnn p' (mkHsPatSigType noAnn 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'}
cvtp (TypeP t) = do { t' <- cvtType t
=====================================
testsuite/tests/th/T24837.hs
=====================================
@@ -0,0 +1,6 @@
+{-# LANGUAGE TemplateHaskell #-}
+module T24837 where
+
+import Language.Haskell.TH
+
+$([d| f ((x :: Bool) :: Bool) = x |])
=====================================
testsuite/tests/th/T24837.stderr
=====================================
@@ -0,0 +1,4 @@
+T24837.hs:6:2-37: Splicing declarations
+ [d| f ((x :: Bool) :: Bool) = x |]
+ ======>
+ f ((x :: Bool) :: Bool) = x
=====================================
testsuite/tests/th/all.T
=====================================
@@ -614,3 +614,4 @@ test('T24557d', normal, compile_fail, [''])
test('T24557e', normal, compile, [''])
test('T24702a', normal, compile, [''])
test('T24702b', normal, compile, [''])
+test('T24837', normal, compile, ['-v0 -ddump-splices -dsuppress-uniques'])
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/a3cd3a1d0d186f2aa4d0273c6b3e74a442de2ef0
--
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/a3cd3a1d0d186f2aa4d0273c6b3e74a442de2ef0
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/20240522/6f85c2b0/attachment-0001.html>
More information about the ghc-commits
mailing list