[commit: ghc] master: tc-trace changes only (d25519e)

git at git.haskell.org git at git.haskell.org
Thu Oct 4 15:03:49 UTC 2018


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

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

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

commit d25519e159d98cbd12f1893781e649ddb5a7fe90
Author: Simon Peyton Jones <simonpj at microsoft.com>
Date:   Thu Oct 4 15:30:04 2018 +0100

    tc-trace changes only


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

d25519e159d98cbd12f1893781e649ddb5a7fe90
 compiler/typecheck/TcExpr.hs | 7 ++++---
 1 file changed, 4 insertions(+), 3 deletions(-)

diff --git a/compiler/typecheck/TcExpr.hs b/compiler/typecheck/TcExpr.hs
index 17a07f6..bb9279e 100644
--- a/compiler/typecheck/TcExpr.hs
+++ b/compiler/typecheck/TcExpr.hs
@@ -1122,9 +1122,9 @@ wrapHsArgs f (HsTypeArg t : args) = wrapHsArgs (mkHsAppType f t) args
 wrapHsArgs f (HsArgPar sp : args) = wrapHsArgs (L sp $ HsPar noExt f) args
 
 instance (Outputable tm, Outputable ty) => Outputable (HsArg tm ty) where
-  ppr (HsValArg tm) = text "HsValArg" <> ppr tm
-  ppr (HsTypeArg ty) = text "HsTypeArg" <> ppr ty
-  ppr (HsArgPar sp) = text "HsArgPar" <> ppr sp
+  ppr (HsValArg tm)  = text "HsValArg"  <+> ppr tm
+  ppr (HsTypeArg ty) = text "HsTypeArg" <+> ppr ty
+  ppr (HsArgPar sp)  = text "HsArgPar"  <+> ppr sp
 
 isHsValArg :: HsArg tm ty -> Bool
 isHsValArg (HsValArg {})  = True
@@ -1232,6 +1232,7 @@ tcFunApp :: Maybe SDoc  -- like "The function `f' is applied to"
 tcFunApp m_herald rn_fun tc_fun fun_sigma rn_args res_ty
   = do { let orig = lexprCtOrigin rn_fun
 
+       ; traceTc "tcFunApp" (ppr rn_fun <+> dcolon <+> ppr fun_sigma $$ ppr rn_args $$ ppr res_ty)
        ; (wrap_fun, tc_args, actual_res_ty)
            <- tcArgs rn_fun fun_sigma orig rn_args
                      (m_herald `orElse` mk_app_msg rn_fun rn_args)



More information about the ghc-commits mailing list