X-Git-Url: http://git.megacz.com/?a=blobdiff_plain;f=compiler%2Ftypes%2FType.lhs;h=fd275da20458eac892841ad1d8b90b9253c0e1ce;hb=0e73a9fbdc8555ffb948cfd72401a700b122c395;hp=e2405a8644f264af58bff8abbb92216d15191be7;hpb=35fb5c6ff0861be5ab72df799df536982d3966b8;p=ghc-hetmet.git diff --git a/compiler/types/Type.lhs b/compiler/types/Type.lhs index e2405a8..fd275da 100644 --- a/compiler/types/Type.lhs +++ b/compiler/types/Type.lhs @@ -41,7 +41,7 @@ module Type ( applyTy, applyTys, applyTysD, isForAllTy, dropForAlls, -- (Newtypes) - newTyConInstRhs, + newTyConInstRhs, carefullySplitNewType_maybe, -- (Type families) tyFamInsts, predFamInsts, @@ -64,7 +64,7 @@ module Type ( Kind, SimpleKind, KindVar, -- ** Deconstructing Kinds - kindFunResult, splitKindFunTys, splitKindFunTysN, + kindFunResult, splitKindFunTys, splitKindFunTysN, splitKindFunTy_maybe, -- ** Common Kinds and SuperKinds liftedTypeKind, unliftedTypeKind, openTypeKind, @@ -87,7 +87,7 @@ module Type ( -- * Type free variables tyVarsOfType, tyVarsOfTypes, tyVarsOfPred, tyVarsOfTheta, - typeKind, + typeKind, expandTypeSynonyms, -- * Tidying type related things up for printing tidyType, tidyTypes, @@ -98,7 +98,8 @@ module Type ( tidyKind, -- * Type comparison - coreEqType, tcEqType, tcEqTypes, tcCmpType, tcCmpTypes, + coreEqType, coreEqType2, + tcEqType, tcEqTypes, tcCmpType, tcCmpTypes, tcEqPred, tcEqPredX, tcCmpPred, tcEqTypeX, tcPartOfType, tcPartOfPred, -- * Forcing evaluation of types @@ -122,7 +123,7 @@ module Type ( emptyTvSubstEnv, emptyTvSubst, mkTvSubst, mkOpenTvSubst, zipOpenTvSubst, zipTopTvSubst, mkTopTvSubst, notElemTvSubst, - getTvSubstEnv, setTvSubstEnv, getTvInScope, extendTvInScope, + getTvSubstEnv, setTvSubstEnv, getTvInScope, extendTvInScope, extendTvInScopeList, extendTvSubst, extendTvSubstList, isInScope, composeTvSubst, zipTyEnv, isEmptyTvSubst, @@ -132,7 +133,7 @@ module Type ( -- * Pretty-printing pprType, pprParendType, pprTypeApp, pprTyThingCategory, pprTyThing, pprForAll, - pprPred, pprTheta, pprThetaArrow, pprClassPred, pprKind, pprParendKind, + pprPred, pprEqPred, pprTheta, pprThetaArrow, pprClassPred, pprKind, pprParendKind, pprSourceTyCon ) where @@ -281,6 +282,29 @@ tcView (TyConApp tc tys) | Just (tenv, rhs, tys') <- tcExpandTyCon_maybe tc tys tcView _ = Nothing ----------------------------------------------- +expandTypeSynonyms :: Type -> Type +-- ^ Expand out all type synonyms. Actually, it'd suffice to expand out +-- just the ones that discard type variables (e.g. type Funny a = Int) +-- But we don't know which those are currently, so we just expand all. +expandTypeSynonyms ty + = go ty + where + go (TyConApp tc tys) + | Just (tenv, rhs, tys') <- tcExpandTyCon_maybe tc tys + = go (mkAppTys (substTy (mkTopTvSubst tenv) rhs) tys') + | otherwise + = TyConApp tc (map go tys) + go (TyVarTy tv) = TyVarTy tv + go (AppTy t1 t2) = AppTy (go t1) (go t2) + go (FunTy t1 t2) = FunTy (go t1) (go t2) + go (ForAllTy tv t) = ForAllTy tv (go t) + go (PredTy p) = PredTy (go_pred p) + + go_pred (ClassP c ts) = ClassP c (map go ts) + go_pred (IParam ip t) = IParam ip (go t) + go_pred (EqPred t1 t2) = EqPred (go t1) (go t2) + +----------------------------------------------- {-# INLINE kindView #-} kindView :: Kind -> Maybe Kind -- ^ Similar to 'coreView' or 'tcView', but works on 'Kind's @@ -380,7 +404,7 @@ repSplitAppTy_maybe :: Type -> Maybe (Type,Type) repSplitAppTy_maybe (FunTy ty1 ty2) = Just (TyConApp funTyCon [ty1], ty2) repSplitAppTy_maybe (AppTy ty1 ty2) = Just (ty1, ty2) repSplitAppTy_maybe (TyConApp tc tys) - | not (isOpenSynTyCon tc) || length tys > tyConArity tc + | isDecomposableTyCon tc || length tys > tyConArity tc = case snocView tys of -- never create unsaturated type family apps Just (tys', ty') -> Just (TyConApp tc tys', ty') Nothing -> Nothing @@ -404,9 +428,9 @@ splitAppTys ty = split ty ty [] split _ (AppTy ty arg) args = split ty ty (arg:args) split _ (TyConApp tc tc_args) args = let -- keep type families saturated - n | isOpenSynTyCon tc = tyConArity tc - | otherwise = 0 - (tc_args1, tc_args2) = splitAt n tc_args + n | isDecomposableTyCon tc = 0 + | otherwise = tyConArity tc + (tc_args1, tc_args2) = splitAt n tc_args in (TyConApp tc tc_args1, tc_args2 ++ args) split _ (FunTy ty1 ty2) args = ASSERT( null args ) @@ -423,8 +447,8 @@ splitAppTys ty = split ty ty [] \begin{code} mkFunTy :: Type -> Type -> Type -- ^ Creates a function type from the given argument and result type -mkFunTy (PredTy (EqPred ty1 ty2)) res = mkForAllTy (mkWildCoVar (PredTy (EqPred ty1 ty2))) res -mkFunTy arg res = FunTy arg res +mkFunTy arg@(PredTy (EqPred {})) res = ForAllTy (mkWildCoVar arg) res +mkFunTy arg res = FunTy arg res mkFunTys :: [Type] -> Type -> Type mkFunTys tys ty = foldr mkFunTy ty tys @@ -534,7 +558,7 @@ splitTyConApp_maybe (FunTy arg res) = Just (funTyCon, [arg,res]) splitTyConApp_maybe _ = Nothing newTyConInstRhs :: TyCon -> [Type] -> Type --- ^ Unwrap one 'layer' of newtype on a type constructor and it's arguments, using an +-- ^ Unwrap one 'layer' of newtype on a type constructor and its arguments, using an -- eta-reduced version of the @newtype@ if possible newTyConInstRhs tycon tys = ASSERT2( equalLength tvs tys1, ppr tycon $$ ppr tys $$ ppr tvs ) @@ -596,14 +620,9 @@ newtype at outermost level; and bale out if we see it again. -- | Looks through: -- -- 1. For-alls --- -- 2. Synonyms --- -- 3. Predicates --- --- 4. Usage annotations --- --- 5. All newtypes, including recursive ones, but not newtype families +-- 4. All newtypes, including recursive ones, but not newtype families -- -- It's useful in the back end of the compiler. repType :: Type -> Type @@ -618,19 +637,25 @@ repType ty go rec_nts (ForAllTy _ ty) -- Look through foralls = go rec_nts ty - go rec_nts ty@(TyConApp tc tys) -- Expand newtypes - | Just _co_con <- newTyConCo_maybe tc -- See Note [Expanding newtypes] - = if tc `elem` rec_nts -- in Type.lhs - then ty - else go rec_nts' nt_rhs - where - nt_rhs = newTyConInstRhs tc tys - rec_nts' | isRecursiveTyCon tc = tc:rec_nts - | otherwise = rec_nts + go rec_nts (TyConApp tc tys) -- Expand newtypes + | Just (rec_nts', ty') <- carefullySplitNewType_maybe rec_nts tc tys + = go rec_nts' ty' go _ ty = ty +carefullySplitNewType_maybe :: [TyCon] -> TyCon -> [Type] -> Maybe ([TyCon],Type) +-- Return the representation of a newtype, unless +-- we've seen it already: see Note [Expanding newtypes] +carefullySplitNewType_maybe rec_nts tc tys + | isNewTyCon tc + , not (tc `elem` rec_nts) = Just (rec_nts', newTyConInstRhs tc tys) + | otherwise = Nothing + where + rec_nts' | isRecursiveTyCon tc = tc:rec_nts + | otherwise = rec_nts + + -- ToDo: this could be moved to the code generator, using splitTyConApp instead -- of inspecting the type directly. @@ -657,7 +682,7 @@ typePrimRep ty = case repType ty of \begin{code} mkForAllTy :: TyVar -> Type -> Type mkForAllTy tyvar ty - = mkForAllTys [tyvar] ty + = ForAllTy tyvar ty -- | Wraps foralls over the type using the provided 'TyVar's from left to right mkForAllTys :: [TyVar] -> Type -> Type @@ -1116,11 +1141,14 @@ See Note [Newtype eta] in TyCon.lhs \begin{code} -- | Type equality test for Core types (i.e. ignores predicate-types, synonyms etc.) coreEqType :: Type -> Type -> Bool -coreEqType t1 t2 - = eq rn_env t1 t2 +coreEqType t1 t2 = coreEqType2 rn_env t1 t2 where rn_env = mkRnEnv2 (mkInScopeSet (tyVarsOfType t1 `unionVarSet` tyVarsOfType t2)) +coreEqType2 :: RnEnv2 -> Type -> Type -> Bool +coreEqType2 rn_env t1 t2 + = eq rn_env t1 t2 + where eq env (TyVarTy tv1) (TyVarTy tv2) = rnOccL env tv1 == rnOccR env tv2 eq env (ForAllTy tv1 t1) (ForAllTy tv2 t2) = eq (rnBndr2 env tv1 tv2) t1 t2 eq env (AppTy s1 t1) (AppTy s2 t2) = eq env s1 s2 && eq env t1 t2 @@ -1409,8 +1437,11 @@ notElemTvSubst tv (TvSubst _ env) = not (tv `elemVarEnv` env) setTvSubstEnv :: TvSubst -> TvSubstEnv -> TvSubst setTvSubstEnv (TvSubst in_scope _) env = TvSubst in_scope env -extendTvInScope :: TvSubst -> [Var] -> TvSubst -extendTvInScope (TvSubst in_scope env) vars = TvSubst (extendInScopeSetList in_scope vars) env +extendTvInScope :: TvSubst -> Var -> TvSubst +extendTvInScope (TvSubst in_scope env) var = TvSubst (extendInScopeSet in_scope var) env + +extendTvInScopeList :: TvSubst -> [Var] -> TvSubst +extendTvInScopeList (TvSubst in_scope env) vars = TvSubst (extendInScopeSetList in_scope vars) env extendTvSubst :: TvSubst -> TyVar -> Type -> TvSubst extendTvSubst (TvSubst in_scope env) tv ty = TvSubst in_scope (extendVarEnv env tv ty) @@ -1696,6 +1727,9 @@ kindFunResult k = funResultTy k splitKindFunTys :: Kind -> ([Kind],Kind) splitKindFunTys k = splitFunTys k +splitKindFunTy_maybe :: Kind -> Maybe (Kind,Kind) +splitKindFunTy_maybe = splitFunTy_maybe + -- | Essentially 'splitFunTysN' on kinds splitKindFunTysN :: Int -> Kind -> ([Kind],Kind) splitKindFunTysN k = splitFunTysN k