[commit: ghc] master: A bit more tc-tracing (f570000)

git at git.haskell.org git at git.haskell.org
Tue Nov 14 11:12:59 UTC 2017


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

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

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

commit f57000014e5c27822c9c618204a7b3fe0cb0f158
Author: Simon Peyton Jones <simonpj at microsoft.com>
Date:   Tue Nov 14 09:21:39 2017 +0000

    A bit more tc-tracing


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

f57000014e5c27822c9c618204a7b3fe0cb0f158
 compiler/typecheck/TcHsType.hs | 4 +++-
 compiler/typecheck/TcType.hs   | 5 ++++-
 2 files changed, 7 insertions(+), 2 deletions(-)

diff --git a/compiler/typecheck/TcHsType.hs b/compiler/typecheck/TcHsType.hs
index 19fd5c1..07cd4d2 100644
--- a/compiler/typecheck/TcHsType.hs
+++ b/compiler/typecheck/TcHsType.hs
@@ -1451,7 +1451,9 @@ kcHsTyVarBndrs name flav cusk all_kind_vars
              tycon = mkTcTyCon name binders res_kind
                                (scoped_kvs ++ binderVars binders) flav
 
-       ; traceTc "kcHsTyVarBndrs: not-cusk" (ppr name <+> ppr binders)
+       ; traceTc "kcHsTyVarBndrs: not-cusk" $
+         vcat [ ppr name, ppr kv_ns, ppr hs_tvs, ppr dep_names
+              , ppr binders, ppr (mkTyConKind binders res_kind) ]
        ; return (tycon, stuff) }
   where
     open_fam = tcFlavourIsOpen flav
diff --git a/compiler/typecheck/TcType.hs b/compiler/typecheck/TcType.hs
index d781aec..f1ea864 100644
--- a/compiler/typecheck/TcType.hs
+++ b/compiler/typecheck/TcType.hs
@@ -1634,7 +1634,10 @@ tcGetTyVar_maybe (TyVarTy tv)   = Just tv
 tcGetTyVar_maybe _              = Nothing
 
 tcGetTyVar :: String -> Type -> TyVar
-tcGetTyVar msg ty = expectJust msg (tcGetTyVar_maybe ty)
+tcGetTyVar msg ty
+  = case tcGetTyVar_maybe ty of
+     Just tv -> tv
+     Nothing -> pprPanic msg (ppr ty)
 
 tcIsTyVarTy :: Type -> Bool
 tcIsTyVarTy ty | Just ty' <- tcView ty = tcIsTyVarTy ty'



More information about the ghc-commits mailing list