Skip to content
Snippets Groups Projects
Commit 9bc10993 authored by Vladislav Zavialov's avatar Vladislav Zavialov Committed by Marge Bot
Browse files

Print role annotations in TemplateHaskell brackets (#16718)

parent 1a3420ca
No related branches found
No related tags found
No related merge requests found
......@@ -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,
......
{-# LANGUAGE RoleAnnotations, TemplateHaskell #-}
module T16718 where
$([d| type role P phantom
data P a
|])
T16718.hs:(5,3)-(7,6): Splicing declarations
[d| type role P phantom
data P a |]
======>
type role P phantom
data P a
......@@ -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'])
......@@ -4,6 +4,8 @@ T15365.hs:(9,3)-(31,6): Splicing declarations
pattern (:!!!) :: Bool
pattern (:!!!) = True
type role (***)
type (|||) = Either
data (***)
class (???)
......
0% Loading or .
You are about to add 0 people to the discussion. Proceed with caution.
Finish editing this message first!
Please register or to comment