X-Git-Url: http://git.megacz.com/?p=ghc-hetmet.git;a=blobdiff_plain;f=compiler%2Ftypes%2FType.lhs;h=b7f521a15d12e245bf5384bf21667c1547dd1d9c;hp=fd8e8c5ac61915e57ef6293ebc19d4457de9217f;hb=6fcf90065dc4e75b7dc6bbf238a9891a71ae5a86;hpb=15cb792d18b1094e98c035dca6ecec5dad516056 diff --git a/compiler/types/Type.lhs b/compiler/types/Type.lhs index fd8e8c5..b7f521a 100644 --- a/compiler/types/Type.lhs +++ b/compiler/types/Type.lhs @@ -24,7 +24,7 @@ module Type ( isLiftedTypeKind, isUnliftedTypeKind, isOpenTypeKind, isUbxTupleKind, isArgTypeKind, isKind, isTySuperKind, - isCoSuperKind, isSuperKind, isCoercionKind, + isCoSuperKind, isSuperKind, isCoercionKind, isEqPred, mkArrowKind, mkArrowKinds, isSubArgTypeKind, isSubOpenTypeKind, isSubKind, defaultKind, eqKind, @@ -56,7 +56,7 @@ module Type ( predTypeRep, mkPredTy, mkPredTys, -- Newtypes - splitRecNewType_maybe, + splitRecNewType_maybe, newTyConInstRhs, -- Lifting and boxity isUnLiftedType, isUnboxedTupleType, isAlgType, isPrimitiveType, @@ -106,7 +106,7 @@ import TypeRep -- friends: import Var ( Var, TyVar, tyVarKind, tyVarName, - setTyVarName, setTyVarKind ) + setTyVarName, setTyVarKind, mkWildTyVar ) import VarEnv import VarSet @@ -164,7 +164,9 @@ coreView :: Type -> Maybe Type -- By being non-recursive and inlined, this case analysis gets efficiently -- joined onto the case analysis that the caller is already doing coreView (NoteTy _ ty) = Just ty -coreView (PredTy p) = Just (predTypeRep p) +coreView (PredTy p) + | isEqPred p = Nothing + | otherwise = Just (predTypeRep p) coreView (TyConApp tc tys) | Just (tenv, rhs, tys') <- coreExpandTyCon_maybe tc tys = Just (mkAppTys (substTy (mkTopTvSubst tenv) rhs) tys') -- Its important to use mkAppTys, rather than (foldl AppTy), @@ -305,10 +307,11 @@ splitAppTys ty = split ty ty [] \begin{code} mkFunTy :: Type -> Type -> Type +mkFunTy (PredTy (EqPred ty1 ty2)) res = mkForAllTy (mkWildTyVar (PredTy (EqPred ty1 ty2))) res mkFunTy arg res = FunTy arg res mkFunTys :: [Type] -> Type -> Type -mkFunTys tys ty = foldr FunTy ty tys +mkFunTys tys ty = foldr mkFunTy ty tys isFunTy :: Type -> Bool isFunTy ty = isJust (splitFunTy_maybe ty) @@ -410,6 +413,12 @@ splitNewTyConApp_maybe (TyConApp tc tys) = Just (tc, tys) splitNewTyConApp_maybe (FunTy arg res) = Just (funTyCon, [arg,res]) splitNewTyConApp_maybe other = Nothing +-- get instantiated newtype rhs, the arguments had better saturate +-- the constructor +newTyConInstRhs :: TyCon -> [Type] -> Type +newTyConInstRhs tycon tys = + let (tvs, ty) = newTyConRhs tycon in substTyWith tvs tys ty + \end{code} @@ -590,6 +599,7 @@ predTypeRep (IParam _ ty) = ty predTypeRep (ClassP clas tys) = mkTyConApp (classTyCon clas) tys -- Result might be a newtype application, but the consumer will -- look through that too if necessary +predTypeRep (EqPred ty1 ty2) = pprPanic "predTypeRep" (ppr (EqPred ty1 ty2)) \end{code} @@ -1417,6 +1427,8 @@ isSubKind :: Kind -> Kind -> Bool -- (k1 `isSubKind` k2) checks that k1 <: k2 isSubKind (TyConApp kc1 []) (TyConApp kc2 []) = kc1 `isSubKindCon` kc1 isSubKind (FunTy a1 r1) (FunTy a2 r2) = (a2 `isSubKind` a1) && (r1 `isSubKind` r2) +isSubKind (PredTy (EqPred ty1 ty2)) (PredTy (EqPred ty1' ty2')) + = ty1 `tcEqType` ty1' && ty2 `tcEqType` ty2' isSubKind k1 k2 = False eqKind :: Kind -> Kind -> Bool @@ -1459,4 +1471,8 @@ isCoercionKind :: Kind -> Bool isCoercionKind k | Just k' <- kindView k = isCoercionKind k' isCoercionKind (PredTy (EqPred {})) = True isCoercionKind other = False + +isEqPred :: PredType -> Bool +isEqPred (EqPred _ _) = True +isEqPred other = False \end{code}