[Git][ghc/ghc][master] Fix deprecation warning when deprecated identifier is from another module
Marge Bot (@marge-bot)
gitlab at gitlab.haskell.org
Wed Jul 5 02:07:46 UTC 2023
Marge Bot pushed to branch master at Glasgow Haskell Compiler / GHC
Commits:
2be99b7e by Matthew Pickering at 2023-07-04T22:07:21-04:00
Fix deprecation warning when deprecated identifier is from another module
A stray 'Just' was being printed in the deprecation message.
Fixes #23573
- - - - -
6 changed files:
- compiler/GHC/Tc/Errors/Ppr.hs
- + testsuite/tests/warnings/should_compile/T23573.hs
- + testsuite/tests/warnings/should_compile/T23573.stderr
- + testsuite/tests/warnings/should_compile/T23573A.hs
- + testsuite/tests/warnings/should_compile/T23573B.hs
- testsuite/tests/warnings/should_compile/all.T
Changes:
=====================================
compiler/GHC/Tc/Errors/Ppr.hs
=====================================
@@ -1099,8 +1099,11 @@ instance Diagnostic TcRnMessage where
, pprWarningTxtForMsg pragma_warning_msg ]
where
impMsg = text "imported from" <+> ppr pragma_warning_import_mod <> extra
- extra | maybe True (pragma_warning_import_mod ==) pragma_warning_defined_mod = empty
- | otherwise = text ", but defined in" <+> ppr pragma_warning_defined_mod
+ extra = case pragma_warning_defined_mod of
+ Just def_mod
+ | def_mod /= pragma_warning_import_mod
+ -> text ", but defined in" <+> ppr def_mod
+ _ -> empty
TcRnDifferentExportWarnings name locs
-> mkSimpleDecorated $ vcat [quotes (ppr name) <+> text "exported with different error messages",
text "at" <+> vcat (map ppr $ sortBy leftmost_smallest $ NE.toList locs)]
=====================================
testsuite/tests/warnings/should_compile/T23573.hs
=====================================
@@ -0,0 +1,5 @@
+module T23573 where
+
+import T23573A
+
+foo = deprec
=====================================
testsuite/tests/warnings/should_compile/T23573.stderr
=====================================
@@ -0,0 +1,5 @@
+
+T23573.hs:5:7: warning: [GHC-68441] [-Wdeprecations (in -Wextended-warnings)]
+ In the use of ‘deprec’
+ (imported from T23573A, but defined in T23573B):
+ Deprecated: "deprec"
=====================================
testsuite/tests/warnings/should_compile/T23573A.hs
=====================================
@@ -0,0 +1,5 @@
+module T23573A(module T23573B) where
+
+import T23573B
+
+
=====================================
testsuite/tests/warnings/should_compile/T23573B.hs
=====================================
@@ -0,0 +1,4 @@
+module T23573B where
+
+{-# DEPRECATED deprec "deprec" #-}
+deprec = ()
=====================================
testsuite/tests/warnings/should_compile/all.T
=====================================
@@ -65,3 +65,4 @@ test('DodgyImports_hiding', normal, compile, ['-Wdodgy-imports'])
test('T22702a', normal, compile, [''])
test('T22702b', normal, compile, [''])
test('T22826', normal, compile, [''])
+test('T23573', [extra_files(["T23573.hs", "T23573A.hs", "T23573B.hs"])], multimod_compile, ['T23573', '-v0'])
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/2be99b7e81e2ae5ef81fef21b0a55cfe77f917a3
--
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/2be99b7e81e2ae5ef81fef21b0a55cfe77f917a3
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/20230704/b43acffa/attachment-0001.html>
More information about the ghc-commits
mailing list