Marge Bot pushed to branch master at Glasgow Haskell Compiler / GHC

Commits:

28 changed files:

Changes:

  • compiler/GHC/Rename/Env.hs
    ... ... @@ -679,19 +679,20 @@ lookupGlobalOccRn will find it.
    679 679
     -}
    
    680 680
     
    
    681 681
     -- | Used in export lists to lookup the children.
    
    682
    -lookupSubBndrOcc_helper :: Bool
    
    682
    +lookupSubBndrOcc_helper :: Bool          -- ^ must have a parent
    
    683
    +                        -> Bool          -- ^ look up in all namespaces
    
    683 684
                             -> DeprecationWarnings
    
    684 685
                             -> ParentGRE     -- ^ parent
    
    685 686
                             -> RdrName       -- ^ thing we are looking up
    
    686 687
                             -> RnM ChildLookupResult
    
    687
    -lookupSubBndrOcc_helper must_have_parent warn_if_deprec parent_gre rdr_name
    
    688
    +lookupSubBndrOcc_helper must_have_parent all_ns warn_if_deprec parent_gre rdr_name
    
    688 689
       | isUnboundName (parentGRE_name parent_gre)
    
    689 690
         -- Avoid an error cascade
    
    690 691
       = return (FoundChild (mkUnboundGRERdr rdr_name))
    
    691 692
     
    
    692 693
       | otherwise = do
    
    693 694
       gre_env <- getGlobalRdrEnv
    
    694
    -  let original_gres = lookupGRE gre_env (LookupChildren parent_gre (rdrNameOcc rdr_name))
    
    695
    +  let original_gres = lookupGRE gre_env (LookupChildren parent_gre (rdrNameOcc rdr_name) all_ns)
    
    695 696
           picked_gres = pick_gres original_gres
    
    696 697
       -- The remaining GREs are things that we *could* export here.
    
    697 698
       -- Note that this includes things which have `NoParent`;
    
    ... ... @@ -844,7 +845,7 @@ lookupSubBndrOcc :: DeprecationWarnings
    844 845
     lookupSubBndrOcc warn_if_deprec the_parent what_subordinate rdr_name =
    
    845 846
       lookupExactOrOrig rdr_name (Right . greName) $
    
    846 847
         -- This happens for built-in classes, see mod052 for example
    
    847
    -    do { child <- lookupSubBndrOcc_helper True warn_if_deprec the_parent rdr_name
    
    848
    +    do { child <- lookupSubBndrOcc_helper True True warn_if_deprec the_parent rdr_name
    
    848 849
            ; return $ case child of
    
    849 850
                FoundChild g       -> Right (greName g)
    
    850 851
                NameNotFound       -> Left unknown_sub
    

  • compiler/GHC/Rename/Names.hs
    ... ... @@ -23,6 +23,7 @@ module GHC.Rename.Names (
    23 23
             checkConName,
    
    24 24
             mkChildEnv,
    
    25 25
             findChildren,
    
    26
    +        mkBadExportSubordinate,
    
    26 27
             findImportUsage,
    
    27 28
             getMinimalImports,
    
    28 29
             printMinimalImports,
    
    ... ... @@ -1423,6 +1424,15 @@ filterImports hsc_env iface decl_spec (Just (want_hiding, L l import_items))
    1423 1424
               where
    
    1424 1425
                 name = greName gre
    
    1425 1426
     
    
    1427
    +-- | Assuming a subordinate item could not be found, do another lookup for a
    
    1428
    +-- more specific error message.
    
    1429
    +mkBadExportSubordinate :: [GlobalRdrElt] -> LIEWrappedName GhcPs -> BadExportSubordinate
    
    1430
    +mkBadExportSubordinate child_gres n =
    
    1431
    +  case lookupChildren child_gres [n] of
    
    1432
    +    (LookupChildNonType {lce_nontype_item = g} : _, _) -> BadExportSubordinateNonType g
    
    1433
    +    (LookupChildNonData {lce_nondata_item = g} : _, _) -> BadExportSubordinateNonData g
    
    1434
    +    _ -> BadExportSubordinateNotFound n
    
    1435
    +
    
    1426 1436
     type IELookupM = MaybeErr IELookupError
    
    1427 1437
     
    
    1428 1438
     data IELookupWarning
    

  • compiler/GHC/Tc/Errors/Ppr.hs
    ... ... @@ -675,6 +675,43 @@ instance Diagnostic TcRnMessage where
    675 675
             what_is = pp_category ty_thing
    
    676 676
             thing = ppr $ nameOccName child
    
    677 677
             parents = map ppr parent_names
    
    678
    +    TcRnExportedSubordinateNotFound parent_gre k _ ->
    
    679
    +      mkSimpleDecorated $
    
    680
    +      case k of
    
    681
    +        BadExportSubordinateNotFound wname ->
    
    682
    +          let child_name      = lieWrappedName wname
    
    683
    +              child_name_fs   = occNameFS (rdrNameOcc child_name)
    
    684
    +              suggest_patsyn  = allow_patsyn && could_be_patsyn
    
    685
    +              could_be_patsyn =
    
    686
    +                case unLoc wname of
    
    687
    +                  IEName{} -> isLexCon child_name_fs
    
    688
    +                  IEData{} -> isLexCon child_name_fs
    
    689
    +                  IEPattern{} -> True
    
    690
    +                  IEType{}    -> False
    
    691
    +                  IEDefault{} -> False
    
    692
    +              basic_msg =
    
    693
    +                what_parent <+> quotes (ppr parent_name)
    
    694
    +                <+> "does not define a child named" <+> quotes (ppr child_name)
    
    695
    +              patsyn_msg =
    
    696
    +                text "nor is there a pattern synonym of that name in scope"
    
    697
    +              combined_msg
    
    698
    +                | suggest_patsyn = basic_msg <> comma $$ patsyn_msg <> dot
    
    699
    +                | otherwise      = basic_msg <> dot
    
    700
    +          in combined_msg
    
    701
    +        BadExportSubordinateNonType gre ->
    
    702
    +          let child_name = greName gre
    
    703
    +          in what_parent <+> quotes (ppr parent_name) <+> "defines a child named" <+> quotes (ppr child_name) <> comma
    
    704
    +             $$ text "but it is not in the type namespace."
    
    705
    +        BadExportSubordinateNonData gre ->
    
    706
    +          let child_name = greName gre
    
    707
    +          in what_parent <+> quotes (ppr parent_name) <+> "defines a child named" <+> quotes (ppr child_name) <> comma
    
    708
    +             $$ text "but it is not in the data namespace."
    
    709
    +      where
    
    710
    +        parent_name = greName parent_gre
    
    711
    +        (what_parent, allow_patsyn) = case greInfo parent_gre of
    
    712
    +          IAmTyCon ClassFlavour -> (text "The class", False)
    
    713
    +          IAmTyCon _            -> (text "The data type", True)
    
    714
    +          _                     -> (text "The item", False)
    
    678 715
         TcRnConflictingExports occ child_gre1 ie1 child_gre2 ie2
    
    679 716
           -> mkSimpleDecorated $
    
    680 717
                vcat [ text "Conflicting exports for" <+> quotes (ppr occ) <> colon
    
    ... ... @@ -2204,6 +2241,8 @@ instance Diagnostic TcRnMessage where
    2204 2241
           -> WarningWithFlag Opt_WarnDuplicateExports
    
    2205 2242
         TcRnExportedParentChildMismatch{}
    
    2206 2243
           -> ErrorWithoutFlag
    
    2244
    +    TcRnExportedSubordinateNotFound{}
    
    2245
    +      -> ErrorWithoutFlag
    
    2207 2246
         TcRnConflictingExports{}
    
    2208 2247
           -> ErrorWithoutFlag
    
    2209 2248
         TcRnDuplicateFieldExport {}
    
    ... ... @@ -2875,6 +2914,13 @@ instance Diagnostic TcRnMessage where
    2875 2914
           -> noHints
    
    2876 2915
         TcRnExportedParentChildMismatch{}
    
    2877 2916
           -> noHints
    
    2917
    +    TcRnExportedSubordinateNotFound _ k similar_names
    
    2918
    +      -> ns_spec_hints ++ similar_names
    
    2919
    +      where
    
    2920
    +        ns_spec_hints = case k of
    
    2921
    +          BadExportSubordinateNotFound{} -> noHints
    
    2922
    +          BadExportSubordinateNonType{}  -> [SuggestChangeExportItem ExportItemRemoveSubordinateType]
    
    2923
    +          BadExportSubordinateNonData{}  -> [SuggestChangeExportItem ExportItemRemoveSubordinateData]
    
    2878 2924
         TcRnConflictingExports{}
    
    2879 2925
           -> noHints
    
    2880 2926
         TcRnDuplicateFieldExport {}
    

  • compiler/GHC/Tc/Errors/Types.hs
    ... ... @@ -83,7 +83,6 @@ module GHC.Tc.Errors.Types (
    83 83
       , Subordinate(..), pprSubordinate
    
    84 84
       , ImportError(..)
    
    85 85
       , WhatLooking(..)
    
    86
    -  , lookingForSubordinate
    
    87 86
       , HoleError(..)
    
    88 87
       , CoercibleMsg(..)
    
    89 88
       , NoBuiltinInstanceMsg(..)
    
    ... ... @@ -117,6 +116,7 @@ module GHC.Tc.Errors.Types (
    117 116
       , HsTyVarBndrExistentialFlag(..)
    
    118 117
       , TySynCycleTyCons
    
    119 118
       , BadImportKind(..)
    
    119
    +  , BadExportSubordinate(..)
    
    120 120
       , DodgyImportsReason (..)
    
    121 121
       , ImportLookupExtensions (..)
    
    122 122
       , ImportLookupReason (..)
    
    ... ... @@ -1664,6 +1664,26 @@ data TcRnMessage where
    1664 1664
                                       -> Name -- ^ child
    
    1665 1665
                                       -> [Name] -> TcRnMessage
    
    1666 1666
     
    
    1667
    +  {-| TcRnExportedSubordinateNotFound is an error that occurs when the name of a
    
    1668
    +      subordinate export item is not in scope.
    
    1669
    +
    
    1670
    +      Example:
    
    1671
    +        module M (T(X)) where  -- X is not in scope
    
    1672
    +        data T = Y
    
    1673
    +
    
    1674
    +      Test cases: module/mod4
    
    1675
    +                  rename/should_fail/T12488a
    
    1676
    +                  rename/should_fail/T12488a_foo
    
    1677
    +                  rename/should_fail/T12488e
    
    1678
    +                  rename/should_fail/T12488g
    
    1679
    +                  rename/should_fail/T25899e2
    
    1680
    +  -}
    
    1681
    +  TcRnExportedSubordinateNotFound
    
    1682
    +    :: GlobalRdrElt                  -- ^ parent
    
    1683
    +    -> BadExportSubordinate
    
    1684
    +    -> [GhcHint]                     -- ^ similar name suggestions
    
    1685
    +    -> TcRnMessage
    
    1686
    +
    
    1667 1687
       {-| TcRnConflictingExports is an error that occurs when different identifiers that
    
    1668 1688
           have the same name are being exported by a module.
    
    1669 1689
     
    
    ... ... @@ -5829,6 +5849,11 @@ data BadImportKind
    5829 5849
       | BadImportAvailVar
    
    5830 5850
       deriving Generic
    
    5831 5851
     
    
    5852
    +data BadExportSubordinate
    
    5853
    +  = BadExportSubordinateNotFound !(LIEWrappedName GhcPs)
    
    5854
    +  | BadExportSubordinateNonType  !GlobalRdrElt
    
    5855
    +  | BadExportSubordinateNonData  !GlobalRdrElt
    
    5856
    +
    
    5832 5857
     {- Note [Reasons for BadImportAvailTyCon]
    
    5833 5858
     ~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~
    
    5834 5859
     BadImportAvailTyCon means a name is available in the TcCls namespace
    
    ... ... @@ -6065,15 +6090,6 @@ data WhatLooking = WL_Anything
    6065 6090
                          -- is no point in suggesting alternative spellings
    
    6066 6091
                      deriving (Eq, Show)
    
    6067 6092
     
    
    6068
    --- | In what namespaces should we look for a subordinate
    
    6069
    --- of the given 'GlobalRdrElt'.
    
    6070
    -lookingForSubordinate :: GlobalRdrElt -> WhatLooking
    
    6071
    -lookingForSubordinate parent_gre =
    
    6072
    -  case greInfo parent_gre of
    
    6073
    -    IAmTyCon ClassFlavour
    
    6074
    -      -> WL_TyCon_or_TermVar
    
    6075
    -    _ -> WL_Term
    
    6076
    -
    
    6077 6093
     -- | This datatype collates instances that match or unifier,
    
    6078 6094
     -- in order to report an error message for an unsolved typeclass constraint.
    
    6079 6095
     data PotentialInstances
    

  • compiler/GHC/Tc/Gen/Export.hs
    ... ... @@ -22,7 +22,7 @@ import GHC.Rename.Doc
    22 22
     import GHC.Rename.Module
    
    23 23
     import GHC.Rename.Names
    
    24 24
     import GHC.Rename.Env
    
    25
    -import GHC.Rename.Unbound ( reportUnboundName )
    
    25
    +import GHC.Rename.Unbound ( mkUnboundNameRdr )
    
    26 26
     import GHC.Rename.Splice
    
    27 27
     import GHC.Unit.Module
    
    28 28
     import GHC.Unit.Module.Imported
    
    ... ... @@ -30,13 +30,13 @@ import GHC.Unit.Module.Warnings
    30 30
     import GHC.Core.TyCon
    
    31 31
     import GHC.Utils.Outputable
    
    32 32
     import GHC.Utils.Panic
    
    33
    +import GHC.Utils.Misc (fuzzyLookup)
    
    33 34
     import GHC.Core.ConLike
    
    34 35
     import GHC.Core.PatSyn
    
    35 36
     import GHC.Data.Maybe
    
    36 37
     import GHC.Data.FastString (fsLit)
    
    37 38
     import GHC.Driver.Env
    
    38 39
     import GHC.Driver.DynFlags
    
    39
    -import GHC.Parser.PostProcess ( setRdrNameSpace )
    
    40 40
     import qualified GHC.LanguageExtensions as LangExt
    
    41 41
     
    
    42 42
     import GHC.Types.Unique.Map
    
    ... ... @@ -50,6 +50,7 @@ import GHC.Types.SourceFile
    50 50
     import GHC.Types.Id
    
    51 51
     import GHC.Types.Id.Info
    
    52 52
     import GHC.Types.Name.Reader
    
    53
    +import GHC.Types.Hint
    
    53 54
     
    
    54 55
     import Control.Arrow ( first )
    
    55 56
     import Control.Monad ( when )
    
    ... ... @@ -590,8 +591,9 @@ exports_from_avail (Just (L _ rdr_items)) rdr_env imports this_mod
    590 591
         lookup_ie_kids_with :: GlobalRdrElt -> [LIEWrappedName GhcPs]
    
    591 592
                        -> RnM ([LIEWrappedName GhcRn], [GlobalRdrElt])
    
    592 593
         lookup_ie_kids_with gre sub_rdrs =
    
    593
    -      do { kids <- lookupChildrenExport gre sub_rdrs
    
    594
    -         ; return (map fst kids, map snd kids) }
    
    594
    +      do { let child_gres = findChildren kids_env (greName gre)
    
    595
    +         ; kids <- lookupChildrenExport gre child_gres sub_rdrs
    
    596
    +         ; return (unzip kids) }
    
    595 597
     
    
    596 598
         lookup_ie_kids_all :: IE GhcPs -> LIEWrappedName GhcPs -> GlobalRdrElt
    
    597 599
                       -> RnM [GlobalRdrElt]
    
    ... ... @@ -782,9 +784,10 @@ If the module has NO main function:
    782 784
     
    
    783 785
     
    
    784 786
     lookupChildrenExport :: GlobalRdrElt
    
    787
    +                     -> [GlobalRdrElt]
    
    785 788
                          -> [LIEWrappedName GhcPs]
    
    786 789
                          -> RnM ([(LIEWrappedName GhcRn, GlobalRdrElt)])
    
    787
    -lookupChildrenExport parent_gre rdr_items = mapAndReportM doOne rdr_items
    
    790
    +lookupChildrenExport parent_gre child_gres rdr_items = mapAndReportM doOne rdr_items
    
    788 791
         where
    
    789 792
             spec_parent = greName parent_gre
    
    790 793
             -- Process an individual child
    
    ... ... @@ -792,24 +795,23 @@ lookupChildrenExport parent_gre rdr_items = mapAndReportM doOne rdr_items
    792 795
                   -> RnM (LIEWrappedName GhcRn, GlobalRdrElt)
    
    793 796
             doOne n = do
    
    794 797
     
    
    795
    -          let bareName = (ieWrappedName . unLoc) n
    
    798
    +          let all_ns = case unLoc n of
    
    799
    +                IEName{} -> True    -- Ignore the namespace iff the name is unadorned
    
    800
    +                _        -> False
    
    801
    +          let bareName = lieWrappedName n
    
    796 802
                     -- Do not report export list declaration deprecations
    
    797
    -          name <-  lookupSubBndrOcc_helper False ExportDeprecationWarnings
    
    803
    +          name <-  lookupSubBndrOcc_helper False all_ns ExportDeprecationWarnings
    
    798 804
                             (ParentGRE spec_parent (greInfo parent_gre)) bareName
    
    799 805
               traceRn "lookupChildrenExport" (ppr name)
    
    800
    -          -- Default to data constructors for slightly better error
    
    801
    -          -- messages
    
    802
    -          let unboundName :: RdrName
    
    803
    -              unboundName = if rdrNameSpace bareName == varName
    
    804
    -                            then bareName
    
    805
    -                            else setRdrNameSpace bareName dataName
    
    806 806
     
    
    807 807
               case name of
    
    808 808
                 NameNotFound ->
    
    809
    -              do { ub <- reportUnboundName (lookingForSubordinate parent_gre) unboundName
    
    810
    -                 ; let l = getLoc n
    
    809
    +              do { let err = mkBadExportSubordinate child_gres n
    
    810
    +                       similar_names = subordinateExportSimilarNames bareName child_gres
    
    811
    +                 ; addDiagnosticTc (TcRnExportedSubordinateNotFound parent_gre err similar_names)
    
    812
    +                 ; let ub  = mkUnboundNameRdr bareName
    
    811 813
                            gre = mkLocalGRE UnboundGRE NoParent ub
    
    812
    -                 ; return (L l (IEName noExtField (L (l2l l) ub)), gre)}
    
    814
    +                 ; return (replaceLWrappedName n ub, gre)}
    
    813 815
                 FoundChild child@(GRE { gre_name = child_nm, gre_par = par }) ->
    
    814 816
                   do { checkPatSynParent spec_parent par child_nm
    
    815 817
                      ; checkThLocalNameNoLift (ieLWrappedUserRdrName n child_nm)
    
    ... ... @@ -817,6 +819,22 @@ lookupChildrenExport parent_gre rdr_items = mapAndReportM doOne rdr_items
    817 819
                      }
    
    818 820
                 IncorrectParent p c gs -> failWithDcErr (parentGRE_name p) (greName c) gs
    
    819 821
     
    
    822
    +subordinateExportSimilarNames :: RdrName -> [GlobalRdrElt] -> [GhcHint]
    
    823
    +subordinateExportSimilarNames rdr_name child_gres =
    
    824
    +  -- At the moment, we only suggest other children of the same parent.
    
    825
    +  -- One possible improvement would be to suggest bundling pattern synonyms with
    
    826
    +  -- data types, but not with classes or type data.
    
    827
    +  case NE.nonEmpty similar_names of
    
    828
    +    Nothing  -> []
    
    829
    +    Just nms -> [SuggestSimilarNames rdr_name (fmap SimilarName nms)]
    
    830
    +  where
    
    831
    +    occ_name = rdrNameOcc rdr_name
    
    832
    +    similar_names =
    
    833
    +      fuzzyLookup (occNameString occ_name)
    
    834
    +                  [(occNameString child_occ_name, greName gre)
    
    835
    +                    | gre <- child_gres
    
    836
    +                    , let child_occ_name = greOccName gre
    
    837
    +                    , occNameFS occ_name /= occNameFS child_occ_name ]
    
    820 838
     
    
    821 839
     -- Note [Typing Pattern Synonym Exports]
    
    822 840
     -- ~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~
    

  • compiler/GHC/Types/Error/Codes.hs
    ... ... @@ -510,6 +510,7 @@ type family GhcDiagnosticCode c = n | n -> c where
    510 510
       GhcDiagnosticCode "TcRnDuplicateExport"                           = 47854
    
    511 511
       GhcDiagnosticCode "TcRnDuplicateNamedDefaultExport"               = 31584
    
    512 512
       GhcDiagnosticCode "TcRnExportedParentChildMismatch"               = 88993
    
    513
    +  GhcDiagnosticCode "TcRnExportedSubordinateNotFound"               = 11592
    
    513 514
       GhcDiagnosticCode "TcRnConflictingExports"                        = 69158
    
    514 515
       GhcDiagnosticCode "TcRnDuplicateFieldExport"                      = 97219
    
    515 516
       GhcDiagnosticCode "TcRnAmbiguousFieldInUpdate"                    = 56428
    

  • compiler/GHC/Types/Hint.hs
    ... ... @@ -7,6 +7,7 @@ module GHC.Types.Hint (
    7 7
       , LanguageExtensionHint(..)
    
    8 8
       , ImportItemSuggestion(..)
    
    9 9
       , ImportSuggestion(..)
    
    10
    +  , ExportItemSuggestion(..)
    
    10 11
       , HowInScope(..)
    
    11 12
       , SimilarName(..)
    
    12 13
       , StarIsType(..)
    
    ... ... @@ -419,6 +420,12 @@ data GhcHint
    419 420
       -}
    
    420 421
       | ImportSuggestion OccName ImportSuggestion
    
    421 422
     
    
    423
    +  {-| Suggest to change an export item, e.g. to remove a namespace specifier.
    
    424
    +
    
    425
    +      Test cases: T12488a, T12488a_foo, T12488e, T12488g, T25899e2
    
    426
    +  -}
    
    427
    +  | SuggestChangeExportItem ExportItemSuggestion
    
    428
    +
    
    422 429
       {-| Found a pragma in the body of a module, suggest placing it in the header.
    
    423 430
       -}
    
    424 431
       | SuggestPlacePragmaInHeader
    
    ... ... @@ -556,6 +563,11 @@ data ImportItemSuggestion =
    556 563
         -- Why no 'ImportItemAddData'?  Because the suggestion to add 'data' is
    
    557 564
         -- represented by the 'ImportDataCon' constructor of 'ImportSuggestion'.
    
    558 565
     
    
    566
    +-- | Suggest to change an export item.
    
    567
    +data ExportItemSuggestion =
    
    568
    +    ExportItemRemoveSubordinateType
    
    569
    +  | ExportItemRemoveSubordinateData
    
    570
    +
    
    559 571
     -- | Suggest how to fix an import.
    
    560 572
     data ImportSuggestion
    
    561 573
       -- | Some module exports what we want, but we aren't explicitly importing it.
    

  • compiler/GHC/Types/Hint/Ppr.hs
    ... ... @@ -214,6 +214,10 @@ instance Outputable GhcHint where
    214 214
                                      <+> pprQuotedList parents
    
    215 215
         ImportSuggestion occ_name import_suggestion
    
    216 216
           -> pprImportSuggestion occ_name import_suggestion
    
    217
    +    SuggestChangeExportItem export_item_suggestion
    
    218
    +      -> case export_item_suggestion of
    
    219
    +           ExportItemRemoveSubordinateType -> text "Remove the" <+> quotes (text "type") <+> text "keyword"
    
    220
    +           ExportItemRemoveSubordinateData -> text "Remove the" <+> quotes (text "data") <+> text "keyword"
    
    217 221
         SuggestPlacePragmaInHeader
    
    218 222
           -> text "Perhaps you meant to place it in the module header?"
    
    219 223
           $$ text "The module header is the section at the top of the file, before the" <+> quotes (text "module") <+> text "keyword"
    

  • compiler/GHC/Types/Name/Reader.hs
    ... ... @@ -1182,8 +1182,12 @@ data LookupGRE info where
    1182 1182
     
    
    1183 1183
       -- | Look up children 'GlobalRdrElt's with a given 'Parent'.
    
    1184 1184
       LookupChildren
    
    1185
    -    :: ParentGRE        -- ^ the parent
    
    1186
    -    -> OccName          -- ^ the child 'OccName' to look up
    
    1185
    +    :: { lookupParentGRE :: ParentGRE     -- ^ the parent
    
    1186
    +       , lookupChildOccName :: OccName    -- ^ the child 'OccName' to look up
    
    1187
    +       , lookupChildrenInAllNameSpaces :: Bool
    
    1188
    +          -- ^ whether to look in *all* 'NameSpace's, or just
    
    1189
    +          -- in the 'NameSpace' of the 'OccName'
    
    1190
    +       }
    
    1187 1191
         -> LookupGRE GREInfo
    
    1188 1192
     
    
    1189 1193
     -- | How should we look up in a 'GlobalRdrEnv'?
    
    ... ... @@ -1420,10 +1424,15 @@ lookupGRE env = \case
    1420 1424
           occ = nameOccName nm
    
    1421 1425
           lkup | all_ns    = concat $ lookupOccEnv_AllNameSpaces env occ
    
    1422 1426
                | otherwise = fromMaybe [] $ lookupOccEnv env occ
    
    1423
    -  LookupChildren parent child_occ ->
    
    1424
    -    let ns = occNameSpace child_occ
    
    1425
    -        all_gres = concat $ lookupOccEnv_AllNameSpaces env child_occ
    
    1426
    -    in highestPriorityGREs (childGREPriority parent ns) all_gres
    
    1427
    +  LookupChildren { lookupParentGRE = parent
    
    1428
    +                 , lookupChildOccName = child_occ
    
    1429
    +                 , lookupChildrenInAllNameSpaces = all_ns } ->
    
    1430
    +      highestPriorityGREs (childGREPriority parent ns) $
    
    1431
    +      concat $ lkup env child_occ
    
    1432
    +    where
    
    1433
    +      ns = occNameSpace child_occ
    
    1434
    +      lkup | all_ns    = lookupOccEnv_AllNameSpaces
    
    1435
    +           | otherwise = lookupOccEnv_WithFields
    
    1427 1436
     
    
    1428 1437
     -- | Collect the 'GlobalRdrElt's with the highest priority according
    
    1429 1438
     -- to the given function (lower value <=> higher priority).
    

  • testsuite/tests/module/mod4.stderr
    1
    -
    
    2
    -mod4.hs:2:10: error: [GHC-76037]
    
    3
    -    • Not in scope: data constructor ‘K2’
    
    1
    +mod4.hs:2:10: error: [GHC-11592]
    
    2
    +    • The data type ‘T’ does not define a child named ‘K2’,
    
    3
    +      nor is there a pattern synonym of that name in scope.
    
    4 4
         • In the export: T(K1, K2)
    
    5
    -    Suggested fix: Perhaps use ‘K1’ (line 3)
    5
    +    Suggested fix: Perhaps use ‘K1’ (Defined at mod4.hs:3:10)
    
    6
    +

  • testsuite/tests/parser/should_fail/T12488c.hs
    1
    +{-# LANGUAGE PatternSynonyms #-}
    
    2
    +module T12488c ( T (pattern A) ) where
    
    3
    +
    
    4
    +data T = A
    \ No newline at end of file

  • testsuite/tests/parser/should_fail/T12488c.stderr
    1
    +T12488c.hs:2:21: error: [GHC-58481] parse error on input ‘pattern’
    
    2
    +

  • testsuite/tests/parser/should_fail/T12488d.hs
    1
    +{-# LANGUAGE NamedDefaults #-}
    
    2
    +module T12488d ( T (default C) ) where
    
    3
    +
    
    4
    +class C a where
    
    5
    +
    
    6
    +data T = A
    \ No newline at end of file

  • testsuite/tests/parser/should_fail/T12488d.stderr
    1
    +T12488d.hs:2:21: error: [GHC-58481] parse error on input ‘default’
    
    2
    +

  • testsuite/tests/parser/should_fail/all.T
    ... ... @@ -242,3 +242,5 @@ test('T25258b', normal, compile_fail, [''])
    242 242
     test('T25258c', normal, compile_fail, [''])
    
    243 243
     test('T25530', normal, compile_fail, [''])
    
    244 244
     test('T26418', normal, compile_fail, [''])
    
    245
    +test('T12488c', normal, compile_fail, [''])
    
    246
    +test('T12488d', normal, compile_fail, [''])

  • testsuite/tests/rename/should_compile/T12488b.hs
    1
    +{-# LANGUAGE ExplicitNamespaces #-}
    
    2
    +{-# LANGUAGE TypeFamilies #-}
    
    3
    +
    
    4
    +module T12488b
    
    5
    +  ( T ( data A,       -- data constructor (alphanumeric name)
    
    6
    +        data fld,     -- record field (alphanumeric name)
    
    7
    +        data (:!!),   -- data constructor (symbolic name)
    
    8
    +        data (///)    -- record field (symbolic name)
    
    9
    +      ),
    
    10
    +    C ( type F,       -- associated type (alphanumeric name)
    
    11
    +        data meth,    -- class method (alphanumeric name)
    
    12
    +        type (+++),   -- associated type (symbolic name)
    
    13
    +        data (***)    -- class method (symbolic name)
    
    14
    +      ),
    
    15
    +  ) where
    
    16
    +
    
    17
    +data T = A { fld :: Int }
    
    18
    +       | (:!!) { (///) :: Int -> Int  }
    
    19
    +
    
    20
    +class C a where
    
    21
    +  type F a
    
    22
    +  type (+++) a
    
    23
    +  meth :: a -> a
    
    24
    +  (***) :: a -> a -> a

  • testsuite/tests/rename/should_compile/T12488f.hs
    1
    +{-# LANGUAGE ExplicitNamespaces #-}
    
    2
    +{-# LANGUAGE TypeFamilies #-}
    
    3
    +
    
    4
    +module T12488f
    
    5
    +  ( C ( type (+++),   -- associated type (symbolic name)
    
    6
    +        data (++-)    -- class method (symbolic name)
    
    7
    +      ),
    
    8
    +  ) where
    
    9
    +
    
    10
    +class C a where
    
    11
    +  type (+++) a      -- exported
    
    12
    +  type (++-) a      -- not exported
    
    13
    +  (+++) :: a -> a   -- not exported
    
    14
    +  (++-) :: a -> a   -- exported

  • testsuite/tests/rename/should_compile/all.T
    ... ... @@ -245,3 +245,5 @@ test('T25899a', normal, compile, [''])
    245 245
     test('T25899b', normal, compile, [''])
    
    246 246
     test('T25899c', [extra_files(['T25899c_helper.hs'])], multimod_compile, ['T25899c', '-v0'])
    
    247 247
     test('T25899d', combined_output, ghci_script, ['T25899d.script'])
    
    248
    +test('T12488b', normal, compile, [''])
    
    249
    +test('T12488f', normal, compile, [''])

  • testsuite/tests/rename/should_fail/T12488a.hs
    1
    +{-# LANGUAGE ExplicitNamespaces #-}
    
    2
    +module T12488a
    
    3
    +  ( T (type A)
    
    4
    +  , (:!) (type (:/))
    
    5
    +  ) where
    
    6
    +
    
    7
    +data T = A
    
    8
    +
    
    9
    +data (:!) = (:/)
    \ No newline at end of file

  • testsuite/tests/rename/should_fail/T12488a.stderr
    1
    +T12488a.hs:3:5: error: [GHC-11592]
    
    2
    +    • The data type ‘T’ defines a child named ‘A’,
    
    3
    +      but it is not in the type namespace.
    
    4
    +    • In the export: T(type A)
    
    5
    +    Suggested fix: Remove the ‘type’ keyword
    
    6
    +
    
    7
    +T12488a.hs:4:5: error: [GHC-11592]
    
    8
    +    • The data type ‘:!’ defines a child named ‘:/’,
    
    9
    +      but it is not in the type namespace.
    
    10
    +    • In the export: (:!)(type (:/))
    
    11
    +    Suggested fix: Remove the ‘type’ keyword
    
    12
    +

  • testsuite/tests/rename/should_fail/T12488a_foo.hs
    1
    +{-# LANGUAGE ExplicitNamespaces #-}
    
    2
    +{-# LANGUAGE TypeFamilies #-}
    
    3
    +module T12488a_foo ( T (type A) ) where
    
    4
    +
    
    5
    +data T = A
    
    6
    +
    
    7
    +class Foo a where
    
    8
    +  type A a
    
    9
    +  foo :: a -> Int

  • testsuite/tests/rename/should_fail/T12488a_foo.stderr
    1
    +T12488a_foo.hs:3:22: error: [GHC-11592]
    
    2
    +    • The data type ‘T’ defines a child named ‘A’,
    
    3
    +      but it is not in the type namespace.
    
    4
    +    • In the export: T(type A)
    
    5
    +    Suggested fix: Remove the ‘type’ keyword
    
    6
    +

  • testsuite/tests/rename/should_fail/T12488e.hs
    1
    +{-# LANGUAGE ExplicitNamespaces #-}
    
    2
    +{-# LANGUAGE TypeFamilies #-}
    
    3
    +module T12488e
    
    4
    +  ( C (data A)
    
    5
    +  , D (data (+++))
    
    6
    +  ) where
    
    7
    +
    
    8
    +class C a where
    
    9
    +  type A a
    
    10
    +
    
    11
    +class D a where
    
    12
    +  type (+++) a
    \ No newline at end of file

  • testsuite/tests/rename/should_fail/T12488e.stderr
    1
    +T12488e.hs:4:5: error: [GHC-11592]
    
    2
    +    • The class ‘C’ defines a child named ‘A’,
    
    3
    +      but it is not in the data namespace.
    
    4
    +    • In the export: C(data A)
    
    5
    +    Suggested fix: Remove the ‘data’ keyword
    
    6
    +
    
    7
    +T12488e.hs:5:5: error: [GHC-11592]
    
    8
    +    • The class ‘D’ defines a child named ‘+++’,
    
    9
    +      but it is not in the data namespace.
    
    10
    +    • In the export: D(data (+++))
    
    11
    +    Suggested fix: Remove the ‘data’ keyword
    
    12
    +

  • testsuite/tests/rename/should_fail/T12488g.hs
    1
    +{-# LANGUAGE ExplicitNamespaces #-}
    
    2
    +{-# LANGUAGE TypeFamilies #-}
    
    3
    +module T12488g
    
    4
    +  ( C (data (+++),
    
    5
    +       type (++-))
    
    6
    +  ) where
    
    7
    +
    
    8
    +class C a where
    
    9
    +  type (+++) a
    
    10
    +  (++-) :: a -> a

  • testsuite/tests/rename/should_fail/T12488g.stderr
    1
    +T12488g.hs:4:5: error: [GHC-11592]
    
    2
    +    • The class ‘C’ defines a child named ‘++-’,
    
    3
    +      but it is not in the type namespace.
    
    4
    +    • In the export: C(data (+++), type (++-))
    
    5
    +    Suggested fixes:
    
    6
    +      • Remove the ‘type’ keyword
    
    7
    +      • Perhaps use ‘+++’ (Defined at T12488g.hs:9:3)
    
    8
    +
    
    9
    +T12488g.hs:4:5: error: [GHC-11592]
    
    10
    +    • The class ‘C’ defines a child named ‘+++’,
    
    11
    +      but it is not in the data namespace.
    
    12
    +    • In the export: C(data (+++), type (++-))
    
    13
    +    Suggested fixes:
    
    14
    +      • Remove the ‘data’ keyword
    
    15
    +      • Perhaps use ‘++-’ (Defined at T12488g.hs:10:3)
    
    16
    +

  • testsuite/tests/rename/should_fail/T25899e2.stderr
    1
    -T25899e2.hs:5:5: error: [GHC-76037]
    
    2
    -    • Not in scope: data constructor ‘MkT’
    
    1
    +T25899e2.hs:5:5: error: [GHC-11592]
    
    2
    +    • The data type ‘T’ defines a child named ‘MkT’,
    
    3
    +      but it is not in the data namespace.
    
    3 4
         • In the export: type T(data MkT)
    
    5
    +    Suggested fix: Remove the ‘data’ keyword
    
    4 6
     

  • testsuite/tests/rename/should_fail/all.T
    ... ... @@ -246,3 +246,7 @@ test('T25899e1', normal, compile_fail, [''])
    246 246
     test('T25899e2', normal, compile_fail, [''])
    
    247 247
     test('T25899e3', [extra_files(['T25899e_helper.hs'])], multimod_compile_fail, ['T25899e3', '-v0'])
    
    248 248
     test('T25899f',  [extra_files(['T25899f_helper.hs'])], multimod_compile_fail, ['T25899f', '-v0'])
    
    249
    +test('T12488a', normal, compile_fail, [''])
    
    250
    +test('T12488a_foo', normal, compile_fail, [''])
    
    251
    +test('T12488e', normal, compile_fail, [''])
    
    252
    +test('T12488g', normal, compile_fail, [''])