[Git][ghc/ghc][wip/16718] Print role annotations in TemplateHaskell brackets (#16718)
Vladislav Zavialov
gitlab at gitlab.haskell.org
Sat Jun 1 21:03:05 UTC 2019
Vladislav Zavialov pushed to branch wip/16718 at Glasgow Haskell Compiler / GHC
Commits:
d0fff215 by Vladislav Zavialov at 2019-06-01T21:02:51Z
Print role annotations in TemplateHaskell brackets (#16718)
- - - - -
5 changed files:
- compiler/hsSyn/HsDecls.hs
- + testsuite/tests/roles/should_compile/T16718.hs
- + testsuite/tests/roles/should_compile/T16718.stderr
- testsuite/tests/roles/should_compile/all.T
- testsuite/tests/th/T15365.stderr
Changes:
=====================================
compiler/hsSyn/HsDecls.hs
=====================================
@@ -302,6 +302,7 @@ instance (p ~ GhcPass pass, OutputableBndrId p) => Outputable (HsGroup p) where
if isEmptyValBinds val_decls
then Nothing
else Just (ppr val_decls),
+ ppr_ds (tyClGroupRoleDecls tycl_decls),
ppr_ds (tyClGroupTyClDecls tycl_decls),
ppr_ds (tyClGroupInstDecls tycl_decls),
ppr_ds deriv_decls,
=====================================
testsuite/tests/roles/should_compile/T16718.hs
=====================================
@@ -0,0 +1,7 @@
+{-# LANGUAGE RoleAnnotations, TemplateHaskell #-}
+
+module T16718 where
+
+$([d| type role P phantom
+ data P a
+ |])
=====================================
testsuite/tests/roles/should_compile/T16718.stderr
=====================================
@@ -0,0 +1,7 @@
+T16718.hs:(5,3)-(7,6): Splicing declarations
+ [d| type role P phantom
+
+ data P a |]
+ ======>
+ type role P phantom
+ data P a
=====================================
testsuite/tests/roles/should_compile/all.T
=====================================
@@ -10,3 +10,4 @@ test('T8958', [normalise_fun(normalise_errmsg), only_ways('normal')], compile, [
test('T10263', normal, compile, [''])
test('T9204b', [], multimod_compile, ['T9204b', '-v0'])
test('T14101', normal, compile, [''])
+test('T16718', normal, compile, ['-v0 -ddump-splices -dsuppress-uniques'])
=====================================
testsuite/tests/th/T15365.stderr
=====================================
@@ -4,6 +4,8 @@ T15365.hs:(9,3)-(31,6): Splicing declarations
pattern (:!!!) :: Bool
pattern (:!!!) = True
+ type role (***)
+
type (|||) = Either
data (***)
class (???)
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/commit/d0fff215da8bd8804ae6d044a0a6be3764125899
--
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/commit/d0fff215da8bd8804ae6d044a0a6be3764125899
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/20190601/504eb422/attachment-0001.html>
More information about the ghc-commits
mailing list