[Git][ghc/ghc][wip/fabu/T25014-mistakenly-accepted-parent] Apply 1 suggestion(s) to 1 file(s)

Fabricio Nascimento (@fabu) gitlab at gitlab.haskell.org
Tue Sep 24 06:48:01 UTC 2024



Fabricio Nascimento pushed to branch wip/fabu/T25014-mistakenly-accepted-parent at Glasgow Haskell Compiler / GHC


Commits:
655f9b9f by Fabricio Nascimento at 2024-09-24T06:47:58+00:00
Apply 1 suggestion(s) to 1 file(s)

Co-authored-by: sheaf <sam.derbyshire at gmail.com>
- - - - -


1 changed file:

- compiler/GHC/Rename/Env.hs


Changes:

=====================================
compiler/GHC/Rename/Env.hs
=====================================
@@ -720,6 +720,39 @@ Test cases:
   - T11970 (both cases)
   - T25014{a,b,c,d,e,f,g,h} (export lists)
   - T23664, T24452{a,b,c,d,e,f} (class instances)
+
+As for reporting an error when renaming fails, we can do better than a simple
+"Not in scope" error. For example:
+
+  (1)
+
+  module IncorrectParent (A (b)) where
+    data A = A { a :: () }
+    data B = B { b :: () }
+
+  Instead of
+    Not in scope: ‘b’
+  we prefer to emit
+    The type constructor ‘A’ is not the parent of the record selector ‘b’
+
+  (2)
+
+  {-# LANGUAGE DuplicateRecordFields #-}
+  module IncorrectParent (A (other)) where
+    data A = A { one :: ()   }
+    data B = B { other :: () }
+    data C = C { other :: () }
+
+   Instead of:
+     Ambiguous occurrence ‘other’.
+        It could refer to
+           either the field ‘other’ of record ‘B’ ...
+               or the field ‘other’ of record ‘C’ ...
+   we also prefer
+     The type constructor ‘A’ is not the parent of the record selector ‘other’ (...)
+
+The work of figuring out which error message to emit is done in
+error_no_occurrence_after_disambiguation.
 -}
 lookupInstanceDeclarationSubBndr :: DeprecationWarnings
                  -> Name     -- ^ Parent



View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/655f9b9f89dd51939816eda3bae36c8bf6edb660

-- 
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/655f9b9f89dd51939816eda3bae36c8bf6edb660
You're receiving this email because of your account on gitlab.haskell.org.


-------------- next part --------------
An HTML attachment was scrubbed...
URL: <http://mail.haskell.org/pipermail/ghc-commits/attachments/20240924/afd25e62/attachment-0001.html>


More information about the ghc-commits mailing list