Repository : ssh://darcs.haskell.org//srv/darcs/ghc

On branch  : ghc-kinds

http://hackage.haskell.org/trac/ghc/changeset/5ec4bf220c2b1e223668a7c82fe346288ebd4001

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

commit 5ec4bf220c2b1e223668a7c82fe346288ebd4001
Author: Julien Cretin <g...@ia0.eu>
Date:   Thu Sep 22 13:37:26 2011 +0200

    add todos for kind unification

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

 compiler/types/FamInstEnv.lhs |    7 ++-----
 compiler/types/Unify.lhs      |    5 ++++-
 2 files changed, 6 insertions(+), 6 deletions(-)

diff --git a/compiler/types/FamInstEnv.lhs b/compiler/types/FamInstEnv.lhs
index f3b1695..da6f26f 100644
--- a/compiler/types/FamInstEnv.lhs
+++ b/compiler/types/FamInstEnv.lhs
@@ -280,9 +280,7 @@ lookupFamInstEnvConflicts
 -- Precondition: the tycon is saturated (or over-saturated)
 
 lookupFamInstEnvConflicts envs fam_inst skol_tvs
-  = pprTrace "IA0_DEBUG" (vcat [ text "(fam, tys)" <+> ppr (fam, tys)
-                               , text "tys'" <+> (ppr tys') ]) $
-    lookup_fam_inst_env my_unify False envs fam tys'
+  = lookup_fam_inst_env my_unify False envs fam tys'
   where
     inst_tycon = famInstTyCon fam_inst
     (fam, tys) = expectJust "FamInstEnv.lookuFamInstEnvConflicts"
@@ -297,8 +295,7 @@ lookupFamInstEnvConflicts envs fam_inst skol_tvs
                  (ppr tpl_tvs <+> ppr tpl_tys) )
                -- Unification will break badly if the variables overlap
                -- They shouldn't because we allocate separate uniques for them
-         case pprTrace "IA0_DEBUG unify" (ppr (tpl_tys, match_tys)) $
-              tcUnifyTys instanceBindFun tpl_tys match_tys of
+         case tcUnifyTys instanceBindFun tpl_tys match_tys of
              Just subst | conflicting old_fam_inst subst -> Just subst
              _other                                      -> Nothing
 
diff --git a/compiler/types/Unify.lhs b/compiler/types/Unify.lhs
index 6f5f1da..2756aa3 100644
--- a/compiler/types/Unify.lhs
+++ b/compiler/types/Unify.lhs
@@ -408,7 +408,9 @@ niSubstTvSet subst tvs
 %************************************************************************
 
 \begin{code}
--- IA0_TODO: Do we need to unify the kinds of the type variables?
+-- IA0_TODO: BUG: all the following function (all this file actually)
+-- needs to handle kind unification during type unification and kind
+-- match during type match !!!
 unify :: TvSubstEnv    -- An existing substitution to extend
       -> Type -> Type  -- Types to be unified, and witness of their equality
       -> UM TvSubstEnv         -- Just the extended substitution, 
@@ -504,6 +506,7 @@ uUnrefined subst tv1 ty2 (TyVarTy tv2)
   = uUnrefined subst tv1 ty' ty'
 
   -- So both are unrefined; next, see if the kinds force the direction
+  -- IA0_TODO: we might need to call unify instead
   | eqKind k1 k2       -- Can update either; so check the bind-flags
   = do { b1 <- tvBindFlag tv1
        ; b2 <- tvBindFlag tv2



_______________________________________________
Cvs-ghc mailing list
Cvs-ghc@haskell.org
http://www.haskell.org/mailman/listinfo/cvs-ghc

Reply via email to