[commit: ghc] master: Never unify a SigTyVar with a non-tyvar type (fixes Trac #7786) (6ebab3d)

Simon Peyton Jones simonpj at microsoft.com
Mon Apr 22 13:59:49 CEST 2013


Repository : http://darcs.haskell.org/ghc.git/

On branch  : master

https://github.com/ghc/ghc/commit/6ebab3df7e68f8325ef60111c0c7755dd6ffcc91

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

commit 6ebab3df7e68f8325ef60111c0c7755dd6ffcc91
Author: Simon Peyton Jones <simonpj at microsoft.com>
Date:   Mon Apr 22 12:50:24 2013 +0100

    Never unify a SigTyVar with a non-tyvar type (fixes Trac #7786)
    
    This unwanted unification was happening in the zonking phase
    which un-flattens type-function applications (TcMType.zonkFlats,
    try_zonk_fun_eq).  The main unifier is careful to make the check,
    but I'd forgotten it here.  That in turn led to a very confusing
    error message.

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

 compiler/typecheck/TcMType.lhs | 4 ++--
 1 file changed, 2 insertions(+), 2 deletions(-)

diff --git a/compiler/typecheck/TcMType.lhs b/compiler/typecheck/TcMType.lhs
index d8d4b63..7ac66d0 100644
--- a/compiler/typecheck/TcMType.lhs
+++ b/compiler/typecheck/TcMType.lhs
@@ -702,9 +702,9 @@ zonkFlats binds_var untch cts
       , Just tv <- getTyVar_maybe ty_rhs
       , ASSERT2( not (isFloatedTouchableMetaTyVar untch tv), ppr tv )
         isTouchableMetaTyVar untch tv
-      , typeKind ty_lhs `tcIsSubKind` tyVarKind tv
+      , not (isSigTyVar tv) || isTyVarTy ty_lhs     -- Never unify a SigTyVar with a non-tyvar
+      , typeKind ty_lhs `tcIsSubKind` tyVarKind tv  -- c.f. TcInteract.trySpontaneousEqOneWay
       , not (tv `elemVarSet` tyVarsOfType ty_lhs)
---       , Just ty_lhs' <- occurCheck tv ty_lhs
       = ASSERT2( isWantedCt orig_ct, ppr orig_ct )
         ASSERT2( case tcSplitTyConApp_maybe ty_lhs of { Just (tc,_) -> isSynFamilyTyCon tc; _ -> False }, ppr orig_ct )
         do { writeMetaTyVar tv ty_lhs





More information about the ghc-commits mailing list