Skip to content
GitLab
Projects
Groups
Snippets
Help
Loading...
Help
Help
Support
Community forum
Keyboard shortcuts
?
Submit feedback
Sign in / Register
Toggle navigation
GHC
Project overview
Project overview
Details
Activity
Releases
Repository
Repository
Files
Commits
Branches
Tags
Contributors
Graph
Compare
Locked Files
Issues
0
Issues
0
List
Boards
Labels
Service Desk
Milestones
Iterations
Merge Requests
0
Merge Requests
0
Requirements
Requirements
List
CI / CD
CI / CD
Pipelines
Jobs
Schedules
Security & Compliance
Security & Compliance
Dependency List
License Compliance
Operations
Operations
Incidents
Environments
Packages & Registries
Packages & Registries
Package Registry
Container Registry
Analytics
Analytics
CI / CD
Code Review
Insights
Issue
Repository
Value Stream
Wiki
Wiki
Snippets
Snippets
Members
Members
Collapse sidebar
Close sidebar
Activity
Graph
Create a new issue
Jobs
Commits
Issue Boards
Open sidebar
Alex D
GHC
Commits
d436c70d
Commit
d436c70d
authored
Jul 06, 2009
by
simonpj@microsoft.com
Browse files
Options
Browse Files
Download
Email Patches
Plain Diff
Trim unused imports detected by new unused-import code
parent
0bde1150
Changes
53
Hide whitespace changes
Inline
Side-by-side
Showing
53 changed files
with
42 additions
and
105 deletions
+42
-105
compiler/basicTypes/DataCon.lhs
compiler/basicTypes/DataCon.lhs
+0
-1
compiler/basicTypes/Id.lhs
compiler/basicTypes/Id.lhs
+0
-1
compiler/basicTypes/OccName.lhs
compiler/basicTypes/OccName.lhs
+0
-2
compiler/basicTypes/UniqSupply.lhs
compiler/basicTypes/UniqSupply.lhs
+0
-1
compiler/cmm/CmmCvt.hs
compiler/cmm/CmmCvt.hs
+0
-1
compiler/cmm/CmmExpr.hs
compiler/cmm/CmmExpr.hs
+0
-3
compiler/cmm/CmmProcPointZ.hs
compiler/cmm/CmmProcPointZ.hs
+0
-1
compiler/cmm/CmmStackLayout.hs
compiler/cmm/CmmStackLayout.hs
+0
-1
compiler/cmm/StackColor.hs
compiler/cmm/StackColor.hs
+1
-1
compiler/cmm/ZipCfg.hs
compiler/cmm/ZipCfg.hs
+0
-1
compiler/cmm/ZipCfgCmmRep.hs
compiler/cmm/ZipCfgCmmRep.hs
+0
-2
compiler/codeGen/ClosureInfo.lhs
compiler/codeGen/ClosureInfo.lhs
+0
-1
compiler/coreSyn/CoreUtils.lhs
compiler/coreSyn/CoreUtils.lhs
+0
-2
compiler/deSugar/DsMeta.hs
compiler/deSugar/DsMeta.hs
+0
-8
compiler/ghci/ByteCodeGen.lhs
compiler/ghci/ByteCodeGen.lhs
+3
-3
compiler/ghci/Debugger.hs
compiler/ghci/Debugger.hs
+4
-4
compiler/ghci/LibFFI.hsc
compiler/ghci/LibFFI.hsc
+1
-1
compiler/ghci/ObjLink.lhs
compiler/ghci/ObjLink.lhs
+1
-1
compiler/ghci/RtClosureInspect.hs
compiler/ghci/RtClosureInspect.hs
+2
-3
compiler/iface/IfaceSyn.lhs
compiler/iface/IfaceSyn.lhs
+0
-3
compiler/main/Annotations.lhs
compiler/main/Annotations.lhs
+0
-1
compiler/main/BreakArray.hs
compiler/main/BreakArray.hs
+0
-1
compiler/main/DriverMkDepend.hs
compiler/main/DriverMkDepend.hs
+2
-2
compiler/main/DriverPipeline.hs
compiler/main/DriverPipeline.hs
+3
-3
compiler/main/GHC.hs
compiler/main/GHC.hs
+3
-3
compiler/main/HscMain.lhs
compiler/main/HscMain.lhs
+2
-2
compiler/main/InteractiveEval.hs
compiler/main/InteractiveEval.hs
+1
-1
compiler/main/Packages.lhs
compiler/main/Packages.lhs
+0
-2
compiler/nativeGen/RegAlloc/Linear/PPC/FreeRegs.hs
compiler/nativeGen/RegAlloc/Linear/PPC/FreeRegs.hs
+1
-1
compiler/nativeGen/RegAlloc/Linear/SPARC/FreeRegs.hs
compiler/nativeGen/RegAlloc/Linear/SPARC/FreeRegs.hs
+1
-1
compiler/nativeGen/SPARC/CodeGen.hs
compiler/nativeGen/SPARC/CodeGen.hs
+0
-1
compiler/nativeGen/X86/Regs.hs
compiler/nativeGen/X86/Regs.hs
+0
-1
compiler/prelude/TysPrim.lhs
compiler/prelude/TysPrim.lhs
+1
-2
compiler/prelude/TysWiredIn.lhs
compiler/prelude/TysWiredIn.lhs
+0
-2
compiler/typecheck/TcAnnotations.lhs
compiler/typecheck/TcAnnotations.lhs
+0
-2
compiler/typecheck/TcArrows.lhs
compiler/typecheck/TcArrows.lhs
+0
-1
compiler/typecheck/TcClassDcl.lhs
compiler/typecheck/TcClassDcl.lhs
+0
-3
compiler/typecheck/TcForeign.lhs
compiler/typecheck/TcForeign.lhs
+0
-1
compiler/typecheck/TcGenDeriv.lhs
compiler/typecheck/TcGenDeriv.lhs
+0
-3
compiler/typecheck/TcInstDcls.lhs
compiler/typecheck/TcInstDcls.lhs
+0
-1
compiler/typecheck/TcRnMonad.lhs
compiler/typecheck/TcRnMonad.lhs
+1
-0
compiler/typecheck/TcTyClsDecls.lhs
compiler/typecheck/TcTyClsDecls.lhs
+0
-3
compiler/typecheck/TcType.lhs
compiler/typecheck/TcType.lhs
+0
-2
compiler/types/Coercion.lhs
compiler/types/Coercion.lhs
+0
-2
compiler/types/TypeRep.lhs
compiler/types/TypeRep.lhs
+0
-1
compiler/utils/Binary.hs
compiler/utils/Binary.hs
+0
-4
compiler/utils/Encoding.hs
compiler/utils/Encoding.hs
+0
-1
compiler/utils/FastMutInt.lhs
compiler/utils/FastMutInt.lhs
+1
-1
compiler/utils/Outputable.lhs
compiler/utils/Outputable.lhs
+3
-3
compiler/utils/Util.lhs
compiler/utils/Util.lhs
+1
-2
ghc/GhciMonad.hs
ghc/GhciMonad.hs
+3
-3
ghc/InteractiveUI.hs
ghc/InteractiveUI.hs
+3
-4
ghc/Main.hs
ghc/Main.hs
+4
-4
No files found.
compiler/basicTypes/DataCon.lhs
View file @
d436c70d
...
...
@@ -51,7 +51,6 @@ import Outputable
import Unique
import ListSetOps
import Util
import Maybes
import FastString
import Module
...
...
compiler/basicTypes/Id.lhs
View file @
d436c70d
...
...
@@ -126,7 +126,6 @@ import Module
import Class
import PrimOp
import ForeignCall
import OccName
import Maybes
import SrcLoc
import Outputable
...
...
compiler/basicTypes/OccName.lhs
View file @
d436c70d
...
...
@@ -102,8 +102,6 @@ import FastString
import FastTypes
import Outputable
import Binary
import GHC.Exts
import Data.Char
\end{code}
...
...
compiler/basicTypes/UniqSupply.lhs
View file @
d436c70d
...
...
@@ -30,7 +30,6 @@ import FastTypes
import MonadUtils
import Control.Monad
import Control.Monad.Fix
#if __GLASGOW_HASKELL__ >= 611
import GHC.IO (unsafeDupableInterleaveIO)
#else
...
...
compiler/cmm/CmmCvt.hs
View file @
d436c70d
...
...
@@ -8,7 +8,6 @@ import BlockId
import
Cmm
import
CmmExpr
import
MkZipCfgCmm
hiding
(
CmmGraph
)
import
ZipCfg
-- imported for reverse conversion
import
ZipCfgCmmRep
-- imported for reverse conversion
import
CmmZipUtil
import
PprCmm
()
...
...
compiler/cmm/CmmExpr.hs
View file @
d436c70d
...
...
@@ -49,10 +49,7 @@ import CLabel
import
Constants
import
FastString
import
FiniteMap
import
Maybes
import
Monad
import
Outputable
import
Panic
import
Unique
import
UniqSet
...
...
compiler/cmm/CmmProcPointZ.hs
View file @
d436c70d
...
...
@@ -5,7 +5,6 @@ module CmmProcPointZ
)
where
import
qualified
Prelude
as
P
import
Prelude
hiding
(
zip
,
unzip
,
last
)
import
BlockId
...
...
compiler/cmm/CmmStackLayout.hs
View file @
d436c70d
...
...
@@ -5,7 +5,6 @@ module CmmStackLayout
where
import
Constants
import
qualified
Prelude
as
P
import
Prelude
hiding
(
zip
,
unzip
,
last
)
import
BlockId
...
...
compiler/cmm/StackColor.hs
View file @
d436c70d
...
...
@@ -16,7 +16,7 @@ import Maybes
import
Panic
import
UniqSet
import
Data.List
--
import Data.List
fold_edge_facts_b
::
LastNode
l
=>
(
DualLive
->
a
->
a
)
->
BackwardTransfers
m
l
DualLive
->
LGraph
m
l
...
...
compiler/cmm/ZipCfg.hs
View file @
d436c70d
...
...
@@ -44,7 +44,6 @@ import CmmExpr ( UserOfLocalRegs(..) )
import
PprCmm
()
import
Outputable
hiding
(
empty
)
import
Panic
import
Maybe
import
Prelude
hiding
(
zip
,
unzip
,
last
)
...
...
compiler/cmm/ZipCfgCmmRep.hs
View file @
d436c70d
...
...
@@ -29,7 +29,6 @@ import CmmTx
import
CLabel
import
FastString
import
ForeignCall
import
qualified
ZipCfg
as
Z
import
qualified
ZipDataflow
as
DF
import
ZipCfg
import
MkZipCfg
...
...
@@ -40,7 +39,6 @@ import Maybes
import
Monad
import
Outputable
import
Prelude
hiding
(
zip
,
unzip
,
last
)
import
qualified
Data.List
as
L
import
SMRep
(
ByteOff
)
import
UniqSupply
...
...
compiler/codeGen/ClosureInfo.lhs
View file @
d436c70d
...
...
@@ -72,7 +72,6 @@ import Id
import IdInfo
import DataCon
import Name
import OccName
import Type
import TypeRep
import TcType
...
...
compiler/coreSyn/CoreUtils.lhs
View file @
d436c70d
...
...
@@ -74,8 +74,6 @@ import Maybes
import Util
import Data.Word
import Data.Bits
import GHC.Exts -- For `xori`
\end{code}
...
...
compiler/deSugar/DsMeta.hs
View file @
d436c70d
...
...
@@ -13,14 +13,6 @@
-- a Royal Pain (triggers other recompilation).
-----------------------------------------------------------------------------
{-# OPTIONS -fno-warn-unused-imports #-}
-- The above warning supression flag is a temporary kludge.
-- While working on this module you are encouraged to remove it and fix
-- any warnings in the module. See
-- http://hackage.haskell.org/trac/ghc/wiki/Commentary/CodingStyle#Warnings
-- for details
-- The kludge is only needed in this module because of trac #2267.
module
DsMeta
(
dsBracket
,
templateHaskellNames
,
qTyConName
,
nameTyConName
,
liftName
,
liftStringName
,
expQTyConName
,
patQTyConName
,
decQTyConName
,
typeQTyConName
,
...
...
compiler/ghci/ByteCodeGen.lhs
View file @
d436c70d
...
...
@@ -31,9 +31,9 @@ import CoreFVs
import Type
import DataCon
import TyCon
import Type
--
import Type
import Util
import DataCon
--
import DataCon
import Var
import VarSet
import TysPrim
...
...
@@ -51,7 +51,7 @@ import Data.List
import Foreign
import Foreign.C
import GHC.Exts ( Int(..), ByteArray#
)
-- import GHC.Exts ( Int(..)
)
import Control.Monad ( when )
import Data.Char
...
...
compiler/ghci/Debugger.hs
View file @
d436c70d
...
...
@@ -20,18 +20,18 @@ import Id
import
Name
import
Var
hiding
(
varName
)
import
VarSet
import
Name
--
import Name
import
UniqSupply
import
TcType
import
GHC
import
DynFlags
--
import DynFlags
import
InteractiveEval
import
Outputable
import
SrcLoc
--
import SrcLoc
import
PprTyThing
import
MonadUtils
import
Exception
--
import Exception
import
Control.Monad
import
Data.List
import
Data.Maybe
...
...
compiler/ghci/LibFFI.hsc
View file @
d436c70d
...
...
@@ -16,7 +16,7 @@ module LibFFI (
import TyCon
import ForeignCall
import Panic
import Outputable
--
import Outputable
import Constants
import Foreign
...
...
compiler/ghci/ObjLink.lhs
View file @
d436c70d
...
...
@@ -28,7 +28,7 @@ import Config ( cLeadingUnderscore )
import Control.Monad ( when )
import Foreign.C
import Foreign ( nullPtr )
import GHC.Exts ( Ptr(..)
, unsafeCoerce#
)
import GHC.Exts ( Ptr(..) )
...
...
compiler/ghci/RtClosureInspect.hs
View file @
d436c70d
...
...
@@ -54,7 +54,7 @@ import TysWiredIn
import
DynFlags
import
Outputable
import
FastString
import
Panic
--
import Panic
import
Constants
(
wORD_SIZE
)
...
...
@@ -76,9 +76,8 @@ import qualified Data.Sequence as Seq
import
Data.Monoid
import
Data.Sequence
hiding
(
null
,
length
,
index
,
take
,
drop
,
splitAt
,
reverse
)
import
Foreign
import
System.IO.Unsafe
--
import System.IO.Unsafe
import
System.IO
---------------------------------------------
-- * A representation of semi evaluated Terms
---------------------------------------------
...
...
compiler/iface/IfaceSyn.lhs
View file @
d436c70d
...
...
@@ -41,9 +41,6 @@ import Outputable
import FastString
import Module
import Data.List
import Data.Maybe
infixl 3 &&&
\end{code}
...
...
compiler/main/Annotations.lhs
View file @
d436c70d
...
...
@@ -22,7 +22,6 @@ import LazyUniqFM
import Serialized
import Unique
import Control.Monad
import Data.Typeable
import Data.Maybe
import Data.Word ( Word8 )
...
...
compiler/main/BreakArray.hs
View file @
d436c70d
...
...
@@ -31,7 +31,6 @@ import GHC.IO ( IO(..) )
#
else
import
GHC.IOBase
(
IO
(
..
)
)
#
endif
import
GHC.Word
import
Constants
data
BreakArray
=
BA
(
MutableByteArray
#
RealWorld
)
...
...
compiler/main/DriverMkDepend.hs
View file @
d436c70d
...
...
@@ -16,7 +16,7 @@ module DriverMkDepend (
#
include
"HsVersions.h"
import
qualified
GHC
import
GHC
(
ModSummary
(
..
),
GhcMonad
)
--
import GHC ( ModSummary(..), GhcMonad )
import
HsSyn
(
ImportDecl
(
..
)
)
import
PrelNames
import
DynFlags
...
...
@@ -35,7 +35,7 @@ import FastString
import
Exception
import
ErrUtils
import
MonadUtils
(
liftIO
)
--
import MonadUtils ( liftIO )
import
System.Directory
import
System.FilePath
...
...
compiler/main/DriverPipeline.hs
View file @
d436c70d
...
...
@@ -48,12 +48,12 @@ import Maybes ( expectJust )
import
ParserCoreUtils
(
getCoreModuleName
)
import
SrcLoc
import
FastString
import
MonadUtils
--
import MonadUtils
import
Data.Either
--
import Data.Either
import
Exception
import
Data.IORef
(
readIORef
)
import
GHC.Exts
(
Int
(
..
)
)
--
import GHC.Exts ( Int(..) )
import
System.Directory
import
System.FilePath
import
System.IO
...
...
compiler/main/GHC.hs
View file @
d436c70d
...
...
@@ -265,10 +265,10 @@ import Var
import
TysPrim
(
alphaTyVars
)
import
TyCon
import
Class
import
FunDeps
--
import FunDeps
import
DataCon
import
Name
hiding
(
varName
)
import
OccName
(
parenSymOcc
)
--
import OccName ( parenSymOcc )
import
InstEnv
(
Instance
,
instanceDFunId
,
pprInstance
,
pprInstanceHdr
,
emptyInstEnv
)
import
FamInstEnv
(
emptyFamInstEnv
)
...
...
@@ -276,7 +276,7 @@ import SrcLoc
--import CoreSyn
import
TidyPgm
import
DriverPipeline
import
DriverPhases
(
HscSource
(
..
),
Phase
(
..
),
isHaskellSrcFilename
,
startPhase
)
import
DriverPhases
(
Phase
(
..
),
isHaskellSrcFilename
,
startPhase
)
import
HeaderInfo
import
Finder
import
HscMain
...
...
compiler/main/HscMain.lhs
View file @
d436c70d
...
...
@@ -112,10 +112,10 @@ import LazyUniqFM ( emptyUFM )
import UniqSupply ( initUs_ )
import Bag ( unitBag )
import Exception
import MonadUtils
--
import MonadUtils
import Control.Monad
import System.IO
--
import System.IO
import Data.IORef
\end{code}
#include "HsVersions.h"
...
...
compiler/main/InteractiveEval.hs
View file @
d436c70d
...
...
@@ -82,7 +82,7 @@ import Data.Array
import
Exception
import
Control.Concurrent
import
Data.List
(
sortBy
)
import
Foreign.StablePtr
--
import Foreign.StablePtr
import
System.IO
-- -----------------------------------------------------------------------------
...
...
compiler/main/Packages.lhs
View file @
d436c70d
...
...
@@ -51,8 +51,6 @@ import Outputable
import System.Environment ( getEnv )
import Distribution.InstalledPackageInfo hiding (depends)
import Distribution.Package hiding (depends, PackageId)
import Distribution.Text
import Distribution.Version
import FastString
import ErrUtils ( debugTraceMsg, putMsg, Message )
import Exception
...
...
compiler/nativeGen/RegAlloc/Linear/PPC/FreeRegs.hs
View file @
d436c70d
...
...
@@ -11,7 +11,7 @@ import Outputable
import
Data.Word
import
Data.Bits
import
Data.List
--
import Data.List
-- The PowerPC has 32 integer and 32 floating point registers.
-- This is 32bit PowerPC, so Word64 is inefficient - two Word32s are much
...
...
compiler/nativeGen/RegAlloc/Linear/SPARC/FreeRegs.hs
View file @
d436c70d
...
...
@@ -13,7 +13,7 @@ import FastBool
import
Data.Word
import
Data.Bits
import
Data.List
--
import Data.List
--------------------------------------------------------------------------------
...
...
compiler/nativeGen/SPARC/CodeGen.hs
View file @
d436c70d
...
...
@@ -42,7 +42,6 @@ import CLabel
-- The rest:
import
StaticFlags
(
opt_PIC
)
import
OrdList
import
qualified
Outputable
as
O
import
Outputable
import
Control.Monad
(
mapAndUnzipM
)
...
...
compiler/nativeGen/X86/Regs.hs
View file @
d436c70d
...
...
@@ -65,7 +65,6 @@ import Cmm
import
CLabel
(
CLabel
)
import
Pretty
import
Outputable
(
panic
)
import
qualified
Outputable
import
FastTypes
import
FastBool
...
...
compiler/prelude/TysPrim.lhs
View file @
d436c70d
...
...
@@ -49,8 +49,7 @@ module TysPrim(
import Var ( TyVar, mkTyVar )
import Name ( Name, BuiltInSyntax(..), mkInternalName, mkWiredInName )
import OccName ( mkTyVarOccFS, mkTcOccFS )
import TyCon ( TyCon, mkPrimTyCon, mkLiftedPrimTyCon,
PrimRep(..) )
import TyCon ( TyCon, mkPrimTyCon, mkLiftedPrimTyCon )
import Type
import SrcLoc
import Unique ( mkAlphaTyVarUnique, pprUnique )
...
...
compiler/prelude/TysWiredIn.lhs
View file @
d436c70d
...
...
@@ -69,8 +69,6 @@ import Constants ( mAX_TUPLE_SIZE )
import Module ( Module )
import RdrName
import Name
import OccName ( mkTcOccFS, mkDataOccFS, mkTupleOcc, mkDataConWorkerOcc,
tcName, dataName )
import DataCon ( DataCon, mkDataCon, dataConWorkId, dataConSourceArity )
import Var
import TyCon ( TyCon, AlgTyConRhs(DataTyCon), tyConDataCons,
...
...
compiler/typecheck/TcAnnotations.lhs
View file @
d436c70d
...
...
@@ -20,8 +20,6 @@ import TcExpr
import {-# SOURCE #-} TcSplice ( runAnnotation )
import FastString
#endif
import Control.Monad
\end{code}
\begin{code}
...
...
compiler/typecheck/TcArrows.lhs
View file @
d436c70d
...
...
@@ -27,7 +27,6 @@ import Name
import TysWiredIn
import VarSet
import TysPrim
import Type
import SrcLoc
import Outputable
...
...
compiler/typecheck/TcClassDcl.lhs
View file @
d436c70d
...
...
@@ -30,21 +30,18 @@ import TcRnMonad
import Generics
import Class
import TyCon
import Type
import MkId
import Id
import Name
import Var
import NameEnv
import NameSet
import OccName
import RdrName
import Outputable
import PrelNames
import DynFlags
import ErrUtils
import Util
import Unique
import ListSetOps
import SrcLoc
import Maybes
...
...
compiler/typecheck/TcForeign.lhs
View file @
d436c70d
...
...
@@ -35,7 +35,6 @@ import Type
import SMRep
#endif
import Name
import OccName
import TcType
import DynFlags
import Outputable
...
...
compiler/typecheck/TcGenDeriv.lhs
View file @
d436c70d
...
...
@@ -42,7 +42,6 @@ import Name
import HscTypes
import PrelInfo
import PrelNames
import MkId
import PrimOp
import SrcLoc
import TyCon
...
...
@@ -58,9 +57,7 @@ import Util
import MonadUtils
import Outputable
import FastString
import OccName
import Bag
import Data.List ( partition, intersperse )
\end{code}
...
...
compiler/typecheck/TcInstDcls.lhs
View file @
d436c70d
...
...
@@ -29,7 +29,6 @@ import TcSimplify
import Type
import Coercion
import TyCon
import TypeRep
import DataCon
import Class
import Var
...
...
compiler/typecheck/TcRnMonad.lhs
View file @
d436c70d
...
...
@@ -45,6 +45,7 @@ import Util
import System.IO
import Data.IORef
import qualified Data.Set as Set
import Control.Monad
\end{code}
...
...
compiler/typecheck/TcTyClsDecls.lhs
View file @
d436c70d
...
...
@@ -13,7 +13,6 @@ module TcTyClsDecls (
#include "HsVersions.h"
import HsSyn
import HsTypes
import HscTypes
import BuildTyCl
import TcUnify
...
...
@@ -36,7 +35,6 @@ import IdInfo
import Var
import VarSet
import Name
import OccName
import Outputable
import Maybes
import Monad
...
...
@@ -52,7 +50,6 @@ import BasicTypes
import Bag
import Data.List
import Control.Monad ( mplus )
\end{code}
...
...
compiler/typecheck/TcType.lhs
View file @
d436c70d
...
...
@@ -153,7 +153,6 @@ import DynFlags
import Name
import NameSet
import VarEnv
import OccName
import PrelNames
import TysWiredIn
import BasicTypes
...
...
@@ -163,7 +162,6 @@ import ListSetOps
import Outputable
import FastString
import Data.List
import Data.IORef
\end{code}
...
...
compiler/types/Coercion.lhs
View file @
d436c70d
...
...
@@ -63,10 +63,8 @@ import TyCon
import Class
import Var
import Name
import OccName
import PrelNames
import Util
import Unique
import BasicTypes
import Outputable
import FastString
...
...
compiler/types/TypeRep.lhs
View file @
d436c70d
...
...
@@ -53,7 +53,6 @@ import {-# SOURCE #-} DataCon( DataCon, dataConName )
-- friends:
import Var
import Name
import OccName
import BasicTypes
import TyCon
import Class
...
...
compiler/utils/Binary.hs
View file @
d436c70d
...
...
@@ -71,9 +71,6 @@ import BasicTypes
import
Foreign
import
Data.Array
import
Data.Bits
import
Data.Int
import
Data.Word
import
Data.IORef
import
Data.Char
(
ord
,
chr
)
import
Data.Typeable
...
...
@@ -84,7 +81,6 @@ import System.IO.Error ( mkIOError, eofErrorType )
import
GHC.Real
(
Ratio
(
..
)
)
import
GHC.Exts
import
GHC.Word
(
Word8
(
..
)
)
import
System.IO
(
openBinaryFile
)
#
if
__GLASGOW_HASKELL__
>=
611
import
GHC.IO
(
IO
(
..
)
)
...
...
compiler/utils/Encoding.hs
View file @
d436c70d
...
...
@@ -31,7 +31,6 @@ module Encoding (
import
Foreign
import
Data.Char
import
Numeric
import
Data.Bits
import
GHC.Ptr
(
Ptr
(
..
)
)
import
GHC.Base
...
...
compiler/utils/FastMutInt.lhs
View file @
d436c70d
...
...
@@ -28,7 +28,7 @@ import GHC.Base
import GHC.Ptr
#if __GLASGOW_HASKELL__ >= 611
import GHC.IO ( IO(..) )
--
import GHC.IO ( IO(..) )
#else
import GHC.IOBase ( IO(..) )
#endif
...
...
compiler/utils/Outputable.lhs
View file @
d436c70d
...
...
@@ -37,13 +37,13 @@ module Outputable (
printForC, printForAsm, printForUser, printForUserPartWay,
pprCode, mkCodeStyle,
showSDoc, showSDocOneLine,
showSDocForUser, showSDocDebug, showSDocDump, showSDocDumpOneLine,
showPpr,
showSDocForUser, showSDocDebug, showSDocDump, showSDocDumpOneLine,
showPpr,
showSDocUnqual, showsPrecSDoc,
pprInfixVar, pprPrefixVar,
pprHsChar, pprHsString, pprHsInfix, pprHsVar,
pprFastFilePath,
pprFastFilePath,
-- * Controlling the style in which output is printed
BindingSite(..),
...
...
compiler/utils/Util.lhs
View file @
d436c70d
...
...
@@ -84,9 +84,8 @@ import System.IO.Unsafe ( unsafePerformIO )
import Data.IORef ( readIORef, writeIORef )
import Data.List hiding (group)
import qualified Data.List as List ( elem )
#ifdef DEBUG
import qualified Data.List as List ( notElem )
import qualified Data.List as List (
elem,
notElem )
import FastTypes
#endif
...
...
ghc/GhciMonad.hs
View file @
d436c70d
...
...
@@ -30,13 +30,13 @@ import qualified MonadUtils
import
qualified
ErrUtils
import
Exception
import
Data.Maybe
--
import Data.Maybe
import
Numeric
import
Data.Array
import
Data.Char
--
import Data.Char
import
Data.Int
(
Int64
)
import
Data.IORef
import
Data.List
--
import Data.List
import
System.CPUTime
import
System.Environment
import
System.IO
...
...
ghc/InteractiveUI.hs
View file @
d436c70d
...
...
@@ -23,14 +23,14 @@ import Debugger
-- The GHC interface
import
qualified
GHC
hiding
(
resume
,
runStmt
)
import
GHC
(
LoadHowMuch
(
..
),
Target
(
..
),
TargetId
(
..
),
Module
,
ModuleName
,
TyThing
(
..
),
Phase
,
BreakIndex
,
SrcSpan
,
Resume
,
SingleStep
,
TyThing
(
..
),
Phase
,
BreakIndex
,
Resume
,
SingleStep
,
Ghc
,
handleSourceError
)
import
PprTyThing
import
DynFlags
import
Packages
import
PackageConfig
--
import PackageConfig
import
UniqFM
import
HscTypes
(
implicitTyThings
,
handleFlagWarnings
)
...
...
@@ -68,7 +68,6 @@ import Control.Monad.Trans
--import SystemExts
import
Exception
hiding
(
catch
,
block
,
unblock
)
import
qualified
Exception