[Git][ghc/ghc][wip/fabu/T24452-confusing-error] wip
Fabricio Nascimento (@fabu)
gitlab at gitlab.haskell.org
Wed Jun 19 11:47:01 UTC 2024
Fabricio Nascimento pushed to branch wip/fabu/T24452-confusing-error at Glasgow Haskell Compiler / GHC
Commits:
3850605a by Fabricio de Sousa Nascimento at 2024-06-19T20:46:51+09:00
wip
- - - - -
9 changed files:
- compiler/GHC/Rename/Env.hs
- + testsuite/tests/rename/T24452/T24452a.hs
- + testsuite/tests/rename/T24452/T24452b.hs
- + testsuite/tests/rename/T24452/T24452b.stderr
- + testsuite/tests/rename/T24452/T24452c.hs
- + testsuite/tests/rename/T24452/T24452c.stderr
- + testsuite/tests/rename/T24452/T24452d.hs
- + testsuite/tests/rename/T24452/T24452d.stderr
- + testsuite/tests/rename/T24452/all.T
Changes:
=====================================
compiler/GHC/Rename/Env.hs
=====================================
@@ -1,4 +1,5 @@
{-# LANGUAGE FlexibleContexts #-}
+
{-# LANGUAGE GADTs #-}
{-# LANGUAGE MultiWayIf #-}
{-# LANGUAGE TypeApplications #-}
@@ -709,7 +710,9 @@ lookupSubBndrOcc_helper must_have_parent warn_if_deprec parent rdr_name how_lkup
DisambiguatedOccurrence g ->
checkFld g
AmbiguousOccurrence gres ->
- mkNameClashErr gres
+ if must_have_parent
+ then noMatchingParentErr original_gres
+ else mkNameClashErr gres
where
checkFld :: GlobalRdrElt -> RnM ChildLookupResult
checkFld g = do
@@ -721,21 +724,25 @@ lookupSubBndrOcc_helper must_have_parent warn_if_deprec parent rdr_name how_lkup
-- 1. There were none to begin with.
-- 2. None of the matching ones were the parent but
-- a. They were from an overloaded record field so we can report
- -- a better error
+ -- a better error, or we were looking for references that must
+ -- have the correct parent. For example instance member names
+ -- that need to match the class they come from. Reporting those
+ -- as clashing errors, gives the user a confusing message
+ -- as in (#24452).
-- b. The original lookup was actually ambiguous.
-- For example, the case where overloading is off and two
-- record fields are in scope from different record
-- constructors, neither of which is the parent.
noMatchingParentErr :: [GlobalRdrElt] -> RnM ChildLookupResult
noMatchingParentErr original_gres = do
- traceRn "npe" (ppr original_gres)
+ traceRn "noMatchingParentErr" (ppr original_gres)
dup_fields_ok <- xoptM LangExt.DuplicateRecordFields
case original_gres of
[] -> return NameNotFound
[g] -> return $ IncorrectParent parent g
[p | ParentIs p <- [greParent g]]
gss@(g:gss'@(_:_)) ->
- if all isRecFldGRE gss && dup_fields_ok
+ if must_have_parent || all isRecFldGRE gss && dup_fields_ok
then return $
IncorrectParent parent g
[p | x <- gss, ParentIs p <- [greParent x]]
@@ -838,6 +845,7 @@ lookupSubBndrOcc warn_if_deprec the_parent doc rdr_name =
lookupExactOrOrig rdr_name (Right . greName) $
-- This happens for built-in classes, see mod052 for example
do { child <- lookupSubBndrOcc_helper True warn_if_deprec the_parent rdr_name what_lkup
+ ; traceTc "Here we go" (vcat [ppr child])
; return $ case child of
FoundChild g -> Right (greName g)
NameNotFound -> Left (UnknownSubordinate doc)
=====================================
testsuite/tests/rename/T24452/T24452a.hs
=====================================
@@ -0,0 +1,11 @@
+-- Note
+{-# LANGUAGE GeneralizedNewtypeDeriving #-}
+module BugReproduce where
+
+import Control.Applicative (Alternative (empty, (<|>)))
+
+newtype Foo a = MkFoo [a] deriving (Functor, Applicative)
+
+instance Alternative Foo where
+ empty = undefined
+ p <|> q = undefined
=====================================
testsuite/tests/rename/T24452/T24452b.hs
=====================================
@@ -0,0 +1,10 @@
+-- Note
+{-# LANGUAGE GeneralizedNewtypeDeriving #-}
+module BugReproduce where
+
+import Control.Applicative (Alternative)
+
+newtype Foo a = MkFoo [a] deriving (Functor, Applicative)
+
+instance Alternative Foo where
+ empty = undefined
=====================================
testsuite/tests/rename/T24452/T24452b.stderr
=====================================
@@ -0,0 +1,2 @@
+T24452b.hs:10:3: error: [GHC-54721]
+ ‘empty’ is not a (visible) method of class ‘Alternative’
\ No newline at end of file
=====================================
testsuite/tests/rename/T24452/T24452c.hs
=====================================
@@ -0,0 +1,11 @@
+-- Note
+{-# LANGUAGE GeneralizedNewtypeDeriving #-}
+module BugReproduce where
+
+import Control.Applicative (Alternative)
+import qualified Data.Map as Map
+
+newtype Foo a = MkFoo [a] deriving (Functor, Applicative)
+
+instance Alternative Foo where
+ empty = undefined
=====================================
testsuite/tests/rename/T24452/T24452c.stderr
=====================================
@@ -0,0 +1,2 @@
+T24452c.hs:11:3: error: [GHC-54721]
+ ‘empty’ is not a (visible) method of class ‘Alternative’
\ No newline at end of file
=====================================
testsuite/tests/rename/T24452/T24452d.hs
=====================================
@@ -0,0 +1,12 @@
+-- Note
+{-# LANGUAGE GeneralizedNewtypeDeriving #-}
+module BugReproduce where
+
+import Control.Applicative (Alternative)
+import qualified Data.Map as Map
+import qualified Data.Set as Set
+
+newtype Foo a = MkFoo [a] deriving (Functor, Applicative)
+
+instance Alternative Foo where
+ empty = undefined
=====================================
testsuite/tests/rename/T24452/T24452d.stderr
=====================================
@@ -0,0 +1,2 @@
+T24452d.hs:12:3: error: [GHC-54721]
+ ‘empty’ is not a (visible) method of class ‘Alternative’
\ No newline at end of file
=====================================
testsuite/tests/rename/T24452/all.T
=====================================
@@ -0,0 +1,4 @@
+test('T24452a', normal, compile, [''])
+test('T24452b', normal, compile_fail, [''])
+test('T24452c', normal, compile_fail, [''])
+test('T24452d', normal, compile_fail, [''])
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/3850605a1151a999aa0ad37ef7e72031b15ecbb1
--
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/3850605a1151a999aa0ad37ef7e72031b15ecbb1
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/20240619/1e936600/attachment-0001.html>
More information about the ghc-commits
mailing list