diff options
| author | simonmar <unknown> | 2000-07-11 16:38:50 +0000 | 
|---|---|---|
| committer | simonmar <unknown> | 2000-07-11 16:38:50 +0000 | 
| commit | ff755dd9a0a0ad2f106c323852553ea247f16141 (patch) | |
| tree | 1b09588b8c5c4f095905c273509c1b0421f0cd81 /ghc/compiler | |
| parent | 1b7a99e3e7f64c6f402e8aece32ba0b9a3703bfa (diff) | |
| download | haskell-ff755dd9a0a0ad2f106c323852553ea247f16141.tar.gz | |
[project @ 2000-07-11 16:24:57 by simonmar]
remove unused imports
Diffstat (limited to 'ghc/compiler')
69 files changed, 78 insertions, 308 deletions
| diff --git a/ghc/compiler/main/CodeOutput.lhs b/ghc/compiler/main/CodeOutput.lhs index 20fe63c6d2..cc66632e98 100644 --- a/ghc/compiler/main/CodeOutput.lhs +++ b/ghc/compiler/main/CodeOutput.lhs @@ -24,13 +24,12 @@ import Id		( Id )  import Class		( Class )  import CoreSyn		( CoreBind )  import StgSyn		( StgBinding ) -import AbsCSyn		( AbstractC, absCNop ) +import AbsCSyn		( AbstractC )  import PprAbsC		( dumpRealC, writeRealC )  import UniqSupply	( UniqSupply ) -import Module		( Module, moduleString ) +import Module		( Module )  import CmdLineOpts -import Maybes		( maybeToBool ) -import ErrUtils		( doIfSet, dumpIfSet ) +import ErrUtils		( dumpIfSet )  import Outputable  import IO		( IOMode(..), hClose, openFile, Handle )  \end{code} diff --git a/ghc/compiler/main/Main.lhs b/ghc/compiler/main/Main.lhs index e9827b4b50..ab318408b7 100644 --- a/ghc/compiler/main/Main.lhs +++ b/ghc/compiler/main/Main.lhs @@ -10,13 +10,12 @@ module Main ( main ) where  import IO		( hPutStr, stderr )  import HsSyn -import BasicTypes	( NewOrData(..) )  import RdrHsSyn		( RdrNameHsModule ) -import FastString	( mkFastCharString, unpackFS ) +import FastString	( unpackFS )  import StringBuffer	( hGetStringBuffer )  import Parser		( parse ) -import Lex		( PState(..), P, ParseResult(..) ) +import Lex		( PState(..), ParseResult(..) )  import SrcLoc		( mkSrcLoc )  import Rename		( renameModule ) @@ -26,25 +25,19 @@ import TcModule		( TcResults(..), typecheckModule )  import Desugar		( deSugar )  import SimplCore	( core2core )  import OccurAnal	( occurAnalyseBinds ) -import CoreLint		( endPass )  import CoreUtils	( coreBindsSize )  import CoreTidy		( tidyCorePgm )  import CoreToStg	( topCoreBindsToStg ) -import StgSyn		( collectFinalStgBinders, pprStgBindings ) +import StgSyn		( collectFinalStgBinders )  import SimplStg		( stg2stg )  import CodeGen		( codeGen )  import CodeOutput	( codeOutput )  import Module		( ModuleName, moduleNameUserString ) -import AbsCSyn		( absCNop )  import CmdLineOpts  import ErrUtils		( ghcExit, doIfSet, dumpIfSet ) -import Maybes		( maybeToBool, MaybeErr(..) ) -import TyCon		( isDataTyCon ) -import Class		( classTyCon )  import UniqSupply	( mkSplitUniqSupply ) -import FiniteMap	( emptyFM )  import Outputable  import Char		( isSpace )  #if REPORT_TO_MOTHERLODE && __GLASGOW_HASKELL__ >= 303 diff --git a/ghc/compiler/nativeGen/AsmRegAlloc.lhs b/ghc/compiler/nativeGen/AsmRegAlloc.lhs index 92f395a3a0..790a955d93 100644 --- a/ghc/compiler/nativeGen/AsmRegAlloc.lhs +++ b/ghc/compiler/nativeGen/AsmRegAlloc.lhs @@ -10,16 +10,13 @@ module AsmRegAlloc ( runRegAllocate ) where  import MachCode		( InstrBlock )  import MachMisc		( Instr(..) ) -import PprMach		( pprUserReg, pprInstr ) -- debugging  import MachRegs  import RegAllocInfo  import FiniteMap	( FiniteMap, emptyFM, addListToFM, delListFromFM,   			  lookupFM, keysFM, eltsFM, mapFM, addToFM_C, addToFM,  			  listToFM, fmToList, lookupWithDefaultFM ) -import Maybes		( maybeToBool )  import Unique		( mkBuiltinUnique ) -import Util		( mapAccumB )  import OrdList		( unitOL, appOL, fromOL, concatOL )  import Outputable  import Unique		( Unique, Uniquable(..), mkPseudoUnique3 ) diff --git a/ghc/compiler/nativeGen/MachCode.lhs b/ghc/compiler/nativeGen/MachCode.lhs index 3fd6dd9dd6..41bec6771d 100644 --- a/ghc/compiler/nativeGen/MachCode.lhs +++ b/ghc/compiler/nativeGen/MachCode.lhs @@ -18,7 +18,6 @@ import MachMisc		-- may differ per-platform  import MachRegs  import OrdList		( OrdList, nilOL, isNilOL, unitOL, appOL, toOL,  			  snocOL, consOL, concatOL ) -import AbsCSyn		( MagicId )  import AbsCUtils	( magicIdPrimRep )  import CallConv		( CallConv )  import CLabel		( isAsmTemp, CLabel, pprCLabel_asm, labelDynamic ) diff --git a/ghc/compiler/nativeGen/MachMisc.lhs b/ghc/compiler/nativeGen/MachMisc.lhs index 0d39e9cd21..b06cac3504 100644 --- a/ghc/compiler/nativeGen/MachMisc.lhs +++ b/ghc/compiler/nativeGen/MachMisc.lhs @@ -50,12 +50,10 @@ import MachRegs		( stgReg, callerSaves, RegLoc(..),  #                         endif  			)  import PrimRep		( PrimRep(..) ) -import SMRep		( SMRep(..) )  import Stix		( StixTree(..), StixReg(..), CodeSegment )  import Panic		( panic ) -import Char		( isDigit )  import GlaExts		( word2Int#, int2Word#, shiftRL#, and#, (/=#) ) -import Outputable	( text, pprPanic, ppr ) +import Outputable	( pprPanic, ppr )  import IOExts		( trace )  \end{code} diff --git a/ghc/compiler/nativeGen/PprMach.lhs b/ghc/compiler/nativeGen/PprMach.lhs index 820a6390b5..dd15c6e555 100644 --- a/ghc/compiler/nativeGen/PprMach.lhs +++ b/ghc/compiler/nativeGen/PprMach.lhs @@ -18,8 +18,6 @@ import MachRegs		-- may differ per-platform  import MachMisc  import CLabel		( pprCLabel_asm, externallyVisibleCLabel, labelDynamic ) -import CStrings		( charToC ) -import Maybes		( maybeToBool )  import Stix		( CodeSegment(..), StixTree(..) )  import Char		( isPrint, isDigit )  import Outputable diff --git a/ghc/compiler/nativeGen/RegAllocInfo.lhs b/ghc/compiler/nativeGen/RegAllocInfo.lhs index a401f852fe..f55e498121 100644 --- a/ghc/compiler/nativeGen/RegAllocInfo.lhs +++ b/ghc/compiler/nativeGen/RegAllocInfo.lhs @@ -37,16 +37,11 @@ module RegAllocInfo (  #include "HsVersions.h"  import List		( partition, sort ) -import OrdList		( unitOL )  import MachMisc  import MachRegs -import MachCode		( InstrBlock ) -import BitSet		( unitBS, mkBS, minusBS, unionBS, listBS, BitSet )  import CLabel		( pprCLabel_asm, isAsmTemp, CLabel{-instance Ord-} )  import FiniteMap	( addToFM, lookupFM, FiniteMap ) -import PrimRep		( PrimRep(..) ) -import UniqSet		-- quite a bit of it  import Outputable  import Constants	( rESERVED_C_STACK_BYTES )  import Unique		( Unique, Uniquable(..) ) diff --git a/ghc/compiler/nativeGen/Stix.lhs b/ghc/compiler/nativeGen/Stix.lhs index e90a6d6add..e222cdc6d5 100644 --- a/ghc/compiler/nativeGen/Stix.lhs +++ b/ghc/compiler/nativeGen/Stix.lhs @@ -28,7 +28,6 @@ module Stix (  import Ratio		( Rational )  import AbsCSyn		( node, tagreg, MagicId(..) ) -import AbsCUtils	( magicIdPrimRep )  import CallConv		( CallConv, pprCallConv )  import CLabel		( mkAsmTempLabel, CLabel, pprCLabel, pprCLabel_asm )  import PrimRep          ( PrimRep(..), showPrimRep ) @@ -37,7 +36,6 @@ import Unique           ( Unique )  import SMRep		( fixedHdrSize, arrWordsHdrSize, arrPtrsHdrSize )  import UniqSupply	( UniqSupply, splitUniqSupply, uniqFromSupply,                            UniqSM, thenUs, returnUs, getUniqueUs ) -import CmdLineOpts	( opt_Static )  import Outputable  \end{code} diff --git a/ghc/compiler/nativeGen/StixInfo.lhs b/ghc/compiler/nativeGen/StixInfo.lhs index 1bfefc32d6..16feabc46e 100644 --- a/ghc/compiler/nativeGen/StixInfo.lhs +++ b/ghc/compiler/nativeGen/StixInfo.lhs @@ -20,7 +20,6 @@ import PrimRep		( PrimRep(..) )  import SMRep		( SMRep(..), getSMRepClosureTypeInt )  import Stix		-- all of it  import UniqSupply	( returnUs, UniqSM ) -import Outputable	( int )  import BitSet		( intBS )  import Maybes		( maybeToBool ) diff --git a/ghc/compiler/nativeGen/StixMacro.lhs b/ghc/compiler/nativeGen/StixMacro.lhs index eb49df231c..19c02d2e52 100644 --- a/ghc/compiler/nativeGen/StixMacro.lhs +++ b/ghc/compiler/nativeGen/StixMacro.lhs @@ -10,7 +10,6 @@ module StixMacro ( macroCode, checkCode ) where  import {-# SOURCE #-} StixPrim ( amodeToStix ) -import MachMisc  import MachRegs  import AbsCSyn		( CStmtMacro(..), MagicId(..), CAddrMode, tagreg,  			  CCheckMacro(..) ) @@ -20,7 +19,6 @@ import PrimOp		( PrimOp(..) )  import PrimRep		( PrimRep(..) )  import Stix  import UniqSupply	( returnUs, thenUs, UniqSM ) -import Outputable  import CLabel		( mkBlackHoleInfoTableLabel, mkIndStaticInfoLabel,  			  mkIndInfoLabel, mkUpdInfoLabel, mkSeqInfoLabel,  			  mkRtsGCEntryLabel, mkStgUpdatePAPLabel ) diff --git a/ghc/compiler/parser/ParseUtil.lhs b/ghc/compiler/parser/ParseUtil.lhs index 430460aa24..c491803e93 100644 --- a/ghc/compiler/parser/ParseUtil.lhs +++ b/ghc/compiler/parser/ParseUtil.lhs @@ -59,7 +59,6 @@ import CmdLineOpts 	( opt_NoImplicitPrelude )  import StringBuffer 	( lexemeToString )  import FastString	( unpackFS )  import BasicTypes	( Boxity(..) ) -import ErrUtils  import UniqFM		( UniqFM, listToUFM, lookupUFM )  import Outputable diff --git a/ghc/compiler/prelude/PrelInfo.lhs b/ghc/compiler/prelude/PrelInfo.lhs index 12acaa9215..94666c7101 100644 --- a/ghc/compiler/prelude/PrelInfo.lhs +++ b/ghc/compiler/prelude/PrelInfo.lhs @@ -41,13 +41,11 @@ import PrelNames	-- Prelude module names  import PrimOp		( PrimOp(..), allThePrimOps, primOpRdrName )  import DataCon		( DataCon, dataConId, dataConWrapId ) -import PrimRep		( PrimRep(..) )  import TysPrim		-- TYPES  import TysWiredIn  -- others:  import RdrName		( RdrName ) -import Var		( varUnique, Id )  import Name		( Name, OccName, Provenance(..),   			  NameSpace, tcName, clsName, varName, dataName,  			  mkKnownKeyGlobal, @@ -61,7 +59,6 @@ import BasicTypes	( Boxity(..) )  import Unique		-- *Key stuff  import UniqFM		( UniqFM, listToUFM )  import Util		( isIn ) -import Panic		( panic )  \end{code}  %************************************************************************ diff --git a/ghc/compiler/prelude/PrelRules.lhs b/ghc/compiler/prelude/PrelRules.lhs index 4e502568d1..801095e7d9 100644 --- a/ghc/compiler/prelude/PrelRules.lhs +++ b/ghc/compiler/prelude/PrelRules.lhs @@ -13,9 +13,9 @@ module PrelRules ( primOpRule, builtinRules ) where  #include "HsVersions.h"  import CoreSyn -import Rules		( ProtoCoreRule(..) ) -import Id		( idUnfolding, mkWildId, isDataConId_maybe ) -import Literal		( Literal(..), isLitLitLit, mkMachInt, mkMachWord, literalType +import Id		( mkWildId ) +import Literal		( Literal(..), isLitLitLit, mkMachInt, mkMachWord +			, inIntRange, inWordRange, literalType  			, word2IntLit, int2WordLit, char2IntLit, int2CharLit  			, float2IntLit, int2FloatLit, double2IntLit, int2DoubleLit  			, addr2IntLit, int2AddrLit, float2DoubleLit, double2FloatLit @@ -24,32 +24,18 @@ import RdrName		( RdrName )  import PrimOp		( PrimOp(..), primOpOcc )  import TysWiredIn	( trueDataConId, falseDataConId )  import TyCon		( tyConDataConsIfAvailable, isEnumerationTyCon, isNewTyCon ) -import DataCon		( DataCon, dataConTag, dataConRepArity, dataConTyCon, dataConId, fIRST_TAG ) -import CoreUnfold	( maybeUnfoldingTemplate ) +import DataCon		( dataConTag, dataConTyCon, dataConId, fIRST_TAG )  import CoreUtils	( exprIsValue, cheapEqExpr, exprIsConApp_maybe )  import Type		( splitTyConApp_maybe )  import OccName		( occNameUserString)  import PrelNames	( unpackCStringFoldr_RDR )  import Unique		( unpackCStringFoldrIdKey, hasKey ) -import Maybes		( maybeToBool ) -import Char		( ord, chr )  import Bits		( Bits(..) ) -import PrelAddr		( wordToInt )  import Word		( Word64 )  import Outputable - -#if __GLASGOW_HASKELL__ > 405 -import PrelAddr ( intToWord ) -#else -import PrelAddr ( Word(..) ) -import PrelGHC  ( int2Word# ) -intToWord :: Int -> Word -intToWord (I# i#) = W# (int2Word# i#) -#endif  \end{code} -  \begin{code}  primOpRule :: PrimOp -> CoreRule  primOpRule op  diff --git a/ghc/compiler/prelude/TysWiredIn.lhs b/ghc/compiler/prelude/TysWiredIn.lhs index 7a809e3eb1..55bb4453c3 100644 --- a/ghc/compiler/prelude/TysWiredIn.lhs +++ b/ghc/compiler/prelude/TysWiredIn.lhs @@ -87,17 +87,14 @@ import Var		( TyVar, tyVarKind )  import TyCon		( TyCon, AlgTyConFlavour(..), ArgVrcs, tyConDataCons,  			  mkAlgTyCon, mkSynTyCon, mkTupleTyCon, isUnLiftedTyCon  			) -import BasicTypes	( Arity, NewOrData(..), RecFlag(..), Boxity(..), isBoxed ) +import BasicTypes	( Arity, RecFlag(..), Boxity(..), isBoxed )  import Type		( Type, mkTyConTy, mkTyConApp, mkSigmaTy, mkTyVarTys,   			  mkArrowKinds, boxedTypeKind, unboxedTypeKind,  			  mkFunTy, mkFunTys,  			  splitTyConApp_maybe, repType,  			  TauType, ClassContext ) -import PrimRep		( PrimRep(..) )  import Unique  import CmdLineOpts      ( opt_GlasgowExts ) -import Util		( assoc ) -import Panic		( panic )  import Array  alpha_tyvar	  = [alphaTyVar] diff --git a/ghc/compiler/profiling/SCCfinal.lhs b/ghc/compiler/profiling/SCCfinal.lhs index 5fc41a1fef..1c22d06e2b 100644 --- a/ghc/compiler/profiling/SCCfinal.lhs +++ b/ghc/compiler/profiling/SCCfinal.lhs @@ -31,15 +31,11 @@ import StgSyn  import CmdLineOpts	( opt_AutoSccsOnIndividualCafs )  import CostCentre	-- lots of things -import Id		( Id, mkSysLocal, idType, idName ) +import Id		( Id )  import Module		( Module )  import UniqSupply	( uniqFromSupply, splitUniqSupply, UniqSupply )  import Unique           ( Unique ) -import Type		( splitForAllTys, splitTyConApp_maybe ) -import TyCon		( isFunTyCon )  import VarSet -import UniqSet -import Name		( isLocallyDefined )  import Util		( removeDups )  import Outputable	 diff --git a/ghc/compiler/rename/Rename.lhs b/ghc/compiler/rename/Rename.lhs index 1a9cc0bcc0..e6229017d3 100644 --- a/ghc/compiler/rename/Rename.lhs +++ b/ghc/compiler/rename/Rename.lhs @@ -23,13 +23,13 @@ import RnMonad  import RnNames		( getGlobalNames )  import RnSource		( rnSourceDecls, rnDecl )  import RnIfaces		( getImportedInstDecls, importDecl, mkImportExportInfo, getInterfaceExports, -			  getImportedRules, loadHomeInterface, getSlurped, removeContext, +			  getImportedRules, getSlurped, removeContext,  			  loadBuiltinRules, getDeferredDecls, ImportDeclResult(..)  			)  import RnEnv		( availName, availsToNameSet,   			  emptyAvailEnv, unitAvailEnv, availEnvElts, plusAvailEnv,   			  warnUnusedImports, warnUnusedLocalBinds, warnUnusedModules, -			  lookupImplicitOccsRn, pprAvail, unknownNameErr, +			  lookupImplicitOccsRn, unknownNameErr,  			  FreeVars, plusFVs, plusFV, unitFV, emptyFVs, isEmptyFVs, addOneFV  			)  import Module           ( Module, ModuleName, WhereFrom(..), @@ -38,7 +38,7 @@ import Module           ( Module, ModuleName, WhereFrom(..),  import Name		( Name, isLocallyDefined, NamedThing(..), getSrcLoc,  			  nameOccName, nameUnique, nameModule, maybeUserImportedFrom,  			  isUserImportedExplicitlyName, isUserImportedName, -			  maybeWiredInTyConName, maybeWiredInIdName, isWiredInName, +			  maybeWiredInTyConName, maybeWiredInIdName,  			  isUserExportedName, toRdrName  			)  import OccName		( occNameFlavour, isValOcc ) diff --git a/ghc/compiler/rename/RnBinds.lhs b/ghc/compiler/rename/RnBinds.lhs index 17284cedc3..33d99ff733 100644 --- a/ghc/compiler/rename/RnBinds.lhs +++ b/ghc/compiler/rename/RnBinds.lhs @@ -38,12 +38,8 @@ import Name		( OccName, Name, nameOccName, mkUnboundName, isUnboundName )  import NameSet  import RdrName		( RdrName, rdrNameOcc  )  import BasicTypes	( RecFlag(..), TopLevelFlag(..) ) -import Util		( thenCmp, removeDups )  import List		( partition ) -import ListSetOps	( minusList )  import Bag		( bagToList ) -import FiniteMap	( lookupFM, listToFM ) -import Maybe		( isJust )  import Outputable  \end{code} diff --git a/ghc/compiler/rename/RnEnv.lhs b/ghc/compiler/rename/RnEnv.lhs index 6bdb45bcb1..14a833959a 100644 --- a/ghc/compiler/rename/RnEnv.lhs +++ b/ghc/compiler/rename/RnEnv.lhs @@ -35,9 +35,7 @@ import OccName		( OccName,  import TysWiredIn	( listTyCon )  import Type		( funTyCon )  import Module		( ModuleName, mkThisModule, moduleName, mkVanillaModule, pprModuleName ) -import TyCon		( TyCon )  import FiniteMap -import Unique		( Unique, Uniquable(..) )  import UniqSupply  import SrcLoc		( SrcLoc, noSrcLoc )  import Outputable diff --git a/ghc/compiler/rename/RnIfaces.lhs b/ghc/compiler/rename/RnIfaces.lhs index f1f51bc430..3f775a4796 100644 --- a/ghc/compiler/rename/RnIfaces.lhs +++ b/ghc/compiler/rename/RnIfaces.lhs @@ -30,19 +30,13 @@ import HsSyn		( HsDecl(..), TyClDecl(..), InstDecl(..), IfaceSig(..),  			)  import HsImpExp		( ieNames )  import CoreSyn		( CoreRule ) -import BasicTypes	( Version, NewOrData(..), defaultFixity ) -import RdrHsSyn		( RdrNameHsDecl, RdrNameInstDecl, RdrNameTyClDecl, RdrNameRuleDecl, -			  RdrNameFixitySig, RdrNameDeprecation, RdrNameIE, +import BasicTypes	( Version, NewOrData(..) ) +import RdrHsSyn		( RdrNameHsDecl, RdrNameInstDecl, RdrNameRuleDecl, +			  RdrNameDeprecation, RdrNameIE,  			  extractHsTyRdrNames   			) -import RnEnv		( mkImportedGlobalName, newTopBinder, mkImportedGlobalFromRdrName, -			  lookupOccRn, lookupImplicitOccRn, -			  pprAvail, rdrAvailInfo, -			  availName, availNames, addAvailToNameSet, addSysAvails, -			  FreeVars, emptyFVs -			) +import RnEnv  import RnMonad -import RnHsSyn          ( RenamedHsDecl, RenamedDeprecation )  import ParseIface	( parseIface, IfaceStuff(..) )  import Name		( Name {-instance NamedThing-}, nameOccName, @@ -56,22 +50,19 @@ import Module		( Module, moduleString, pprModule,  			)  import RdrName		( RdrName, rdrNameOcc )  import NameSet -import Var		( Id )  import SrcLoc		( mkSrcLoc, SrcLoc ) -import PrelInfo		( pREL_GHC, cCallishTyKeys ) +import PrelInfo		( cCallishTyKeys )  import Maybes		( MaybeErr(..), maybeToBool, orElse ) -import ListSetOps	( unionLists ) -import Unique		( Unique, Uniquable(..) ) -import StringBuffer     ( StringBuffer, hGetStringBuffer ) +import Unique		( Uniquable(..) ) +import StringBuffer     ( hGetStringBuffer )  import FastString	( mkFastString )  import ErrUtils         ( Message ) -import Util		( sortLt, lengthExceeds ) +import Util		( sortLt )  import Lex  import FiniteMap  import Outputable  import Bag -import IO	( isDoesNotExistError )  import List	( nub )  \end{code} diff --git a/ghc/compiler/rename/RnMonad.lhs b/ghc/compiler/rename/RnMonad.lhs index 1756133f3e..1159bfe651 100644 --- a/ghc/compiler/rename/RnMonad.lhs +++ b/ghc/compiler/rename/RnMonad.lhs @@ -57,17 +57,13 @@ import Module		( Module, ModuleName, ModuleHiMap, SearchPath, WhereFrom,  import NameSet		  import CmdLineOpts	( opt_D_dump_rn_trace, opt_HiMap )  import PrelInfo		( builtinNames ) -import TysWiredIn	( boolTyCon )  import SrcLoc		( SrcLoc, mkGeneratedSrcLoc )  import Unique		( Unique, getUnique, unboundKey )  import FiniteMap	( FiniteMap, emptyFM, bagToFM, lookupFM, addToFM, addListToFM,   			  addListToFM_C, addToFM_C, eltsFM, fmToList  			)  import Bag		( Bag, mapBag, emptyBag, isEmptyBag, snocBag ) -import Maybes		( mapMaybe ) -import UniqSet  import UniqSupply -import Util  import Outputable  infixr 9 `thenRn`, `thenRn_` diff --git a/ghc/compiler/rename/RnNames.lhs b/ghc/compiler/rename/RnNames.lhs index 979bc00861..f07651e24f 100644 --- a/ghc/compiler/rename/RnNames.lhs +++ b/ghc/compiler/rename/RnNames.lhs @@ -46,7 +46,6 @@ import NameSet	( elemNameSet, emptyNameSet )  import Outputable  import Maybes	( maybeToBool, catMaybes, mapMaybe )  import UniqFM   ( emptyUFM, listToUFM, plusUFM_C ) -import Unique	( getUnique )  import Util	( removeDups, equivClassesByUniq, sortLt )  import List	( partition )  \end{code} diff --git a/ghc/compiler/rename/RnSource.lhs b/ghc/compiler/rename/RnSource.lhs index ddacf62ee2..b2c4aa26f8 100644 --- a/ghc/compiler/rename/RnSource.lhs +++ b/ghc/compiler/rename/RnSource.lhs @@ -43,7 +43,6 @@ import Name		( Name, OccName,  			)  import NameSet  import OccName		( mkDefaultMethodOcc ) -import BasicTypes	( TopLevelFlag(..) )  import FiniteMap	( elemFM )  import PrelInfo		( derivableClassKeys, cCallishClassKeys,  			  deRefStablePtr_RDR, makeStablePtr_RDR,  @@ -55,7 +54,6 @@ import Outputable  import SrcLoc		( SrcLoc )  import CmdLineOpts	( opt_GlasgowExts, opt_WarnUnusedMatches )	-- Warn of unused for-all'd tyvars  import Unique		( Uniquable(..) ) -import UniqFM		( lookupUFM )  import ErrUtils		( Message )  import CStrings		( isCLabelString )  import Maybes		( maybeToBool, catMaybes ) diff --git a/ghc/compiler/simplCore/FloatOut.lhs b/ghc/compiler/simplCore/FloatOut.lhs index c929be3370..cf95cbe505 100644 --- a/ghc/compiler/simplCore/FloatOut.lhs +++ b/ghc/compiler/simplCore/FloatOut.lhs @@ -19,11 +19,9 @@ import CostCentre	( dupifyCC, CostCentre )  import Id		( Id, idType )  import VarEnv  import CoreLint		( beginPass, endPass ) -import PprCore  import SetLevels	( setLevels,  		 	  Level(..), tOP_LEVEL, ltMajLvl, ltLvl, isTopLvl  			) -import BasicTypes	( Unused )  import Type		( isUnLiftedType )  import Var		( TyVar )  import UniqSupply       ( UniqSupply ) diff --git a/ghc/compiler/simplCore/LiberateCase.lhs b/ghc/compiler/simplCore/LiberateCase.lhs index f70b692ac7..bd9bac25e7 100644 --- a/ghc/compiler/simplCore/LiberateCase.lhs +++ b/ghc/compiler/simplCore/LiberateCase.lhs @@ -15,8 +15,6 @@ import CoreUnfold	( couldBeSmallEnoughToInline )  import Var		( Id )  import VarEnv  import Maybes -import Outputable -import Util  \end{code}  This module walks over @Core@, and looks for @case@ on free variables. diff --git a/ghc/compiler/simplCore/OccurAnal.lhs b/ghc/compiler/simplCore/OccurAnal.lhs index ef5ce99979..4681aa3eda 100644 --- a/ghc/compiler/simplCore/OccurAnal.lhs +++ b/ghc/compiler/simplCore/OccurAnal.lhs @@ -18,11 +18,9 @@ module OccurAnal (  #include "HsVersions.h"  import BinderInfo -import CmdLineOpts	( SimplifierSwitch(..) )  import CoreSyn  import CoreFVs		( idRuleVars )  import CoreUtils	( exprIsTrivial ) -import Literal		( Literal(..) )  import Id		( isSpecPragmaId, isDataConId, isOneShotLambda, setOneShotLambda,   			  idOccInfo, setIdOccInfo,  			  isExportedId, modifyIdInfo, idInfo, diff --git a/ghc/compiler/simplCore/SetLevels.lhs b/ghc/compiler/simplCore/SetLevels.lhs index e5f020a6bf..91dbe75aee 100644 --- a/ghc/compiler/simplCore/SetLevels.lhs +++ b/ghc/compiler/simplCore/SetLevels.lhs @@ -49,7 +49,7 @@ import Id		( Id, idType, idFreeTyVars, mkSysLocal, isOneShotLambda, modifyIdInfo  			  idSpecialisation, idWorkerInfo, setIdInfo  			)  import IdInfo		( workerExists, vanillaIdInfo, demandInfo, setDemandInfo ) -import Var		( Var, TyVar, setVarUnique ) +import Var		( Var, setVarUnique )  import VarSet  import VarEnv  import Name		( getOccName ) diff --git a/ghc/compiler/simplCore/SimplCore.lhs b/ghc/compiler/simplCore/SimplCore.lhs index 11b14f10a8..fda56fe4ea 100644 --- a/ghc/compiler/simplCore/SimplCore.lhs +++ b/ghc/compiler/simplCore/SimplCore.lhs @@ -9,11 +9,11 @@ module SimplCore ( core2core ) where  #include "HsVersions.h"  import CmdLineOpts	( CoreToDo(..), SimplifierSwitch(..),  -			  SwitchResult(..), switchIsOn, intSwitchSet, +			  SwitchResult(..), intSwitchSet,  			  opt_D_dump_occur_anal, opt_D_dump_rules,  			  opt_D_dump_simpl_iterations,  			  opt_D_dump_simpl_stats, -			  opt_D_dump_simpl, opt_D_dump_rules, +			  opt_D_dump_rules,  			  opt_D_verbose_core2core,  			  opt_D_dump_occur_anal,                            opt_UsageSPOn, @@ -22,34 +22,19 @@ import CoreLint		( beginPass, endPass )  import CoreSyn  import CSE		( cseProgram )  import Rules		( RuleBase, ProtoCoreRule(..), pprProtoCoreRule, prepareLocalRuleBase, -                          prepareOrphanRuleBase, unionRuleBase, localRule, orphanRule ) +                          prepareOrphanRuleBase, unionRuleBase, localRule )  import CoreUnfold  import PprCore		( pprCoreBindings )  import OccurAnal	( occurAnalyseBinds )  import CoreUtils	( exprIsTrivial, etaReduceExpr, coreBindsSize )  import Simplify		( simplTopBinds, simplExpr ) -import SimplUtils	( findDefault, simplBinders ) +import SimplUtils	( simplBinders )  import SimplMonad -import Literal		( Literal(..), literalType, mkMachInt )  import ErrUtils		( dumpIfSet )  import FloatIn		( floatInwards )  import FloatOut		( floatOutwards ) -import Id		( Id, mkSysLocal, mkVanillaId, isBottomingId, isDataConWrapId, -			  idType, setIdType, idName, idInfo, setIdNoDiscard -			) -import VarEnv +import Id		( isDataConWrapId )  import VarSet -import Module		( Module ) -import Name		( mkLocalName, tidyOccName, tidyTopName,  -			  NamedThing(..), OccName -			) -import TyCon		( TyCon, isDataTyCon ) -import Type		( Type,  -			  isUnLiftedType, -			  tidyType, tidyTypes, tidyTopType, tidyTyVar, tidyTyVars, -			  Type -			) -import TysWiredIn	( smallIntegerDataCon, isIntegerTy )  import LiberateCase	( liberateCase )  import SAT		( doStaticArgs )  import Specialise	( specProgram) @@ -58,16 +43,10 @@ import StrictAnal	( saBinds )  import WorkWrap	        ( wwTopBinds )  import CprAnalyse       ( cprAnalyse ) -import Unique		( Unique, Uniquable(..) ) -import UniqSupply	( UniqSupply, mkSplitUniqSupply, splitUniqSupply, uniqFromSupply ) -import Util		( mapAccumL ) -import SrcLoc		( noSrcLoc ) -import Bag -import Maybes +import UniqSupply	( UniqSupply, mkSplitUniqSupply, splitUniqSupply )  import IO		( hPutStr, stderr )  import Outputable -import Ratio 		( numerator, denominator )  import List             ( partition )  \end{code} diff --git a/ghc/compiler/simplCore/SimplMonad.lhs b/ghc/compiler/simplCore/SimplMonad.lhs index 97dee5c0cd..a5d5a9806a 100644 --- a/ghc/compiler/simplCore/SimplMonad.lhs +++ b/ghc/compiler/simplCore/SimplMonad.lhs @@ -46,24 +46,19 @@ module SimplMonad (  #include "HsVersions.h"  import Id		( Id, mkSysLocal, idUnfolding, isDataConWrapId ) -import IdInfo		( InlinePragInfo(..) ) -import Demand		( Demand )  import CoreSyn -import CoreUnfold	( isCompulsoryUnfolding, isEvaldUnfolding ) +import CoreUnfold	( isCompulsoryUnfolding )  import PprCore		()	-- Instances -import Rules		( RuleBase )  import CostCentre	( CostCentreStack, subsumedCCS )  import Name		( isLocallyDefined )  import OccName		( UserFS ) -import Var		( TyVar )  import VarEnv  import VarSet  import qualified Subst -import Subst		( Subst, emptySubst, mkSubst,  -			  substTy, substEnv,  +import Subst		( Subst, mkSubst, substEnv,   			  InScopeSet, substInScope, isInScope  			) -import Type             ( Type, TyVarSubst, applyTy ) +import Type             ( Type )  import UniqSupply	( uniqsFromSupply, uniqFromSupply, splitUniqSupply,  			  UniqSupply  			) diff --git a/ghc/compiler/simplCore/SimplUtils.lhs b/ghc/compiler/simplCore/SimplUtils.lhs index 34ee7d6115..d346292c33 100644 --- a/ghc/compiler/simplCore/SimplUtils.lhs +++ b/ghc/compiler/simplCore/SimplUtils.lhs @@ -18,12 +18,9 @@ module SimplUtils (  #include "HsVersions.h" -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 )  import Subst		( InScopeSet, mkSubst, substBndrs, substBndr, substIds, lookupIdSubst )  import Id		( Id, idType, isId, idName,  @@ -38,14 +35,9 @@ import Type		( Type, tyVarsOfType, tyVarsOfTypes, mkForAllTys, seqType, repType,  			  splitTyConApp_maybe, mkTyVarTys, applyTys, splitFunTys, mkFunTys  			)  import TyCon		( tyConDataConsIfAvailable ) -import PprType		( {- instance Outputable Type -} )  import DataCon		( dataConRepArity ) -import TysPrim		( statePrimTyCon ) -import Var		( setVarUnique )  import VarSet  import VarEnv		( SubstEnv, SubstResult(..) ) -import UniqSupply	( splitUniqSupply, uniqFromSupply ) -import Util		( zipWithEqual, mapAccumL )  import Outputable  \end{code} diff --git a/ghc/compiler/simplCore/Simplify.lhs b/ghc/compiler/simplCore/Simplify.lhs index 4b7f32d7f9..ae04f14c65 100644 --- a/ghc/compiler/simplCore/Simplify.lhs +++ b/ghc/compiler/simplCore/Simplify.lhs @@ -8,9 +8,8 @@ module Simplify ( simplTopBinds, simplExpr ) where  #include "HsVersions.h" -import CmdLineOpts	( intSwitchSet, switchIsOn, -			  opt_SccProfilingOn, opt_PprStyle_Debug, opt_SimplDoEtaReduction, -			  opt_SimplNoPreInlining, opt_DictsStrict, opt_SimplPedanticBottoms, +import CmdLineOpts	( switchIsOn, opt_SimplDoEtaReduction, +			  opt_SimplNoPreInlining, opt_DictsStrict,  			  SimplifierSwitch(..)  			)  import SimplMonad @@ -19,60 +18,50 @@ import SimplUtils	( mkCase, transformRhs, findAlt,  			  SimplCont(..), DupFlag(..), contResultType, analyseCont,   			  discardInline, countArgs, countValArgs, discardCont, contIsDupable  			) -import Var		( TyVar, mkSysTyVar, tyVarKind, maybeModifyIdInfo ) +import Var		( mkSysTyVar, tyVarKind )  import VarEnv -import VarSet -import Id		( Id, idType, idInfo, idUnique, isDataConId, isDataConId_maybe, +import Id		( Id, idType, idInfo, isDataConId,  			  idUnfolding, setIdUnfolding, isExportedId, isDeadBinder, -			  idSpecialisation, setIdSpecialisation, -			  idDemandInfo,  -			  setIdInfo, +			  idDemandInfo, setIdInfo,  			  idOccInfo, setIdOccInfo, -			  zapLamIdInfo, zapFragileIdInfo, -			  idStrictness, isBottomingId, -			  setInlinePragma,  -			  setOneShotLambda, maybeModifyIdInfo +			  zapLamIdInfo, idStrictness, setOneShotLambda,   			) -import IdInfo		( InlinePragInfo(..), OccInfo(..), StrictnessInfo(..),  -		 	  ArityInfo(..), atLeastArity, arityLowerBound, unknownArity, -			  specInfo, inlinePragInfo, setArityInfo, setInlinePragInfo, setUnfoldingInfo, -			  CprInfo(..), cprInfo, occInfo +import IdInfo		( OccInfo(..), StrictnessInfo(..), ArityInfo(..), +			  setArityInfo, setUnfoldingInfo, +			  occInfo  			)  import Demand		( Demand, isStrict, wwLazy ) -import DataCon		( DataCon, dataConNumInstArgs, dataConRepStrictness, dataConRepArity, +import DataCon		( dataConNumInstArgs, dataConRepStrictness,  			  dataConSig, dataConArgTys  			)  import CoreSyn -import CoreFVs		( exprFreeVars, mustHaveLocalBinding ) -import CoreUnfold	( Unfolding, mkOtherCon, mkUnfolding, otherCons, maybeUnfoldingTemplate, -			  callSiteInline, hasSomeUnfolding, noUnfolding +import CoreFVs		( mustHaveLocalBinding ) +import CoreUnfold	( mkOtherCon, mkUnfolding, otherCons, +			  callSiteInline  			) -import CoreUtils	( cheapEqExpr, exprIsDupable, exprIsCheap, exprIsTrivial, exprIsConApp_maybe, +import CoreUtils	( cheapEqExpr, exprIsDupable, exprIsTrivial, exprIsConApp_maybe,  			  exprType, coreAltsType, exprArity, exprIsValue, idAppIsCheap,  			  exprOkForSpeculation, etaReduceExpr,  			  mkCoerce, mkSCC, mkInlineMe, mkAltExpr  			)  import Rules		( lookupRule ) -import CostCentre	( isSubsumedCCS, currentCCS, isEmptyCC ) -import Type		( Type, mkTyVarTy, mkTyVarTys, isUnLiftedType, seqType, -			  mkFunTy, splitFunTy, splitFunTys, splitFunTy_maybe, -			  splitTyConApp_maybe,  -			  funResultTy, isDictTy, isDataType, applyTy, applyTys, mkFunTys +import CostCentre	( currentCCS ) +import Type		( mkTyVarTys, isUnLiftedType, seqType, +			  mkFunTy, splitFunTy, splitTyConApp_maybe,  +			  funResultTy, isDictTy, isDataType, applyTy   			) -import Subst		( Subst, mkSubst, emptySubst, substTy, substExpr, -			  substEnv, isInScope, lookupIdSubst, substIdInfo +import Subst		( mkSubst, substTy, substExpr, +			  isInScope, lookupIdSubst, substIdInfo  			)  import TyCon		( isDataTyCon, tyConDataConsIfAvailable,  -			  tyConClass_maybe, tyConArity, isDataTyCon +			  isDataTyCon  			)  import TysPrim		( realWorldStatePrimTy )  import PrelInfo		( realWorldPrimId ) -import BasicTypes	( TopLevelFlag(..), isTopLevel, isLoopBreaker ) +import BasicTypes	( isLoopBreaker )  import Maybes		( maybeToBool )  import Util		( zipWithEqual, lengthExceeds ) -import PprCore  import Outputable -import Unique		( foldrIdKey )	-- Temp  \end{code} diff --git a/ghc/compiler/simplStg/SimplStg.lhs b/ghc/compiler/simplStg/SimplStg.lhs index 3f04f51b4e..466f7fafee 100644 --- a/ghc/compiler/simplStg/SimplStg.lhs +++ b/ghc/compiler/simplStg/SimplStg.lhs @@ -24,7 +24,6 @@ import CmdLineOpts	( opt_StgDoLetNoEscapes, opt_D_verbose_stg2stg,  			)  import Id		( Id )  import Module		( Module, moduleString ) -import VarEnv  import ErrUtils		( doIfSet, dumpIfSet )  import UniqSupply	( splitUniqSupply, UniqSupply )  import IO		( hPutStr, stdout ) diff --git a/ghc/compiler/specialise/Rules.lhs b/ghc/compiler/specialise/Rules.lhs index 7a70d519c5..b5c7002f95 100644 --- a/ghc/compiler/specialise/Rules.lhs +++ b/ghc/compiler/specialise/Rules.lhs @@ -15,32 +15,28 @@ module Rules (  import CoreSyn		-- All of it  import OccurAnal	( occurAnalyseRule ) -import BinderInfo	( markMany )  import CoreFVs		( exprFreeVars, idRuleVars, ruleRhsFreeVars, ruleSomeLhsFreeVars )  import CoreUnfold	( isCheapUnfolding, unfoldingTemplate )  import CoreUtils	( eqExpr )  import PprCore		( pprCoreRule ) -import Subst		( Subst, InScopeSet, substBndr, lookupSubst, extendSubst, -			  mkSubst, substEnv, setSubstEnv, emptySubst, isInScope, -			  unBindSubst, bindSubstList, unBindSubstList, substInScope +import Subst		( Subst, InScopeSet, lookupSubst, extendSubst, +			  substEnv, setSubstEnv, emptySubst, isInScope, +			  bindSubstList, unBindSubstList, substInScope  			)  import Id		( Id, idUnfolding, zapLamIdInfo,   			  idSpecialisation, setIdSpecialisation, -			  setIdNoDiscard, maybeModifyIdInfo, modifyIdInfo +			  setIdNoDiscard  			)  -import Name		( Name, isLocallyDefined ) +import Name		( isLocallyDefined )  import Var		( isTyVar, isId )  import VarSet  import VarEnv -import Type		( mkTyVarTy, getTyVar_maybe ) +import Type		( mkTyVarTy )  import qualified Unify	( match ) -import CmdLineOpts	( opt_D_dump_simpl, opt_D_verbose_core2core )  import UniqFM -import ErrUtils		( dumpIfSet )  import Outputable  import Maybes		( maybeToBool ) -import List		( partition )  import Util		( sortLt )  \end{code} diff --git a/ghc/compiler/specialise/Specialise.lhs b/ghc/compiler/specialise/Specialise.lhs index 312609aa6c..d73e2c3f41 100644 --- a/ghc/compiler/specialise/Specialise.lhs +++ b/ghc/compiler/specialise/Specialise.lhs @@ -21,7 +21,6 @@ import Type		( Type, mkTyVarTy, splitSigmaTy, splitFunTysN,  			  tyVarsOfType, tyVarsOfTypes, tyVarsOfTheta, applyTys,  			  mkForAllTys, boxedTypeKind  			) -import PprType		( {- instance Outputable Type -} )  import Subst		( Subst, mkSubst, substTy, mkSubst, substBndrs, extendSubstList,  			  substId, substAndCloneId, substAndCloneIds, lookupIdSubst, substInScope  			)  diff --git a/ghc/compiler/stgSyn/CoreToStg.lhs b/ghc/compiler/stgSyn/CoreToStg.lhs index 44cff7e945..05ceb4d092 100644 --- a/ghc/compiler/stgSyn/CoreToStg.lhs +++ b/ghc/compiler/stgSyn/CoreToStg.lhs @@ -17,32 +17,26 @@ 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 ) -import Id		( Id, mkSysLocal, idType, idStrictness, idUnique, isExportedId, mkVanillaId, -			  externallyVisibleId, setIdUnique, idName,  -			  idDemandInfo, idArity, setIdType, idFlavour +import Id		( Id, mkSysLocal, idType, idStrictness, isExportedId,  +			  mkVanillaId, idName, idDemandInfo, idArity, setIdType, +			  idFlavour, idUnique  			) -import Var		( Var, varType, modifyIdInfo ) -import IdInfo		( setDemandInfo, StrictnessInfo(..), IdFlavour(..) ) -import UsageSPUtils     ( primOpUsgTys ) -import DataCon		( DataCon, dataConName, dataConWrapId ) -import Demand		( Demand, isStrict, wwStrict, wwLazy ) -import Name	        ( Name, nameModule, isLocallyDefinedName, setNameUnique ) -import Literal	        ( Literal(..) ) +import IdInfo		( StrictnessInfo(..), IdFlavour(..) ) +import DataCon		( dataConWrapId ) +import Demand		( Demand, isStrict, wwLazy ) +import Name	        ( setNameUnique )  import VarEnv -import PrimOp		( PrimOp(..), setCCallUnique, primOpUsg ) +import PrimOp		( PrimOp(..), setCCallUnique )  import Type		( isUnLiftedType, isUnboxedTupleType, Type, splitFunTy_maybe, -                          UsageAnn(..), tyUsg, applyTy, mkUsgTy, repType, seqType, +                          UsageAnn(..), tyUsg, applyTy, repType, seqType,  			  splitRepFunTys, mkFunTys  			) -import TysPrim		( intPrimTy )  import UniqSupply	-- all of it, really -import Util		( lengthExceeds ) -import BasicTypes	( TopLevelFlag(..), isNotTopLevel, Arity ) -import CmdLineOpts	( opt_D_verbose_stg2stg, opt_UsageSPOn ) +import BasicTypes	( TopLevelFlag(..), isNotTopLevel ) +import CmdLineOpts	( opt_D_verbose_stg2stg )  import UniqSet		( emptyUniqSet )  import Maybes  import Outputable diff --git a/ghc/compiler/stgSyn/StgLint.lhs b/ghc/compiler/stgSyn/StgLint.lhs index 24bad62f18..6a72b9e9d8 100644 --- a/ghc/compiler/stgSyn/StgLint.lhs +++ b/ghc/compiler/stgSyn/StgLint.lhs @@ -22,7 +22,6 @@ 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 fabedee554..2f0fc0b507 100644 --- a/ghc/compiler/stgSyn/StgSyn.lhs +++ b/ghc/compiler/stgSyn/StgSyn.lhs @@ -48,12 +48,10 @@ import CostCentre	( CostCentreStack, CostCentre )  import Id		( Id, idName, idPrimRep, idType )  import Name		( isDllName )  import Literal		( Literal, literalType, isLitLitLit, literalPrimRep ) -import DataCon		( DataCon, dataConName, isNullaryDataCon ) +import DataCon		( DataCon, dataConName )  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/stranal/SaLib.lhs b/ghc/compiler/stranal/SaLib.lhs index f3d5dc8fc9..7e485c9097 100644 --- a/ghc/compiler/stranal/SaLib.lhs +++ b/ghc/compiler/stranal/SaLib.lhs @@ -18,9 +18,7 @@ module SaLib (  #include "HsVersions.h" -import Id		( Id )  import Type		( Type ) -import CoreSyn		( CoreExpr )  import VarEnv  import IdInfo		( StrictnessInfo(..) )  import Demand		( Demand, pprDemands ) diff --git a/ghc/compiler/stranal/StrictAnal.lhs b/ghc/compiler/stranal/StrictAnal.lhs index 032176a6e1..15520cbec9 100644 --- a/ghc/compiler/stranal/StrictAnal.lhs +++ b/ghc/compiler/stranal/StrictAnal.lhs @@ -13,7 +13,7 @@ module StrictAnal ( saBinds ) where  import CmdLineOpts	( opt_D_dump_stranal, opt_D_dump_simpl_stats,  opt_D_verbose_core2core )  import CoreSyn -import Id		( idType, setIdStrictness, setInlinePragma,  +import Id		( setIdStrictness, setInlinePragma,   			  idDemandInfo, setIdDemandInfo, isBottomingId,  			  Id  			) @@ -23,7 +23,6 @@ import ErrUtils		( dumpIfSet )  import SaAbsInt  import SaLib  import Demand		( Demand, wwStrict, isStrict, isLazy ) -import UniqSupply       ( UniqSupply )  import Util		( zipWith3Equal, stretchZipWith )  import Outputable  \end{code} diff --git a/ghc/compiler/stranal/WorkWrap.lhs b/ghc/compiler/stranal/WorkWrap.lhs index 87f560b575..0ad75460de 100644 --- a/ghc/compiler/stranal/WorkWrap.lhs +++ b/ghc/compiler/stranal/WorkWrap.lhs @@ -15,21 +15,17 @@ import CmdLineOpts	( opt_UF_CreationThreshold , opt_D_verbose_core2core,  			)  import CoreLint		( beginPass, endPass )  import CoreUtils	( exprType, exprArity, exprEtaExpandArity ) -import DataCon		( DataCon )  import MkId		( mkWorkerId )  import Id		( Id, idType, idStrictness, setIdArityInfo, isOneShotLambda,  			  setIdStrictness, idInlinePragma,   			  setIdWorkerInfo, idCprInfo, setInlinePragma ) -import VarSet  import Type		( Type, isNewType, splitForAllTys, splitFunTys )  import IdInfo		( mkStrictnessInfo, noStrictnessInfo, StrictnessInfo(..),  			  CprInfo(..), exactArity, InlinePragInfo(..), isNeverInlinePrag,  			  WorkerInfo(..)  			)  import Demand           ( Demand, wwLazy ) -import SaLib  import UniqSupply	( UniqSupply, initUs_, returnUs, thenUs, mapUs, getUniqueUs, UniqSM ) -import UniqSet  import WwLib  import Outputable  \end{code} diff --git a/ghc/compiler/stranal/WwLib.lhs b/ghc/compiler/stranal/WwLib.lhs index 9083d37f81..f156430461 100644 --- a/ghc/compiler/stranal/WwLib.lhs +++ b/ghc/compiler/stranal/WwLib.lhs @@ -29,7 +29,6 @@ import Type		( isUnLiftedType,  			  mkTyConApp, mkFunTys,  			  Type  			) -import TyCon            ( isNewTyCon, isProductTyCon, TyCon )  import BasicTypes	( NewOrData(..), Arity, Boxity(..) )  import Var              ( TyVar, Var, isId )  import UniqSupply	( returnUs, thenUs, getUniqueUs, getUniquesUs,  diff --git a/ghc/compiler/typecheck/Inst.lhs b/ghc/compiler/typecheck/Inst.lhs index 1e99572c5e..f3b13c803e 100644 --- a/ghc/compiler/typecheck/Inst.lhs +++ b/ghc/compiler/typecheck/Inst.lhs @@ -38,7 +38,6 @@ module Inst (  #include "HsVersions.h"  import HsSyn	( HsLit(..), HsExpr(..) ) -import RnHsSyn	( RenamedArithSeqInfo, RenamedHsExpr, RenamedPat )  import TcHsSyn	( TcExpr, TcId,   		  mkHsTyApp, mkHsDictApp, mkHsConApp, zonkId  		) @@ -59,7 +58,6 @@ import PrelInfo	( isStandardClass, isCcallishClass, isNoDictClass )  import Name	( OccName, Name, mkDictOcc, mkMethodOcc, mkIPOcc,  		  getOccName, nameUnique )  import PprType	( pprPred )	 -import SrcLoc	( SrcLoc )  import Type	( Type, PredType(..), ThetaType,  		  mkTyVarTy, isTyVarTy, mkDictTy, mkPredTy,  		  splitForAllTys, splitSigmaTy, @@ -69,9 +67,7 @@ import Type	( Type, PredType(..), ThetaType,  import Subst	( emptyInScopeSet, mkSubst,  		  substTy, substClasses, mkTyVarSubst, mkTopTyVarSubst  		) -import TyCon	( TyCon )  import Literal	( inIntRange ) -import Var	( TyVar )  import VarEnv	( lookupVarEnv, TidyEnv,  		  lookupSubstEnv, SubstResult(..)  		) @@ -86,7 +82,6 @@ import TysWiredIn ( intDataCon, isIntTy,  import Unique	( fromRationalClassOpKey, rationalTyConKey,  		  fromIntClassOpKey, fromIntegerClassOpKey, Unique  		) -import Maybes	( expectJust )  import Maybe	( catMaybes )  import Util	( thenCmp, zipWithEqual, mapAccumL )  import Outputable diff --git a/ghc/compiler/typecheck/TcBinds.lhs b/ghc/compiler/typecheck/TcBinds.lhs index 48279327b8..7d8b4c3b03 100644 --- a/ghc/compiler/typecheck/TcBinds.lhs +++ b/ghc/compiler/typecheck/TcBinds.lhs @@ -61,7 +61,6 @@ import Maybes		( maybeToBool )  import BasicTypes	( TopLevelFlag(..), RecFlag(..), isNotTopLevel )  import FiniteMap	( listToFM, lookupFM )  import Unique		( ioTyConKey, mainKey, hasKey, Uniquable(..) ) -import SrcLoc           ( SrcLoc )  import Outputable  \end{code} diff --git a/ghc/compiler/typecheck/TcClassDcl.lhs b/ghc/compiler/typecheck/TcClassDcl.lhs index 1af35c735d..eae1c69d27 100644 --- a/ghc/compiler/typecheck/TcClassDcl.lhs +++ b/ghc/compiler/typecheck/TcClassDcl.lhs @@ -17,7 +17,6 @@ import HsSyn		( HsDecl(..), TyClDecl(..), Sig(..), MonoBinds(..),  			  andMonoBinds, andMonoBindList, getTyVarName,   			  isClassDecl, isClassOpSig, isPragSig, collectMonoBinders  			) -import HsPragmas	( ClassPragmas(..) )  import BasicTypes	( NewOrData(..), TopLevelFlag(..), RecFlag(..) )  import RnHsSyn		( RenamedTyClDecl, RenamedClassPragmas,  			  RenamedClassOpSig, RenamedMonoBinds, @@ -32,7 +31,6 @@ import TcEnv		( TcId, ValueEnv, TcTyThing(..), tcAddImportedIdInfo,  			)  import TcBinds		( tcBindWithSigs, tcSpecSigs )  import TcTyDecls	( mkNewTyConRep ) -import TcUnify		( unifyKinds )  import TcMonad  import TcMonoType	( kcHsType, tcHsTopType, tcExtendTopTyVarScope,   			  tcContext, checkSigTyVars, sigCtxt, mkTcSig @@ -41,15 +39,12 @@ import TcSimplify	( tcSimplifyAndCheck, bindInstsOfLocalFuns )  import TcType		( TcType, TcTyVar, tcInstTyVars, zonkTcTyVarBndr, tcGetTyVar )  import TcInstUtil	( classDataCon )  import PrelInfo		( nO_METHOD_BINDING_ERROR_ID ) -import FieldLabel	( firstFieldLabelTag )  import Bag		( unionManyBags, bagToList )  import Class		( mkClass, classBigSig, classSelIds, Class, ClassOpItem )  import CmdLineOpts      ( opt_GlasgowExts, opt_WarnMissingMethods )  import MkId		( mkDictSelId, mkDataConId, mkDataConWrapId, mkDefaultMethodId )  import DataCon		( mkDataCon, dataConId, dataConWrapId, notMarkedStrict )  import Id		( Id, setInlinePragma, idUnfolding, idType, idName ) -import CoreUnfold	( unfoldingTemplate ) -import IdInfo  import Name		( Name, nameOccName, isLocallyDefined, NamedThing(..) )  import NameSet		( emptyNameSet )  import Outputable @@ -61,8 +56,6 @@ import Type		( Type, ThetaType, ClassContext,  import Var		( tyVarKind, TyVar )  import VarSet		( mkVarSet, emptyVarSet )  import TyCon		( AlgTyConFlavour(..), mkClassTyCon ) -import Unique		( Unique, Uniquable(..) ) -import Util  import Maybes		( seqMaybe )  import FiniteMap        ( lookupWithDefaultFM )  \end{code} diff --git a/ghc/compiler/typecheck/TcDefaults.lhs b/ghc/compiler/typecheck/TcDefaults.lhs index a3c292b823..aaed7c2221 100644 --- a/ghc/compiler/typecheck/TcDefaults.lhs +++ b/ghc/compiler/typecheck/TcDefaults.lhs @@ -19,9 +19,7 @@ import TcSimplify	( tcSimplifyCheckThetas )  import TysWiredIn	( integerTy, doubleTy )  import Type             ( Type )  import Unique		( numClassKey ) -import ErrUtils		( addShortErrLocLine )  import Outputable -import Util  \end{code}  \begin{code} diff --git a/ghc/compiler/typecheck/TcDeriv.lhs b/ghc/compiler/typecheck/TcDeriv.lhs index a5ef4d81d1..44a0c5ee8e 100644 --- a/ghc/compiler/typecheck/TcDeriv.lhs +++ b/ghc/compiler/typecheck/TcDeriv.lhs @@ -50,7 +50,6 @@ 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/TcEnv.lhs b/ghc/compiler/typecheck/TcEnv.lhs index db0d64f432..30999e89c2 100644 --- a/ghc/compiler/typecheck/TcEnv.lhs +++ b/ghc/compiler/typecheck/TcEnv.lhs @@ -36,7 +36,6 @@ module TcEnv(  #include "HsVersions.h" -import HsTypes	( HsTyVarBndr, getTyVarName )  import Id	( mkUserLocal, isDataConWrapId_maybe )  import MkId 	( mkSpecPragmaId )  import Var	( TyVar, Id, setVarName, @@ -46,7 +45,6 @@ import TcType	( TcType, TcTyVar, TcTyVarSet, TcThetaType,  		  tcInstTyVars, zonkTcTyVars,  		  TcKind, kindToTcKind  		) -import VarEnv  import VarSet  import Type	( Kind, Type, superKind,  		  tyVarsOfType, tyVarsOfTypes, mkTyVarTy, @@ -71,11 +69,9 @@ import Name		( Name, OccName, nameOccName, getSrcLoc,  			)  import Unify		( unifyTyListsX, matchTys )  import Unique		( pprUnique10, Unique, Uniquable(..) ) -import FiniteMap	( lookupFM, addToFM )  import UniqFM  import Unique		( Uniquable(..) )  import Util		( zipEqual, zipWith3Equal, mapAccumL ) -import Bag		( bagToList )  import SrcLoc		( SrcLoc )  import FastString	( FastString )  import Maybes diff --git a/ghc/compiler/typecheck/TcExpr.lhs b/ghc/compiler/typecheck/TcExpr.lhs index 2bb3060185..d171a36d80 100644 --- a/ghc/compiler/typecheck/TcExpr.lhs +++ b/ghc/compiler/typecheck/TcExpr.lhs @@ -44,7 +44,6 @@ import TcType		( TcType, TcTauType,  			  tcInstTcType, tcSplitRhoTy,  			  newTyVarTy, newTyVarTy_OpenKind, zonkTcType ) -import Class		( Class )  import FieldLabel	( FieldLabel, fieldLabelName, fieldLabelType, fieldLabelTyCon )  import Id		( idType, recordSelectorFieldLabel, isRecordSelector,  			  Id, mkVanillaId diff --git a/ghc/compiler/typecheck/TcForeign.lhs b/ghc/compiler/typecheck/TcForeign.lhs index aa2434704a..7e4140799b 100644 --- a/ghc/compiler/typecheck/TcForeign.lhs +++ b/ghc/compiler/typecheck/TcForeign.lhs @@ -33,7 +33,6 @@ import TcHsSyn		( TcMonoBinds, TypecheckedForeignDecl,  			  TcForeignExportDecl )  import TcExpr		( tcId, tcPolyExpr )			  import Inst		( emptyLIE, LIE, plusLIE ) -import CoreSyn  import ErrUtils		( Message )  import Id		( Id, idName, mkVanillaId ) @@ -42,16 +41,12 @@ import Type		( splitFunTys  			, splitTyConApp_maybe  			, splitForAllTys  			) -import PprType		( {- instance Outputable Type -} )  import TysWiredIn	( isFFIArgumentTy, isFFIResultTy,   			  isFFIExternalTy, isAddrTy  			)  import Type             ( Type )  import Unique  import Outputable -import Util -import CmdLineOpts	( opt_GlasgowExts ) -import Maybes		( maybeToBool )  \end{code} diff --git a/ghc/compiler/typecheck/TcGenDeriv.lhs b/ghc/compiler/typecheck/TcGenDeriv.lhs index d216ae6409..b19f84e434 100644 --- a/ghc/compiler/typecheck/TcGenDeriv.lhs +++ b/ghc/compiler/typecheck/TcGenDeriv.lhs @@ -49,7 +49,6 @@ import Name		( getOccString, getOccName, getSrcLoc, occNameString,  			  isDataSymOcc, isSymOcc  			) -import PrimOp		( PrimOp(..) )  import PrelInfo		-- Lots of RdrNames  import SrcLoc		( mkGeneratedSrcLoc, SrcLoc )  import TyCon		( TyCon, isNewTyCon, tyConDataCons, isEnumerationTyCon, @@ -65,7 +64,6 @@ import Panic		( panic, assertPanic )  import Maybes		( maybeToBool )  import Constants  import List		( partition, intersperse ) -import Char		( isAlpha )  #if __GLASGOW_HASKELL__ >= 404  import GlaExts		( fromInt ) diff --git a/ghc/compiler/typecheck/TcHsSyn.lhs b/ghc/compiler/typecheck/TcHsSyn.lhs index c45fab7501..1252cfd913 100644 --- a/ghc/compiler/typecheck/TcHsSyn.lhs +++ b/ghc/compiler/typecheck/TcHsSyn.lhs @@ -49,16 +49,11 @@ import TcMonad  import TcType	( TcType, TcTyVar,  		  zonkTcTypeToType, zonkTcTyVarToTyVar, zonkTcTyVarBndr, zonkTcType  		) -import Type	( mkTyVarTy, isUnLiftedType, Type )  import Name	( isLocallyDefined ) -import Var	( TyVar ) -import VarEnv	( TyVarEnv, emptyVarEnv, extendVarEnvList ) -import VarSet	( isEmptyVarSet )  import CoreSyn  ( Expr )  import CoreUnfold( unfoldingTemplate )  import BasicTypes ( RecFlag(..) )  import Bag -import UniqFM  import Outputable  \end{code} diff --git a/ghc/compiler/typecheck/TcIfaceSig.lhs b/ghc/compiler/typecheck/TcIfaceSig.lhs index 56d74688f5..27b4f1845f 100644 --- a/ghc/compiler/typecheck/TcIfaceSig.lhs +++ b/ghc/compiler/typecheck/TcIfaceSig.lhs @@ -21,7 +21,6 @@ import TcEnv		( ValueEnv, tcExtendTyVarEnv,  			  tcLookupValueMaybe,  			  explicitLookupValue, badCon, badPrimOp, valueEnvIds  			) -import TcType		( TcKind, kindToTcKind )  import RnHsSyn		( RenamedHsDecl )  import HsCore @@ -31,7 +30,6 @@ import CoreUtils	( exprType )  import CoreUnfold  import CoreLint		( lintUnfolding )  import WorkWrap		( mkWrapper ) -import PrimOp		( PrimOp(..) )  import Id		( Id, mkId, mkVanillaId,  			  isDataConWrapId_maybe @@ -41,12 +39,9 @@ import IdInfo  import DataCon		( dataConSig, dataConArgTys )  import Type		( mkSynTy, mkTyVarTys, splitAlgTyConApp, splitAlgTyConApp_maybe, splitFunTys, unUsgTy )  import Var		( mkTyVar, tyVarKind ) -import VarEnv  import Name		( Name, NamedThing(..), isLocallyDefined ) -import TysWiredIn	( integerTy, stringTy )  import Demand		( wwLazy )  import ErrUtils		( pprBagOfErrors ) -import Maybes		( maybeToBool, MaybeErr(..) )  import Outputable	  import Util		( zipWithEqual )  \end{code} diff --git a/ghc/compiler/typecheck/TcInstDcls.lhs b/ghc/compiler/typecheck/TcInstDcls.lhs index a140b9c832..e55ea763f1 100644 --- a/ghc/compiler/typecheck/TcInstDcls.lhs +++ b/ghc/compiler/typecheck/TcInstDcls.lhs @@ -38,7 +38,6 @@ import Bag		( emptyBag, unitBag, unionBags, unionManyBags,  import CmdLineOpts	( opt_GlasgowExts, opt_AllowUndecidableInstances )  import Class		( classBigSig, Class )  import Var		( idName, idType, Id, TyVar ) -import DataCon		( isNullaryDataCon, splitProductType_maybe )  import Maybes 		( maybeToBool, catMaybes, expectJust )  import MkId		( mkDictFunId )  import Module		( ModuleName ) @@ -46,7 +45,6 @@ import Name		( isLocallyDefined, NamedThing(..)	)  import NameSet		( emptyNameSet )  import PrelInfo		( eRROR_ID )  import PprType		( pprConstraint ) -import SrcLoc		( SrcLoc )  import TyCon		( isSynTyCon, tyConDerivings )  import Type		( Type, isUnLiftedType, mkTyVarTys,  			  splitSigmaTy, isTyVarTy, @@ -57,7 +55,6 @@ import Type		( Type, isUnLiftedType, mkTyVarTys,  			)  import Subst		( mkTopTyVarSubst, substClasses )  import VarSet		( mkVarSet, varSetElems ) -import TysPrim		( byteArrayPrimTyCon, mutableByteArrayPrimTyCon )  import TysWiredIn	( stringTy, isFFIArgumentTy, isFFIResultTy )  import Unique		( Unique, cCallableClassKey, cReturnableClassKey, hasKey, Uniquable(..) )  import Outputable diff --git a/ghc/compiler/typecheck/TcInstUtil.lhs b/ghc/compiler/typecheck/TcInstUtil.lhs index 8a83d3da28..5638cf1acd 100644 --- a/ghc/compiler/typecheck/TcInstUtil.lhs +++ b/ghc/compiler/typecheck/TcInstUtil.lhs @@ -25,7 +25,7 @@ import Var		( TyVar, Id, idName )  import Maybes		( MaybeErr(..), mkLookupFunDef )  import Name		( getSrcLoc, nameModule, isLocallyDefined )  import SrcLoc		( SrcLoc ) -import Type		( ThetaType, Type, ClassContext ) +import Type		( Type, ClassContext )  import PprType		( pprConstraint )  import Class		( classTyCon )  import DataCon		( DataCon ) diff --git a/ghc/compiler/typecheck/TcMatches.lhs b/ghc/compiler/typecheck/TcMatches.lhs index ebd6ba56e2..4d73dbe36b 100644 --- a/ghc/compiler/typecheck/TcMatches.lhs +++ b/ghc/compiler/typecheck/TcMatches.lhs @@ -34,7 +34,6 @@ import BasicTypes	( RecFlag(..) )  import Type		( Kind, tyVarsOfType, isTauTy, mkFunTy, boxedTypeKind )  import VarSet  import Var		( Id ) -import Util  import Bag  import Outputable  import List		( nub ) diff --git a/ghc/compiler/typecheck/TcModule.lhs b/ghc/compiler/typecheck/TcModule.lhs index 142ad99593..d10c84b307 100644 --- a/ghc/compiler/typecheck/TcModule.lhs +++ b/ghc/compiler/typecheck/TcModule.lhs @@ -31,7 +31,6 @@ import TcEnv		( tcExtendGlobalValEnv, tcExtendTypeEnv,  			  initEnv,   			  ValueEnv, TcTyThing(..)  			) -import TcExpr		( tcId )  import TcRules		( tcRules )  import TcForeign	( tcForeignImports, tcForeignExports )  import TcIfaceSig	( tcInterfaceSigs ) @@ -56,19 +55,13 @@ import Name		( Name, nameUnique, nameOccName, isLocallyDefined,  			)  import TyCon		( TyCon, tyConKind )  import Class		( Class, classSelIds, classTyCon ) -import Type		( mkTyConApp, mkForAllTy, -			  boxedTypeKind, getTyVar, Type ) -import TysWiredIn	( unitTy )  import PrelInfo		( mAIN_Name ) -import TcUnify		( unifyTauTy )  import Unique		( Unique, mainKey )  import UniqSupply       ( UniqSupply )  import Maybes		( maybeToBool )  import Util  import Bag		( Bag, isEmptyBag )  import Outputable - -import IOExts  \end{code}  Outside-world interface: diff --git a/ghc/compiler/typecheck/TcMonad.lhs b/ghc/compiler/typecheck/TcMonad.lhs index a4d8ef1a1d..8e4b190625 100644 --- a/ghc/compiler/typecheck/TcMonad.lhs +++ b/ghc/compiler/typecheck/TcMonad.lhs @@ -49,7 +49,6 @@ 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 ) @@ -63,11 +62,9 @@ import VarSet		( TyVarSet )  import UniqSupply	( UniqSupply, uniqFromSupply, uniqsFromSupply, splitUniqSupply,  			  UniqSM, initUs_ )  import SrcLoc		( SrcLoc, noSrcLoc ) -import FiniteMap	( FiniteMap, emptyFM )  import UniqFM		( UniqFM, emptyUFM )  import Unique		( Unique )  import BasicTypes	( Unused ) -import Util  import Outputable  import FastString	( FastString ) diff --git a/ghc/compiler/typecheck/TcMonoType.lhs b/ghc/compiler/typecheck/TcMonoType.lhs index c535684936..f734b78236 100644 --- a/ghc/compiler/typecheck/TcMonoType.lhs +++ b/ghc/compiler/typecheck/TcMonoType.lhs @@ -48,15 +48,12 @@ import Id		( mkVanillaId, idName, idType, idFreeTyVars )  import Var		( TyVar, mkTyVar, mkNamedUVar, varName )  import VarEnv  import VarSet -import Bag		( bagToList )  import ErrUtils		( Message ) -import TyCon		( TyCon )  import Name		( Name, OccName, isLocallyDefined )  import TysWiredIn	( mkListTy, mkTupleTy )  import UniqFM		( elemUFM, foldUFM )  import BasicTypes	( Boxity(..) )  import SrcLoc		( SrcLoc ) -import Unique		( Unique, Uniquable(..) )  import Util		( mapAccumL, isSingleton, removeDups )  import Outputable  \end{code} diff --git a/ghc/compiler/typecheck/TcPat.lhs b/ghc/compiler/typecheck/TcPat.lhs index f5045e409b..e974cfaa2d 100644 --- a/ghc/compiler/typecheck/TcPat.lhs +++ b/ghc/compiler/typecheck/TcPat.lhs @@ -8,8 +8,6 @@ module TcPat ( tcPat, tcPatBndr_NoSigs, badFieldCon, polyPatSig ) where  #include "HsVersions.h" -import {-# SOURCE #-}	TcExpr( tcExpr ) -  import HsSyn		( InPat(..), OutPat(..), HsLit(..), HsExpr(..), Sig(..) )  import RnHsSyn		( RenamedPat )  import TcHsSyn		( TcPat, TcId ) @@ -34,13 +32,11 @@ 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  			)  import TysWiredIn	( charTy, stringTy, intTy ) -import SrcLoc		( SrcLoc )  import Unique		( eqClassOpKey, geClassOpKey, minusClassOpKey,  			  cCallableClassKey  			) diff --git a/ghc/compiler/typecheck/TcSimplify.lhs b/ghc/compiler/typecheck/TcSimplify.lhs index 3f7c2a29e4..861f908f5d 100644 --- a/ghc/compiler/typecheck/TcSimplify.lhs +++ b/ghc/compiler/typecheck/TcSimplify.lhs @@ -161,7 +161,6 @@ import PprType		( pprConstraint )  import TysWiredIn	( unitTy )  import VarSet  import FiniteMap -import BasicTypes	( TopLevelFlag(..) )  import CmdLineOpts	( opt_GlasgowExts )  import Outputable  import Util diff --git a/ghc/compiler/typecheck/TcTyClsDecls.lhs b/ghc/compiler/typecheck/TcTyClsDecls.lhs index bf8baadcad..030e710213 100644 --- a/ghc/compiler/typecheck/TcTyClsDecls.lhs +++ b/ghc/compiler/typecheck/TcTyClsDecls.lhs @@ -30,11 +30,8 @@ import TcType		( TcKind, newKindVar, newKindVars, kindToTcKind, zonkTcKindToKind  import Type		( mkArrowKind, boxedTypeKind ) -import Class		( Class ) -import Var		( TyVar, tyVarKind )  import FiniteMap  import Bag	 -import VarSet  import Digraph		( stronglyConnComp, SCC(..) )  import Name		( Name, NamedThing(..), getSrcLoc, isTvOcc, nameOccName )  import Outputable @@ -43,7 +40,6 @@ import UniqSet		( UniqSet, emptyUniqSet,  			  unitUniqSet, unionUniqSets,   			  unionManyUniqSets, uniqSetToList )   import ErrUtils		( Message ) -import SrcLoc		( SrcLoc )  import TyCon		( TyCon, ArgVrcs )  import Variance         ( calcTyConArgVrcs )  import Unique		( Unique, Uniquable(..) ) diff --git a/ghc/compiler/typecheck/TcTyDecls.lhs b/ghc/compiler/typecheck/TcTyDecls.lhs index a6f151d3b8..464d1b6240 100644 --- a/ghc/compiler/typecheck/TcTyDecls.lhs +++ b/ghc/compiler/typecheck/TcTyDecls.lhs @@ -55,7 +55,6 @@ import VarSet		( intersectVarSet, isEmptyVarSet )  import Unique		( unpackCStringIdKey )  import Util		( equivClasses )  import FiniteMap        ( FiniteMap, lookupWithDefaultFM ) -import CmdLineOpts	( opt_GlasgowExts )  \end{code}  %************************************************************************ diff --git a/ghc/compiler/typecheck/TcType.lhs b/ghc/compiler/typecheck/TcType.lhs index dd48b71b60..81b4ee8ecd 100644 --- a/ghc/compiler/typecheck/TcType.lhs +++ b/ghc/compiler/typecheck/TcType.lhs @@ -51,7 +51,6 @@ module TcType (  -- friends: -import PprType		( pprType )  import TypeRep		( Type(..), Kind, TyNote(..),   			  typeCon, openTypeKind, boxedTypeKind, boxedKind, superKind, superBoxity  			)  -- friend @@ -63,8 +62,6 @@ import Type		( ThetaType, PredType(..),  import Subst		( Subst, mkTopTyVarSubst, substTy )  import TyCon		( tyConKind, mkPrimTyCon )  import PrimRep		( PrimRep(VoidRep) ) -import VarEnv -import VarSet		( emptyVarSet )  import Var		( TyVar, tyVarKind, tyVarName, isTyVar, isMutTyVar, mkTyVar )  -- others: diff --git a/ghc/compiler/typecheck/TcUnify.lhs b/ghc/compiler/typecheck/TcUnify.lhs index 9d684c1999..ba131c09d5 100644 --- a/ghc/compiler/typecheck/TcUnify.lhs +++ b/ghc/compiler/typecheck/TcUnify.lhs @@ -28,17 +28,15 @@ import Type	( tyVarsOfType,  import TyCon	( TyCon, isTupleTyCon, tupleTyConBoxity, tyConArity )  import Name	( hasBetterProv )  import Var	( TyVar, tyVarKind, varName, isSigTyVar ) -import VarEnv	  import VarSet	( varSetElems )  import TcType	( TcType, TcTauType, TcTyVar, TcKind,   		  newTyVarTy, newOpenTypeKind, newTyVarTy_OpenKind,  		  tcGetTyVar, tcPutTyVar, zonkTcType, tcTypeKind  		) +  -- others:  import BasicTypes ( Arity, Boxity, isBoxed )  import TysWiredIn ( listTyCon, mkListTy, mkTupleTy ) -import PprType	()		-- Instances -import Util  import Outputable  \end{code} diff --git a/ghc/compiler/types/PprType.lhs b/ghc/compiler/types/PprType.lhs index 93742231b1..00ff1e8720 100644 --- a/ghc/compiler/types/PprType.lhs +++ b/ghc/compiler/types/PprType.lhs @@ -30,7 +30,6 @@ import Type		( PredType(..), ThetaType,  import Var		( TyVar, tyVarKind,  			  tyVarName, setTyVarName  			) -import VarEnv  import TyCon		( TyCon, isPrimTyCon, isTupleTyCon, isUnboxedTupleTyCon,   			  maybeTyConSingleCon, isEnumerationTyCon,   			  tyConArity, tyConUnique @@ -44,7 +43,6 @@ import Outputable  import PprEnv  import Unique		( Uniquable(..) )  import Unique		-- quite a few *Keys -import Util  \end{code}  %************************************************************************ diff --git a/ghc/compiler/types/Unify.lhs b/ghc/compiler/types/Unify.lhs index f5f6111473..756a5ed314 100644 --- a/ghc/compiler/types/Unify.lhs +++ b/ghc/compiler/types/Unify.lhs @@ -27,7 +27,6 @@ import VarEnv	( TyVarSubstEnv, emptySubstEnv, lookupSubstEnv, extendSubstEnv,  		  SubstResult(..)  		) -import Unique	( Uniquable(..) )  import Outputable( panic )  import Util	( snocView )  \end{code} diff --git a/ghc/compiler/usageSP/UConSet.lhs b/ghc/compiler/usageSP/UConSet.lhs index 674bbd8b68..2c5cc0038a 100644 --- a/ghc/compiler/usageSP/UConSet.lhs +++ b/ghc/compiler/usageSP/UConSet.lhs @@ -24,7 +24,6 @@ module UConSet ( UConSet,  import VarEnv  import Type		( UsageAnn(..) )  import Var		( UVar ) -import Monad		( foldM )  import Bag              ( Bag, unitBag, emptyBag, unionBags, foldlBag, bagToList )  import Outputable  import PprType diff --git a/ghc/compiler/usageSP/UsageSPInf.lhs b/ghc/compiler/usageSP/UsageSPInf.lhs index b0f5f56b52..bfd5e71307 100644 --- a/ghc/compiler/usageSP/UsageSPInf.lhs +++ b/ghc/compiler/usageSP/UsageSPInf.lhs @@ -27,13 +27,11 @@ 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 )  import IdInfo           ( setLBVarInfo, LBVarInfo(..) )  import Id               ( isExportedId ) -import Name             ( isLocallyDefined )  import VarEnv  import VarSet  import UniqSupply       ( UniqSupply, UniqSM, diff --git a/ghc/compiler/usageSP/UsageSPLint.lhs b/ghc/compiler/usageSP/UsageSPLint.lhs index 1c97ffc021..6fb6b058a2 100644 --- a/ghc/compiler/usageSP/UsageSPLint.lhs +++ b/ghc/compiler/usageSP/UsageSPLint.lhs @@ -21,15 +21,12 @@ 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 )  import IdInfo           ( LBVarInfo(..) ) -import SrcLoc           ( noSrcLoc ) -import ErrUtils         ( Message, ghcExit ) +import ErrUtils         ( ghcExit )  import Util             ( zipWithEqual ) -import PprCore  import Bag  import Outputable  \end{code} diff --git a/ghc/compiler/usageSP/UsageSPUtils.lhs b/ghc/compiler/usageSP/UsageSPUtils.lhs index 4fb51f0eeb..92467090af 100644 --- a/ghc/compiler/usageSP/UsageSPUtils.lhs +++ b/ghc/compiler/usageSP/UsageSPUtils.lhs @@ -26,21 +26,17 @@ module UsageSPUtils ( AnnotM(AnnotM), initAnnotM,  import CoreSyn  import CoreFVs		( mustHaveLocalBinding ) -import Literal          ( Literal(..) )  import Var              ( Var, varName, varType, setVarType, mkUVar )  import Id               ( 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  import PrimOp           ( PrimOp, primOpUsg ) -import Maybes           ( expectJust )  import UniqSupply       ( UniqSupply, UniqSM, initUs, getUniqueUs, thenUs, returnUs )  import Outputable -import PprCore          ( )  -- instances only  \end{code}  ====================================================================== | 
