[Git][ghc/ghc][master] Fixes #25256, missing parens inside TH-printed pattern type signature
Marge Bot (@marge-bot)
gitlab at gitlab.haskell.org
Mon Oct 7 23:24:53 UTC 2024
Marge Bot pushed to branch master at Glasgow Haskell Compiler / GHC
Commits:
3fe621dd by Mario Blažević at 2024-10-07T19:24:18-04:00
Fixes #25256, missing parens inside TH-printed pattern type signature
- - - - -
4 changed files:
- libraries/ghc-boot-th/GHC/Internal/TH/Ppr.hs
- + testsuite/tests/th/T25256.hs
- + testsuite/tests/th/T25256.stdout
- testsuite/tests/th/all.T
Changes:
=====================================
libraries/ghc-boot-th/GHC/Internal/TH/Ppr.hs
=====================================
@@ -398,7 +398,8 @@ pprPat _ (RecP nm fs)
<+> braces (sep $ punctuate comma $
map (\(s,p) -> pprName' Applied s <+> equals <+> ppr p) fs)
pprPat _ (ListP ps) = brackets (commaSep ps)
-pprPat i (SigP p t) = parensIf (i > noPrec) $ ppr p <+> dcolon <+> ppr t
+pprPat i (SigP p t) = parensIf (i > noPrec) $ pprPat sigPrec p
+ <+> dcolon <+> pprType sigPrec t
pprPat _ (ViewP e p) = parens $ pprExp noPrec e <+> text "->" <+> pprPat noPrec p
pprPat _ (TypeP t) = parens $ text "type" <+> ppr t
pprPat _ (InvisP t) = parens $ text "@" <+> ppr t
=====================================
testsuite/tests/th/T25256.hs
=====================================
@@ -0,0 +1,6 @@
+{-# LANGUAGE Haskell2010, ScopedTypeVariables, TemplateHaskell #-}
+
+import Language.Haskell.TH (runQ, Type (UnboxedSumT, UnboxedTupleT))
+import Language.Haskell.TH.Ppr (pprint)
+
+main = runQ [d| f ((a :: [Char]) :: String) = (a :: [Char]) :: String |] >>= putStrLn . pprint
=====================================
testsuite/tests/th/T25256.stdout
=====================================
@@ -0,0 +1 @@
+f_0 ((a_1 :: [GHC.Types.Char]) :: GHC.Internal.Base.String) = (a_1 :: [GHC.Types.Char]) :: GHC.Internal.Base.String
=====================================
testsuite/tests/th/all.T
=====================================
@@ -618,6 +618,7 @@ 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, [''])
+test('T25256', normal, compile_and_run, [''])
test('T24572a', normal, compile, [''])
test('T24572b', normal, compile_fail, [''])
test('T24572c', normal, compile_fail, [''])
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/3fe621dd0e3209291b100e25909ef751ec9612f5
--
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/3fe621dd0e3209291b100e25909ef751ec9612f5
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/20241007/454059e3/attachment-0001.html>
More information about the ghc-commits
mailing list