Skip to content

Commit 58bb39c

Browse files
mpickeringbgamari
authored andcommitted
Fix deprecation warning when deprecated identifier is from another module
A stray 'Just' was being printed in the deprecation message. Fixes #23573 (cherry picked from commit 2be99b7)
1 parent 62cb821 commit 58bb39c

File tree

6 files changed

+25
-2
lines changed

6 files changed

+25
-2
lines changed

compiler/GHC/Tc/Errors/Ppr.hs

Lines changed: 5 additions & 2 deletions
Original file line numberDiff line numberDiff line change
@@ -1100,8 +1100,11 @@ instance Diagnostic TcRnMessage where
11001100
, pprWarningTxtForMsg pragma_warning_msg ]
11011101
where
11021102
impMsg = text "imported from" <+> ppr pragma_warning_import_mod <> extra
1103-
extra | maybe True (pragma_warning_import_mod ==) pragma_warning_defined_mod = empty
1104-
| otherwise = text ", but defined in" <+> ppr pragma_warning_defined_mod
1103+
extra = case pragma_warning_defined_mod of
1104+
Just def_mod
1105+
| def_mod /= pragma_warning_import_mod
1106+
-> text ", but defined in" <+> ppr def_mod
1107+
_ -> empty
11051108
TcRnDifferentExportWarnings name locs
11061109
-> mkSimpleDecorated $ vcat [quotes (ppr name) <+> text "exported with different error messages",
11071110
text "at" <+> vcat (map ppr $ sortBy leftmost_smallest $ NE.toList locs)]
Lines changed: 5 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -0,0 +1,5 @@
1+
module T23573 where
2+
3+
import T23573A
4+
5+
foo = deprec
Lines changed: 5 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -0,0 +1,5 @@
1+
2+
T23573.hs:5:7: warning: [GHC-68441] [-Wdeprecations (in -Wextended-warnings)]
3+
In the use of ‘deprec’
4+
(imported from T23573A, but defined in T23573B):
5+
Deprecated: "deprec"
Lines changed: 5 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -0,0 +1,5 @@
1+
module T23573A(module T23573B) where
2+
3+
import T23573B
4+
5+
Lines changed: 4 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -0,0 +1,4 @@
1+
module T23573B where
2+
3+
{-# DEPRECATED deprec "deprec" #-}
4+
deprec = ()

testsuite/tests/warnings/should_compile/all.T

Lines changed: 1 addition & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -65,3 +65,4 @@ test('DodgyImports_hiding', normal, compile, ['-Wdodgy-imports'])
6565
test('T22702a', normal, compile, [''])
6666
test('T22702b', normal, compile, [''])
6767
test('T22826', normal, compile, [''])
68+
test('T23573', [extra_files(["T23573.hs", "T23573A.hs", "T23573B.hs"])], multimod_compile, ['T23573', '-v0'])

0 commit comments

Comments
 (0)