From 1b7a99e3e7f64c6f402e8aece32ba0b9a3703bfa Mon Sep 17 00:00:00 2001 From: simonmar <unknown> Date: Tue, 11 Jul 2000 16:12:59 +0000 Subject: [PATCH] [project @ 2000-07-11 16:12:11 by simonmar] remove unused imports --- ghc/compiler/deSugar/Desugar.lhs | 11 ++++------- ghc/compiler/deSugar/DsBinds.lhs | 2 -- ghc/compiler/deSugar/DsCCall.lhs | 19 ++++++++----------- ghc/compiler/deSugar/DsExpr.lhs | 12 ++++-------- ghc/compiler/deSugar/DsGRHSs.lhs | 1 - ghc/compiler/deSugar/DsHsSyn.lhs | 1 - ghc/compiler/deSugar/DsListComp.lhs | 13 ++++++------- ghc/compiler/deSugar/DsMonad.lhs | 7 ++----- ghc/compiler/deSugar/Match.lhs | 16 ++-------------- ghc/compiler/deSugar/MatchCon.lhs | 5 ++--- ghc/compiler/deSugar/MatchLit.lhs | 2 -- ghc/compiler/hsSyn/HsBinds.lhs | 5 ----- ghc/compiler/hsSyn/HsCore.lhs | 7 +++---- ghc/compiler/hsSyn/HsDecls.lhs | 3 --- 14 files changed, 31 insertions(+), 73 deletions(-) diff --git a/ghc/compiler/deSugar/Desugar.lhs b/ghc/compiler/deSugar/Desugar.lhs index a870cd433cbe..c42d127de391 100644 --- a/ghc/compiler/deSugar/Desugar.lhs +++ b/ghc/compiler/deSugar/Desugar.lhs @@ -10,7 +10,7 @@ module Desugar ( deSugar ) where import CmdLineOpts ( opt_D_dump_ds ) import HsSyn ( MonoBinds, RuleDecl(..), RuleBndr(..), HsExpr(..), HsBinds(..), MonoBinds(..) ) -import TcHsSyn ( TypecheckedMonoBinds, TypecheckedForeignDecl, TypecheckedRuleDecl ) +import TcHsSyn ( TypecheckedRuleDecl ) import TcModule ( TcResults(..) ) import CoreSyn import Rules ( ProtoCoreRule(..), pprProtoCoreRule ) @@ -19,20 +19,17 @@ import DsMonad import DsExpr ( dsExpr ) import DsBinds ( dsMonoBinds, AutoScc(..) ) import DsForeign ( dsForeigns ) -import DsUtils import DsExpr () -- Forces DsExpr to be compiled; DsBinds only -- depends on DsExpr.hi-boot. -import Module ( Module, moduleString ) -import Id ( Id ) -import Name ( isLocallyDefined ) +import Module ( Module ) import VarEnv import VarSet -import Bag ( isEmptyBag, unionBags ) +import Bag ( isEmptyBag ) import CmdLineOpts ( opt_SccProfilingOn ) import CoreLint ( beginPass, endPass ) import ErrUtils ( doIfSet, pprBagOfWarnings ) import Outputable -import UniqSupply ( splitUniqSupply, UniqSupply ) +import UniqSupply ( UniqSupply ) \end{code} %************************************************************************ diff --git a/ghc/compiler/deSugar/DsBinds.lhs b/ghc/compiler/deSugar/DsBinds.lhs index 7c2ce8dddca8..98af452779ff 100644 --- a/ghc/compiler/deSugar/DsBinds.lhs +++ b/ghc/compiler/deSugar/DsBinds.lhs @@ -24,14 +24,12 @@ import DsGRHSs ( dsGuarded ) import DsUtils import Match ( matchWrapper ) -import BasicTypes ( RecFlag(..) ) import CmdLineOpts ( opt_SccProfilingOn, opt_AutoSccsOnAllToplevs, opt_AutoSccsOnExportedToplevs, opt_AutoSccsOnDicts ) import CostCentre ( CostCentre, mkAutoCC, IsCafCC(..) ) import Id ( idType, idName, isUserExportedId, isSpecPragmaId, Id ) import NameSet -import VarEnv import VarSet import Type ( mkTyVarTy, isDictTy ) import Subst ( mkTyVarSubst, substTy ) diff --git a/ghc/compiler/deSugar/DsCCall.lhs b/ghc/compiler/deSugar/DsCCall.lhs index 6d488c44e7c0..4384e66f74b9 100644 --- a/ghc/compiler/deSugar/DsCCall.lhs +++ b/ghc/compiler/deSugar/DsCCall.lhs @@ -17,34 +17,31 @@ module DsCCall import CoreSyn import DsMonad -import DsUtils import CoreUtils ( exprType, mkCoerce ) -import Id ( Id, mkWildId ) +import Id ( mkWildId ) import MkId ( mkCCallOpId, realWorldPrimId ) import Maybes ( maybeToBool ) -import PrimOp ( PrimOp(..), CCall(..), CCallTarget(..) ) -import DataCon ( DataCon, splitProductType_maybe, dataConSourceArity, dataConWrapId ) +import PrimOp ( CCall(..), CCallTarget(..) ) +import DataCon ( splitProductType_maybe, dataConSourceArity, dataConWrapId ) import CallConv import Type ( isUnLiftedType, splitAlgTyConApp_maybe, mkFunTys, splitTyConApp_maybe, tyVarsOfType, mkForAllTys, isNewType, repType, isUnLiftedType, mkFunTy, mkTyConApp, Type ) -import PprType ( {- instance Outputable Type -} ) -import TysPrim ( byteArrayPrimTy, realWorldStatePrimTy, +import TysPrim ( realWorldStatePrimTy, byteArrayPrimTyCon, mutableByteArrayPrimTyCon, intPrimTy ) -import TysWiredIn ( unitDataConId, stringTy, +import TysWiredIn ( unitDataConId, unboxedSingletonDataCon, unboxedPairDataCon, unboxedSingletonTyCon, unboxedPairTyCon, - mkTupleTy, tupleCon, - boolTy, trueDataCon, falseDataCon, trueDataConId, falseDataConId, - unitTy + boolTy, trueDataCon, falseDataCon, + trueDataConId, falseDataConId, unitTy ) import Literal ( mkMachInt ) import CStrings ( CLabelString ) -import Unique ( Unique, Uniquable(..), hasKey, ioTyConKey ) +import Unique ( Unique, hasKey, ioTyConKey ) import VarSet ( varSetElems ) import Outputable \end{code} diff --git a/ghc/compiler/deSugar/DsExpr.lhs b/ghc/compiler/deSugar/DsExpr.lhs index 94149c29c44e..94e1ec50103c 100644 --- a/ghc/compiler/deSugar/DsExpr.lhs +++ b/ghc/compiler/deSugar/DsExpr.lhs @@ -18,7 +18,6 @@ import TcHsSyn ( TypecheckedHsExpr, TypecheckedHsBinds, TypecheckedStmt ) import CoreSyn -import PprCore ( {- instance Outputable Expr -} ) import CoreUtils ( exprType, mkIfThenElse, bindNonRec ) import DsMonad @@ -32,26 +31,23 @@ import DsUtils ( mkErrorAppDs, mkDsLets, mkStringLit, mkStringLitFS, import Match ( matchWrapper, matchSimply ) import CostCentre ( mkUserCC ) -import FieldLabel ( FieldLabel ) import Id ( Id, idType, recordSelectorFieldLabel ) -import PrelInfo ( rEC_CON_ERROR_ID, rEC_UPD_ERROR_ID, iRREFUT_PAT_ERROR_ID ) +import PrelInfo ( rEC_CON_ERROR_ID, iRREFUT_PAT_ERROR_ID ) import DataCon ( DataCon, dataConWrapId, dataConTyCon, dataConArgTys, dataConFieldLabels ) -import TyCon ( isNewTyCon ) import DataCon ( isExistentialDataCon ) import Literal ( Literal(..), inIntRange ) -import Type ( splitFunTys, mkTyConApp, +import Type ( splitFunTys, splitAlgTyConApp, splitAlgTyConApp_maybe, splitTyConApp_maybe, isNotUsgTy, unUsgTy, splitAppTy, isUnLiftedType, Type ) -import TysWiredIn ( tupleCon, - listTyCon, mkListTy, +import TysWiredIn ( tupleCon, listTyCon, charDataCon, charTy, stringTy, smallIntegerDataCon, isIntegerTy ) import BasicTypes ( RecFlag(..), Boxity(..) ) import Maybes ( maybeToBool ) -import Unique ( Uniquable(..), hasKey, ratioTyConKey, addr2IntegerIdKey ) +import Unique ( hasKey, ratioTyConKey, addr2IntegerIdKey ) import Util ( zipEqual, zipWithEqual ) import Outputable diff --git a/ghc/compiler/deSugar/DsGRHSs.lhs b/ghc/compiler/deSugar/DsGRHSs.lhs index e413c58e81a1..9c2557ffb6ea 100644 --- a/ghc/compiler/deSugar/DsGRHSs.lhs +++ b/ghc/compiler/deSugar/DsGRHSs.lhs @@ -20,7 +20,6 @@ import DsMonad import DsUtils import PrelInfo ( nON_EXHAUSTIVE_GUARDS_ERROR_ID ) import Unique ( otherwiseIdKey, trueDataConKey, hasKey, Uniquable(..) ) -import Outputable \end{code} @dsGuarded@ is used for both @case@ expressions and pattern bindings. diff --git a/ghc/compiler/deSugar/DsHsSyn.lhs b/ghc/compiler/deSugar/DsHsSyn.lhs index f7c78f04fbcf..65911987f71b 100644 --- a/ghc/compiler/deSugar/DsHsSyn.lhs +++ b/ghc/compiler/deSugar/DsHsSyn.lhs @@ -16,7 +16,6 @@ import Id ( idType, Id ) import Type ( Type ) import TysWiredIn ( mkListTy, mkTupleTy, unitTy ) import BasicTypes ( Boxity(..) ) -import Panic ( panic ) \end{code} Note: If @outPatType@ doesn't bear a strong resemblance to @exprType@, diff --git a/ghc/compiler/deSugar/DsListComp.lhs b/ghc/compiler/deSugar/DsListComp.lhs index 8b79313f9513..9931da8ca271 100644 --- a/ghc/compiler/deSugar/DsListComp.lhs +++ b/ghc/compiler/deSugar/DsListComp.lhs @@ -10,8 +10,8 @@ module DsListComp ( dsListComp ) where import {-# SOURCE #-} DsExpr ( dsExpr, dsLet ) -import HsSyn ( Stmt(..), HsExpr ) -import TcHsSyn ( TypecheckedStmt, TypecheckedHsExpr ) +import HsSyn ( Stmt(..) ) +import TcHsSyn ( TypecheckedStmt ) import DsHsSyn ( outPatType ) import CoreSyn @@ -21,13 +21,12 @@ import DsUtils import CmdLineOpts ( opt_FoldrBuildOn ) import CoreUtils ( exprType, mkIfThenElse ) import Id ( idType ) -import Var ( Id, TyVar ) -import Type ( mkTyVarTy, mkForAllTy, mkFunTys, mkFunTy, Type ) -import TysPrim ( alphaTyVar, alphaTy ) -import TysWiredIn ( nilDataCon, consDataCon, listTyCon ) +import Var ( Id ) +import Type ( mkTyVarTy, mkFunTys, mkFunTy, Type ) +import TysPrim ( alphaTyVar ) +import TysWiredIn ( nilDataCon, consDataCon ) import Match ( matchSimply ) import Unique ( foldrIdKey, buildIdKey ) -import Outputable \end{code} List comprehensions may be desugared in one of two ways: ``ordinary'' diff --git a/ghc/compiler/deSugar/DsMonad.lhs b/ghc/compiler/deSugar/DsMonad.lhs index ae58ca9eb666..056068d9cc4c 100644 --- a/ghc/compiler/deSugar/DsMonad.lhs +++ b/ghc/compiler/deSugar/DsMonad.lhs @@ -25,14 +25,11 @@ module DsMonad ( #include "HsVersions.h" -import Bag ( emptyBag, snocBag, bagToList, Bag ) -import ErrUtils ( WarnMsg, pprBagOfErrors ) -import HsSyn ( OutPat ) +import Bag ( emptyBag, snocBag, Bag ) +import ErrUtils ( WarnMsg ) import Id ( mkSysLocal, setIdUnique, Id ) import Module ( Module ) -import Name ( Name, maybeWiredInIdName ) import Var ( TyVar, setTyVarUnique ) -import VarEnv import Outputable import SrcLoc ( noSrcLoc, SrcLoc ) import TcHsSyn ( TypecheckedPat ) diff --git a/ghc/compiler/deSugar/Match.lhs b/ghc/compiler/deSugar/Match.lhs index 7d0e47fffdb6..9a188716f36c 100644 --- a/ghc/compiler/deSugar/Match.lhs +++ b/ghc/compiler/deSugar/Match.lhs @@ -8,8 +8,6 @@ module Match ( match, matchExport, matchWrapper, matchSimply, matchSinglePat ) w #include "HsVersions.h" -import {-# SOURCE #-} DsExpr ( dsExpr, dsLet ) - import CmdLineOpts ( opt_WarnIncompletePatterns, opt_WarnOverlappingPatterns, opt_WarnSimplePatterns ) @@ -27,18 +25,8 @@ import DataCon ( dataConFieldLabels, dataConArgTys ) import MatchCon ( matchConFamily ) import MatchLit ( matchLiterals ) import PrelInfo ( pAT_ERROR_ID ) -import Type ( isUnLiftedType, splitAlgTyConApp, - mkTyVarTys, Type - ) -import TysPrim ( intPrimTy, charPrimTy, floatPrimTy, doublePrimTy, - addrPrimTy, wordPrimTy - ) -import TysWiredIn ( nilDataCon, consDataCon, mkTupleTy, mkListTy, - charTy, charDataCon, intTy, intDataCon, - floatTy, floatDataCon, doubleTy, tupleCon, - doubleDataCon, addrTy, - addrDataCon, wordTy, wordDataCon - ) +import Type ( splitAlgTyConApp, mkTyVarTys, Type ) +import TysWiredIn ( nilDataCon, consDataCon, mkTupleTy, mkListTy, tupleCon ) import BasicTypes ( Boxity(..) ) import UniqSet import ErrUtils ( addErrLocHdrLine, dontAddErrLoc ) diff --git a/ghc/compiler/deSugar/MatchCon.lhs b/ghc/compiler/deSugar/MatchCon.lhs index 11918c1e0447..eaf006b2feab 100644 --- a/ghc/compiler/deSugar/MatchCon.lhs +++ b/ghc/compiler/deSugar/MatchCon.lhs @@ -1,4 +1,4 @@ -% + % (c) The GRASP/AQUA Project, Glasgow University, 1992-1998 % \section[MatchCon]{Pattern-matching constructors} @@ -19,8 +19,7 @@ import Id ( Id ) import CoreSyn import Type ( mkTyVarTys ) import Util ( equivClassesByUniq ) -import Unique ( Uniquable(..), Unique ) -import Outputable +import Unique ( Uniquable(..) ) \end{code} We are confronted with the first column of patterns in a set of diff --git a/ghc/compiler/deSugar/MatchLit.lhs b/ghc/compiler/deSugar/MatchLit.lhs index f3e10ff5c031..fd57f0dc40e2 100644 --- a/ghc/compiler/deSugar/MatchLit.lhs +++ b/ghc/compiler/deSugar/MatchLit.lhs @@ -12,7 +12,6 @@ import {-# SOURCE #-} Match ( match ) import {-# SOURCE #-} DsExpr ( dsExpr ) import HsSyn ( HsLit(..), OutPat(..), HsExpr(..) ) -import TcHsSyn ( TypecheckedHsExpr, TypecheckedPat ) import CoreSyn ( Expr(..), Bind(..) ) import Id ( Id ) @@ -20,7 +19,6 @@ import DsMonad import DsUtils import Literal ( mkMachInt, Literal(..) ) -import PrimRep ( PrimRep(IntRep) ) import Maybes ( catMaybes ) import Type ( Type, isUnLiftedType ) import Panic ( panic, assertPanic ) diff --git a/ghc/compiler/hsSyn/HsBinds.lhs b/ghc/compiler/hsSyn/HsBinds.lhs index 1e7f80bfb5d5..db83e15794d1 100644 --- a/ghc/compiler/hsSyn/HsBinds.lhs +++ b/ghc/compiler/hsSyn/HsBinds.lhs @@ -15,20 +15,15 @@ import {-# SOURCE #-} HsMatches ( pprMatches, Match, pprGRHSs, GRHSs ) -- friends: import HsTypes ( HsType ) -import HsImpExp ( IE(..), ieName ) import CoreSyn ( CoreExpr ) -import PprCore () -- Instances for Outputable --others: -import Id ( Id ) import Name ( Name, isUnboundName ) import NameSet ( NameSet, elemNameSet, nameSetToList ) import BasicTypes ( RecFlag(..), Fixity ) import Outputable -import Bag import SrcLoc ( SrcLoc ) import Var ( TyVar ) -import Util ( thenCmp ) \end{code} %************************************************************************ diff --git a/ghc/compiler/hsSyn/HsCore.lhs b/ghc/compiler/hsSyn/HsCore.lhs index 4124ad83f8d1..c21a2d3185d5 100644 --- a/ghc/compiler/hsSyn/HsCore.lhs +++ b/ghc/compiler/hsSyn/HsCore.lhs @@ -38,19 +38,18 @@ import IdInfo ( ArityInfo, UpdateInfo, InlinePragInfo, pprInlinePragInfo, ppArityInfo, ppStrictnessInfo ) import RdrName ( RdrName ) -import Name ( Name, toRdrName ) +import Name ( toRdrName ) import CoreSyn import CostCentre ( pprCostCentreCore ) import PrimOp ( PrimOp(CCallOp) ) -import Demand ( Demand, StrictnessInfo ) +import Demand ( StrictnessInfo ) import Literal ( Literal, maybeLitLit ) import PrimOp ( CCall, pprCCallOp ) import DataCon ( dataConTyCon ) import TyCon ( isTupleTyCon, tupleTyConBoxity ) -import Type ( Type, Kind ) +import Type ( Kind ) import CostCentre import SrcLoc ( SrcLoc ) -import BasicTypes ( Arity ) import Outputable \end{code} diff --git a/ghc/compiler/hsSyn/HsDecls.lhs b/ghc/compiler/hsSyn/HsDecls.lhs index 4e6c2b422000..033f426acb36 100644 --- a/ghc/compiler/hsSyn/HsDecls.lhs +++ b/ghc/compiler/hsSyn/HsDecls.lhs @@ -30,17 +30,14 @@ import HsCore ( UfExpr(UfVar), UfBinder, IfaceSig(..), eq_ufBinders, eq_ufExpr, import CoreSyn ( CoreRule(..) ) import BasicTypes ( Fixity, NewOrData(..) ) import CallConv ( CallConv, pprCallConv ) -import Var ( TyVar, Id ) import Name ( toRdrName ) -- others: -import PprType import FunDeps ( pprFundeps ) import Class ( FunDep ) import CStrings ( CLabelString, pprCLabelString ) import Outputable import SrcLoc ( SrcLoc, noSrcLoc ) -import Util \end{code} -- GitLab