[commit: ghc] wip/ttypeable: TcTypeable: A bit more debug output and fix binder ordering (0129388)

git at git.haskell.org git at git.haskell.org
Sun Jan 29 20:21:53 UTC 2017


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

On branch  : wip/ttypeable
Link       : http://ghc.haskell.org/trac/ghc/changeset/01293886816aeae11b479679fa5909f044924525/ghc

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

commit 01293886816aeae11b479679fa5909f044924525
Author: Ben Gamari <ben at smart-cactus.org>
Date:   Sat Jan 28 03:14:52 2017 -0500

    TcTypeable: A bit more debug output and fix binder ordering


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

01293886816aeae11b479679fa5909f044924525
 compiler/typecheck/TcTypeable.hs | 8 ++++++--
 1 file changed, 6 insertions(+), 2 deletions(-)

diff --git a/compiler/typecheck/TcTypeable.hs b/compiler/typecheck/TcTypeable.hs
index e35a27c..96c05d4 100644
--- a/compiler/typecheck/TcTypeable.hs
+++ b/compiler/typecheck/TcTypeable.hs
@@ -429,8 +429,12 @@ F :: forall k. k -> forall k'. k' -> Type
 mkTyConKindRep :: TypeableStuff -> TyCon -> TcRn (LHsExpr Id)
 mkTyConKindRep (Stuff {..}) tycon = do
     let bndrs = mkVarEnv $ (`zip` [0..]) $ map binderVar
-                $ reverse $ filter isNamedTyConBinder (tyConBinders tycon)
-    pprTrace "mkTyConKeyRepBinds" (ppr tycon <+> pprType' (tyConKind tycon)) $ go bndrs (tyConResKind tycon)
+                $ filter isNamedTyConBinder (tyConBinders tycon)
+    pprTrace "mkTyConKindRepBinds"
+             (ppr tycon
+             $$ pprType' (tyConKind tycon)
+             $$ ppr (map binderVar $ filter isNamedTyConBinder $ tyConBinders tycon))
+        $ go bndrs (tyConResKind tycon)
   where
     -- Compute RHS
     go :: VarEnv Int -> Kind -> TcRn (LHsExpr Id)



More information about the ghc-commits mailing list