summaryrefslogtreecommitdiff
path: root/ghc/compiler/codeGen
diff options
context:
space:
mode:
Diffstat (limited to 'ghc/compiler/codeGen')
-rw-r--r--ghc/compiler/codeGen/CgBindery.lhs4
-rw-r--r--ghc/compiler/codeGen/CgCase.lhs6
-rw-r--r--ghc/compiler/codeGen/CgConTbls.lhs5
-rw-r--r--ghc/compiler/codeGen/CgExpr.lhs4
-rw-r--r--ghc/compiler/codeGen/CgHeapery.lhs3
-rw-r--r--ghc/compiler/codeGen/CgLetNoEscape.lhs3
-rw-r--r--ghc/compiler/codeGen/CgMonad.lhs3
-rw-r--r--ghc/compiler/codeGen/CgRetConv.lhs5
-rw-r--r--ghc/compiler/codeGen/CgTailCall.lhs5
-rw-r--r--ghc/compiler/codeGen/CgUpdate.lhs2
-rw-r--r--ghc/compiler/codeGen/CodeGen.lhs5
11 files changed, 14 insertions, 31 deletions
diff --git a/ghc/compiler/codeGen/CgBindery.lhs b/ghc/compiler/codeGen/CgBindery.lhs
index 92acdfbdd8..45481368d8 100644
--- a/ghc/compiler/codeGen/CgBindery.lhs
+++ b/ghc/compiler/codeGen/CgBindery.lhs
@@ -32,7 +32,7 @@ import AbsCSyn
import CgMonad
import CgUsages ( getHpRelOffset, getSpRelOffset, getRealSp )
-import CgStackery ( freeStackSlots, addFreeSlots )
+import CgStackery ( freeStackSlots )
import CLabel ( mkClosureLabel,
mkBitmapLabel, pprCLabel )
import ClosureInfo ( mkLFImported, mkLFArgument, LambdaFormInfo )
@@ -45,7 +45,7 @@ import VarEnv
import VarSet ( varSetElems )
import Literal ( Literal )
import Maybes ( catMaybes, maybeToBool )
-import Name ( isLocallyDefined, isWiredInName, NamedThing(..) )
+import Name ( isLocallyDefined, NamedThing(..) )
#ifdef DEBUG
import PprAbsC ( pprAmode )
#endif
diff --git a/ghc/compiler/codeGen/CgCase.lhs b/ghc/compiler/codeGen/CgCase.lhs
index d64755b4b8..de7a898468 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.42 2000/05/25 12:41:15 simonpj Exp $
+% $Id: CgCase.lhs,v 1.43 2000/07/11 16:03:37 simonmar Exp $
%
%********************************************************
%* *
@@ -25,7 +25,7 @@ import AbsCUtils ( mkAbstractCs, mkAbsCStmts, mkAlgAltsCSwitch,
getAmodeRep, nonemptyAbsC
)
import CgUpdate ( reserveSeqFrame )
-import CgBindery ( getVolatileRegs, getArgAmodes, getArgAmode,
+import CgBindery ( getVolatileRegs, getArgAmodes,
bindNewToReg, bindNewToTemp,
bindNewPrimToAmode,
rebindToStack, getCAddrMode,
@@ -48,7 +48,6 @@ import CLabel ( CLabel, mkVecTblLabel, mkReturnPtLabel,
)
import ClosureInfo ( mkLFArgument )
import CmdLineOpts ( opt_SccProfilingOn, opt_GranMacros )
-import CostCentre ( CostCentre )
import Id ( Id, idPrimRep, isDeadBinder )
import DataCon ( DataCon, dataConTag, fIRST_TAG, ConTag,
isUnboxedTupleCon )
@@ -62,7 +61,6 @@ import TyCon ( TyCon, isEnumerationTyCon, isUnboxedTupleTyCon,
)
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/CgConTbls.lhs b/ghc/compiler/codeGen/CgConTbls.lhs
index 40769f66c4..fcee09f5b4 100644
--- a/ghc/compiler/codeGen/CgConTbls.lhs
+++ b/ghc/compiler/codeGen/CgConTbls.lhs
@@ -11,7 +11,6 @@ module CgConTbls ( genStaticConBits ) where
import AbsCSyn
import CgMonad
-import StgSyn ( SRT(..) )
import AbsCUtils ( mkAbstractCs, mkAbsCStmts )
import CgTailCall ( performReturn, mkStaticAlgReturnCode )
import CLabel ( mkConEntryLabel )
@@ -19,14 +18,12 @@ import ClosureInfo ( layOutStaticClosure, layOutDynCon,
mkConLFInfo, ClosureInfo
)
import CostCentre ( dontCareCCS )
-import FiniteMap ( fmToList, FiniteMap )
import DataCon ( DataCon, dataConName, dataConRepArgTys, isNullaryDataCon )
import Name ( getOccName )
import OccName ( occNameUserString )
import PrimRep ( getPrimRepSize, PrimRep(..) )
import TyCon ( tyConDataCons, isEnumerationTyCon, TyCon )
-import Type ( typePrimRep, Type )
-import Outputable
+import Type ( typePrimRep )
\end{code}
For every constructor we generate the following info tables:
diff --git a/ghc/compiler/codeGen/CgExpr.lhs b/ghc/compiler/codeGen/CgExpr.lhs
index 9a9b931af3..9ab2ab2a55 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.34 2000/04/13 20:41:30 panne Exp $
+% $Id: CgExpr.lhs,v 1.35 2000/07/11 16:03:37 simonmar Exp $
%
%********************************************************
%* *
@@ -40,7 +40,6 @@ import CostCentre ( sccAbleCostCentre, isSccCountCostCentre )
import Id ( idPrimRep, idType, Id )
import VarSet
import DataCon ( DataCon, dataConTyCon )
-import IdInfo ( ArityInfo(..) )
import PrimOp ( primOpOutOfLine, ccallMayGC,
getPrimOpResultInfo, PrimOp(..), PrimOpResultInfo(..)
)
@@ -48,7 +47,6 @@ 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/codeGen/CgHeapery.lhs b/ghc/compiler/codeGen/CgHeapery.lhs
index 566cfcbbdf..23928f69b7 100644
--- a/ghc/compiler/codeGen/CgHeapery.lhs
+++ b/ghc/compiler/codeGen/CgHeapery.lhs
@@ -1,7 +1,7 @@
%
% (c) The GRASP/AQUA Project, Glasgow University, 1992-1998
%
-% $Id: CgHeapery.lhs,v 1.20 2000/01/13 14:33:58 hwloidl Exp $
+% $Id: CgHeapery.lhs,v 1.21 2000/07/11 16:03:37 simonmar Exp $
%
\section[CgHeapery]{Heap management functions}
@@ -21,7 +21,6 @@ import CLabel
import CgMonad
import CgStackery ( getFinalStackHW, mkTaggedStkAmodes, mkTagAssts )
-import SMRep ( fixedHdrSize )
import AbsCUtils ( mkAbstractCs, getAmodeRep )
import CgUsages ( getVirtAndRealHp, getRealSp, setVirtHp, setRealHp,
initHeapUsage
diff --git a/ghc/compiler/codeGen/CgLetNoEscape.lhs b/ghc/compiler/codeGen/CgLetNoEscape.lhs
index f122b963b4..07cacd4841 100644
--- a/ghc/compiler/codeGen/CgLetNoEscape.lhs
+++ b/ghc/compiler/codeGen/CgLetNoEscape.lhs
@@ -1,7 +1,7 @@
%
% (c) The GRASP/AQUA Project, Glasgow University, 1993-1998
%
-% $Id: CgLetNoEscape.lhs,v 1.13 1999/05/13 17:30:57 simonm Exp $
+% $Id: CgLetNoEscape.lhs,v 1.14 2000/07/11 16:03:37 simonmar Exp $
%
%********************************************************
%* *
@@ -19,7 +19,6 @@ import {-# SOURCE #-} CgExpr ( cgExpr )
import StgSyn
import CgMonad
import AbsCSyn
-import CLabel ( CLabel )
import CgBindery ( letNoEscapeIdInfo, bindArgsToRegs,
bindNewToStack, buildContLivenessMask, CgIdInfo,
diff --git a/ghc/compiler/codeGen/CgMonad.lhs b/ghc/compiler/codeGen/CgMonad.lhs
index 484cc48870..8f68ad40cb 100644
--- a/ghc/compiler/codeGen/CgMonad.lhs
+++ b/ghc/compiler/codeGen/CgMonad.lhs
@@ -1,7 +1,7 @@
%
% (c) The GRASP/AQUA Project, Glasgow University, 1992-1998
%
-% $Id: CgMonad.lhs,v 1.23 1999/10/13 16:39:16 simonmar Exp $
+% $Id: CgMonad.lhs,v 1.24 2000/07/11 16:03:37 simonmar Exp $
%
\section[CgMonad]{The code generation monad}
@@ -54,7 +54,6 @@ import DataCon ( ConTag )
import Id ( Id )
import VarEnv
import PrimRep ( PrimRep(..) )
-import StgSyn ( StgLiveVars )
import Outputable
infixr 9 `thenC` -- Right-associative!
diff --git a/ghc/compiler/codeGen/CgRetConv.lhs b/ghc/compiler/codeGen/CgRetConv.lhs
index e292ea1d9f..3b6131254b 100644
--- a/ghc/compiler/codeGen/CgRetConv.lhs
+++ b/ghc/compiler/codeGen/CgRetConv.lhs
@@ -1,7 +1,7 @@
%
% (c) The GRASP Project, Glasgow University, 1992-1998
%
-% $Id: CgRetConv.lhs,v 1.22 2000/05/25 12:41:15 simonpj Exp $
+% $Id: CgRetConv.lhs,v 1.23 2000/07/11 16:03:37 simonmar Exp $
%
\section[CgRetConv]{Return conventions for the code generator}
@@ -27,11 +27,8 @@ import CmdLineOpts ( opt_UseVanillaRegs, opt_UseFloatRegs,
opt_UseDoubleRegs, opt_UseLongRegs
)
import Maybes ( catMaybes )
-import DataCon ( DataCon )
-import PrimOp ( PrimOp{-instance Outputable-} )
import PrimRep ( isFloatingRep, PrimRep(..), is64BitRep )
import TyCon ( TyCon, tyConFamilySize )
-import Type ( Type, typePrimRep, isUnLiftedType )
import Util ( isn'tIn )
import Outputable
diff --git a/ghc/compiler/codeGen/CgTailCall.lhs b/ghc/compiler/codeGen/CgTailCall.lhs
index 82c64a4c48..c1a6ec31d7 100644
--- a/ghc/compiler/codeGen/CgTailCall.lhs
+++ b/ghc/compiler/codeGen/CgTailCall.lhs
@@ -1,7 +1,7 @@
%
% (c) The GRASP/AQUA Project, Glasgow University, 1992-1998
%
-% $Id: CgTailCall.lhs,v 1.24 2000/03/23 17:45:19 simonpj Exp $
+% $Id: CgTailCall.lhs,v 1.25 2000/07/11 16:03:37 simonmar Exp $
%
%********************************************************
%* *
@@ -30,7 +30,7 @@ import CgMonad
import AbsCSyn
import PprAbsC ( pprAmode )
-import AbsCUtils ( mkAbstractCs, mkAbsCStmts, getAmodeRep )
+import AbsCUtils ( mkAbstractCs, getAmodeRep )
import CgBindery ( getArgAmodes, getCAddrMode, getCAddrModeAndInfo )
import CgRetConv ( dataReturnConvPrim,
ctrlReturnConvAlg, CtrlReturnConvention(..),
@@ -48,7 +48,6 @@ import ClosureInfo ( nodeMustPointToIt,
import CmdLineOpts ( opt_DoSemiTagging )
import Id ( Id, idType, idName )
import DataCon ( DataCon, dataConTyCon, dataConTag, fIRST_TAG )
-import Literal ( mkMachInt )
import Maybes ( assocMaybe, maybeToBool )
import PrimRep ( PrimRep(..) )
import StgSyn ( StgArg, GenStgArg(..) )
diff --git a/ghc/compiler/codeGen/CgUpdate.lhs b/ghc/compiler/codeGen/CgUpdate.lhs
index 82a08001c8..33883a09ab 100644
--- a/ghc/compiler/codeGen/CgUpdate.lhs
+++ b/ghc/compiler/codeGen/CgUpdate.lhs
@@ -11,10 +11,8 @@ module CgUpdate ( pushUpdateFrame, reserveSeqFrame, pushSeqFrame ) where
import CgMonad
import AbsCSyn
-import PrimRep ( PrimRep(..) )
import CgStackery ( allocStackTop, updateFrameSize, seqFrameSize )
import CgUsages ( getVirtSp, getSpRelOffset )
-import CmdLineOpts ( opt_SccProfilingOn )
import Panic ( assertPanic )
\end{code}
diff --git a/ghc/compiler/codeGen/CodeGen.lhs b/ghc/compiler/codeGen/CodeGen.lhs
index 584d48e9b2..80fd8f923d 100644
--- a/ghc/compiler/codeGen/CodeGen.lhs
+++ b/ghc/compiler/codeGen/CodeGen.lhs
@@ -25,7 +25,7 @@ import AbsCSyn
import CLabel ( CLabel, mkSRTLabel, mkClosureLabel, mkModuleInitLabel )
import PprAbsC ( dumpRealC )
-import AbsCUtils ( mkAbstractCs, mkAbsCStmts, flattenAbsC )
+import AbsCUtils ( mkAbstractCs, flattenAbsC )
import CgBindery ( CgIdInfo, addBindC, addBindsC )
import CgClosure ( cgTopRhsClosure )
import CgCon ( cgTopRhsCon )
@@ -35,10 +35,9 @@ import CmdLineOpts ( opt_SccProfilingOn, opt_EnsureSplittableC,
opt_D_dump_absC
)
import CostCentre ( CostCentre, CostCentreStack )
-import FiniteMap ( FiniteMap )
import Id ( Id, idName )
import Module ( Module, moduleString, moduleName,
- ModuleName, moduleNameString )
+ ModuleName )
import PrimRep ( getPrimRepSize, PrimRep(..) )
import Type ( Type )
import TyCon ( TyCon, isDataTyCon )