Skip to content
Snippets Groups Projects
Commit ef7fd0ae authored by Eugene Akentyev's avatar Eugene Akentyev Committed by Ben Gamari
Browse files

Parenthesize infix type names in data declarations in TH printer

Previously datatype names were not paraenthesized (#13887).

Reviewers: austin, bgamari, RyanGlScott

Reviewed By: RyanGlScott

Subscribers: RyanGlScott, rwbarton, thomie

Differential Revision: https://phabricator.haskell.org/D3717
parent 85ac65c5
No related merge requests found
......@@ -399,7 +399,7 @@ ppr_data :: Doc -> Cxt -> Name -> Doc -> Maybe Kind -> [Con] -> [DerivClause]
ppr_data maybeInst ctxt t argsDoc ksig cs decs
= sep [text "data" <+> maybeInst
<+> pprCxt ctxt
<+> ppr t <+> argsDoc <+> ksigDoc <+> maybeWhere,
<+> pprName' Applied t <+> argsDoc <+> ksigDoc <+> maybeWhere,
nest nestDepth (sep (pref $ map ppr cs)),
if null decs
then empty
......@@ -679,8 +679,9 @@ pprStrictType = pprBangType
------------------------------
pprParendType :: Type -> Doc
pprParendType (VarT v) = ppr v
pprParendType (ConT c) = ppr c
pprParendType (VarT v) = pprName' Applied v
-- `Applied` is used here instead of `ppr` because of infix names (#13887)
pprParendType (ConT c) = pprName' Applied c
pprParendType (TupleT 0) = text "()"
pprParendType (TupleT n) = parens (hcat (replicate (n-1) comma))
pprParendType (UnboxedTupleT n) = hashParens $ hcat $ replicate (n-1) comma
......
......@@ -8,7 +8,7 @@ newtype Bar_13 :: * -> GHC.Types.Bool -> *
= MkBar_14 :: a_15 -> Bar_13 a_15 b_16
data T10828.T (a_0 :: *) where
T10828.MkT :: forall (a_1 :: *) . a_1 -> a_1 -> T10828.T a_1
T10828.MkC :: forall (a_2 :: *) (b_3 :: *) . Data.Type.Equality.~ a_2
T10828.MkC :: forall (a_2 :: *) (b_3 :: *) . (Data.Type.Equality.~) a_2
GHC.Types.Int => {T10828.foo :: a_2,
T10828.bar :: b_3} -> T10828.T GHC.Types.Int
data T'_0 a_1 :: * where
......
data Main.T
= Main.T ((# , #) GHC.Types.Int
GHC.Types.Int :: GHC.Prim.TYPE (GHC.Types.TupleRep (GHC.Types.: GHC.Types.LiftedRep
(GHC.Types.: GHC.Types.LiftedRep
GHC.Types.[]))))
GHC.Types.Int :: GHC.Prim.TYPE (GHC.Types.TupleRep ((GHC.Types.:) GHC.Types.LiftedRep
((GHC.Types.:) GHC.Types.LiftedRep
GHC.Types.[]))))
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