summaryrefslogtreecommitdiff
path: root/ghc/compiler/main/GHC.hs
diff options
context:
space:
mode:
authorsimonpj <unknown>2005-05-19 11:15:44 +0000
committersimonpj <unknown>2005-05-19 11:15:44 +0000
commit4a5870490196e05c40a9362ac2fef0081567bffc (patch)
treecc37e04dc4452a45bf2c947f2c1fbf1afad4f42e /ghc/compiler/main/GHC.hs
parentf01b31dd2e962b5d2ffcad547b3c781d41ec186b (diff)
downloadhaskell-4a5870490196e05c40a9362ac2fef0081567bffc.tar.gz
[project @ 2005-05-19 11:15:40 by simonpj]
Tune up the reporting of unused imports Merge to STABLE (I think the earlier change made it across) (PS: the commit also does some trimming of redundant imports. If they don't merge, just discard them.) My earlier fixes to the reporting of unused imports still missed some obscure cases, some of which are now fixed by this commit. I had to make the import-provenance data type yet richer, but in fact it has more sharing now, so it may be cheaper on space. There's still one infelicity. Consider import M( x ) imoprt N( x ) where the same underlying 'x' is involved in both cases. Currently we don't report a redundant import, because dropping either import would change the qualified names in scope (M.x, N.x). But if the qualified names aren't used, the import is indeed redundant. Sadly we don't know that, because we only know what Names are used. Left for the future! There's a comment in RnNames.warnDuplicateImports This commit also trims quite a few redundant imports disovered by the new setup.
Diffstat (limited to 'ghc/compiler/main/GHC.hs')
-rw-r--r--ghc/compiler/main/GHC.hs25
1 files changed, 12 insertions, 13 deletions
diff --git a/ghc/compiler/main/GHC.hs b/ghc/compiler/main/GHC.hs
index 36558f4e3c..43f271d459 100644
--- a/ghc/compiler/main/GHC.hs
+++ b/ghc/compiler/main/GHC.hs
@@ -138,10 +138,10 @@ module GHC (
#ifdef GHCI
import qualified Linker
import Linker ( HValue, extendLinkEnv )
-import NameEnv ( lookupNameEnv )
import TcRnDriver ( getModuleContents, tcRnLookupRdrName,
getModuleExports )
-import RdrName ( plusGlobalRdrEnv, Provenance(..), ImportSpec(..),
+import RdrName ( plusGlobalRdrEnv, Provenance(..),
+ ImportSpec(..), ImpDeclSpec(..), ImpItemSpec(..),
emptyGlobalRdrEnv, mkGlobalRdrEnv )
import HscMain ( hscGetInfo, GetInfoResult, hscParseIdentifier,
hscStmt, hscTcExpr, hscKcType )
@@ -149,14 +149,12 @@ import Type ( tidyType )
import VarEnv ( emptyTidyEnv )
import GHC.Exts ( unsafeCoerce# )
import IfaceSyn ( IfaceDecl )
-import Name ( getName, nameModule_maybe )
-import SrcLoc ( mkSrcLoc, srcLocSpan, interactiveSrcLoc )
-import Bag ( unitBag, emptyBag )
+import SrcLoc ( srcLocSpan, interactiveSrcLoc )
#endif
import Packages ( initPackages )
import NameSet ( NameSet, nameSetToList, elemNameSet )
-import RdrName ( GlobalRdrEnv, GlobalRdrElt(..), RdrName, gre_name,
+import RdrName ( GlobalRdrEnv, GlobalRdrElt(..), RdrName,
globalRdrEnvElts )
import HsSyn
import Type ( Kind, Type, dropForAlls )
@@ -194,16 +192,15 @@ import StringBuffer ( StringBuffer, hGetStringBuffer )
import Outputable
import SysTools ( cleanTempFilesExcept )
import BasicTypes ( SuccessFlag(..), succeeded, failed )
-import Maybes ( orElse, expectJust, mapCatMaybes )
import TcType ( tcSplitSigmaTy, isDictTy )
import FastString ( mkFastString )
import Directory ( getModificationTime, doesFileExist )
-import Maybe ( isJust, isNothing, fromJust, fromMaybe, catMaybes )
-import Maybes ( expectJust )
+import Maybe ( isJust, isNothing, fromJust )
+import Maybes ( orElse, expectJust, mapCatMaybes )
import List ( partition, nub )
import qualified List
-import Monad ( unless, when, foldM )
+import Monad ( unless, when )
import System ( exitWith, ExitCode(..) )
import Time ( ClockTime )
import EXCEPTION as Exception hiding (handle)
@@ -1745,9 +1742,11 @@ nameSetToGlobalRdrEnv names mod =
vanillaProv :: Module -> Provenance
-- We're building a GlobalRdrEnv as if the user imported
-- all the specified modules into the global interactive module
-vanillaProv mod = Imported [ImportSpec { is_mod = mod, is_as = mod,
- is_qual = False, is_explicit = False,
- is_loc = srcLocSpan interactiveSrcLoc }]
+vanillaProv mod = Imported [ImpSpec { is_decl = decl, is_item = ImpAll}]
+ where
+ decl = ImpDeclSpec { is_mod = mod, is_as = mod,
+ is_qual = False,
+ is_dloc = srcLocSpan interactiveSrcLoc }
checkModuleExists :: HscEnv -> HomePackageTable -> Module -> IO ()
checkModuleExists hsc_env hpt mod =