[Git][ghc/ghc][master] Don't bundle children for non-parent Avails
Marge Bot (@marge-bot)
gitlab at gitlab.haskell.org
Wed Aug 30 14:18:55 UTC 2023
Marge Bot pushed to branch master at Glasgow Haskell Compiler / GHC
Commits:
694ec5b1 by sheaf at 2023-08-30T10:18:32-04:00
Don't bundle children for non-parent Avails
We used to bundle all children of the parent Avail with things that
aren't the parent, e.g. with
class C a where
type T a
meth :: ..
we would bundle the whole Avail (C, T, meth) with all of C, T and meth,
instead of only with C.
Avoiding this fixes #23570
- - - - -
7 changed files:
- compiler/GHC/Rename/Names.hs
- + testsuite/tests/rename/should_fail/T23570.hs
- + testsuite/tests/rename/should_fail/T23570.stderr
- + testsuite/tests/rename/should_fail/T23570_aux.hs
- + testsuite/tests/rename/should_fail/T23570b.hs
- + testsuite/tests/rename/should_fail/T23570b.stderr
- testsuite/tests/rename/should_fail/all.T
Changes:
=====================================
compiler/GHC/Rename/Names.hs
=====================================
@@ -1303,8 +1303,13 @@ filterImports hsc_env iface decl_spec (Just (want_hiding, L l import_items))
, export_depr_warns )
IEThingAll _ (L l tc) -> do
- ImpOccItem gre child_gres _ <- lookup_parent ie $ ieWrappedName tc
+ ImpOccItem { imp_item = gre
+ , imp_bundled = bundled_gres
+ , imp_is_parent = is_par
+ }
+ <- lookup_parent ie $ ieWrappedName tc
let name = greName gre
+ child_gres = if is_par then bundled_gres else []
imp_list_warn
| null child_gres
@@ -1445,18 +1450,23 @@ data ImpOccItem
mkImportOccEnv :: HscEnv -> ImpDeclSpec -> [IfaceExport] -> OccEnv (NameEnv ImpOccItem)
mkImportOccEnv hsc_env decl_spec all_avails =
mkOccEnv_C (plusNameEnv_C combine)
- [ (occ, mkNameEnv [(nm, ImpOccItem g bundled is_parent)])
+ [ (occ, mkNameEnv [(nm, item)])
| avail <- all_avails
- , let gs = gresFromAvail hsc_env (Just hiding_spec) avail
- , g <- gs
- , let nm = greName g
- occ = greOccName g
+ , let gres = gresFromAvail hsc_env (Just hiding_spec) avail
+ , gre <- gres
+ , let nm = greName gre
+ occ = greOccName gre
(is_parent, bundled) = case avail of
AvailTC c _
- -> if c == nm -- (Recall the AvailTC invariant)
- then ( True, case gs of { g0 : gs' | greName g0 == nm -> gs'; _ -> gs } )
- else ( False, gs )
+ | c == nm -- (Recall the AvailTC invariant from GHC.Types.AvailInfo)
+ -> ( True, drop 1 gres ) -- "drop 1": don't include the parent itself.
+ | otherwise
+ -> ( False, gres )
_ -> ( False, [] )
+ item = ImpOccItem
+ { imp_item = gre
+ , imp_bundled = bundled
+ , imp_is_parent = is_parent }
]
where
=====================================
testsuite/tests/rename/should_fail/T23570.hs
=====================================
@@ -0,0 +1,6 @@
+module T23570 where
+
+import T23570_aux (T(..))
+
+f :: C a => a -> T a ()
+f = meth
=====================================
testsuite/tests/rename/should_fail/T23570.stderr
=====================================
@@ -0,0 +1,6 @@
+
+T23570.hs:5:6: error: [GHC-76037]
+ Not in scope: type constructor or class ‘C’
+ Suggested fix:
+ Add ‘C’ to the import list in the import of ‘T23570_aux’
+ (at T23570.hs:3:1-25).
=====================================
testsuite/tests/rename/should_fail/T23570_aux.hs
=====================================
@@ -0,0 +1,7 @@
+{-# LANGUAGE TypeFamilies #-}
+
+module T23570_aux where
+
+class C a where
+ type T a
+ meth :: a -> T a
=====================================
testsuite/tests/rename/should_fail/T23570b.hs
=====================================
@@ -0,0 +1,5 @@
+{-# OPTIONS_GHC -Wdodgy-imports #-}
+
+module T23570b where
+
+import T23570_aux (T(..))
=====================================
testsuite/tests/rename/should_fail/T23570b.stderr
=====================================
@@ -0,0 +1,5 @@
+
+T23570b.hs:5:20: warning: [GHC-99623] [-Wdodgy-imports (in -Wextra)]
+ The import item ‘T23570_aux.T(..)’ suggests that
+ ‘T23570_aux.T’ has (in-scope) constructors or record fields,
+ but it has none
=====================================
testsuite/tests/rename/should_fail/all.T
=====================================
@@ -210,3 +210,5 @@ test('T22478b', normal, compile_fail, [''])
test('T22478d', normal, compile_fail, [''])
test('T22478e', normal, compile_fail, [''])
test('T22478f', normal, compile_fail, [''])
+test('T23570', [extra_files(['T23570_aux.hs'])], multimod_compile_fail, ['T23570', '-v0'])
+test('T23570b', [extra_files(['T23570_aux.hs'])], multimod_compile, ['T23570b', '-v0'])
\ No newline at end of file
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/694ec5b1d3d1f67ba5b14b84e054b0716dc5cb6d
--
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/694ec5b1d3d1f67ba5b14b84e054b0716dc5cb6d
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/20230830/b28f0f51/attachment-0001.html>
More information about the ghc-commits
mailing list