X-Git-Url: http://git.megacz.com/?p=ghc-hetmet.git;a=blobdiff_plain;f=compiler%2Ftypes%2FType.lhs;h=6eaac8c5ccecdc7bb58129787a61a976ef3e5ffc;hp=686bba849f16e8a005e2e7ec4bc66a75ad13ebb6;hb=526c3af1dc98987b6949f4df73c0debccf9875bd;hpb=30c122df62ec75f9ed7f392f24c2925675bf1d06 diff --git a/compiler/types/Type.lhs b/compiler/types/Type.lhs index 686bba8..6eaac8c 100644 --- a/compiler/types/Type.lhs +++ b/compiler/types/Type.lhs @@ -55,7 +55,7 @@ module Type ( splitTyConApp_maybe, splitTyConApp, splitNewTyConApp_maybe, splitNewTyConApp, - repType, typePrimRep, coreView, tcView, kindView, rttiView, + repType, typePrimRep, coreView, tcView, kindView, mkForAllTy, mkForAllTys, splitForAllTy_maybe, splitForAllTys, applyTy, applyTys, isForAllTy, dropForAlls, @@ -87,7 +87,7 @@ module Type ( -- Comparison coreEqType, tcEqType, tcEqTypes, tcCmpType, tcCmpTypes, - tcEqPred, tcCmpPred, tcEqTypeX, tcPartOfType, tcPartOfPred, + tcEqPred, tcEqPredX, tcCmpPred, tcEqTypeX, tcPartOfType, tcPartOfPred, -- Seq seqType, seqTypes, @@ -188,16 +188,6 @@ tcView (TyConApp tc tys) | Just (tenv, rhs, tys') <- tcExpandTyCon_maybe tc tys tcView _ = Nothing ----------------------------------------------- -rttiView :: Type -> Type --- Same, but for the RTTI system, which cannot deal with predicates nor polymorphism -rttiView (ForAllTy _ ty) = rttiView ty -rttiView (FunTy PredTy{} ty) = rttiView ty -rttiView ty@TyConApp{} | Just ty' <- coreView ty - = rttiView ty' -rttiView (TyConApp tc tys) = mkTyConApp tc (map rttiView tys) -rttiView ty = ty - ------------------------------------------------ {-# INLINE kindView #-} kindView :: Kind -> Maybe Kind -- C.f. coreView, tcView @@ -1028,6 +1018,9 @@ tcCmpTypes tys1 tys2 = cmpTypes tys1 tys2 tcEqPred :: PredType -> PredType -> Bool tcEqPred p1 p2 = isEqual $ cmpPred p1 p2 +tcEqPredX :: RnEnv2 -> PredType -> PredType -> Bool +tcEqPredX env p1 p2 = isEqual $ cmpPredX env p1 p2 + tcCmpPred :: PredType -> PredType -> Ordering tcCmpPred p1 p2 = cmpPred p1 p2 @@ -1268,6 +1261,19 @@ extendTvSubstList (TvSubst in_scope env) tvs tys -- the types given; but it's just a thunk so with a bit of luck -- it'll never be evaluated +-- Note [Generating the in-scope set for a substitution] +-- ~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~ +-- If we want to substitute [a -> ty1, b -> ty2] I used to +-- think it was enough to generate an in-scope set that includes +-- fv(ty1,ty2). But that's not enough; we really should also take the +-- free vars of the type we are substituting into! Example: +-- (forall b. (a,b,x)) [a -> List b] +-- Then if we use the in-scope set {b}, there is a danger we will rename +-- the forall'd variable to 'x' by mistake, getting this: +-- (forall x. (List b, x, x) +-- Urk! This means looking at all the calls to mkOpenTvSubst.... + + mkOpenTvSubst :: TvSubstEnv -> TvSubst mkOpenTvSubst env = TvSubst (mkInScopeSet (tyVarsOfTypes (varEnvElts env))) env @@ -1320,9 +1326,9 @@ zip_ty_env tvs tys env = pprTrace "Var/Type length mismatch: " (ppr instance Outputable TvSubst where ppr (TvSubst ins env) - = brackets $ sep[ ptext SLIT("TvSubst"), - nest 2 (ptext SLIT("In scope:") <+> ppr ins), - nest 2 (ptext SLIT("Env:") <+> ppr env) ] + = brackets $ sep[ ptext (sLit "TvSubst"), + nest 2 (ptext (sLit "In scope:") <+> ppr ins), + nest 2 (ptext (sLit "Env:") <+> ppr env) ] \end{code} %************************************************************************