[commit: ghc] wip/T13064: Improve ambiguous-occurrence error message (c599fb4)

git at git.haskell.org git at git.haskell.org
Mon Aug 20 09:07:59 UTC 2018


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

On branch  : wip/T13064
Link       : http://ghc.haskell.org/trac/ghc/changeset/c599fb49f255a0f382a61689f9478b65d5cd2edf/ghc

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

commit c599fb49f255a0f382a61689f9478b65d5cd2edf
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.


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

c599fb49f255a0f382a61689f9478b65d5cd2edf
 compiler/rename/RnUtils.hs                       | 40 +++++++++++++++++++-----
 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         |  1 +
 5 files changed, 49 insertions(+), 8 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/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 413b24f..2da8689 100644
--- a/testsuite/tests/rename/should_fail/all.T
+++ b/testsuite/tests/rename/should_fail/all.T
@@ -131,3 +131,4 @@ test('T13847', normal, multimod_compile_fail, ['T13847','-v0'])
 test('T14307', normal, compile_fail, [''])
 test('T14591', normal, compile_fail, [''])
 test('T15214', normal, compile_fail, [''])
+test('T15487', normal, multimod_compile_fail, ['T15487','-v0'])



More information about the ghc-commits mailing list