Vladislav Zavialov pushed to branch wip/int-index/subordinate-export-namespaces at Glasgow Haskell Compiler / GHC

Commits:

20 changed files:

Changes:

  • 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
    ... ... @@ -674,6 +674,43 @@ instance Diagnostic TcRnMessage where
    674 674
             what_is = pp_category ty_thing
    
    675 675
             thing = ppr $ nameOccName child
    
    676 676
             parents = map ppr parent_names
    
    677
    +    TcRnExportedSubordinateNotFound parent_gre k _ ->
    
    678
    +      mkSimpleDecorated $
    
    679
    +      case k of
    
    680
    +        BadExportSubordinateNotFound wname ->
    
    681
    +          let child_name      = lieWrappedName wname
    
    682
    +              child_name_fs   = occNameFS (rdrNameOcc child_name)
    
    683
    +              suggest_patsyn  = allow_patsyn && could_be_patsyn
    
    684
    +              could_be_patsyn =
    
    685
    +                case unLoc wname of
    
    686
    +                  IEName{} -> isLexCon child_name_fs
    
    687
    +                  IEData{} -> isLexCon child_name_fs
    
    688
    +                  IEPattern{} -> True
    
    689
    +                  IEType{}    -> False
    
    690
    +                  IEDefault{} -> False
    
    691
    +              basic_msg =
    
    692
    +                what_parent <+> quotes (ppr parent_name)
    
    693
    +                <+> "does not define a child named" <+> quotes (ppr child_name)
    
    694
    +              patsyn_msg =
    
    695
    +                text "nor is there a pattern synonym of that name in scope"
    
    696
    +              combined_msg
    
    697
    +                | suggest_patsyn = basic_msg <> comma $$ patsyn_msg <> dot
    
    698
    +                | otherwise      = basic_msg <> dot
    
    699
    +          in combined_msg
    
    700
    +        BadExportSubordinateNonType gre ->
    
    701
    +          let child_name = greName gre
    
    702
    +          in what_parent <+> quotes (ppr parent_name) <+> "defines a child named" <+> quotes (ppr child_name) <> comma
    
    703
    +             $$ text "but it is not in the type namespace."
    
    704
    +        BadExportSubordinateNonData gre ->
    
    705
    +          let child_name = greName gre
    
    706
    +          in what_parent <+> quotes (ppr parent_name) <+> "defines a child named" <+> quotes (ppr child_name) <> comma
    
    707
    +             $$ text "but it is not in the data namespace."
    
    708
    +      where
    
    709
    +        parent_name = greName parent_gre
    
    710
    +        (what_parent, allow_patsyn) = case greInfo parent_gre of
    
    711
    +          IAmTyCon ClassFlavour -> (text "The class", False)
    
    712
    +          IAmTyCon _            -> (text "The data type", True)
    
    713
    +          _                     -> (text "The item", False)
    
    677 714
         TcRnConflictingExports occ child_gre1 ie1 child_gre2 ie2
    
    678 715
           -> mkSimpleDecorated $
    
    679 716
                vcat [ text "Conflicting exports for" <+> quotes (ppr occ) <> colon
    
    ... ... @@ -2203,6 +2240,8 @@ instance Diagnostic TcRnMessage where
    2203 2240
           -> WarningWithFlag Opt_WarnDuplicateExports
    
    2204 2241
         TcRnExportedParentChildMismatch{}
    
    2205 2242
           -> ErrorWithoutFlag
    
    2243
    +    TcRnExportedSubordinateNotFound{}
    
    2244
    +      -> ErrorWithoutFlag
    
    2206 2245
         TcRnConflictingExports{}
    
    2207 2246
           -> ErrorWithoutFlag
    
    2208 2247
         TcRnDuplicateFieldExport {}
    
    ... ... @@ -2874,6 +2913,13 @@ instance Diagnostic TcRnMessage where
    2874 2913
           -> noHints
    
    2875 2914
         TcRnExportedParentChildMismatch{}
    
    2876 2915
           -> noHints
    
    2916
    +    TcRnExportedSubordinateNotFound _ k similar_names
    
    2917
    +      -> ns_spec_hints ++ similar_names
    
    2918
    +      where
    
    2919
    +        ns_spec_hints = case k of
    
    2920
    +          BadExportSubordinateNotFound{} -> noHints
    
    2921
    +          BadExportSubordinateNonType{}  -> [SuggestChangeExportItem ExportItemRemoveSubordinateType]
    
    2922
    +          BadExportSubordinateNonData{}  -> [SuggestChangeExportItem ExportItemRemoveSubordinateData]
    
    2877 2923
         TcRnConflictingExports{}
    
    2878 2924
           -> noHints
    
    2879 2925
         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
       , PotentialInstances(..)
    
    ... ... @@ -114,6 +113,7 @@ module GHC.Tc.Errors.Types (
    114 113
       , HsTyVarBndrExistentialFlag(..)
    
    115 114
       , TySynCycleTyCons
    
    116 115
       , BadImportKind(..)
    
    116
    +  , BadExportSubordinate(..)
    
    117 117
       , DodgyImportsReason (..)
    
    118 118
       , ImportLookupExtensions (..)
    
    119 119
       , ImportLookupReason (..)
    
    ... ... @@ -1663,6 +1663,26 @@ data TcRnMessage where
    1663 1663
                                       -> Name -- ^ child
    
    1664 1664
                                       -> [Name] -> TcRnMessage
    
    1665 1665
     
    
    1666
    +  {-| TcRnExportedSubordinateNotFound is an error that occurs when the name of a
    
    1667
    +      subordinate export item is not in scope.
    
    1668
    +
    
    1669
    +      Example:
    
    1670
    +        module M (T(X)) where  -- X is not in scope
    
    1671
    +        data T = Y
    
    1672
    +
    
    1673
    +      Test cases: module/mod4
    
    1674
    +                  rename/should_fail/T12488a
    
    1675
    +                  rename/should_fail/T12488a_foo
    
    1676
    +                  rename/should_fail/T12488e
    
    1677
    +                  rename/should_fail/T12488g
    
    1678
    +                  rename/should_fail/T25899e2
    
    1679
    +  -}
    
    1680
    +  TcRnExportedSubordinateNotFound
    
    1681
    +    :: GlobalRdrElt                  -- ^ parent
    
    1682
    +    -> BadExportSubordinate
    
    1683
    +    -> [GhcHint]                     -- ^ similar name suggestions
    
    1684
    +    -> TcRnMessage
    
    1685
    +
    
    1666 1686
       {-| TcRnConflictingExports is an error that occurs when different identifiers that
    
    1667 1687
           have the same name are being exported by a module.
    
    1668 1688
     
    
    ... ... @@ -5822,6 +5842,11 @@ data BadImportKind
    5822 5842
       | BadImportAvailVar
    
    5823 5843
       deriving Generic
    
    5824 5844
     
    
    5845
    +data BadExportSubordinate
    
    5846
    +  = BadExportSubordinateNotFound !(LIEWrappedName GhcPs)
    
    5847
    +  | BadExportSubordinateNonType  !GlobalRdrElt
    
    5848
    +  | BadExportSubordinateNonData  !GlobalRdrElt
    
    5849
    +
    
    5825 5850
     {- Note [Reasons for BadImportAvailTyCon]
    
    5826 5851
     ~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~
    
    5827 5852
     BadImportAvailTyCon means a name is available in the TcCls namespace
    
    ... ... @@ -6016,15 +6041,6 @@ data WhatLooking = WL_Anything
    6016 6041
                          -- is no point in suggesting alternative spellings
    
    6017 6042
                      deriving (Eq, Show)
    
    6018 6043
     
    
    6019
    --- | In what namespaces should we look for a subordinate
    
    6020
    --- of the given 'GlobalRdrElt'.
    
    6021
    -lookingForSubordinate :: GlobalRdrElt -> WhatLooking
    
    6022
    -lookingForSubordinate parent_gre =
    
    6023
    -  case greInfo parent_gre of
    
    6024
    -    IAmTyCon ClassFlavour
    
    6025
    -      -> WL_TyCon_or_TermVar
    
    6026
    -    _ -> WL_Term
    
    6027
    -
    
    6028 6044
     -- | This datatype collates instances that match or unifier,
    
    6029 6045
     -- in order to report an error message for an unsolved typeclass constraint.
    
    6030 6046
     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,6 +30,7 @@ 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
    
    ... ... @@ -49,6 +50,7 @@ import GHC.Types.SourceFile
    49 50
     import GHC.Types.Id
    
    50 51
     import GHC.Types.Id.Info
    
    51 52
     import GHC.Types.Name.Reader
    
    53
    +import GHC.Types.Hint
    
    52 54
     
    
    53 55
     import Control.Arrow ( first )
    
    54 56
     import Control.Monad ( when )
    
    ... ... @@ -589,8 +591,9 @@ exports_from_avail (Just (L _ rdr_items)) rdr_env imports this_mod
    589 591
         lookup_ie_kids_with :: GlobalRdrElt -> [LIEWrappedName GhcPs]
    
    590 592
                        -> RnM ([LIEWrappedName GhcRn], [GlobalRdrElt])
    
    591 593
         lookup_ie_kids_with gre sub_rdrs =
    
    592
    -      do { kids <- lookupChildrenExport gre sub_rdrs
    
    593
    -         ; 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) }
    
    594 597
     
    
    595 598
         lookup_ie_kids_all :: IE GhcPs -> LIEWrappedName GhcPs -> GlobalRdrElt
    
    596 599
                       -> RnM [GlobalRdrElt]
    
    ... ... @@ -781,9 +784,10 @@ If the module has NO main function:
    781 784
     
    
    782 785
     
    
    783 786
     lookupChildrenExport :: GlobalRdrElt
    
    787
    +                     -> [GlobalRdrElt]
    
    784 788
                          -> [LIEWrappedName GhcPs]
    
    785 789
                          -> RnM ([(LIEWrappedName GhcRn, GlobalRdrElt)])
    
    786
    -lookupChildrenExport parent_gre rdr_items = mapAndReportM doOne rdr_items
    
    790
    +lookupChildrenExport parent_gre child_gres rdr_items = mapAndReportM doOne rdr_items
    
    787 791
         where
    
    788 792
             spec_parent = greName parent_gre
    
    789 793
             -- Process an individual child
    
    ... ... @@ -794,23 +798,20 @@ lookupChildrenExport parent_gre rdr_items = mapAndReportM doOne rdr_items
    794 798
               let all_ns = case unLoc n of
    
    795 799
                     IEName{} -> True    -- Ignore the namespace iff the name is unadorned
    
    796 800
                     _        -> False
    
    797
    -          let bareName = (ieWrappedName . unLoc) n
    
    801
    +          let bareName = lieWrappedName n
    
    798 802
                     -- Do not report export list declaration deprecations
    
    799 803
               name <-  lookupSubBndrOcc_helper False all_ns ExportDeprecationWarnings
    
    800 804
                             (ParentGRE spec_parent (greInfo parent_gre)) bareName
    
    801 805
               traceRn "lookupChildrenExport" (ppr name)
    
    802
    -          -- Default to data namespace for slightly better error messages
    
    803
    -          let unboundName :: RdrName
    
    804
    -              unboundName
    
    805
    -                | all_ns = fromMaybe bareName (demoteRdrName bareName)
    
    806
    -                | otherwise = bareName
    
    807 806
     
    
    808 807
               case name of
    
    809 808
                 NameNotFound ->
    
    810
    -              do { ub <- reportUnboundName (lookingForSubordinate parent_gre) unboundName
    
    811
    -                 ; let l = getLoc n
    
    812
    -                       gre = mkLocalGRE UnboundGRE NoParent ub
    
    813
    -                 ; return (L l (IEName noExtField (L (l2l l) ub)), gre)}
    
    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
    
    813
    +                 ; let gre = mkLocalGRE UnboundGRE NoParent ub
    
    814
    +                 ; return (replaceLWrappedName n ub, gre)}
    
    814 815
                 FoundChild child@(GRE { gre_name = child_nm, gre_par = par }) ->
    
    815 816
                   do { checkPatSynParent spec_parent par child_nm
    
    816 817
                      ; checkThLocalNameNoLift (ieLWrappedUserRdrName n child_nm)
    
    ... ... @@ -818,6 +819,22 @@ lookupChildrenExport parent_gre rdr_items = mapAndReportM doOne rdr_items
    818 819
                      }
    
    819 820
                 IncorrectParent p c gs -> failWithDcErr (parentGRE_name p) (greName c) gs
    
    820 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 ]
    
    821 838
     
    
    822 839
     -- Note [Typing Pattern Synonym Exports]
    
    823 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(..)
    
    ... ... @@ -411,6 +412,12 @@ data GhcHint
    411 412
       -}
    
    412 413
       | ImportSuggestion OccName ImportSuggestion
    
    413 414
     
    
    415
    +  {-| Suggest to change an export item, e.g. to remove a namespace specifier.
    
    416
    +
    
    417
    +      Test cases: T12488a, T12488a_foo, T12488e, T12488g, T25899e2
    
    418
    +  -}
    
    419
    +  | SuggestChangeExportItem ExportItemSuggestion
    
    420
    +
    
    414 421
       {-| Found a pragma in the body of a module, suggest placing it in the header.
    
    415 422
       -}
    
    416 423
       | SuggestPlacePragmaInHeader
    
    ... ... @@ -551,6 +558,11 @@ data ImportItemSuggestion =
    551 558
         -- Why no 'ImportItemAddData'?  Because the suggestion to add 'data' is
    
    552 559
         -- represented by the 'ImportDataCon' constructor of 'ImportSuggestion'.
    
    553 560
     
    
    561
    +-- | Suggest to change an export item.
    
    562
    +data ExportItemSuggestion =
    
    563
    +    ExportItemRemoveSubordinateType
    
    564
    +  | ExportItemRemoveSubordinateData
    
    565
    +
    
    554 566
     -- | Suggest how to fix an import.
    
    555 567
     data ImportSuggestion
    
    556 568
       -- | Some module exports what we want, but we aren't explicitly importing it.
    

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

  • 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/rename/should_compile/T12488b.hs
    1 1
     {-# LANGUAGE ExplicitNamespaces #-}
    
    2
    -module T12488b ( T (data A) ) where
    
    2
    +{-# LANGUAGE TypeFamilies #-}
    
    3 3
     
    
    4
    -data T = A
    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
    ... ... @@ -246,3 +246,4 @@ 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 248
     test('T12488b', normal, compile, [''])
    
    249
    +test('T12488f', normal, compile, [''])

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

  • testsuite/tests/rename/should_fail/T12488a.stderr
    1
    -T12488a.hs:2:18: error: [GHC-76037]
    
    2
    -    • Not in scope: type constructor or class ‘A’
    
    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.
    
    3 4
         • In the export: T(type A)
    
    4
    -    Suggested fix: Perhaps use data constructor ‘A’ (line 4)
    
    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
    
    5 12
     

  • testsuite/tests/rename/should_fail/T12488a_foo.stderr
    1
    -T12488a_foo.hs:3:22: error: [GHC-76037]
    
    2
    -    • Not in scope: type constructor or class ‘A’
    
    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.
    
    3 4
         • In the export: T(type A)
    
    4
    -    Suggested fix: Perhaps use data constructor ‘A’ (line 5)
    
    5
    +    Suggested fix: Remove the ‘type’ keyword
    
    5 6
     

  • testsuite/tests/rename/should_fail/T12488e.hs
    1 1
     {-# LANGUAGE ExplicitNamespaces #-}
    
    2 2
     {-# LANGUAGE TypeFamilies #-}
    
    3
    -module T12488e ( C (data A) ) where
    
    3
    +module T12488e
    
    4
    +  ( C (data A)
    
    5
    +  , D (data (+++))
    
    6
    +  ) where
    
    4 7
     
    
    5 8
     class C a where
    
    6 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:3:18: error: [GHC-76037]
    
    2
    -    • Not in scope: data constructor ‘A’
    
    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.
    
    3 4
         • In the export: C(data A)
    
    4
    -    Suggested fix: Perhaps use type constructor or class ‘A’ (line 6)
    
    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
    
    5 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
    ... ... @@ -249,3 +249,4 @@ test('T25899f', [extra_files(['T25899f_helper.hs'])], multimod_compile_fail, ['
    249 249
     test('T12488a', normal, compile_fail, [''])
    
    250 250
     test('T12488a_foo', normal, compile_fail, [''])
    
    251 251
     test('T12488e', normal, compile_fail, [''])
    
    252
    +test('T12488g', normal, compile_fail, [''])