diff --git a/ghc/compiler/codeGen/CgCase.lhs b/ghc/compiler/codeGen/CgCase.lhs
index 0bc6508726c934bc5ac5853b559ac485bd0f8cdd..b9c314919492e076ea0a3f681d8fa48a5612ed89 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.40 2000/03/27 16:22:09 simonpj Exp $
+% $Id: CgCase.lhs,v 1.41 2000/04/13 20:41:30 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 d30731f77aa23a88ba5c6af3b422a110c0086fb9..9a9b931af37b25e0b166df836addf756b1ff0be4 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.33 2000/03/27 16:22:09 simonpj Exp $
+% $Id: CgExpr.lhs,v 1.34 2000/04/13 20:41:30 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 b1602d3c8c28af5eb54301cde042ae8b3009b09f..3dc98933d2ad52f390a75470457d5c3edf580942 100644
--- a/ghc/compiler/coreSyn/CoreLint.lhs
+++ b/ghc/compiler/coreSyn/CoreLint.lhs
@@ -39,6 +39,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 052a9a253f1c13d3f7d3aa3549f43877b09aa250..11ca5a093a9d71390a45f8c9afcaff1522eb3d34 100644
--- a/ghc/compiler/deSugar/DsCCall.lhs
+++ b/ghc/compiler/deSugar/DsCCall.lhs
@@ -31,6 +31,7 @@ import Type		( isUnLiftedType, splitAlgTyConApp_maybe, mkFunTys,
 			  isNewType, repType, isUnLiftedType, mkFunTy,
 			  Type
 			)
+import PprType		( {- instance Outputable Type -} )
 import TysPrim		( byteArrayPrimTy, realWorldStatePrimTy,
 			  byteArrayPrimTyCon, mutableByteArrayPrimTyCon, intPrimTy
 			)
diff --git a/ghc/compiler/deSugar/DsExpr.lhs b/ghc/compiler/deSugar/DsExpr.lhs
index 8ab7d4dde2048640b0c23567bd9d8559b05aad4c..e1023c2b63a40485fc7cc59e0b1fd8669a2ae459 100644
--- a/ghc/compiler/deSugar/DsExpr.lhs
+++ b/ghc/compiler/deSugar/DsExpr.lhs
@@ -18,6 +18,7 @@ import TcHsSyn		( TypecheckedHsExpr, TypecheckedHsBinds,
 			  TypecheckedStmt
 			)
 import CoreSyn
+import PprCore		( {- instance Outputable Expr -} )
 import CoreUtils	( exprType, mkIfThenElse, bindNonRec )
 
 import DsMonad
diff --git a/ghc/compiler/deSugar/DsForeign.lhs b/ghc/compiler/deSugar/DsForeign.lhs
index f946acbb50e06e67575115385d163e1823e920ba..b3ca8dbbaec668412bcbf715aadb731b7e9695d4 100644
--- a/ghc/compiler/deSugar/DsForeign.lhs
+++ b/ghc/compiler/deSugar/DsForeign.lhs
@@ -36,6 +36,7 @@ import Type		( unUsgTy,
 			  Type, mkFunTys, mkForAllTys, mkTyConApp,
 			  mkTyVarTy, mkFunTy, splitAppTy, applyTy, funResultTy
 			)
+import PprType		( {- instance Outputable Type -} )
 import PrimOp		( PrimOp(..), CCall(..), CCallTarget(..) )
 import Var		( TyVar )
 import TysPrim		( realWorldStatePrimTy, addrPrimTy )
diff --git a/ghc/compiler/hsSyn/HsCore.lhs b/ghc/compiler/hsSyn/HsCore.lhs
index 183702701580cde6e448a7db36479980cb675bad..d7f1317d1fc0ddec25b41d4c4dd32ead17022e5b 100644
--- a/ghc/compiler/hsSyn/HsCore.lhs
+++ b/ghc/compiler/hsSyn/HsCore.lhs
@@ -30,6 +30,7 @@ import Demand		( Demand )
 import Literal		( Literal )
 import PrimOp		( CCall, pprCCallOp )
 import Type		( Kind )
+import PprType		( {- instance Outputable Type -} )
 import CostCentre
 import SrcLoc		( SrcLoc )
 import Outputable
diff --git a/ghc/compiler/simplCore/SimplUtils.lhs b/ghc/compiler/simplCore/SimplUtils.lhs
index f84278ebd92792dde0cfa3389d591da25fdcb583..fd5f21e5cc50fbea0ec615e0478eadd25029d375 100644
--- a/ghc/compiler/simplCore/SimplUtils.lhs
+++ b/ghc/compiler/simplCore/SimplUtils.lhs
@@ -21,6 +21,7 @@ module SimplUtils (
 import BinderInfo
 import CmdLineOpts	( opt_SimplDoLambdaEtaExpansion, opt_SimplCaseMerge )
 import CoreSyn
+import PprCore		( {- instance Outputable Expr -} )
 import CoreUnfold	( isValueUnfolding )
 import CoreFVs		( exprFreeVars )
 import CoreUtils	( exprIsTrivial, cheapEqExpr, exprType, exprIsCheap, exprEtaExpandArity, bindNonRec )
@@ -36,6 +37,7 @@ import SimplMonad
 import Type		( Type, tyVarsOfType, tyVarsOfTypes, mkForAllTys, seqType, repType,
 			  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 3154df772966d8e4399bb3dada24ab42b5bb9eb0..24a8b619cc25b0b79475e2c8ddc785ffbe22997d 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/CoreToStg.lhs b/ghc/compiler/stgSyn/CoreToStg.lhs
index 481c6f50354b695edfa936e5a8c847e07b56cfdd..c62f6ef3a87ffc6004b0e032d76b9f85f770d829 100644
--- a/ghc/compiler/stgSyn/CoreToStg.lhs
+++ b/ghc/compiler/stgSyn/CoreToStg.lhs
@@ -17,6 +17,7 @@ module CoreToStg ( topCoreBindsToStg ) where
 import CoreSyn		-- input
 import StgSyn		-- output
 
+import PprCore		( {- instance Outputable Bind/Expr -} )
 import CoreUtils	( exprType )
 import SimplUtils	( findDefault )
 import CostCentre	( noCCS )
diff --git a/ghc/compiler/stgSyn/StgLint.lhs b/ghc/compiler/stgSyn/StgLint.lhs
index c0300a5cf73d30b386faf9362078b41ad58de867..67b4c135078d06e2994bac549d30692756e873d2 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 aacde304a87fc404c7a37908e5212a807fbf28c7..0b429a0aaedc0f7f72a44f69332509e071ecabe1 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/TcDeriv.lhs b/ghc/compiler/typecheck/TcDeriv.lhs
index 156a180ef6725327b980da87ddbcc1c1d3dc8d26..efa3e3de7b9efbd9d74c2a80976c6727eb0f66d3 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 1a7b6e93b70ed017adac11ab16ce1849c04587ae..77e9e42851002151cbd01ac19fac653f98390e06 100644
--- a/ghc/compiler/typecheck/TcForeign.lhs
+++ b/ghc/compiler/typecheck/TcForeign.lhs
@@ -45,7 +45,7 @@ import Type		( splitFunTys
 			, isForAllTy
 			, mkForAllTys
 			)
-
+import PprType		( {- instance Outputable Type -} )
 import TysWiredIn	( isFFIArgumentTy, isFFIResultTy, 
 			  isFFIExternalTy, isAddrTy
 			)
diff --git a/ghc/compiler/typecheck/TcMonad.lhs b/ghc/compiler/typecheck/TcMonad.lhs
index 1b442afdda6cd743f0029bfc88b260413e372d79..a4d8ef1a1db415a182adea60e295ea56fe0a1d48 100644
--- a/ghc/compiler/typecheck/TcMonad.lhs
+++ b/ghc/compiler/typecheck/TcMonad.lhs
@@ -49,6 +49,7 @@ import HsSyn		( HsLit )
 import RnHsSyn		( RenamedPat, RenamedArithSeqInfo, RenamedHsExpr )
 import Type		( Type, Kind, PredType, ThetaType, RhoType, TauType,
 			)
+import PprType		( {- instance Outputable Type -} )
 import ErrUtils		( addShortErrLocLine, addShortWarnLocLine, pprBagOfErrors, ErrMsg, Message, WarnMsg )
 import CmdLineOpts      ( opt_PprStyle_Debug )
 
diff --git a/ghc/compiler/typecheck/TcPat.lhs b/ghc/compiler/typecheck/TcPat.lhs
index 88914acc899a805b61bee8cacc3f959abe148e04..b036e39fbc6eca5210bde34c5d68b75d10a39278 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
diff --git a/ghc/compiler/usageSP/UsageSPInf.lhs b/ghc/compiler/usageSP/UsageSPInf.lhs
index 60faf602267e68a2df54abd15695d993f2eb98de..ee9be6ee0201dfc861a546119555a4e1c56b5a14 100644
--- a/ghc/compiler/usageSP/UsageSPInf.lhs
+++ b/ghc/compiler/usageSP/UsageSPInf.lhs
@@ -25,6 +25,7 @@ import Type             ( UsageAnn(..),
                           mkUsgTy, splitUsgTy, isUsgTy, isNotUsgTy, unUsgTy, tyUsg,
                           splitUsForAllTys, substUsTy,
                           mkFunTy, mkForAllTy )
+import PprType		( {- instance Outputable Type -} )
 import TyCon            ( tyConArgVrcs_maybe, isFunTyCon )
 import Literal          ( Literal(..), literalType )
 import Var              ( Var, UVar, varType, setVarType, mkUVar, modifyIdInfo )
diff --git a/ghc/compiler/usageSP/UsageSPLint.lhs b/ghc/compiler/usageSP/UsageSPLint.lhs
index 7d6f5e0000f22496168562c6c084a90b7762c6d8..1c97ffc02196d291884f283b60251dd10f63cd0f 100644
--- a/ghc/compiler/usageSP/UsageSPLint.lhs
+++ b/ghc/compiler/usageSP/UsageSPLint.lhs
@@ -21,6 +21,7 @@ import UsageSPUtils
 import CoreSyn
 import TypeRep          ( Type(..), TyNote(..) )  -- friend
 import Type             ( UsageAnn(..), isUsgTy, tyUsg )
+import PprType		( {- instance Outputable Type -} )
 import TyCon            ( isAlgTyCon, isPrimTyCon, isSynTyCon, isFunTyCon )
 import Var              ( Var, varType )
 import Id		( idLBVarInfo )
diff --git a/ghc/compiler/usageSP/UsageSPUtils.lhs b/ghc/compiler/usageSP/UsageSPUtils.lhs
index c45f83e3047f62e4d5e6bb8a5e8ebb6dedf19517..1628413e31c2e3f88cb5587710a5b0154d60161e 100644
--- a/ghc/compiler/usageSP/UsageSPUtils.lhs
+++ b/ghc/compiler/usageSP/UsageSPUtils.lhs
@@ -31,6 +31,7 @@ import Id               ( mayHaveNoBinding, isExportedId )
 import Name             ( isLocallyDefined )
 import TypeRep          ( Type(..), TyNote(..) )  -- friend
 import Type             ( UsageAnn(..), isUsgTy, splitFunTys )
+import PprType		( {- instance Outputable Type -} )
 import Subst		( substTy, mkTyVarSubst )
 import TyCon            ( isAlgTyCon, isPrimTyCon, isSynTyCon, isFunTyCon )
 import VarEnv