[Git][ghc/ghc][master] Fix namespace specifiers in subordinate exports (#12488)
Marge Bot pushed to branch master at Glasgow Haskell Compiler / GHC Commits: 5618645b by Vladislav Zavialov at 2025-10-30T12:39:33-04:00 Fix namespace specifiers in subordinate exports (#12488) This patch fixes an oversight in the `lookupChildrenExport` function that caused explicit namespace specifiers of subordinate export items to be ignored: module M (T (type A)) where -- should be rejected data T = A Based on the `IEWrappedName` data type, there are 5 cases to consider: 1. Unadorned name: P(X) 2. Named default: P(default X) 3. Pattern synonym: P(pattern X) 4. Type name: P(type X) 5. Data name: P(data X) Case 1 is already handled correctly; cases 2 and 3 are parse errors; and it is cases 4 and 5 that we are concerned with in this patch. Following the precedent established in `LookupExactName`, we introduce a boolean flag in `LookupChildren` to control whether to look up in all namespaces or in a specific one. If an export item is accompanied by an explicit namespace specifier `type` or `data`, we restrict the lookup in `lookupGRE` to a specific namespace. The newly introduced diagnostic `TcRnExportedSubordinateNotFound` provides error messages and suggestions more tailored to this context than the previously used `reportUnboundName`. - - - - - 28 changed files: - compiler/GHC/Rename/Env.hs - compiler/GHC/Rename/Names.hs - compiler/GHC/Tc/Errors/Ppr.hs - compiler/GHC/Tc/Errors/Types.hs - compiler/GHC/Tc/Gen/Export.hs - compiler/GHC/Types/Error/Codes.hs - compiler/GHC/Types/Hint.hs - compiler/GHC/Types/Hint/Ppr.hs - compiler/GHC/Types/Name/Reader.hs - testsuite/tests/module/mod4.stderr - + testsuite/tests/parser/should_fail/T12488c.hs - + testsuite/tests/parser/should_fail/T12488c.stderr - + testsuite/tests/parser/should_fail/T12488d.hs - + testsuite/tests/parser/should_fail/T12488d.stderr - testsuite/tests/parser/should_fail/all.T - + testsuite/tests/rename/should_compile/T12488b.hs - + testsuite/tests/rename/should_compile/T12488f.hs - testsuite/tests/rename/should_compile/all.T - + testsuite/tests/rename/should_fail/T12488a.hs - + testsuite/tests/rename/should_fail/T12488a.stderr - + testsuite/tests/rename/should_fail/T12488a_foo.hs - + testsuite/tests/rename/should_fail/T12488a_foo.stderr - + testsuite/tests/rename/should_fail/T12488e.hs - + testsuite/tests/rename/should_fail/T12488e.stderr - + testsuite/tests/rename/should_fail/T12488g.hs - + testsuite/tests/rename/should_fail/T12488g.stderr - testsuite/tests/rename/should_fail/T25899e2.stderr - testsuite/tests/rename/should_fail/all.T Changes: ===================================== compiler/GHC/Rename/Env.hs ===================================== @@ -679,19 +679,20 @@ lookupGlobalOccRn will find it. -} -- | Used in export lists to lookup the children. -lookupSubBndrOcc_helper :: Bool +lookupSubBndrOcc_helper :: Bool -- ^ must have a parent + -> Bool -- ^ look up in all namespaces -> DeprecationWarnings -> ParentGRE -- ^ parent -> RdrName -- ^ thing we are looking up -> RnM ChildLookupResult -lookupSubBndrOcc_helper must_have_parent warn_if_deprec parent_gre rdr_name +lookupSubBndrOcc_helper must_have_parent all_ns warn_if_deprec parent_gre rdr_name | isUnboundName (parentGRE_name parent_gre) -- Avoid an error cascade = return (FoundChild (mkUnboundGRERdr rdr_name)) | otherwise = do gre_env <- getGlobalRdrEnv - let original_gres = lookupGRE gre_env (LookupChildren parent_gre (rdrNameOcc rdr_name)) + let original_gres = lookupGRE gre_env (LookupChildren parent_gre (rdrNameOcc rdr_name) all_ns) picked_gres = pick_gres original_gres -- The remaining GREs are things that we *could* export here. -- Note that this includes things which have `NoParent`; @@ -844,7 +845,7 @@ lookupSubBndrOcc :: DeprecationWarnings lookupSubBndrOcc warn_if_deprec the_parent what_subordinate rdr_name = lookupExactOrOrig rdr_name (Right . greName) $ -- This happens for built-in classes, see mod052 for example - do { child <- lookupSubBndrOcc_helper True warn_if_deprec the_parent rdr_name + do { child <- lookupSubBndrOcc_helper True True warn_if_deprec the_parent rdr_name ; return $ case child of FoundChild g -> Right (greName g) NameNotFound -> Left unknown_sub ===================================== compiler/GHC/Rename/Names.hs ===================================== @@ -23,6 +23,7 @@ module GHC.Rename.Names ( checkConName, mkChildEnv, findChildren, + mkBadExportSubordinate, findImportUsage, getMinimalImports, printMinimalImports, @@ -1423,6 +1424,15 @@ filterImports hsc_env iface decl_spec (Just (want_hiding, L l import_items)) where name = greName gre +-- | Assuming a subordinate item could not be found, do another lookup for a +-- more specific error message. +mkBadExportSubordinate :: [GlobalRdrElt] -> LIEWrappedName GhcPs -> BadExportSubordinate +mkBadExportSubordinate child_gres n = + case lookupChildren child_gres [n] of + (LookupChildNonType {lce_nontype_item = g} : _, _) -> BadExportSubordinateNonType g + (LookupChildNonData {lce_nondata_item = g} : _, _) -> BadExportSubordinateNonData g + _ -> BadExportSubordinateNotFound n + type IELookupM = MaybeErr IELookupError data IELookupWarning ===================================== compiler/GHC/Tc/Errors/Ppr.hs ===================================== @@ -675,6 +675,43 @@ instance Diagnostic TcRnMessage where what_is = pp_category ty_thing thing = ppr $ nameOccName child parents = map ppr parent_names + TcRnExportedSubordinateNotFound parent_gre k _ -> + mkSimpleDecorated $ + case k of + BadExportSubordinateNotFound wname -> + let child_name = lieWrappedName wname + child_name_fs = occNameFS (rdrNameOcc child_name) + suggest_patsyn = allow_patsyn && could_be_patsyn + could_be_patsyn = + case unLoc wname of + IEName{} -> isLexCon child_name_fs + IEData{} -> isLexCon child_name_fs + IEPattern{} -> True + IEType{} -> False + IEDefault{} -> False + basic_msg = + what_parent <+> quotes (ppr parent_name) + <+> "does not define a child named" <+> quotes (ppr child_name) + patsyn_msg = + text "nor is there a pattern synonym of that name in scope" + combined_msg + | suggest_patsyn = basic_msg <> comma $$ patsyn_msg <> dot + | otherwise = basic_msg <> dot + in combined_msg + BadExportSubordinateNonType gre -> + let child_name = greName gre + in what_parent <+> quotes (ppr parent_name) <+> "defines a child named" <+> quotes (ppr child_name) <> comma + $$ text "but it is not in the type namespace." + BadExportSubordinateNonData gre -> + let child_name = greName gre + in what_parent <+> quotes (ppr parent_name) <+> "defines a child named" <+> quotes (ppr child_name) <> comma + $$ text "but it is not in the data namespace." + where + parent_name = greName parent_gre + (what_parent, allow_patsyn) = case greInfo parent_gre of + IAmTyCon ClassFlavour -> (text "The class", False) + IAmTyCon _ -> (text "The data type", True) + _ -> (text "The item", False) TcRnConflictingExports occ child_gre1 ie1 child_gre2 ie2 -> mkSimpleDecorated $ vcat [ text "Conflicting exports for" <+> quotes (ppr occ) <> colon @@ -2204,6 +2241,8 @@ instance Diagnostic TcRnMessage where -> WarningWithFlag Opt_WarnDuplicateExports TcRnExportedParentChildMismatch{} -> ErrorWithoutFlag + TcRnExportedSubordinateNotFound{} + -> ErrorWithoutFlag TcRnConflictingExports{} -> ErrorWithoutFlag TcRnDuplicateFieldExport {} @@ -2875,6 +2914,13 @@ instance Diagnostic TcRnMessage where -> noHints TcRnExportedParentChildMismatch{} -> noHints + TcRnExportedSubordinateNotFound _ k similar_names + -> ns_spec_hints ++ similar_names + where + ns_spec_hints = case k of + BadExportSubordinateNotFound{} -> noHints + BadExportSubordinateNonType{} -> [SuggestChangeExportItem ExportItemRemoveSubordinateType] + BadExportSubordinateNonData{} -> [SuggestChangeExportItem ExportItemRemoveSubordinateData] TcRnConflictingExports{} -> noHints TcRnDuplicateFieldExport {} ===================================== compiler/GHC/Tc/Errors/Types.hs ===================================== @@ -83,7 +83,6 @@ module GHC.Tc.Errors.Types ( , Subordinate(..), pprSubordinate , ImportError(..) , WhatLooking(..) - , lookingForSubordinate , HoleError(..) , CoercibleMsg(..) , NoBuiltinInstanceMsg(..) @@ -117,6 +116,7 @@ module GHC.Tc.Errors.Types ( , HsTyVarBndrExistentialFlag(..) , TySynCycleTyCons , BadImportKind(..) + , BadExportSubordinate(..) , DodgyImportsReason (..) , ImportLookupExtensions (..) , ImportLookupReason (..) @@ -1664,6 +1664,26 @@ data TcRnMessage where -> Name -- ^ child -> [Name] -> TcRnMessage + {-| TcRnExportedSubordinateNotFound is an error that occurs when the name of a + subordinate export item is not in scope. + + Example: + module M (T(X)) where -- X is not in scope + data T = Y + + Test cases: module/mod4 + rename/should_fail/T12488a + rename/should_fail/T12488a_foo + rename/should_fail/T12488e + rename/should_fail/T12488g + rename/should_fail/T25899e2 + -} + TcRnExportedSubordinateNotFound + :: GlobalRdrElt -- ^ parent + -> BadExportSubordinate + -> [GhcHint] -- ^ similar name suggestions + -> TcRnMessage + {-| TcRnConflictingExports is an error that occurs when different identifiers that have the same name are being exported by a module. @@ -5829,6 +5849,11 @@ data BadImportKind | BadImportAvailVar deriving Generic +data BadExportSubordinate + = BadExportSubordinateNotFound !(LIEWrappedName GhcPs) + | BadExportSubordinateNonType !GlobalRdrElt + | BadExportSubordinateNonData !GlobalRdrElt + {- Note [Reasons for BadImportAvailTyCon] ~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~ BadImportAvailTyCon means a name is available in the TcCls namespace @@ -6065,15 +6090,6 @@ data WhatLooking = WL_Anything -- is no point in suggesting alternative spellings deriving (Eq, Show) --- | In what namespaces should we look for a subordinate --- of the given 'GlobalRdrElt'. -lookingForSubordinate :: GlobalRdrElt -> WhatLooking -lookingForSubordinate parent_gre = - case greInfo parent_gre of - IAmTyCon ClassFlavour - -> WL_TyCon_or_TermVar - _ -> WL_Term - -- | This datatype collates instances that match or unifier, -- in order to report an error message for an unsolved typeclass constraint. data PotentialInstances ===================================== compiler/GHC/Tc/Gen/Export.hs ===================================== @@ -22,7 +22,7 @@ import GHC.Rename.Doc import GHC.Rename.Module import GHC.Rename.Names import GHC.Rename.Env -import GHC.Rename.Unbound ( reportUnboundName ) +import GHC.Rename.Unbound ( mkUnboundNameRdr ) import GHC.Rename.Splice import GHC.Unit.Module import GHC.Unit.Module.Imported @@ -30,13 +30,13 @@ import GHC.Unit.Module.Warnings import GHC.Core.TyCon import GHC.Utils.Outputable import GHC.Utils.Panic +import GHC.Utils.Misc (fuzzyLookup) import GHC.Core.ConLike import GHC.Core.PatSyn import GHC.Data.Maybe import GHC.Data.FastString (fsLit) import GHC.Driver.Env import GHC.Driver.DynFlags -import GHC.Parser.PostProcess ( setRdrNameSpace ) import qualified GHC.LanguageExtensions as LangExt import GHC.Types.Unique.Map @@ -50,6 +50,7 @@ import GHC.Types.SourceFile import GHC.Types.Id import GHC.Types.Id.Info import GHC.Types.Name.Reader +import GHC.Types.Hint import Control.Arrow ( first ) import Control.Monad ( when ) @@ -590,8 +591,9 @@ exports_from_avail (Just (L _ rdr_items)) rdr_env imports this_mod lookup_ie_kids_with :: GlobalRdrElt -> [LIEWrappedName GhcPs] -> RnM ([LIEWrappedName GhcRn], [GlobalRdrElt]) lookup_ie_kids_with gre sub_rdrs = - do { kids <- lookupChildrenExport gre sub_rdrs - ; return (map fst kids, map snd kids) } + do { let child_gres = findChildren kids_env (greName gre) + ; kids <- lookupChildrenExport gre child_gres sub_rdrs + ; return (unzip kids) } lookup_ie_kids_all :: IE GhcPs -> LIEWrappedName GhcPs -> GlobalRdrElt -> RnM [GlobalRdrElt] @@ -782,9 +784,10 @@ If the module has NO main function: lookupChildrenExport :: GlobalRdrElt + -> [GlobalRdrElt] -> [LIEWrappedName GhcPs] -> RnM ([(LIEWrappedName GhcRn, GlobalRdrElt)]) -lookupChildrenExport parent_gre rdr_items = mapAndReportM doOne rdr_items +lookupChildrenExport parent_gre child_gres rdr_items = mapAndReportM doOne rdr_items where spec_parent = greName parent_gre -- Process an individual child @@ -792,24 +795,23 @@ lookupChildrenExport parent_gre rdr_items = mapAndReportM doOne rdr_items -> RnM (LIEWrappedName GhcRn, GlobalRdrElt) doOne n = do - let bareName = (ieWrappedName . unLoc) n + let all_ns = case unLoc n of + IEName{} -> True -- Ignore the namespace iff the name is unadorned + _ -> False + let bareName = lieWrappedName n -- Do not report export list declaration deprecations - name <- lookupSubBndrOcc_helper False ExportDeprecationWarnings + name <- lookupSubBndrOcc_helper False all_ns ExportDeprecationWarnings (ParentGRE spec_parent (greInfo parent_gre)) bareName traceRn "lookupChildrenExport" (ppr name) - -- Default to data constructors for slightly better error - -- messages - let unboundName :: RdrName - unboundName = if rdrNameSpace bareName == varName - then bareName - else setRdrNameSpace bareName dataName case name of NameNotFound -> - do { ub <- reportUnboundName (lookingForSubordinate parent_gre) unboundName - ; let l = getLoc n + do { let err = mkBadExportSubordinate child_gres n + similar_names = subordinateExportSimilarNames bareName child_gres + ; addDiagnosticTc (TcRnExportedSubordinateNotFound parent_gre err similar_names) + ; let ub = mkUnboundNameRdr bareName gre = mkLocalGRE UnboundGRE NoParent ub - ; return (L l (IEName noExtField (L (l2l l) ub)), gre)} + ; return (replaceLWrappedName n ub, gre)} FoundChild child@(GRE { gre_name = child_nm, gre_par = par }) -> do { checkPatSynParent spec_parent par child_nm ; checkThLocalNameNoLift (ieLWrappedUserRdrName n child_nm) @@ -817,6 +819,22 @@ lookupChildrenExport parent_gre rdr_items = mapAndReportM doOne rdr_items } IncorrectParent p c gs -> failWithDcErr (parentGRE_name p) (greName c) gs +subordinateExportSimilarNames :: RdrName -> [GlobalRdrElt] -> [GhcHint] +subordinateExportSimilarNames rdr_name child_gres = + -- At the moment, we only suggest other children of the same parent. + -- One possible improvement would be to suggest bundling pattern synonyms with + -- data types, but not with classes or type data. + case NE.nonEmpty similar_names of + Nothing -> [] + Just nms -> [SuggestSimilarNames rdr_name (fmap SimilarName nms)] + where + occ_name = rdrNameOcc rdr_name + similar_names = + fuzzyLookup (occNameString occ_name) + [(occNameString child_occ_name, greName gre) + | gre <- child_gres + , let child_occ_name = greOccName gre + , occNameFS occ_name /= occNameFS child_occ_name ] -- Note [Typing Pattern Synonym Exports] -- ~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~ ===================================== compiler/GHC/Types/Error/Codes.hs ===================================== @@ -510,6 +510,7 @@ type family GhcDiagnosticCode c = n | n -> c where GhcDiagnosticCode "TcRnDuplicateExport" = 47854 GhcDiagnosticCode "TcRnDuplicateNamedDefaultExport" = 31584 GhcDiagnosticCode "TcRnExportedParentChildMismatch" = 88993 + GhcDiagnosticCode "TcRnExportedSubordinateNotFound" = 11592 GhcDiagnosticCode "TcRnConflictingExports" = 69158 GhcDiagnosticCode "TcRnDuplicateFieldExport" = 97219 GhcDiagnosticCode "TcRnAmbiguousFieldInUpdate" = 56428 ===================================== compiler/GHC/Types/Hint.hs ===================================== @@ -7,6 +7,7 @@ module GHC.Types.Hint ( , LanguageExtensionHint(..) , ImportItemSuggestion(..) , ImportSuggestion(..) + , ExportItemSuggestion(..) , HowInScope(..) , SimilarName(..) , StarIsType(..) @@ -419,6 +420,12 @@ data GhcHint -} | ImportSuggestion OccName ImportSuggestion + {-| Suggest to change an export item, e.g. to remove a namespace specifier. + + Test cases: T12488a, T12488a_foo, T12488e, T12488g, T25899e2 + -} + | SuggestChangeExportItem ExportItemSuggestion + {-| Found a pragma in the body of a module, suggest placing it in the header. -} | SuggestPlacePragmaInHeader @@ -556,6 +563,11 @@ data ImportItemSuggestion = -- Why no 'ImportItemAddData'? Because the suggestion to add 'data' is -- represented by the 'ImportDataCon' constructor of 'ImportSuggestion'. +-- | Suggest to change an export item. +data ExportItemSuggestion = + ExportItemRemoveSubordinateType + | ExportItemRemoveSubordinateData + -- | Suggest how to fix an import. data ImportSuggestion -- | 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 <+> pprQuotedList parents ImportSuggestion occ_name import_suggestion -> pprImportSuggestion occ_name import_suggestion + SuggestChangeExportItem export_item_suggestion + -> case export_item_suggestion of + ExportItemRemoveSubordinateType -> text "Remove the" <+> quotes (text "type") <+> text "keyword" + ExportItemRemoveSubordinateData -> text "Remove the" <+> quotes (text "data") <+> text "keyword" SuggestPlacePragmaInHeader -> text "Perhaps you meant to place it in the module header?" $$ 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 -- | Look up children 'GlobalRdrElt's with a given 'Parent'. LookupChildren - :: ParentGRE -- ^ the parent - -> OccName -- ^ the child 'OccName' to look up + :: { lookupParentGRE :: ParentGRE -- ^ the parent + , lookupChildOccName :: OccName -- ^ the child 'OccName' to look up + , lookupChildrenInAllNameSpaces :: Bool + -- ^ whether to look in *all* 'NameSpace's, or just + -- in the 'NameSpace' of the 'OccName' + } -> LookupGRE GREInfo -- | How should we look up in a 'GlobalRdrEnv'? @@ -1420,10 +1424,15 @@ lookupGRE env = \case occ = nameOccName nm lkup | all_ns = concat $ lookupOccEnv_AllNameSpaces env occ | otherwise = fromMaybe [] $ lookupOccEnv env occ - LookupChildren parent child_occ -> - let ns = occNameSpace child_occ - all_gres = concat $ lookupOccEnv_AllNameSpaces env child_occ - in highestPriorityGREs (childGREPriority parent ns) all_gres + LookupChildren { lookupParentGRE = parent + , lookupChildOccName = child_occ + , lookupChildrenInAllNameSpaces = all_ns } -> + highestPriorityGREs (childGREPriority parent ns) $ + concat $ lkup env child_occ + where + ns = occNameSpace child_occ + lkup | all_ns = lookupOccEnv_AllNameSpaces + | otherwise = lookupOccEnv_WithFields -- | Collect the 'GlobalRdrElt's with the highest priority according -- to the given function (lower value <=> higher priority). ===================================== testsuite/tests/module/mod4.stderr ===================================== @@ -1,5 +1,6 @@ - -mod4.hs:2:10: error: [GHC-76037] - • Not in scope: data constructor ‘K2’ +mod4.hs:2:10: error: [GHC-11592] + • The data type ‘T’ does not define a child named ‘K2’, + nor is there a pattern synonym of that name in scope. • In the export: T(K1, K2) - Suggested fix: Perhaps use ‘K1’ (line 3) + Suggested fix: Perhaps use ‘K1’ (Defined at mod4.hs:3:10) + ===================================== testsuite/tests/parser/should_fail/T12488c.hs ===================================== @@ -0,0 +1,4 @@ +{-# LANGUAGE PatternSynonyms #-} +module T12488c ( T (pattern A) ) where + +data T = A \ No newline at end of file ===================================== testsuite/tests/parser/should_fail/T12488c.stderr ===================================== @@ -0,0 +1,2 @@ +T12488c.hs:2:21: error: [GHC-58481] parse error on input ‘pattern’ + ===================================== testsuite/tests/parser/should_fail/T12488d.hs ===================================== @@ -0,0 +1,6 @@ +{-# LANGUAGE NamedDefaults #-} +module T12488d ( T (default C) ) where + +class C a where + +data T = A \ No newline at end of file ===================================== testsuite/tests/parser/should_fail/T12488d.stderr ===================================== @@ -0,0 +1,2 @@ +T12488d.hs:2:21: error: [GHC-58481] parse error on input ‘default’ + ===================================== testsuite/tests/parser/should_fail/all.T ===================================== @@ -242,3 +242,5 @@ test('T25258b', normal, compile_fail, ['']) test('T25258c', normal, compile_fail, ['']) test('T25530', normal, compile_fail, ['']) test('T26418', normal, compile_fail, ['']) +test('T12488c', normal, compile_fail, ['']) +test('T12488d', normal, compile_fail, ['']) ===================================== testsuite/tests/rename/should_compile/T12488b.hs ===================================== @@ -0,0 +1,24 @@ +{-# LANGUAGE ExplicitNamespaces #-} +{-# LANGUAGE TypeFamilies #-} + +module T12488b + ( T ( data A, -- data constructor (alphanumeric name) + data fld, -- record field (alphanumeric name) + data (:!!), -- data constructor (symbolic name) + data (///) -- record field (symbolic name) + ), + C ( type F, -- associated type (alphanumeric name) + data meth, -- class method (alphanumeric name) + type (+++), -- associated type (symbolic name) + data (***) -- class method (symbolic name) + ), + ) where + +data T = A { fld :: Int } + | (:!!) { (///) :: Int -> Int } + +class C a where + type F a + type (+++) a + meth :: a -> a + (***) :: a -> a -> a ===================================== testsuite/tests/rename/should_compile/T12488f.hs ===================================== @@ -0,0 +1,14 @@ +{-# LANGUAGE ExplicitNamespaces #-} +{-# LANGUAGE TypeFamilies #-} + +module T12488f + ( C ( type (+++), -- associated type (symbolic name) + data (++-) -- class method (symbolic name) + ), + ) where + +class C a where + type (+++) a -- exported + type (++-) a -- not exported + (+++) :: a -> a -- not exported + (++-) :: a -> a -- exported ===================================== testsuite/tests/rename/should_compile/all.T ===================================== @@ -245,3 +245,5 @@ test('T25899a', normal, compile, ['']) test('T25899b', normal, compile, ['']) test('T25899c', [extra_files(['T25899c_helper.hs'])], multimod_compile, ['T25899c', '-v0']) test('T25899d', combined_output, ghci_script, ['T25899d.script']) +test('T12488b', normal, compile, ['']) +test('T12488f', normal, compile, ['']) ===================================== testsuite/tests/rename/should_fail/T12488a.hs ===================================== @@ -0,0 +1,9 @@ +{-# LANGUAGE ExplicitNamespaces #-} +module T12488a + ( T (type A) + , (:!) (type (:/)) + ) where + +data T = A + +data (:!) = (:/) \ No newline at end of file ===================================== testsuite/tests/rename/should_fail/T12488a.stderr ===================================== @@ -0,0 +1,12 @@ +T12488a.hs:3:5: error: [GHC-11592] + • The data type ‘T’ defines a child named ‘A’, + but it is not in the type namespace. + • In the export: T(type A) + Suggested fix: Remove the ‘type’ keyword + +T12488a.hs:4:5: error: [GHC-11592] + • The data type ‘:!’ defines a child named ‘:/’, + but it is not in the type namespace. + • In the export: (:!)(type (:/)) + Suggested fix: Remove the ‘type’ keyword + ===================================== testsuite/tests/rename/should_fail/T12488a_foo.hs ===================================== @@ -0,0 +1,9 @@ +{-# LANGUAGE ExplicitNamespaces #-} +{-# LANGUAGE TypeFamilies #-} +module T12488a_foo ( T (type A) ) where + +data T = A + +class Foo a where + type A a + foo :: a -> Int ===================================== testsuite/tests/rename/should_fail/T12488a_foo.stderr ===================================== @@ -0,0 +1,6 @@ +T12488a_foo.hs:3:22: error: [GHC-11592] + • The data type ‘T’ defines a child named ‘A’, + but it is not in the type namespace. + • In the export: T(type A) + Suggested fix: Remove the ‘type’ keyword + ===================================== testsuite/tests/rename/should_fail/T12488e.hs ===================================== @@ -0,0 +1,12 @@ +{-# LANGUAGE ExplicitNamespaces #-} +{-# LANGUAGE TypeFamilies #-} +module T12488e + ( C (data A) + , D (data (+++)) + ) where + +class C a where + type A a + +class D a where + type (+++) a \ No newline at end of file ===================================== testsuite/tests/rename/should_fail/T12488e.stderr ===================================== @@ -0,0 +1,12 @@ +T12488e.hs:4:5: error: [GHC-11592] + • The class ‘C’ defines a child named ‘A’, + but it is not in the data namespace. + • In the export: C(data A) + Suggested fix: Remove the ‘data’ keyword + +T12488e.hs:5:5: error: [GHC-11592] + • The class ‘D’ defines a child named ‘+++’, + but it is not in the data namespace. + • In the export: D(data (+++)) + Suggested fix: Remove the ‘data’ keyword + ===================================== testsuite/tests/rename/should_fail/T12488g.hs ===================================== @@ -0,0 +1,10 @@ +{-# LANGUAGE ExplicitNamespaces #-} +{-# LANGUAGE TypeFamilies #-} +module T12488g + ( C (data (+++), + type (++-)) + ) where + +class C a where + type (+++) a + (++-) :: a -> a ===================================== testsuite/tests/rename/should_fail/T12488g.stderr ===================================== @@ -0,0 +1,16 @@ +T12488g.hs:4:5: error: [GHC-11592] + • The class ‘C’ defines a child named ‘++-’, + but it is not in the type namespace. + • In the export: C(data (+++), type (++-)) + Suggested fixes: + • Remove the ‘type’ keyword + • Perhaps use ‘+++’ (Defined at T12488g.hs:9:3) + +T12488g.hs:4:5: error: [GHC-11592] + • The class ‘C’ defines a child named ‘+++’, + but it is not in the data namespace. + • In the export: C(data (+++), type (++-)) + Suggested fixes: + • Remove the ‘data’ keyword + • Perhaps use ‘++-’ (Defined at T12488g.hs:10:3) + ===================================== testsuite/tests/rename/should_fail/T25899e2.stderr ===================================== @@ -1,4 +1,6 @@ -T25899e2.hs:5:5: error: [GHC-76037] - • Not in scope: data constructor ‘MkT’ +T25899e2.hs:5:5: error: [GHC-11592] + • The data type ‘T’ defines a child named ‘MkT’, + but it is not in the data namespace. • In the export: type T(data MkT) + Suggested fix: Remove the ‘data’ keyword ===================================== testsuite/tests/rename/should_fail/all.T ===================================== @@ -246,3 +246,7 @@ test('T25899e1', normal, compile_fail, ['']) test('T25899e2', normal, compile_fail, ['']) test('T25899e3', [extra_files(['T25899e_helper.hs'])], multimod_compile_fail, ['T25899e3', '-v0']) test('T25899f', [extra_files(['T25899f_helper.hs'])], multimod_compile_fail, ['T25899f', '-v0']) +test('T12488a', normal, compile_fail, ['']) +test('T12488a_foo', normal, compile_fail, ['']) +test('T12488e', normal, compile_fail, ['']) +test('T12488g', normal, compile_fail, ['']) View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/5618645b5860bf65546108e578a7ebfd... -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/5618645b5860bf65546108e578a7ebfd... You're receiving this email because of your account on gitlab.haskell.org.
participants (1)
-
Marge Bot (@marge-bot)