Skip to content
GitLab
Menu
Projects
Groups
Snippets
Help
Help
Support
Community forum
Keyboard shortcuts
?
Submit feedback
Sign in / Register
Toggle navigation
Menu
Open sidebar
Glasgow Haskell Compiler
GHC
Commits
d436c70d
Commit
d436c70d
authored
Jul 06, 2009
by
simonpj@microsoft.com
Browse files
Trim unused imports detected by new unused-import code
parent
0bde1150
Changes
53
Hide whitespace changes
Inline
Side-by-side
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}
...
...
Prev
1
2
3
Next
Write
Preview
Supports
Markdown
0%
Try again
or
attach a new file
.
Attach a file
Cancel
You are about to add
0
people
to the discussion. Proceed with caution.
Finish editing this message first!
Cancel
Please
register
or
sign in
to comment