[commit: ghc] master: pprIfaceContextArr: print a context including the "=>" arrow (23c0f1e)
git at git.haskell.org
git at git.haskell.org
Thu Mar 13 13:21:39 UTC 2014
Repository : ssh://git@git.haskell.org/ghc
On branch : master
Link : http://ghc.haskell.org/trac/ghc/changeset/23c0f1ec2cf06c0178c2ae7414fe57ea648689e7/ghc
>---------------------------------------------------------------
commit 23c0f1ec2cf06c0178c2ae7414fe57ea648689e7
Author: Dr. ERDI Gergo <gergo at erdi.hu>
Date: Wed Mar 12 20:38:26 2014 +0800
pprIfaceContextArr: print a context including the "=>" arrow
>---------------------------------------------------------------
23c0f1ec2cf06c0178c2ae7414fe57ea648689e7
compiler/iface/IfaceSyn.lhs | 2 +-
compiler/iface/IfaceType.lhs | 16 ++++++++--------
2 files changed, 9 insertions(+), 9 deletions(-)
diff --git a/compiler/iface/IfaceSyn.lhs b/compiler/iface/IfaceSyn.lhs
index b582305..3691fca 100644
--- a/compiler/iface/IfaceSyn.lhs
+++ b/compiler/iface/IfaceSyn.lhs
@@ -1152,7 +1152,7 @@ instance Outputable IfaceAT where
pprIfaceDeclHead :: IfaceContext -> OccName -> [IfaceTvBndr] -> SDoc
pprIfaceDeclHead context thing tyvars
- = hsep [pprIfaceContext context, parenSymOcc thing (ppr thing),
+ = hsep [pprIfaceContextArr context, parenSymOcc thing (ppr thing),
pprIfaceTvBndrs tyvars]
pp_condecls :: OccName -> IfaceConDecls -> SDoc
diff --git a/compiler/iface/IfaceType.lhs b/compiler/iface/IfaceType.lhs
index 822e3da..8c1791a 100644
--- a/compiler/iface/IfaceType.lhs
+++ b/compiler/iface/IfaceType.lhs
@@ -22,7 +22,7 @@ module IfaceType (
toIfaceCoercion,
-- Printing
- pprIfaceType, pprParendIfaceType, pprIfaceContext,
+ pprIfaceType, pprParendIfaceType, pprIfaceContext, pprIfaceContextArr,
pprIfaceIdBndr, pprIfaceTvBndr, pprIfaceTvBndrs,
pprIfaceBndrs,
tOP_PREC, tYCON_PREC, noParens, maybeParen, pprIfaceForAllPart,
@@ -253,7 +253,7 @@ ppr_ty ctxt_prec ty@(IfaceForAllTy _ _)
-- generality
pprIfaceForAllPart :: Outputable a => [IfaceTvBndr] -> [a] -> SDoc -> SDoc
pprIfaceForAllPart tvs ctxt doc
- = sep [ppr_tvs, pprIfaceContext ctxt, doc]
+ = sep [ppr_tvs, pprIfaceContextArr ctxt, doc]
where
ppr_tvs | null tvs = empty
| otherwise = ptext (sLit "forall") <+> pprIfaceTvBndrs tvs <> dot
@@ -386,14 +386,14 @@ instance Binary IfaceTyLit where
_ -> panic ("get IfaceTyLit " ++ show tag)
-------------------
-pprIfaceContext :: Outputable a => [a] -> SDoc
+pprIfaceContextArr :: Outputable a => [a] -> SDoc
-- Prints "(C a, D b) =>", including the arrow
-pprIfaceContext [] = empty
-pprIfaceContext theta = ppr_preds theta <+> darrow
+pprIfaceContextArr [] = empty
+pprIfaceContextArr theta = pprIfaceContext theta <+> darrow
-ppr_preds :: Outputable a => [a] -> SDoc
-ppr_preds [pred] = ppr pred -- No parens
-ppr_preds preds = parens (sep (punctuate comma (map ppr preds)))
+pprIfaceContext :: Outputable a => [a] -> SDoc
+pprIfaceContext [pred] = ppr pred -- No parens
+pprIfaceContext preds = parens (sep (punctuate comma (map ppr preds)))
instance Binary IfaceType where
put_ bh (IfaceForAllTy aa ab) = do
More information about the ghc-commits
mailing list