[Git][ghc/ghc][master] Fix and test TH pretty-printing of type operator role declarations
Marge Bot (@marge-bot)
gitlab at gitlab.haskell.org
Fri Sep 15 15:19:07 UTC 2023
Marge Bot pushed to branch master at Glasgow Haskell Compiler / GHC
Commits:
566ef411 by Mario Blažević at 2023-09-15T11:18:43-04:00
Fix and test TH pretty-printing of type operator role declarations
This commit fixes and tests `Language.Haskell.TH.Ppr.pprint` so that it
correctly pretty-prints `type role` declarations for operator names.
Fixes #23954
- - - - -
4 changed files:
- libraries/template-haskell/Language/Haskell/TH/Ppr.hs
- + testsuite/tests/th/T23954.hs
- + testsuite/tests/th/T23954.stdout
- testsuite/tests/th/all.T
Changes:
=====================================
libraries/template-haskell/Language/Haskell/TH/Ppr.hs
=====================================
@@ -456,7 +456,7 @@ ppr_dec _ (ClosedTypeFamilyD tfhead eqns)
ppr_eqn (TySynEqn mb_bndrs lhs rhs)
= ppr_bndrs mb_bndrs <+> ppr lhs <+> text "=" <+> ppr rhs
ppr_dec _ (RoleAnnotD name roles)
- = hsep [ text "type role", ppr name ] <+> hsep (map ppr roles)
+ = hsep [ text "type role", pprName' Applied name ] <+> hsep (map ppr roles)
ppr_dec _ (StandaloneDerivD ds cxt ty)
= hsep [ text "deriving"
, maybe empty ppr_deriv_strategy ds
=====================================
testsuite/tests/th/T23954.hs
=====================================
@@ -0,0 +1,11 @@
+{-# LANGUAGE Haskell2010, RoleAnnotations, TemplateHaskell, TypeOperators #-}
+
+import Language.Haskell.TH (runQ)
+import Language.Haskell.TH.Ppr (pprint)
+
+main =
+ runQ [d|
+ data a ## b
+ type role (##) nominal nominal
+ |]
+ >>= putStrLn . pprint
=====================================
testsuite/tests/th/T23954.stdout
=====================================
@@ -0,0 +1,2 @@
+data (##_0) a_1 b_2
+type role (##_0) nominal nominal
\ No newline at end of file
=====================================
testsuite/tests/th/all.T
=====================================
@@ -580,7 +580,6 @@ test('T22559a', normal, compile_fail, [''])
test('T22559b', normal, compile_fail, [''])
test('T22559c', normal, compile_fail, [''])
test('T23525', normal, compile, [''])
-test('T23927', normal, compile_and_run, [''])
test('CodeQ_HKD', normal, compile, [''])
test('T23748', normal, compile, [''])
test('T23796', normal, compile, [''])
@@ -588,3 +587,5 @@ test('T23829_timely', normal, compile, [''])
test('T23829_tardy', normal, warn_and_run, [''])
test('T23829_hasty', normal, compile_fail, [''])
test('T23829_hasty_b', normal, compile_fail, [''])
+test('T23927', normal, compile_and_run, [''])
+test('T23954', normal, compile_and_run, [''])
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/566ef411ed720fe9821767fd63697799117b6ee6
--
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/566ef411ed720fe9821767fd63697799117b6ee6
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/20230915/07bbc89f/attachment-0001.html>
More information about the ghc-commits
mailing list