[commit: ghc] master: Second go at fixing #9061 (5b73dc5)

git at git.haskell.org git at git.haskell.org
Tue May 6 08:43:39 UTC 2014


Repository : ssh://git@git.haskell.org/ghc

On branch  : master
Link       : http://ghc.haskell.org/trac/ghc/changeset/5b73dc5fda1941d51827ea72614782c10a355a3d/ghc

>---------------------------------------------------------------

commit 5b73dc5fda1941d51827ea72614782c10a355a3d
Author: Simon Peyton Jones <simonpj at microsoft.com>
Date:   Tue May 6 08:20:28 2014 +0100

    Second go at fixing #9061
    
    My first attempt introduce a bug in -fprint-minimal-imports, but
    fortunately a regression test caught it.


>---------------------------------------------------------------

5b73dc5fda1941d51827ea72614782c10a355a3d
 compiler/rename/RnNames.lhs | 46 +++++++++++++++++++++++----------------------
 1 file changed, 24 insertions(+), 22 deletions(-)

diff --git a/compiler/rename/RnNames.lhs b/compiler/rename/RnNames.lhs
index 678eb73..5599764 100644
--- a/compiler/rename/RnNames.lhs
+++ b/compiler/rename/RnNames.lhs
@@ -1301,11 +1301,14 @@ type ImportDeclUsage
 warnUnusedImportDecls :: TcGblEnv -> RnM ()
 warnUnusedImportDecls gbl_env
   = do { uses <- readMutVar (tcg_used_rdrnames gbl_env)
-       ; let imports = filterOut un_warnable_import (tcg_rn_imports gbl_env)
+       ; let user_imports = filterOut (ideclImplicit . unLoc) (tcg_rn_imports gbl_env)
+                            -- This whole function deals only with *user* imports
+                            -- both for warning about unnecessary ones, and for
+                            -- deciding the minimal ones
              rdr_env = tcg_rdr_env gbl_env
 
        ; let usage :: [ImportDeclUsage]
-             usage = findImportUsage imports rdr_env (Set.elems uses)
+             usage = findImportUsage user_imports rdr_env (Set.elems uses)
 
        ; traceRn (vcat [ ptext (sLit "Uses:") <+> ppr (Set.elems uses)
                        , ptext (sLit "Import usage") <+> ppr usage])
@@ -1314,28 +1317,8 @@ warnUnusedImportDecls gbl_env
 
        ; whenGOptM Opt_D_dump_minimal_imports $
          printMinimalImports usage }
-  where
-    un_warnable_import (L _ decl)  -- See Note [Un-warnable import decls]
-       | ideclImplicit decl
-       = True
-       | Just (True, hides) <- ideclHiding decl
-       , not (null hides)
-       , pRELUDE_NAME == unLoc (ideclName decl)
-       = True
-       | otherwise
-       = False
 \end{code}
 
-Note [Un-warnable import decls]
-~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~
-We do not warn about the implicit import of Prelude, since the user can't remove it
-
-We do not warn about
-   import Prelude hiding( x, y )
-because even if nothing else from Prelude is used, it may be essential to hide
-x,y to avoid name-shadowing warnings.  Example (Trac #9061)
-   import Prelude hiding( log )
-   f x = log where log = ()
 
 Note [The ImportMap]
 ~~~~~~~~~~~~~~~~~~~~
@@ -1449,6 +1432,11 @@ warnUnusedImport :: ImportDeclUsage -> RnM ()
 warnUnusedImport (L loc decl, used, unused)
   | Just (False,[]) <- ideclHiding decl
                 = return ()            -- Do not warn for 'import M()'
+
+  | Just (True, hides) <- ideclHiding decl
+  , not (null hides)
+  , pRELUDE_NAME == unLoc (ideclName decl)
+                = return ()            -- Note [Do not warn about Prelude hiding]
   | null used   = addWarnAt loc msg1   -- Nothing used; drop entire decl
   | null unused = return ()            -- Everything imported is used; nop
   | otherwise   = addWarnAt loc msg2   -- Some imports are unused
@@ -1468,6 +1456,19 @@ warnUnusedImport (L loc decl, used, unused)
     pp_not_used = text "is redundant"
 \end{code}
 
+Note [Do not warn about Prelude hiding]
+~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~
+We do not warn about
+   import Prelude hiding( x, y )
+because even if nothing else from Prelude is used, it may be essential to hide
+x,y to avoid name-shadowing warnings.  Example (Trac #9061)
+   import Prelude hiding( log )
+   f x = log where log = ()
+
+
+
+Note [Printing minimal imports]
+~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~
 To print the minimal imports we walk over the user-supplied import
 decls, and simply trim their import lists.  NB that
 
@@ -1478,6 +1479,7 @@ decls, and simply trim their import lists.  NB that
 
 \begin{code}
 printMinimalImports :: [ImportDeclUsage] -> RnM ()
+-- See Note [Printing minimal imports]
 printMinimalImports imports_w_usage
   = do { imports' <- mapM mk_minimal imports_w_usage
        ; this_mod <- getModule



More information about the ghc-commits mailing list