[commit: ghc] master: Debug tracing only (5a7c657)
git at git.haskell.org
git at git.haskell.org
Fri May 18 16:16:48 UTC 2018
Repository : ssh://git@git.haskell.org/ghc
On branch : master
Link : http://ghc.haskell.org/trac/ghc/changeset/5a7c657e02b1e801c84f26ea383f326234cd993c/ghc
>---------------------------------------------------------------
commit 5a7c657e02b1e801c84f26ea383f326234cd993c
Author: Simon Peyton Jones <simonpj at microsoft.com>
Date: Fri May 18 08:47:26 2018 +0100
Debug tracing only
>---------------------------------------------------------------
5a7c657e02b1e801c84f26ea383f326234cd993c
compiler/typecheck/TcHsType.hs | 4 +++-
compiler/typecheck/TcRnTypes.hs | 9 +++++----
compiler/typecheck/TcSimplify.hs | 2 ++
3 files changed, 10 insertions(+), 5 deletions(-)
diff --git a/compiler/typecheck/TcHsType.hs b/compiler/typecheck/TcHsType.hs
index 125891f..ba1fc3f 100644
--- a/compiler/typecheck/TcHsType.hs
+++ b/compiler/typecheck/TcHsType.hs
@@ -213,7 +213,8 @@ tcHsSigType :: UserTypeCtxt -> LHsSigType GhcRn -> TcM Type
-- See Note [Recipe for checking a signature]
tcHsSigType ctxt sig_ty
= addSigCtxt ctxt (hsSigType sig_ty) $
- do { kind <- case expectedKindInCtxt ctxt of
+ do { traceTc "tcHsSigType {" (ppr sig_ty)
+ ; kind <- case expectedKindInCtxt ctxt of
AnythingKind -> newMetaKindVar
TheKind k -> return k
OpenKind -> newOpenTypeKind
@@ -227,6 +228,7 @@ tcHsSigType ctxt sig_ty
else tc_hs_sig_type skol_info sig_ty kind
; checkValidType ctxt ty
+ ; traceTc "end tcHsSigType }" (ppr ty)
; return ty }
where
skol_info = SigTypeSkol ctxt
diff --git a/compiler/typecheck/TcRnTypes.hs b/compiler/typecheck/TcRnTypes.hs
index cc5c7ec..ba07ff8 100644
--- a/compiler/typecheck/TcRnTypes.hs
+++ b/compiler/typecheck/TcRnTypes.hs
@@ -2511,8 +2511,9 @@ instance Outputable Implication where
ppr (Implic { ic_tclvl = tclvl, ic_skols = skols
, ic_given = given, ic_no_eqs = no_eqs
, ic_wanted = wanted, ic_status = status
- , ic_binds = binds, ic_need_inner = need_in
- , ic_need_outer = need_out, ic_info = info })
+ , ic_binds = binds
+-- , ic_need_inner = need_in, ic_need_outer = need_out
+ , ic_info = info })
= hang (text "Implic" <+> lbrace)
2 (sep [ text "TcLevel =" <+> ppr tclvl
, text "Skolems =" <+> pprTyVars skols
@@ -2521,8 +2522,8 @@ instance Outputable Implication where
, hang (text "Given =") 2 (pprEvVars given)
, hang (text "Wanted =") 2 (ppr wanted)
, text "Binds =" <+> ppr binds
- , text "Needed inner =" <+> ppr need_in
- , text "Needed outer =" <+> ppr need_out
+-- , text "Needed inner =" <+> ppr need_in
+-- , text "Needed outer =" <+> ppr need_out
, pprSkolInfo info ] <+> rbrace)
instance Outputable ImplicStatus where
diff --git a/compiler/typecheck/TcSimplify.hs b/compiler/typecheck/TcSimplify.hs
index 136e60a..84f4eca 100644
--- a/compiler/typecheck/TcSimplify.hs
+++ b/compiler/typecheck/TcSimplify.hs
@@ -154,6 +154,8 @@ solveLocalEqualities thing_inside
; traceTc "solveLocalEqualities: running solver }" (ppr reduced_wanted)
; emitConstraints reduced_wanted
+
+ ; traceTc "solveLocalEqualities end }" empty
; return result }
-- | Type-check a thing that emits only equality constraints, then
More information about the ghc-commits
mailing list