[commit: ghc] master: Show parentheses when printing type (forall x. T1) T2 (#8428) (a83652e)

git at git.haskell.org git
Wed Oct 9 20:10:24 UTC 2013


Repository : ssh://git at git.haskell.org/ghc

On branch  : master
Link       : http://ghc.haskell.org/trac/ghc/changeset/a83652ed4aee321063c17df1ad8560712b33103a/ghc

>---------------------------------------------------------------

commit a83652ed4aee321063c17df1ad8560712b33103a
Author: Krzysztof Gogolewski <krz.gogolewski at gmail.com>
Date:   Wed Oct 9 22:08:02 2013 +0200

    Show parentheses when printing type (forall x. T1) T2 (#8428)
    
    Patch by klao


>---------------------------------------------------------------

a83652ed4aee321063c17df1ad8560712b33103a
 compiler/types/TypeRep.lhs |    5 ++---
 1 file changed, 2 insertions(+), 3 deletions(-)

diff --git a/compiler/types/TypeRep.lhs b/compiler/types/TypeRep.lhs
index 62c5a11..a843be3 100644
--- a/compiler/types/TypeRep.lhs
+++ b/compiler/types/TypeRep.lhs
@@ -473,7 +473,6 @@ This invariant has several crucial consequences:
   the TvSubstEnv is enough
 
 * In substTy, substTheta, we can short-circuit when the TvSubstEnv is empty
-\end{code}
 
 
 
@@ -585,7 +584,7 @@ ppr_type p (LitTy l)          = ppr_tylit p l
 ppr_type p ty@(ForAllTy {})   = ppr_forall_type p ty
 
 ppr_type p (AppTy t1 t2) = maybeParen p TyConPrec $
-			   pprType t1 <+> ppr_type TyConPrec t2
+			   ppr_type FunPrec t1 <+> ppr_type TyConPrec t2
 
 ppr_type p fun_ty@(FunTy ty1 ty2)
   | isPredTy ty1
@@ -601,7 +600,7 @@ ppr_type p fun_ty@(FunTy ty1 ty2)
 
 ppr_forall_type :: Prec -> Type -> SDoc
 ppr_forall_type p ty
-  = maybeParen p FunPrec $ (ppr_sigma_type True ty)
+  = maybeParen p FunPrec $ ppr_sigma_type True ty
 
 ppr_tvar :: TyVar -> SDoc
 ppr_tvar tv  -- Note [Infix type variables]




More information about the ghc-commits mailing list