[commit: ghc] master: Improve ambiguous-occurrence error message (18c302c)

git at git.haskell.org git at git.haskell.org
Tue Aug 21 16:12:19 UTC 2018


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

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

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

commit 18c302cb3802e485e0837538d7d09e1ac21c3ee2
Author: Simon Peyton Jones <simonpj at microsoft.com>
Date:   Mon Aug 20 10:01:16 2018 +0100

    Improve ambiguous-occurrence error message
    
    Trac #15487 correctly reported that the qualification
    of a Name in an ambiguous-occurrence error message was
    wrong.  This patch fixes it.
    
    It's easily done, in RnUtils.addNameClashErrRn
    
    The problem was that in complaining about M.x we must
    enusre that 'M' part is the same as that used in
    pprNameProvenance.


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

18c302cb3802e485e0837538d7d09e1ac21c3ee2
 compiler/rename/RnUtils.hs                         | 40 +++++++++++++++++-----
 .../ghci/duplicaterecfldsghci01.stdout             | 18 +++++-----
 testsuite/tests/rename/should_fail/T15487.hs       |  7 ++++
 testsuite/tests/rename/should_fail/T15487.stderr   |  8 +++++
 testsuite/tests/rename/should_fail/T15487a.hs      |  1 +
 testsuite/tests/rename/should_fail/all.T           |  2 ++
 .../tests/rename/should_fail/rnfail044.stderr      |  9 ++---
 7 files changed, 64 insertions(+), 21 deletions(-)

diff --git a/compiler/rename/RnUtils.hs b/compiler/rename/RnUtils.hs
index 99272c2..0451e28 100644
--- a/compiler/rename/RnUtils.hs
+++ b/compiler/rename/RnUtils.hs
@@ -295,16 +295,40 @@ addNameClashErrRn rdr_name gres
                -- If there are two or more *local* defns, we'll have reported
   = return ()  -- that already, and we don't want an error cascade
   | otherwise
-  = addErr (vcat [text "Ambiguous occurrence" <+> quotes (ppr rdr_name),
-                  text "It could refer to" <+> vcat (msg1 : msgs)])
+  = addErr (vcat [ text "Ambiguous occurrence" <+> quotes (ppr rdr_name)
+                 , text "It could refer to"
+                 , nest 3 (vcat (msg1 : msgs)) ])
   where
     (np1:nps) = gres
-    msg1 = ptext  (sLit "either") <+> mk_ref np1
-    msgs = [text "    or" <+> mk_ref np | np <- nps]
-    mk_ref gre = sep [nom <> comma, pprNameProvenance gre]
-      where nom = case gre_par gre of
-                    FldParent { par_lbl = Just lbl } -> text "the field" <+> quotes (ppr lbl)
-                    _                                -> quotes (ppr (gre_name gre))
+    msg1 =  text "either" <+> ppr_gre np1
+    msgs = [text "    or" <+> ppr_gre np | np <- nps]
+    ppr_gre gre = sep [ pp_gre_name gre <> comma
+                      , pprNameProvenance gre]
+
+    -- When printing the name, take care to qualify it in the same
+    -- way as the provenance reported by pprNameProvenance, namely
+    -- the head of 'gre_imp'.  Otherwise we get confusing reports like
+    --   Ambiguous occurrence ‘null’
+    --   It could refer to either ‘T15487a.null’,
+    --                            imported from ‘Prelude’ at T15487.hs:1:8-13
+    --                     or ...
+    -- See Trac #15487
+    pp_gre_name gre@(GRE { gre_name = name, gre_par = parent
+                         , gre_lcl = lcl, gre_imp = iss })
+      | FldParent { par_lbl = Just lbl } <- parent
+      = text "the field" <+> quotes (ppr lbl)
+      | otherwise
+      = quotes (pp_qual <> dot <> ppr (nameOccName name))
+      where
+        pp_qual | lcl
+                = ppr (nameModule name)
+                | imp : _ <- iss  -- This 'imp' is the one that
+                                  -- pprNameProvenance chooses
+                , ImpDeclSpec { is_as = mod } <- is_decl imp
+                = ppr mod
+                | otherwise
+                = pprPanic "addNameClassErrRn" (ppr gre $$ ppr iss)
+                  -- Invariant: either 'lcl' is True or 'iss' is non-empty
 
 shadowedNameWarn :: OccName -> [SDoc] -> SDoc
 shadowedNameWarn occ shadowed_locs
diff --git a/testsuite/tests/overloadedrecflds/ghci/duplicaterecfldsghci01.stdout b/testsuite/tests/overloadedrecflds/ghci/duplicaterecfldsghci01.stdout
index 3270089..cfed45f 100644
--- a/testsuite/tests/overloadedrecflds/ghci/duplicaterecfldsghci01.stdout
+++ b/testsuite/tests/overloadedrecflds/ghci/duplicaterecfldsghci01.stdout
@@ -6,21 +6,21 @@ data T a = MkT {Ghci2.foo :: Bool, ...}
 
 <interactive>:1:1: error:
     Ambiguous occurrence ‘foo’
-    It could refer to either the field ‘foo’,
-                             defined at <interactive>:3:16
-                          or the field ‘foo’, defined at <interactive>:4:18
+    It could refer to
+       either the field ‘foo’, defined at <interactive>:3:16
+           or the field ‘foo’, defined at <interactive>:4:18
 
 <interactive>:9:1: error:
     Ambiguous occurrence ‘foo’
-    It could refer to either the field ‘foo’,
-                             defined at <interactive>:3:16
-                          or the field ‘foo’, defined at <interactive>:4:18
+    It could refer to
+       either the field ‘foo’, defined at <interactive>:3:16
+           or the field ‘foo’, defined at <interactive>:4:18
 True
 
 <interactive>:1:1: error:
     Ambiguous occurrence ‘foo’
-    It could refer to either the field ‘foo’,
-                             defined at <interactive>:3:16
-                          or the field ‘foo’, defined at <interactive>:4:18
+    It could refer to
+       either the field ‘foo’, defined at <interactive>:3:16
+           or the field ‘foo’, defined at <interactive>:4:18
 foo :: U -> Int
 42
diff --git a/testsuite/tests/rename/should_fail/T15487.hs b/testsuite/tests/rename/should_fail/T15487.hs
new file mode 100644
index 0000000..62e69e3
--- /dev/null
+++ b/testsuite/tests/rename/should_fail/T15487.hs
@@ -0,0 +1,7 @@
+module T15487 where
+
+import qualified T15487a
+
+null = 42
+
+foo x = null
diff --git a/testsuite/tests/rename/should_fail/T15487.stderr b/testsuite/tests/rename/should_fail/T15487.stderr
new file mode 100644
index 0000000..bb25939
--- /dev/null
+++ b/testsuite/tests/rename/should_fail/T15487.stderr
@@ -0,0 +1,8 @@
+
+T15487.hs:7:9: error:
+    Ambiguous occurrence ‘null’
+    It could refer to
+       either ‘Prelude.null’,
+              imported from ‘Prelude’ at T15487.hs:1:8-13
+              (and originally defined in ‘Data.Foldable’)
+           or ‘T15487.null’, defined at T15487.hs:5:1
diff --git a/testsuite/tests/rename/should_fail/T15487a.hs b/testsuite/tests/rename/should_fail/T15487a.hs
new file mode 100644
index 0000000..e8687ee
--- /dev/null
+++ b/testsuite/tests/rename/should_fail/T15487a.hs
@@ -0,0 +1 @@
+module T15487a (null) where
diff --git a/testsuite/tests/rename/should_fail/all.T b/testsuite/tests/rename/should_fail/all.T
index 2eef29f..c69efb9 100644
--- a/testsuite/tests/rename/should_fail/all.T
+++ b/testsuite/tests/rename/should_fail/all.T
@@ -133,3 +133,5 @@ test('T14307', normal, compile_fail, [''])
 test('T14591', normal, compile_fail, [''])
 test('T15214', normal, compile_fail, [''])
 test('T15539', normal, compile_fail, [''])
+test('T15487', normal, multimod_compile_fail, ['T15487','-v0'])
+
diff --git a/testsuite/tests/rename/should_fail/rnfail044.stderr b/testsuite/tests/rename/should_fail/rnfail044.stderr
index 6dcf2ca..39f7b77 100644
--- a/testsuite/tests/rename/should_fail/rnfail044.stderr
+++ b/testsuite/tests/rename/should_fail/rnfail044.stderr
@@ -1,7 +1,8 @@
 
 rnfail044.hs:5:12: error:
     Ambiguous occurrence ‘splitAt’
-    It could refer to either ‘Data.List.splitAt’,
-                             imported from ‘Prelude’ at rnfail044.hs:5:8
-                             (and originally defined in ‘GHC.List’)
-                          or ‘A.splitAt’, defined at rnfail044.hs:8:3
+    It could refer to
+       either ‘Prelude.splitAt’,
+              imported from ‘Prelude’ at rnfail044.hs:5:8
+              (and originally defined in ‘GHC.List’)
+           or ‘A.splitAt’, defined at rnfail044.hs:8:3



More information about the ghc-commits mailing list