summaryrefslogtreecommitdiff
path: root/ghc
diff options
context:
space:
mode:
Diffstat (limited to 'ghc')
-rw-r--r--ghc/compiler/codeGen/CgCase.lhs3
-rw-r--r--ghc/compiler/codeGen/CgExpr.lhs3
-rw-r--r--ghc/compiler/coreSyn/CoreLint.lhs1
-rw-r--r--ghc/compiler/deSugar/DsCCall.lhs1
-rw-r--r--ghc/compiler/deSugar/DsExpr.lhs1
-rw-r--r--ghc/compiler/deSugar/DsForeign.lhs1
-rw-r--r--ghc/compiler/simplCore/SimplUtils.lhs1
-rw-r--r--ghc/compiler/specialise/Specialise.lhs1
-rw-r--r--ghc/compiler/stgSyn/StgLint.lhs1
-rw-r--r--ghc/compiler/stgSyn/StgSyn.lhs1
-rw-r--r--ghc/compiler/typecheck/TcBinds.lhs1
-rw-r--r--ghc/compiler/typecheck/TcClassDcl.lhs1
-rw-r--r--ghc/compiler/typecheck/TcDeriv.lhs1
-rw-r--r--ghc/compiler/typecheck/TcForeign.lhs1
-rw-r--r--ghc/compiler/typecheck/TcPat.lhs1
15 files changed, 17 insertions, 2 deletions
diff --git a/ghc/compiler/codeGen/CgCase.lhs b/ghc/compiler/codeGen/CgCase.lhs
index 9ede65019e..8bf74fa31a 100644
--- a/ghc/compiler/codeGen/CgCase.lhs
+++ b/ghc/compiler/codeGen/CgCase.lhs
@@ -1,7 +1,7 @@
%
% (c) The GRASP/AQUA Project, Glasgow University, 1992-1998
%
-% $Id: CgCase.lhs,v 1.38 2000/03/23 17:45:19 simonpj Exp $
+% $Id: CgCase.lhs,v 1.39 2000/03/25 12:38:40 panne Exp $
%
%********************************************************
%* *
@@ -62,6 +62,7 @@ import TyCon ( TyCon, isEnumerationTyCon, isUnboxedTupleTyCon,
tyConDataCons, tyConFamilySize )
import Type ( Type, typePrimRep, splitAlgTyConApp,
splitTyConApp_maybe, repType )
+import PprType ( {- instance Outputable Type -} )
import Unique ( Unique, Uniquable(..), mkPseudoUnique1 )
import Maybes ( maybeToBool )
import Util
diff --git a/ghc/compiler/codeGen/CgExpr.lhs b/ghc/compiler/codeGen/CgExpr.lhs
index 78e8a300d4..9c8dfd3a34 100644
--- a/ghc/compiler/codeGen/CgExpr.lhs
+++ b/ghc/compiler/codeGen/CgExpr.lhs
@@ -1,7 +1,7 @@
%
% (c) The GRASP/AQUA Project, Glasgow University, 1992-1998
%
-% $Id: CgExpr.lhs,v 1.31 2000/03/23 17:45:19 simonpj Exp $
+% $Id: CgExpr.lhs,v 1.32 2000/03/25 12:38:40 panne Exp $
%
%********************************************************
%* *
@@ -48,6 +48,7 @@ import PrimRep ( getPrimRepSize, PrimRep(..), isFollowableRep )
import TyCon ( maybeTyConSingleCon,
isUnboxedTupleTyCon, isEnumerationTyCon )
import Type ( Type, typePrimRep, splitTyConApp_maybe, repType )
+import PprType ( {- instance Outputable Type -} )
import Maybes ( assocMaybe, maybeToBool )
import Unique ( mkBuiltinUnique )
import BasicTypes ( TopLevelFlag(..), RecFlag(..) )
diff --git a/ghc/compiler/coreSyn/CoreLint.lhs b/ghc/compiler/coreSyn/CoreLint.lhs
index 7881f4a6ac..c1e66acb52 100644
--- a/ghc/compiler/coreSyn/CoreLint.lhs
+++ b/ghc/compiler/coreSyn/CoreLint.lhs
@@ -40,6 +40,7 @@ import Type ( Type, Kind, tyVarsOfType,
isUnboxedTupleType,
hasMoreBoxityInfo
)
+import PprType ( {- instance Outputable Type -} )
import TyCon ( TyCon, isPrimTyCon, tyConDataCons )
import BasicTypes ( RecFlag(..), isNonRec )
import Outputable
diff --git a/ghc/compiler/deSugar/DsCCall.lhs b/ghc/compiler/deSugar/DsCCall.lhs
index 35722fae20..7752c427f0 100644
--- a/ghc/compiler/deSugar/DsCCall.lhs
+++ b/ghc/compiler/deSugar/DsCCall.lhs
@@ -33,6 +33,7 @@ import CallConv
import Type ( isUnLiftedType, splitAlgTyConApp_maybe, mkFunTys,
splitTyConApp_maybe, tyVarsOfType, mkForAllTys, Type
)
+import PprType ( {- instance Outputable Type -} )
import TysPrim ( byteArrayPrimTy, realWorldStatePrimTy,
byteArrayPrimTyCon, mutableByteArrayPrimTyCon )
import TysWiredIn ( unitDataConId, stringTy,
diff --git a/ghc/compiler/deSugar/DsExpr.lhs b/ghc/compiler/deSugar/DsExpr.lhs
index 70e548940c..a4c50c0d4b 100644
--- a/ghc/compiler/deSugar/DsExpr.lhs
+++ b/ghc/compiler/deSugar/DsExpr.lhs
@@ -43,6 +43,7 @@ import Type ( splitFunTys, mkTyConApp,
isNotUsgTy, unUsgTy,
splitAppTy, isUnLiftedType, Type
)
+import PprType ( {- instance Outputable Type -} )
import TysWiredIn ( tupleCon, unboxedTupleCon,
listTyCon, mkListTy,
charDataCon, charTy, stringTy,
diff --git a/ghc/compiler/deSugar/DsForeign.lhs b/ghc/compiler/deSugar/DsForeign.lhs
index 2766fa9b68..f15666016c 100644
--- a/ghc/compiler/deSugar/DsForeign.lhs
+++ b/ghc/compiler/deSugar/DsForeign.lhs
@@ -36,6 +36,7 @@ import Type ( splitAlgTyConApp_maybe, unUsgTy,
Type, mkFunTys, mkForAllTys, mkTyConApp,
mkTyVarTy, mkFunTy, splitAppTy
)
+import PprType ( {- instance Outputable Type -} )
import PrimOp ( PrimOp(..), CCall(..), CCallTarget(..) )
import Var ( TyVar )
import TysPrim ( realWorldStatePrimTy, addrPrimTy )
diff --git a/ghc/compiler/simplCore/SimplUtils.lhs b/ghc/compiler/simplCore/SimplUtils.lhs
index 3fee8361ac..4f8e25c800 100644
--- a/ghc/compiler/simplCore/SimplUtils.lhs
+++ b/ghc/compiler/simplCore/SimplUtils.lhs
@@ -36,6 +36,7 @@ import SimplMonad
import Type ( Type, tyVarsOfType, tyVarsOfTypes, mkForAllTys, seqType,
splitTyConApp_maybe, splitAlgTyConApp_maybe, mkTyVarTys, applyTys, splitFunTys, mkFunTys
)
+import PprType ( {- instance Outputable Type -} )
import DataCon ( dataConRepArity )
import TysPrim ( statePrimTyCon )
import Var ( setVarUnique )
diff --git a/ghc/compiler/specialise/Specialise.lhs b/ghc/compiler/specialise/Specialise.lhs
index 3154df7729..81799e520b 100644
--- a/ghc/compiler/specialise/Specialise.lhs
+++ b/ghc/compiler/specialise/Specialise.lhs
@@ -21,6 +21,7 @@ import Type ( Type, mkTyVarTy, splitSigmaTy, splitFunTysN,
tyVarsOfType, tyVarsOfTypes, tyVarsOfTheta, applyTys,
mkForAllTys, boxedTypeKind
)
+import PprType ( {- instance Outputable Type -} )
import Subst ( Subst, mkSubst, substTy, emptySubst, substBndrs, extendSubstList,
substId, substAndCloneId, substAndCloneIds, lookupIdSubst
)
diff --git a/ghc/compiler/stgSyn/StgLint.lhs b/ghc/compiler/stgSyn/StgLint.lhs
index c0300a5cf7..c7c126d13e 100644
--- a/ghc/compiler/stgSyn/StgLint.lhs
+++ b/ghc/compiler/stgSyn/StgLint.lhs
@@ -22,6 +22,7 @@ import ErrUtils ( ErrMsg, Message, addErrLocHdrLine, pprBagOfErrors, dontAddErr
import Type ( mkFunTys, splitFunTys, splitAlgTyConApp_maybe,
isUnLiftedType, isTyVarTy, splitForAllTys, Type
)
+import PprType ( {- instance Outputable Type -} )
import TyCon ( TyCon, isDataTyCon )
import Util ( zipEqual )
import Outputable
diff --git a/ghc/compiler/stgSyn/StgSyn.lhs b/ghc/compiler/stgSyn/StgSyn.lhs
index 759c174f09..429d24f3f6 100644
--- a/ghc/compiler/stgSyn/StgSyn.lhs
+++ b/ghc/compiler/stgSyn/StgSyn.lhs
@@ -53,6 +53,7 @@ import PrimOp ( PrimOp )
import PrimRep ( PrimRep(..) )
import Outputable
import Type ( Type )
+import PprType ( {- instance Outputable Type -} )
import UniqSet ( isEmptyUniqSet, uniqSetToList, UniqSet )
\end{code}
diff --git a/ghc/compiler/typecheck/TcBinds.lhs b/ghc/compiler/typecheck/TcBinds.lhs
index b52ef1ff22..69bde889a9 100644
--- a/ghc/compiler/typecheck/TcBinds.lhs
+++ b/ghc/compiler/typecheck/TcBinds.lhs
@@ -54,6 +54,7 @@ import Type ( mkTyVarTy, tyVarsOfTypes, mkTyConApp,
mkPredTy, splitRhoTy, mkForAllTy, isUnLiftedType,
isUnboxedType, unboxedTypeKind, boxedTypeKind
)
+import PprType ( {- instance Outputable Type -} )
import FunDeps ( tyVarFunDep, oclose )
import Var ( TyVar, tyVarKind )
import VarSet
diff --git a/ghc/compiler/typecheck/TcClassDcl.lhs b/ghc/compiler/typecheck/TcClassDcl.lhs
index 3c39da119d..be025215c9 100644
--- a/ghc/compiler/typecheck/TcClassDcl.lhs
+++ b/ghc/compiler/typecheck/TcClassDcl.lhs
@@ -57,6 +57,7 @@ import Type ( Type, ThetaType, ClassContext,
mkSigmaTy, mkForAllTys, mkClassPred, classesOfPreds,
boxedTypeKind, mkArrowKind
)
+import PprType ( {- instance Outputable Type -} )
import Var ( tyVarKind, TyVar )
import VarSet ( mkVarSet )
import TyCon ( mkAlgTyCon )
diff --git a/ghc/compiler/typecheck/TcDeriv.lhs b/ghc/compiler/typecheck/TcDeriv.lhs
index 156a180ef6..c929ed1412 100644
--- a/ghc/compiler/typecheck/TcDeriv.lhs
+++ b/ghc/compiler/typecheck/TcDeriv.lhs
@@ -51,6 +51,7 @@ import Type ( TauType, mkTyVarTys, mkTyConApp,
mkSigmaTy, mkDictTy, isUnboxedType,
splitAlgTyConApp, classesToPreds
)
+import PprType ( {- instance Outputable Type -} )
import TysWiredIn ( voidTy )
import Var ( TyVar )
import Unique -- Keys stuff
diff --git a/ghc/compiler/typecheck/TcForeign.lhs b/ghc/compiler/typecheck/TcForeign.lhs
index 58c73ab36f..27c6c1497d 100644
--- a/ghc/compiler/typecheck/TcForeign.lhs
+++ b/ghc/compiler/typecheck/TcForeign.lhs
@@ -45,6 +45,7 @@ import Type ( splitFunTys
, isForAllTy
, mkForAllTys
)
+import PprType ( {- instance Outputable Type -} )
import TysWiredIn ( isFFIArgumentTy, isFFIResultTy,
isFFIExternalTy, isAddrTy
diff --git a/ghc/compiler/typecheck/TcPat.lhs b/ghc/compiler/typecheck/TcPat.lhs
index 88914acc89..5cd7e0559f 100644
--- a/ghc/compiler/typecheck/TcPat.lhs
+++ b/ghc/compiler/typecheck/TcPat.lhs
@@ -37,6 +37,7 @@ import DataCon ( DataCon, dataConSig, dataConFieldLabels,
)
import Id ( Id, idType, isDataConWrapId_maybe )
import Type ( Type, isTauTy, mkTyConApp, mkClassPred, boxedTypeKind )
+import PprType ( {- instance Outputable Type -} )
import Subst ( substTy, substClasses )
import TysPrim ( charPrimTy, intPrimTy, floatPrimTy,
doublePrimTy, addrPrimTy