[Git][ghc/ghc][master] Add missing parenthesizeHsType in cvtp's InvisP case
Marge Bot (@marge-bot)
gitlab at gitlab.haskell.org
Wed Aug 28 18:17:41 UTC 2024
Marge Bot pushed to branch master at Glasgow Haskell Compiler / GHC
Commits:
c2525e9e by Ryan Scott at 2024-08-28T14:17:17-04:00
Add missing parenthesizeHsType in cvtp's InvisP case
We need to ensure that when we convert an `InvisP` (invisible type pattern) to
a `Pat`, we parenthesize it (at precedence `appPrec`) so that patterns such as
`@(a :: k)` will parse correctly when roundtripped back through the parser.
Fixes #25209.
- - - - -
4 changed files:
- compiler/GHC/ThToHs.hs
- + testsuite/tests/th/T25209.hs
- + testsuite/tests/th/T25209.stderr
- testsuite/tests/th/all.T
Changes:
=====================================
compiler/GHC/ThToHs.hs
=====================================
@@ -1519,7 +1519,7 @@ cvtp (ViewP e p) = do { e' <- cvtl e; p' <- cvtPat 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
+cvtp (InvisP t) = do { t' <- parenthesizeHsType appPrec <$> cvtType t
; pure (InvisPat noAnn (mkHsTyPat t'))}
cvtp (OrP ps) = do { ps' <- cvtPats ps
; pure (OrPat noExtField ps')}
=====================================
testsuite/tests/th/T25209.hs
=====================================
@@ -0,0 +1,9 @@
+{-# LANGUAGE TemplateHaskell #-}
+{-# LANGUAGE TypeAbstractions #-}
+module T25209 where
+
+import Data.Proxy
+
+$([d| f :: Proxy a -> Proxy a
+ f @(a :: k) p = p
+ |])
=====================================
testsuite/tests/th/T25209.stderr
=====================================
@@ -0,0 +1,6 @@
+T25209.hs:(7,2)-(9,7): Splicing declarations
+ [d| f :: Proxy a -> Proxy a
+ f @(a :: k) p = p |]
+ ======>
+ f :: Proxy a -> Proxy a
+ f @(a :: k) p = p
=====================================
testsuite/tests/th/all.T
=====================================
@@ -622,4 +622,5 @@ test('T24572a', normal, compile, [''])
test('T24572b', normal, compile_fail, [''])
test('T24572c', normal, compile_fail, [''])
test('T24572d', normal, compile, [''])
+test('T25209', normal, compile, ['-v0 -ddump-splices -dsuppress-uniques'])
test('TH_MultilineStrings', normal, compile_and_run, [''])
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/c2525e9eaacc62e7f11db0bf0793554c01ca1544
--
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/c2525e9eaacc62e7f11db0bf0793554c01ca1544
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/20240828/bd7b695c/attachment-0001.html>
More information about the ghc-commits
mailing list