Remove dead code
[ghc-hetmet.git] / compiler / types / Type.lhs
index fd81795..a5ff5ad 100644 (file)
@@ -54,11 +54,10 @@ module Type (
        applyTy, applyTys, isForAllTy, dropForAlls,
 
        -- Source types
-       predTypeRep, mkPredTy, mkPredTys,
-       tyConOrigHead, pprSourceTyCon,
+       predTypeRep, mkPredTy, mkPredTys, pprSourceTyCon, mkFamilyTyConApp,
 
        -- Newtypes
-       splitRecNewType_maybe, newTyConInstRhs,
+       newTyConInstRhs,
 
        -- Lifting and boxity
        isUnLiftedType, isUnboxedTupleType, isAlgType, isPrimitiveType,
@@ -89,6 +88,7 @@ module Type (
        mkTvSubst, mkOpenTvSubst, zipOpenTvSubst, zipTopTvSubst, mkTopTvSubst, notElemTvSubst,
        getTvSubstEnv, setTvSubstEnv, getTvInScope, extendTvInScope,
        extendTvSubst, extendTvSubstList, isInScope, composeTvSubst, zipTyEnv,
+        isEmptyTvSubst,
 
        -- Performing substitution on types
        substTy, substTys, substTyWith, substTheta, 
@@ -122,6 +122,7 @@ import Util
 import Outputable
 import UniqSet
 
+import Data.List
 import Data.Maybe      ( isJust )
 \end{code}
 
@@ -603,20 +604,27 @@ predTypeRep (ClassP clas tys) = mkTyConApp (classTyCon clas) tys
        -- look through that too if necessary
 predTypeRep (EqPred ty1 ty2) = pprPanic "predTypeRep" (ppr (EqPred ty1 ty2))
 
--- The original head is the tycon and its variables for a vanilla tycon and it
--- is the family tycon and its type indexes for a family instance.
-tyConOrigHead :: TyCon -> (TyCon, [Type])
-tyConOrigHead tycon = case tyConFamInst_maybe tycon of
-                       Nothing      -> (tycon, mkTyVarTys (tyConTyVars tycon))
-                       Just famInst -> famInst
+mkFamilyTyConApp :: TyCon -> [Type] -> Type
+-- Given a family instance TyCon and its arg types, return the
+-- corresponding family type.  E.g.
+--     data family T a
+--     data instance T (Maybe b) = MkT b       -- Instance tycon :RTL
+-- Then 
+--     mkFamilyTyConApp :RTL Int  =  T (Maybe Int)
+mkFamilyTyConApp tc tys
+  | Just (fam_tc, fam_tys) <- tyConFamInst_maybe tc
+  , let fam_subst = zipTopTvSubst (tyConTyVars tc) tys
+  = mkTyConApp fam_tc (substTys fam_subst fam_tys)
+  | otherwise
+  = mkTyConApp tc tys
 
 -- Pretty prints a tycon, using the family instance in case of a
 -- representation tycon.  For example
 --     e.g.  data T [a] = ...
 -- In that case we want to print `T [a]', where T is the family TyCon
 pprSourceTyCon tycon 
-  | Just (repTyCon, tys) <- tyConFamInst_maybe tycon
-  = ppr $ repTyCon `TyConApp` tys             -- can't be FunTyCon
+  | Just (fam_tc, tys) <- tyConFamInst_maybe tycon
+  = ppr $ fam_tc `TyConApp` tys               -- can't be FunTyCon
   | otherwise
   = ppr tycon
 \end{code}
@@ -624,34 +632,6 @@ pprSourceTyCon tycon
 
 %************************************************************************
 %*                                                                     *
-               NewTypes
-%*                                                                     *
-%************************************************************************
-
-\begin{code}
-splitRecNewType_maybe :: Type -> Maybe Type
--- Sometimes we want to look through a recursive newtype, and that's what happens here
--- It only strips *one layer* off, so the caller will usually call itself recursively
--- Only applied to types of kind *, hence the newtype is always saturated
-splitRecNewType_maybe ty | Just ty' <- coreView ty = splitRecNewType_maybe ty'
-splitRecNewType_maybe (TyConApp tc tys)
-  | isClosedNewTyCon tc
-  = ASSERT( tys `lengthIs` tyConArity tc )     -- splitRecNewType_maybe only be applied 
-                                               --      to *types* (of kind *)
-    ASSERT( isRecursiveTyCon tc )              -- Guaranteed by coreView
-    case newTyConRhs tc of
-       (tvs, rep_ty) -> ASSERT( length tvs == length tys )
-                        Just (substTyWith tvs tys rep_ty)
-       
-splitRecNewType_maybe other = Nothing
-
-
-
-\end{code}
-
-
-%************************************************************************
-%*                                                                     *
 \subsection{Kinds and free variables}
 %*                                                                     *
 %************************************************************************
@@ -733,13 +713,17 @@ It doesn't change the uniques at all, just the print names.
 
 \begin{code}
 tidyTyVarBndr :: TidyEnv -> TyVar -> (TidyEnv, TyVar)
-tidyTyVarBndr (tidy_env, subst) tyvar
+tidyTyVarBndr env@(tidy_env, subst) tyvar
   = case tidyOccName tidy_env (getOccName name) of
-      (tidy', occ') ->         ((tidy', subst'), tyvar')
-                   where
-                       subst' = extendVarEnv subst tyvar tyvar'
-                       tyvar' = setTyVarName tyvar name'
-                       name'  = tidyNameOcc name occ'
+      (tidy', occ') -> ((tidy', subst'), tyvar'')
+       where
+         subst' = extendVarEnv subst tyvar tyvar''
+         tyvar' = setTyVarName tyvar name'
+         name'  = tidyNameOcc name occ'
+               -- Don't forget to tidy the kind for coercions!
+         tyvar'' | isCoVar tyvar = setTyVarKind tyvar' kind'
+                 | otherwise     = tyvar'
+         kind'  = tidyType env (tyVarKind tyvar)
   where
     name = tyVarName tyvar
 
@@ -1216,7 +1200,7 @@ zipTopTvSubst :: [TyVar] -> [Type] -> TvSubst
 zipTopTvSubst tyvars tys 
 #ifdef DEBUG
   | length tyvars /= length tys
-  = pprTrace "zipOpenTvSubst" (ppr tyvars $$ ppr tys) emptyTvSubst
+  = pprTrace "zipTopTvSubst" (ppr tyvars $$ ppr tys) emptyTvSubst
   | otherwise
 #endif
   = TvSubst emptyInScopeSet (zipTyEnv tyvars tys)