summaryrefslogtreecommitdiff
path: root/ghc/compiler
diff options
context:
space:
mode:
authorsof <unknown>2003-09-23 16:52:45 +0000
committersof <unknown>2003-09-23 16:52:45 +0000
commitb23e6e00a3f4d02e6095b2033fa0dc97e4176c59 (patch)
tree524e335e6dbe12a06e4b22af15f68f18fb700c5d /ghc/compiler
parent9c9c4ea91664b802dff3b580f21ea1f3c3ccb369 (diff)
downloadhaskell-b23e6e00a3f4d02e6095b2033fa0dc97e4176c59.tar.gz
[project @ 2003-09-23 16:52:44 by sof]
If the user explicitly did an instances-only import, i.e., "import Foo ()", don't emit an unused-import warning.
Diffstat (limited to 'ghc/compiler')
-rw-r--r--ghc/compiler/main/MkIface.lhs4
-rw-r--r--ghc/compiler/rename/RnNames.lhs18
-rw-r--r--ghc/compiler/typecheck/TcRnTypes.lhs12
3 files changed, 24 insertions, 10 deletions
diff --git a/ghc/compiler/main/MkIface.lhs b/ghc/compiler/main/MkIface.lhs
index 0172930b07..9f31e7019b 100644
--- a/ghc/compiler/main/MkIface.lhs
+++ b/ghc/compiler/main/MkIface.lhs
@@ -519,8 +519,8 @@ mkUsageInfo hsc_env eps
pit = eps_PIT eps
import_all mod = case lookupModuleEnv dir_imp_mods mod of
- Just (_,imp_all) -> imp_all
- Nothing -> False
+ Just (_, Nothing) -> True
+ _ -> False
-- ent_map groups together all the things imported and used
-- from a particular module in this package
diff --git a/ghc/compiler/rename/RnNames.lhs b/ghc/compiler/rename/RnNames.lhs
index 9197fd978d..d1a4f016df 100644
--- a/ghc/compiler/rename/RnNames.lhs
+++ b/ghc/compiler/rename/RnNames.lhs
@@ -193,9 +193,10 @@ importsFromImportDecl this_mod
not_self (m, _) = m /= this_mod_name
import_all = case imp_spec of
- (Just (False, _)) -> False -- Imports are spec'd explicitly
- other -> True -- Everything is imported,
- -- (or almost everything [hiding])
+ Just (isHid, ls) -- Imports are spec'd explicitly
+ | not isHid -> Just (not (null ls))
+ _ -> Nothing -- Everything is imported,
+ -- (or almost everything [hiding])
qual_mod_name = case as_mod of
Nothing -> imp_mod_name
@@ -788,14 +789,21 @@ reportUnusedNames gbl_env dus
direct_import_mods = map (moduleName . fst)
(moduleEnvElts (imp_mods imports))
+ hasEmptyImpList :: ModuleName -> Bool
+ hasEmptyImpList m =
+ case lookupModuleEnvByName (imp_mods imports) m of
+ Just (_,Just x) -> not x
+ _ -> False
+
-- unused_imp_mods are the directly-imported modules
-- that are not mentioned in minimal_imports1
-- [Note: not 'minimal_imports', because that includes direcly-imported
-- modules even if we use nothing from them; see notes above]
unused_imp_mods = [m | m <- direct_import_mods,
isNothing (lookupFM minimal_imports1 m),
- m /= pRELUDE_Name]
-
+ m /= pRELUDE_Name,
+ not (hasEmptyImpList m)]
+
module_unused :: Module -> Bool
module_unused mod = moduleName mod `elem` unused_imp_mods
diff --git a/ghc/compiler/typecheck/TcRnTypes.lhs b/ghc/compiler/typecheck/TcRnTypes.lhs
index 1408eda7e6..47a9ed8a58 100644
--- a/ghc/compiler/typecheck/TcRnTypes.lhs
+++ b/ghc/compiler/typecheck/TcRnTypes.lhs
@@ -595,10 +595,16 @@ data ImportAvails
-- combine stuff coming from different (unqualified)
-- imports of the same module
- imp_mods :: ModuleEnv (Module, Bool),
+ imp_mods :: ModuleEnv (Module, Maybe Bool),
-- Domain is all directly-imported modules
- -- Bool is True if there was an unrestricted import
- -- (i.e. not a selective list)
+ -- Maybe value answers the question "is the import restricted?"
+ -- Nothing => unrestricted import (e.g., "import Foo")
+ -- Just True => restricted import, at least one entity (e.g., "import Foo(x)")
+ -- Just False => fully restricted import (e.g., "import Foo ()")
+ --
+ -- A distinction is made between the first and the third in order
+ -- to more precisely emit warnings about unused imports.
+ --
-- We need the Module in the range because we can't get
-- the keys of a ModuleEnv
-- Used