[commit: ghc] master: Improve the warning message of qualified unused imports. (fad822e)

git at git.haskell.org git at git.haskell.org
Mon Mar 19 16:38:15 UTC 2018


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

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

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

commit fad822e2a5aa4373c3aa64e913e51fd5509c3f67
Author: HE, Tao <sighingnow at gmail.com>
Date:   Mon Mar 19 11:58:26 2018 -0400

    Improve the warning message of qualified unused imports.
    
    Pretty-print unused imported names unqualified unconditionally to
    make the warning message consistent for ambiguous/unambiguous
    identifiers.
    
    Signed-off-by: HE, Tao <sighingnow at gmail.com>
    
    Test Plan: make test TEST="T14881"
    
    Reviewers: bgamari, simonpj
    
    Reviewed By: simonpj
    
    Subscribers: simonpj, rwbarton, thomie, carter
    
    GHC Trac Issues: #14881
    
    Differential Revision: https://phabricator.haskell.org/D4461


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

fad822e2a5aa4373c3aa64e913e51fd5509c3f67
 compiler/basicTypes/Name.hs                         |  6 +++++-
 compiler/rename/RnNames.hs                          |  7 +++++--
 testsuite/tests/rename/should_compile/T14881.hs     |  5 +++++
 testsuite/tests/rename/should_compile/T14881.stderr |  6 ++++++
 testsuite/tests/rename/should_compile/T14881Aux.hs  | 13 +++++++++++++
 testsuite/tests/rename/should_compile/all.T         |  1 +
 6 files changed, 35 insertions(+), 3 deletions(-)

diff --git a/compiler/basicTypes/Name.hs b/compiler/basicTypes/Name.hs
index 02eb067..6941dd9 100644
--- a/compiler/basicTypes/Name.hs
+++ b/compiler/basicTypes/Name.hs
@@ -70,7 +70,7 @@ module Name (
         NamedThing(..),
         getSrcLoc, getSrcSpan, getOccString, getOccFS,
 
-        pprInfixName, pprPrefixName, pprModulePrefix,
+        pprInfixName, pprPrefixName, pprModulePrefix, pprNameUnqualified,
         nameStableString,
 
         -- Re-export the OccName stuff
@@ -535,6 +535,10 @@ pprName (Name {n_sort = sort, n_uniq = uniq, n_occ = occ})
       System                  -> pprSystem sty uniq occ
       Internal                -> pprInternal sty uniq occ
 
+-- | Print the string of Name unqualifiedly directly.
+pprNameUnqualified :: Name -> SDoc
+pprNameUnqualified Name { n_occ = occ } = ppr_occ_name occ
+
 pprExternal :: PprStyle -> Unique -> Module -> OccName -> Bool -> BuiltInSyntax -> SDoc
 pprExternal sty uniq mod occ is_wired is_builtin
   | codeStyle sty = ppr mod <> char '_' <> ppr_z_occ_name occ
diff --git a/compiler/rename/RnNames.hs b/compiler/rename/RnNames.hs
index 769b34e..af00056 100644
--- a/compiler/rename/RnNames.hs
+++ b/compiler/rename/RnNames.hs
@@ -1401,9 +1401,12 @@ warnUnusedImport flag fld_env (L loc decl, used, unused)
     pp_mod      = ppr (unLoc (ideclName decl))
     pp_not_used = text "is redundant"
 
+    -- In warning message, pretty-print identifiers unqualified unconditionally
+    -- to improve the consistent for ambiguous/unambiguous identifiers.
+    -- See trac#14881.
     ppr_possible_field n = case lookupNameEnv fld_env n of
-                               Just (fld, p) -> ppr p <> parens (ppr fld)
-                               Nothing  -> ppr n
+                               Just (fld, p) -> pprNameUnqualified p <> parens (ppr fld)
+                               Nothing  -> pprNameUnqualified n
 
     -- Print unused names in a deterministic (lexicographic) order
     sort_unused = pprWithCommas ppr_possible_field $
diff --git a/testsuite/tests/rename/should_compile/T14881.hs b/testsuite/tests/rename/should_compile/T14881.hs
new file mode 100644
index 0000000..c1b955c
--- /dev/null
+++ b/testsuite/tests/rename/should_compile/T14881.hs
@@ -0,0 +1,5 @@
+module T14881 where
+
+import qualified T14881Aux as Aux (L(Cons), x, tail, adjust, length)
+
+x = Aux.Cons
diff --git a/testsuite/tests/rename/should_compile/T14881.stderr b/testsuite/tests/rename/should_compile/T14881.stderr
new file mode 100644
index 0000000..bfb6ca9
--- /dev/null
+++ b/testsuite/tests/rename/should_compile/T14881.stderr
@@ -0,0 +1,6 @@
+[1 of 2] Compiling T14881Aux        ( T14881Aux.hs, T14881Aux.o )
+[2 of 2] Compiling T14881           ( T14881.hs, T14881.o )
+
+T14881.hs:3:1: warning: [-Wunused-imports (in -Wextra)]
+    The qualified import of ‘adjust, length, L(tail), L(x)’
+    from module ‘T14881Aux’ is redundant
diff --git a/testsuite/tests/rename/should_compile/T14881Aux.hs b/testsuite/tests/rename/should_compile/T14881Aux.hs
new file mode 100644
index 0000000..13b8f31
--- /dev/null
+++ b/testsuite/tests/rename/should_compile/T14881Aux.hs
@@ -0,0 +1,13 @@
+module T14881Aux where
+
+-- unambiguous function name.
+adjust :: ()
+adjust = undefined
+
+-- ambiguous function name.
+length :: ()
+length = undefined
+
+data L = Cons { x :: Int      -- unambiguous field selector
+              , tail :: [Int] -- ambiguous field selector
+              }
diff --git a/testsuite/tests/rename/should_compile/all.T b/testsuite/tests/rename/should_compile/all.T
index 4eb584f..80bcb09 100644
--- a/testsuite/tests/rename/should_compile/all.T
+++ b/testsuite/tests/rename/should_compile/all.T
@@ -153,3 +153,4 @@ test('T12548', normal, compile, [''])
 test('T13132', normal, compile, [''])
 test('T13646', normal, compile, [''])
 test('LookupSub', [], multimod_compile, ['LookupSub', '-v0'])
+test('T14881', [], multimod_compile, ['T14881', '-W'])



More information about the ghc-commits mailing list