[commit: ghc] master: Use mkTcEqPred rather than mkEqPred in the type checker (8668c54)

git at git.haskell.org git at git.haskell.org
Wed May 28 08:17:20 UTC 2014


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

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

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

commit 8668c549e8d558ab27126a743c23b0894ce19523
Author: Simon Peyton Jones <simonpj at microsoft.com>
Date:   Wed May 28 09:16:16 2014 +0100

    Use mkTcEqPred rather than mkEqPred in the type checker
    
    Type.mkEqPred has an assertion warning for kind compatibility.  But
    during type checking we may form equality predicates with incompatible
    kinds; hence TcType.mkTcEqPred, which does not check.  We were calling
    the former instead of the latter in a couple of places, leading to
    spurious debug warnings.


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

8668c549e8d558ab27126a743c23b0894ce19523
 compiler/typecheck/TcCanonical.lhs | 2 +-
 compiler/typecheck/TcErrors.lhs    | 2 +-
 compiler/typecheck/TcSMonad.lhs    | 2 +-
 3 files changed, 3 insertions(+), 3 deletions(-)

diff --git a/compiler/typecheck/TcCanonical.lhs b/compiler/typecheck/TcCanonical.lhs
index 670f4cf..43cbb2c 100644
--- a/compiler/typecheck/TcCanonical.lhs
+++ b/compiler/typecheck/TcCanonical.lhs
@@ -1262,7 +1262,7 @@ checkKind new_ev s1 k1 s2 k2   -- See Note [Equalities with incompatible kinds]
     do { traceTcS "canEqLeaf: incompatible kinds" (vcat [ppr k1, ppr k2])
 
          -- Create a derived kind-equality, and solve it
-       ; mw <- newDerived kind_co_loc (mkEqPred k1 k2)
+       ; mw <- newDerived kind_co_loc (mkTcEqPred k1 k2)
        ; case mw of
            Nothing  -> return ()
            Just kev -> emitWorkNC [kev]
diff --git a/compiler/typecheck/TcErrors.lhs b/compiler/typecheck/TcErrors.lhs
index 4732769..88894b4 100644
--- a/compiler/typecheck/TcErrors.lhs
+++ b/compiler/typecheck/TcErrors.lhs
@@ -793,7 +793,7 @@ misMatchOrCND ctxt ct oriented ty1 ty2
        -- or there is no context, don't report the context
   = misMatchMsg oriented ty1 ty2
   | otherwise      
-  = couldNotDeduce givens ([mkEqPred ty1 ty2], orig)
+  = couldNotDeduce givens ([mkTcEqPred ty1 ty2], orig)
   where
     givens = getUserGivens ctxt
     orig   = TypeEqOrigin { uo_actual = ty1, uo_expected = ty2 }
diff --git a/compiler/typecheck/TcSMonad.lhs b/compiler/typecheck/TcSMonad.lhs
index 4e391dc..ec9b6e3 100644
--- a/compiler/typecheck/TcSMonad.lhs
+++ b/compiler/typecheck/TcSMonad.lhs
@@ -1393,7 +1393,7 @@ checkWellStagedDFun pred dfun_id loc
     bind_lvl = TcM.topIdLvl dfun_id
 
 pprEq :: TcType -> TcType -> SDoc
-pprEq ty1 ty2 = pprType $ mkEqPred ty1 ty2
+pprEq ty1 ty2 = pprParendType ty1 <+> char '~' <+> pprParendType ty2
 
 isTouchableMetaTyVarTcS :: TcTyVar -> TcS Bool
 isTouchableMetaTyVarTcS tv



More information about the ghc-commits mailing list