Vladislav Zavialov pushed to branch wip/int-index/dodgy-hidden-components at Glasgow Haskell Compiler / GHC
Commits:
-
2a425efa
by Vladislav Zavialov at 2025-10-30T14:07:52+03:00
10 changed files:
- compiler/GHC/Tc/Errors/Ppr.hs
- compiler/GHC/Tc/Errors/Types.hs
- compiler/GHC/Tc/Gen/Export.hs
- compiler/GHC/Types/Error/Codes.hs
- testsuite/tests/diagnostic-codes/codes.stdout
- + testsuite/tests/warnings/should_compile/DodgyExports02.hs
- + testsuite/tests/warnings/should_compile/DodgyExports02.stderr
- + testsuite/tests/warnings/should_compile/DodgyExports03.hs
- + testsuite/tests/warnings/should_compile/DodgyExports03.stderr
- testsuite/tests/warnings/should_compile/all.T
Changes:
| ... | ... | @@ -636,11 +636,6 @@ instance Diagnostic TcRnMessage where |
| 636 | 636 | $ formatExportItemError
|
| 637 | 637 | (text "module" <+> ppr mod)
|
| 638 | 638 | "is missing an export list"
|
| 639 | - TcRnExportHiddenComponents export_item
|
|
| 640 | - -> mkSimpleDecorated
|
|
| 641 | - $ formatExportItemError
|
|
| 642 | - (ppr export_item)
|
|
| 643 | - "attempts to export constructors or class methods that are not visible here"
|
|
| 644 | 639 | TcRnExportHiddenDefault export_item
|
| 645 | 640 | -> mkSimpleDecorated
|
| 646 | 641 | $ formatExportItemError
|
| ... | ... | @@ -2194,8 +2189,6 @@ instance Diagnostic TcRnMessage where |
| 2194 | 2189 | -> WarningWithFlag Opt_WarnDodgyExports
|
| 2195 | 2190 | TcRnMissingExportList{}
|
| 2196 | 2191 | -> WarningWithFlag Opt_WarnMissingExportList
|
| 2197 | - TcRnExportHiddenComponents{}
|
|
| 2198 | - -> ErrorWithoutFlag
|
|
| 2199 | 2192 | TcRnExportHiddenDefault{}
|
| 2200 | 2193 | -> ErrorWithoutFlag
|
| 2201 | 2194 | TcRnDuplicateExport{}
|
| ... | ... | @@ -2865,8 +2858,6 @@ instance Diagnostic TcRnMessage where |
| 2865 | 2858 | -> noHints
|
| 2866 | 2859 | TcRnMissingExportList{}
|
| 2867 | 2860 | -> noHints
|
| 2868 | - TcRnExportHiddenComponents{}
|
|
| 2869 | - -> noHints
|
|
| 2870 | 2861 | TcRnExportHiddenDefault{}
|
| 2871 | 2862 | -> noHints
|
| 2872 | 2863 | TcRnDuplicateExport{}
|
| ... | ... | @@ -1606,15 +1606,6 @@ data TcRnMessage where |
| 1606 | 1606 | -}
|
| 1607 | 1607 | TcRnMissingExportList :: ModuleName -> TcRnMessage
|
| 1608 | 1608 | |
| 1609 | - {-| TcRnExportHiddenComponents is an error that occurs when an export contains
|
|
| 1610 | - constructor or class methods that are not visible.
|
|
| 1611 | - |
|
| 1612 | - Example(s): None
|
|
| 1613 | - |
|
| 1614 | - Test cases: None
|
|
| 1615 | - -}
|
|
| 1616 | - TcRnExportHiddenComponents :: IE GhcPs -> TcRnMessage
|
|
| 1617 | - |
|
| 1618 | 1609 | {-| TcRnExportHiddenDefault is an error that occurs when an export contains
|
| 1619 | 1610 | a class default (with language extension NamedDefaults) that is not visible.
|
| 1620 | 1611 |
| ... | ... | @@ -525,7 +525,7 @@ exports_from_avail (Just (L _ rdr_items)) rdr_env imports this_mod |
| 525 | 525 | } (L loc ie@(IEThingAll (warn_txt_ps, ann) l doc))
|
| 526 | 526 | = do mb_gre <- lookupGreAvailRn (ieLWrappedNameWhatLooking l) $ lieWrappedName l
|
| 527 | 527 | for mb_gre $ \ par -> do
|
| 528 | - all_kids <- lookup_ie_kids_all ie l par
|
|
| 528 | + all_kids <- lookup_ie_kids_all l par
|
|
| 529 | 529 | let name = greName par
|
| 530 | 530 | all_gres = par : all_kids
|
| 531 | 531 | all_names = map greName all_gres
|
| ... | ... | @@ -561,7 +561,7 @@ exports_from_avail (Just (L _ rdr_items)) rdr_env imports this_mod |
| 561 | 561 | wc_kids <-
|
| 562 | 562 | case wc of
|
| 563 | 563 | NoIEWildcard -> return []
|
| 564 | - IEWildcard _ -> lookup_ie_kids_all ie l par
|
|
| 564 | + IEWildcard _ -> lookup_ie_kids_all l par
|
|
| 565 | 565 | |
| 566 | 566 | let name = greName par
|
| 567 | 567 | all_kids = with_kids ++ wc_kids
|
| ... | ... | @@ -593,20 +593,15 @@ exports_from_avail (Just (L _ rdr_items)) rdr_env imports this_mod |
| 593 | 593 | do { kids <- lookupChildrenExport gre sub_rdrs
|
| 594 | 594 | ; return (map fst kids, map snd kids) }
|
| 595 | 595 | |
| 596 | - lookup_ie_kids_all :: IE GhcPs -> LIEWrappedName GhcPs -> GlobalRdrElt
|
|
| 596 | + lookup_ie_kids_all :: LIEWrappedName GhcPs -> GlobalRdrElt
|
|
| 597 | 597 | -> RnM [GlobalRdrElt]
|
| 598 | - lookup_ie_kids_all ie (L _loc rdr) gre =
|
|
| 598 | + lookup_ie_kids_all (L _loc rdr) gre =
|
|
| 599 | 599 | do { let name = greName gre
|
| 600 | 600 | gres = findChildren kids_env name
|
| 601 | 601 | -- We only choose level 0 exports when filling in part of an export list implicitly.
|
| 602 | 602 | ; let kids_0 = mapMaybe pickLevelZeroGRE gres
|
| 603 | 603 | ; addUsedKids (ieWrappedName rdr) kids_0
|
| 604 | - ; when (null kids_0) $
|
|
| 605 | - if isTyConName name
|
|
| 606 | - then addTcRnDiagnostic (TcRnDodgyExports gre)
|
|
| 607 | - else -- This occurs when you export T(..), but
|
|
| 608 | - -- only import T abstractly, or T is a synonym.
|
|
| 609 | - addErr (TcRnExportHiddenComponents ie)
|
|
| 604 | + ; when (null kids_0) $ addTcRnDiagnostic (TcRnDodgyExports gre)
|
|
| 610 | 605 | ; return kids_0 }
|
| 611 | 606 | |
| 612 | 607 | -------------
|
| ... | ... | @@ -505,7 +505,7 @@ type family GhcDiagnosticCode c = n | n -> c where |
| 505 | 505 | GhcDiagnosticCode "TcRnExportedModNotImported" = 90973
|
| 506 | 506 | GhcDiagnosticCode "TcRnNullExportedModule" = 64649
|
| 507 | 507 | GhcDiagnosticCode "TcRnMissingExportList" = 85401
|
| 508 | - GhcDiagnosticCode "TcRnExportHiddenComponents" = 94558
|
|
| 508 | + GhcDiagnosticCode "TcRnExportHiddenComponents" = Outdated 94558
|
|
| 509 | 509 | GhcDiagnosticCode "TcRnExportHiddenDefault" = 74775
|
| 510 | 510 | GhcDiagnosticCode "TcRnDuplicateExport" = 47854
|
| 511 | 511 | GhcDiagnosticCode "TcRnDuplicateNamedDefaultExport" = 31584
|
| ... | ... | @@ -52,7 +52,6 @@ |
| 52 | 52 | [GHC-55868] is untested (constructor = TcRnArrowIfThenElsePredDependsOnResultTy)
|
| 53 | 53 | [GHC-51876] is untested (constructor = TcRnDupeModuleExport)
|
| 54 | 54 | [GHC-64649] is untested (constructor = TcRnNullExportedModule)
|
| 55 | -[GHC-94558] is untested (constructor = TcRnExportHiddenComponents)
|
|
| 56 | 55 | [GHC-63055] is untested (constructor = TcRnFieldUpdateInvalidType)
|
| 57 | 56 | [GHC-26133] is untested (constructor = TcRnForeignImportPrimSafeAnn)
|
| 58 | 57 | [GHC-03355] is untested (constructor = TcRnIllegalForeignDeclBackend)
|
| 1 | +module DodgyExports02
|
|
| 2 | + ( Identity(..) -- type constructor has out-of-scope children
|
|
| 3 | + , Void(..) -- type constructor has no children
|
|
| 4 | + ) where
|
|
| 5 | + |
|
| 6 | +import Data.Void (Void)
|
|
| 7 | +import Data.Functor.Identity (Identity) |
| 1 | +DodgyExports02.hs:2:5: warning: [GHC-75356] [-Wdodgy-exports (in -Wextra)]
|
|
| 2 | + The export item ‘Identity(..)’ suggests that
|
|
| 3 | + ‘Identity’ has (in-scope) constructors or record fields,
|
|
| 4 | + but it has none
|
|
| 5 | + |
|
| 6 | +DodgyExports02.hs:3:5: warning: [GHC-75356] [-Wdodgy-exports (in -Wextra)]
|
|
| 7 | + The export item ‘Void(..)’ suggests that
|
|
| 8 | + ‘Void’ has (in-scope) constructors or record fields,
|
|
| 9 | + but it has none
|
|
| 10 | + |
| 1 | +{-# LANGUAGE ExplicitNamespaces #-}
|
|
| 2 | + |
|
| 3 | +module DodgyExports03
|
|
| 4 | + ( data MkR(..) -- data constructors never have children ('fld' belongs to 'R')
|
|
| 5 | + ) where
|
|
| 6 | + |
|
| 7 | +data R = MkR { fld :: Int } |
| 1 | +DodgyExports03.hs:4:5: warning: [GHC-75356] [-Wdodgy-exports (in -Wextra)]
|
|
| 2 | + The export item ‘MkR(..)’ suggests that
|
|
| 3 | + ‘MkR’ has children, but it is not a type constructor or a class
|
|
| 4 | + |
| ... | ... | @@ -54,6 +54,8 @@ test('T19564d', normal, compile, ['']) |
| 54 | 54 | # Also, suppress uniques as one of the warnings is unstable in CI, otherwise.
|
| 55 | 55 | test('T19296', normal, compile, ['-fdiagnostics-show-caret -Wredundant-constraints -dsuppress-uniques'])
|
| 56 | 56 | test('DodgyExports01', normal, compile, ['-Wdodgy-exports'])
|
| 57 | +test('DodgyExports02', normal, compile, ['-Wdodgy-exports'])
|
|
| 58 | +test('DodgyExports03', normal, compile, ['-Wdodgy-exports'])
|
|
| 57 | 59 | test('DerivingTypeable', normal, compile, ['-Wderiving-typeable'])
|
| 58 | 60 | test('T18862a', normal, compile, [''])
|
| 59 | 61 | test('T18862b', normal, compile, [''])
|