Module header tidyup, phase 1
[ghc-hetmet.git] / compiler / typecheck / TcType.lhs
index f266f4b..cb1c68b 100644 (file)
@@ -1,4 +1,4 @@
-
+%
 % (c) The GRASP/AQUA Project, Glasgow University, 1992-1998
 %
 \section[TcType]{Types used in the typechecker}
@@ -10,7 +10,7 @@ compiler.  These parts
                newtypes, and predicates are meaningful. 
        * look through usage types
 
-The "tc" prefix is for "typechechecker", because the type checker
+The "tc" prefix is for "TypeChecker", because the type checker
 is the principal client.
 
 \begin{code}
@@ -68,7 +68,7 @@ module TcType (
   isClassPred, isTyVarClassPred, isEqPred, 
   mkDictTy, tcSplitPredTy_maybe, 
   isPredTy, isDictTy, tcSplitDFunTy, tcSplitDFunHead, predTyUnique, 
-  mkClassPred, isInheritablePred, isLinearPred, isIPPred, mkPredName, 
+  mkClassPred, isInheritablePred, isIPPred, mkPredName, 
   dataConsStupidTheta, isRefineableTy,
 
   ---------------------------------
@@ -131,44 +131,7 @@ module TcType (
 -- friends:
 import TypeRep         ( Type(..), funTyCon, Kind )  -- friend
 
-import Type            (       -- Re-exports
-                         tyVarsOfType, tyVarsOfTypes, tyVarsOfPred,
-                         tyVarsOfTheta, Kind, PredType(..), KindVar,
-                         ThetaType, isUnliftedTypeKind, unliftedTypeKind, 
-                         argTypeKind,
-                         liftedTypeKind, openTypeKind, mkArrowKind,
-                         tySuperKind, isLiftedTypeKind,
-                         mkArrowKinds, mkForAllTy, mkForAllTys,
-                         defaultKind, isSubArgTypeKind, isSubOpenTypeKind,
-                         mkFunTy, mkFunTys, zipFunTys, 
-                         mkTyConApp, mkAppTy,
-                         mkAppTys, applyTy, applyTys,
-                         mkTyVarTy, mkTyVarTys, mkTyConTy, mkPredTy,
-                         mkPredTys, isUnLiftedType, 
-                         isUnboxedTupleType, isPrimitiveType,
-                         splitTyConApp_maybe,
-                         tidyTopType, tidyType, tidyPred, tidyTypes,
-                         tidyFreeTyVars, tidyOpenType, tidyOpenTypes,
-                         tidyTyVarBndr, tidyOpenTyVar,
-                         tidyOpenTyVars, tidyKind,
-                         isSubKind, tcView,
-
-                         tcEqType, tcEqTypes, tcCmpType, tcCmpTypes, 
-                         tcEqPred, tcCmpPred, tcEqTypeX, eqKind,
-
-                         TvSubst(..),
-                         TvSubstEnv, emptyTvSubst, mkTvSubst, zipTyEnv,
-                         mkOpenTvSubst, zipOpenTvSubst, zipTopTvSubst, mkTopTvSubst,
-                         getTvSubstEnv, setTvSubstEnv, getTvInScope, extendTvInScope,
-                         extendTvSubst, extendTvSubstList, isInScope, notElemTvSubst,
-                         substTy, substTys, substTyWith, substTheta, 
-                         substTyVar, substTyVarBndr, substPred, lookupTyVar,
-
-                         typeKind, repType, coreView, repSplitAppTy_maybe,
-                         pprKind, pprParendKind,
-                         pprType, pprParendType, pprTyThingCategory,
-                         pprPred, pprTheta, pprThetaArrow, pprClassPred
-                       )
+import Type
 import TyCon           ( TyCon, isUnLiftedTyCon, isSynTyCon, isOpenTyCon,
                          synTyConDefn, tyConUnique )    
 import DataCon         ( DataCon, dataConStupidTheta, dataConResTys )
@@ -186,14 +149,15 @@ import VarEnv             ( TidyEnv )
 import OccName         ( OccName, mkDictOcc, mkOccName, tvName )
 import PrelNames       -- Lots (e.g. in isFFIArgumentTy)
 import TysWiredIn      ( unitTyCon, charTyCon, listTyCon )
-import BasicTypes      ( IPName(..), Arity, ipNameName )
+import BasicTypes      ( Arity, ipNameName )
 import SrcLoc          ( SrcLoc, SrcSpan )
 import Util            ( equalLength )
 import Maybes          ( maybeToBool, expectJust, mapCatMaybes )
 import ListSetOps      ( hasNoDups )
 import List            ( nubBy )
 import Outputable
-import DATA_IOREF
+
+import Data.IORef
 \end{code}
 
 
@@ -698,10 +662,14 @@ tcMultiSplitSigmaTy sigma
 
 -----------------------
 tcTyConAppTyCon :: Type -> TyCon
-tcTyConAppTyCon ty = fst (tcSplitTyConApp ty)
+tcTyConAppTyCon ty = case tcSplitTyConApp_maybe ty of
+                       Just (tc, _) -> tc
+                       Nothing      -> pprPanic "tcTyConAppTyCon" (pprType ty)
 
 tcTyConAppArgs :: Type -> [Type]
-tcTyConAppArgs ty = snd (tcSplitTyConApp ty)
+tcTyConAppArgs ty = case tcSplitTyConApp_maybe ty of
+                       Just (_, args) -> args
+                       Nothing        -> pprPanic "tcTyConAppArgs" (pprType ty)
 
 tcSplitTyConApp :: Type -> (TyCon, [Type])
 tcSplitTyConApp ty = case tcSplitTyConApp_maybe ty of
@@ -860,10 +828,6 @@ getClassPredTys :: PredType -> (Class, [Type])
 getClassPredTys (ClassP clas tys) = (clas, tys)
 getClassPredTys other = panic "getClassPredTys"
 
-isEqPred :: PredType -> Bool
-isEqPred (EqPred {}) = True
-isEqPred _          = False
-
 mkDictTy :: Class -> [Type] -> Type
 mkDictTy clas tys = mkPredTy (ClassP clas tys)
 
@@ -891,10 +855,6 @@ isInheritablePred :: PredType -> Bool
 -- which can be free in g's rhs, and shared by both calls to g
 isInheritablePred (ClassP _ _) = True
 isInheritablePred other             = False
-
-isLinearPred :: TcPredType -> Bool
-isLinearPred (IParam (Linear n) _) = True
-isLinearPred other                = False
 \end{code}
 
 --------------------- Equality predicates ---------------------------------