[commit: ghc] master: Add a bit more typechecker tracing (02227dd)

git at git.haskell.org git at git.haskell.org
Tue May 6 08:43:43 UTC 2014


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

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

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

commit 02227ddddf56301a9c9bafac81742c0585e9a108
Author: Simon Peyton Jones <simonpj at microsoft.com>
Date:   Tue May 6 08:23:26 2014 +0100

    Add a bit more typechecker tracing
    
    This is in pursuit of Trac #9063


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

02227ddddf56301a9c9bafac81742c0585e9a108
 compiler/typecheck/TcInstDcls.lhs | 8 ++++++--
 1 file changed, 6 insertions(+), 2 deletions(-)

diff --git a/compiler/typecheck/TcInstDcls.lhs b/compiler/typecheck/TcInstDcls.lhs
index fc18429..51e1528 100644
--- a/compiler/typecheck/TcInstDcls.lhs
+++ b/compiler/typecheck/TcInstDcls.lhs
@@ -37,6 +37,7 @@ import TcDeriv
 import TcEnv
 import TcHsType
 import TcUnify
+import Coercion   ( pprCoAxiom, pprCoAxBranch )
 import MkCore     ( nO_METHOD_BINDING_ERROR_ID )
 import Type
 import TcEvidence
@@ -545,13 +546,16 @@ tcClsInstDecl (L loc (ClsInstDecl { cid_poly_ty = poly_ty, cid_binds = binds
                  --            instance C [x]
                  -- Then we want to generate the decl:   type F [x] b = ()
                 | otherwise 
-                = forM defs $ \(CoAxBranch { cab_lhs = pat_tys, cab_rhs = rhs }) ->
+                = forM defs $ \br@(CoAxBranch { cab_lhs = pat_tys, cab_rhs = rhs }) ->
                   do { let pat_tys' = substTys mini_subst pat_tys
                            rhs'     = substTy  mini_subst rhs
                            tv_set'  = tyVarsOfTypes pat_tys'
-                           tvs'     = varSetElems tv_set'
+                           tvs'     = varSetElemsKvsFirst tv_set'
                      ; rep_tc_name <- newFamInstTyConName (noLoc (tyConName fam_tc)) pat_tys'
                      ; let axiom = mkSingleCoAxiom rep_tc_name tvs' fam_tc pat_tys' rhs'
+                     ; traceTc "mk_deflt_at_instance" (vcat [ ppr (tyvars, theta, clas, inst_tys)
+                                                            , pprCoAxBranch fam_tc br
+                                                            , pprCoAxiom axiom ])
                      ; ASSERT( tyVarsOfType rhs' `subVarSet` tv_set' ) 
                        newFamInst SynFamilyInst axiom }
 



More information about the ghc-commits mailing list