Vladislav Zavialov pushed to branch wip/int-index/enforce-namespaces at Glasgow Haskell Compiler / GHC
Commits:
-
b911a6f1
by Vladislav Zavialov at 2025-04-26T02:18:54+02:00
29 changed files:
- compiler/GHC/Rename/Names.hs
- compiler/GHC/Tc/Errors/Ppr.hs
- compiler/GHC/Tc/Errors/Types.hs
- compiler/GHC/Types/Error/Codes.hs
- docs/users_guide/9.14.1-notes.rst
- docs/users_guide/exts/explicit_namespaces.rst
- testsuite/tests/driver/RecompExports/RecompExports1.stderr
- testsuite/tests/driver/RecompExports/RecompExports4.stderr
- testsuite/tests/module/T21826.stderr
- testsuite/tests/module/mod81.stderr
- testsuite/tests/module/mod91.stderr
- + testsuite/tests/rename/should_compile/T22581c.hs
- + testsuite/tests/rename/should_compile/T22581c_helper.hs
- + testsuite/tests/rename/should_compile/T22581d.script
- + testsuite/tests/rename/should_compile/T22581d.stdout
- + testsuite/tests/rename/should_compile/T25991a.hs
- + testsuite/tests/rename/should_compile/T25991a_helper.hs
- testsuite/tests/rename/should_compile/all.T
- + testsuite/tests/rename/should_fail/T22581a.hs
- + testsuite/tests/rename/should_fail/T22581a.stderr
- + testsuite/tests/rename/should_fail/T22581a_helper.hs
- + testsuite/tests/rename/should_fail/T22581b.hs
- + testsuite/tests/rename/should_fail/T22581b.stderr
- + testsuite/tests/rename/should_fail/T22581b_helper.hs
- + testsuite/tests/rename/should_fail/T25991b1.hs
- + testsuite/tests/rename/should_fail/T25991b2.hs
- + testsuite/tests/rename/should_fail/T25991b_helper.hs
- testsuite/tests/rename/should_fail/T9006.stderr
- testsuite/tests/rename/should_fail/all.T
Changes:
| ... | ... | @@ -1256,7 +1256,7 @@ filterImports hsc_env iface decl_spec (Just (want_hiding, L l import_items)) |
| 1256 | 1256 | -- 'BadImportW' is only constructed below in 'handle_bad_import', in
|
| 1257 | 1257 | -- the 'EverythingBut' case, so that's what we pass to
|
| 1258 | 1258 | -- 'badImportItemErr'.
|
| 1259 | - reason <- badImportItemErr iface decl_spec ie IsNotSubordinate all_avails
|
|
| 1259 | + (reason : _) <- badImportItemErr iface decl_spec ie IsNotSubordinate all_avails
|
|
| 1260 | 1260 | pure (TcRnDodgyImports (DodgyImportsHiding reason))
|
| 1261 | 1261 | warning_msg (DeprecatedExport n w) =
|
| 1262 | 1262 | pure $ TcRnPragmaWarning
|
| ... | ... | @@ -1268,15 +1268,15 @@ filterImports hsc_env iface decl_spec (Just (want_hiding, L l import_items)) |
| 1268 | 1268 | run_lookup :: IELookupM a -> TcRn (Maybe a)
|
| 1269 | 1269 | run_lookup m = case m of
|
| 1270 | 1270 | Failed err -> do
|
| 1271 | - msg <- lookup_err_msg err
|
|
| 1272 | - addErr (TcRnImportLookup msg)
|
|
| 1271 | + msgs <- lookup_err_msgs err
|
|
| 1272 | + mapM_ addErr [TcRnImportLookup msg | msg <- msgs]
|
|
| 1273 | 1273 | return Nothing
|
| 1274 | 1274 | Succeeded a -> return (Just a)
|
| 1275 | 1275 | |
| 1276 | - lookup_err_msg err = case err of
|
|
| 1276 | + lookup_err_msgs err = case err of
|
|
| 1277 | 1277 | BadImport ie sub -> badImportItemErr iface decl_spec ie sub all_avails
|
| 1278 | - IllegalImport -> pure ImportLookupIllegal
|
|
| 1279 | - QualImportError rdr -> pure (ImportLookupQualified rdr)
|
|
| 1278 | + IllegalImport -> pure [ImportLookupIllegal]
|
|
| 1279 | + QualImportError rdr -> pure [ImportLookupQualified rdr]
|
|
| 1280 | 1280 | |
| 1281 | 1281 | -- For each import item, we convert its RdrNames to Names,
|
| 1282 | 1282 | -- and at the same time compute all the GlobalRdrElt corresponding
|
| ... | ... | @@ -1362,13 +1362,24 @@ filterImports hsc_env iface decl_spec (Just (want_hiding, L l import_items)) |
| 1362 | 1362 | -- See Note [Importing DuplicateRecordFields]
|
| 1363 | 1363 | case lookupChildren subnames rdr_ns of
|
| 1364 | 1364 | |
| 1365 | - Failed rdrs -> failLookupWith $
|
|
| 1366 | - BadImport (IEThingWith (deprecation, ann) ltc wc rdrs noDocstring)
|
|
| 1367 | - (IsSubordinate { subordinate_parent = gre})
|
|
| 1365 | + Failed errs -> failLookupWith $ BadImport ie subordinate_err
|
|
| 1368 | 1366 | -- We are trying to import T( a,b,c,d ), and failed
|
| 1369 | 1367 | -- to find 'b' and 'd'. So we make up an import item
|
| 1370 | 1368 | -- to report as failing, namely T( b, d ).
|
| 1371 | - -- c.f. #15412
|
|
| 1369 | + -- c.f. #15413
|
|
| 1370 | + where
|
|
| 1371 | + items = map lce_wrapped_name errs
|
|
| 1372 | + ie = IEThingWith (deprecation, ann) ltc wc items noDocstring
|
|
| 1373 | + subordinate_err =
|
|
| 1374 | + assertPpr (length unavailable + length nontype == length items)
|
|
| 1375 | + (ppr items) $
|
|
| 1376 | + IsSubordinateError { subordinate_err_parent = gre
|
|
| 1377 | + , subordinate_err_unavailable = unavailable
|
|
| 1378 | + , subordinate_err_nontype = nontype }
|
|
| 1379 | + unavailable =
|
|
| 1380 | + [ (occNameFS . rdrNameOcc . ieWrappedName) wname
|
|
| 1381 | + | LookupChildNotFound (L _ wname) <- errs ]
|
|
| 1382 | + nontype = [ g | LookupChildNonType _ g <- errs ]
|
|
| 1372 | 1383 | |
| 1373 | 1384 | Succeeded childnames ->
|
| 1374 | 1385 | return ([ (IEThingWith (Nothing, ann) (L l name') wc childnames' noDocstring
|
| ... | ... | @@ -1414,13 +1425,15 @@ data IELookupWarning |
| 1414 | 1425 | | DeprecatedExport Name (WarningTxt GhcRn)
|
| 1415 | 1426 | |
| 1416 | 1427 | -- | Is this import/export item a subordinate or not?
|
| 1417 | -data IsSubordinate
|
|
| 1418 | - = IsSubordinate { subordinate_parent :: GlobalRdrElt }
|
|
| 1428 | +data IsSubordinateError
|
|
| 1429 | + = IsSubordinateError { subordinate_err_parent :: !GlobalRdrElt
|
|
| 1430 | + , subordinate_err_unavailable :: [FastString]
|
|
| 1431 | + , subordinate_err_nontype :: [GlobalRdrElt] }
|
|
| 1419 | 1432 | | IsNotSubordinate
|
| 1420 | 1433 | |
| 1421 | 1434 | data IELookupError
|
| 1422 | 1435 | = QualImportError RdrName
|
| 1423 | - | BadImport (IE GhcPs) IsSubordinate
|
|
| 1436 | + | BadImport (IE GhcPs) IsSubordinateError
|
|
| 1424 | 1437 | | IllegalImport
|
| 1425 | 1438 | |
| 1426 | 1439 | failLookupWith :: IELookupError -> IELookupM a
|
| ... | ... | @@ -1603,9 +1616,14 @@ mkChildEnv gres = foldr add emptyNameEnv gres |
| 1603 | 1616 | findChildren :: NameEnv [a] -> Name -> [a]
|
| 1604 | 1617 | findChildren env n = lookupNameEnv env n `orElse` []
|
| 1605 | 1618 | |
| 1619 | +data LookupChildError
|
|
| 1620 | + = LookupChildNotFound { lce_wrapped_name :: !(LIEWrappedName GhcPs) }
|
|
| 1621 | + | LookupChildNonType { lce_wrapped_name :: !(LIEWrappedName GhcPs)
|
|
| 1622 | + , _lce_nontype_item :: !GlobalRdrElt }
|
|
| 1623 | + |
|
| 1606 | 1624 | lookupChildren :: [GlobalRdrElt]
|
| 1607 | 1625 | -> [LIEWrappedName GhcPs]
|
| 1608 | - -> MaybeErr [LIEWrappedName GhcPs] -- The ones for which the lookup failed
|
|
| 1626 | + -> MaybeErr [LookupChildError] -- The ones for which the lookup failed
|
|
| 1609 | 1627 | [LocatedA GlobalRdrElt]
|
| 1610 | 1628 | -- (lookupChildren all_kids rdr_items) maps each rdr_item to its
|
| 1611 | 1629 | -- corresponding Name all_kids, if the former exists
|
| ... | ... | @@ -1623,21 +1641,25 @@ lookupChildren all_kids rdr_items |
| 1623 | 1641 | = Failed fails
|
| 1624 | 1642 | where
|
| 1625 | 1643 | mb_xs = map doOne rdr_items
|
| 1626 | - fails = [ bad_rdr | Failed bad_rdr <- mb_xs ]
|
|
| 1627 | - oks = [ ok | Succeeded ok <- mb_xs ]
|
|
| 1644 | + fails = [ err | Failed err <- mb_xs ]
|
|
| 1645 | + oks = [ ok | Succeeded ok <- mb_xs ]
|
|
| 1628 | 1646 | oks :: [[LocatedA GlobalRdrElt]]
|
| 1629 | 1647 | |
| 1630 | - doOne item@(L l r)
|
|
| 1631 | - = case (lookupFsEnv kid_env . occNameFS . rdrNameOcc . ieWrappedName) r of
|
|
| 1632 | - Just [g]
|
|
| 1633 | - | not $ isRecFldGRE g
|
|
| 1634 | - -> Succeeded [L l g]
|
|
| 1635 | - Just gs
|
|
| 1636 | - | all isRecFldGRE gs
|
|
| 1637 | - -> Succeeded $ map (L l) gs
|
|
| 1638 | - _ -> Failed item
|
|
| 1648 | + doOne :: LIEWrappedName GhcPs -> MaybeErr LookupChildError [LocatedA GlobalRdrElt]
|
|
| 1649 | + doOne item@(L l r) =
|
|
| 1650 | + case r of
|
|
| 1651 | + IEName{} | notNull val_gs -> Succeeded [L l g | g <- val_gs]
|
|
| 1652 | + IEName{} | notNull typ_gs -> Succeeded [L l g | g <- typ_gs]
|
|
| 1653 | + IEType{} | notNull typ_gs -> Succeeded [L l g | g <- typ_gs]
|
|
| 1654 | + IEType{} | (g:_) <- val_gs -> Failed $ LookupChildNonType item g
|
|
| 1655 | + _ -> Failed $ LookupChildNotFound item
|
|
| 1656 | + where
|
|
| 1657 | + fs = (occNameFS . rdrNameOcc . ieWrappedName) r
|
|
| 1658 | + gs = fromMaybe [] (lookupFsEnv kid_env fs)
|
|
| 1659 | + (val_gs, typ_gs) = partition (isValNameSpace . greNameSpace) gs
|
|
| 1639 | 1660 | |
| 1640 | 1661 | -- See Note [Children for duplicate record fields]
|
| 1662 | + kid_env :: FastStringEnv [GlobalRdrElt]
|
|
| 1641 | 1663 | kid_env = extendFsEnvList_C (++) emptyFsEnv
|
| 1642 | 1664 | [(occNameFS (occName x), [x]) | x <- all_kids]
|
| 1643 | 1665 | |
| ... | ... | @@ -2297,9 +2319,10 @@ DRFPatSynExport for a test of this. |
| 2297 | 2319 | -}
|
| 2298 | 2320 | |
| 2299 | 2321 | badImportItemErr
|
| 2300 | - :: ModIface -> ImpDeclSpec -> IE GhcPs -> IsSubordinate
|
|
| 2322 | + :: ModIface -> ImpDeclSpec -> IE GhcPs
|
|
| 2323 | + -> IsSubordinateError
|
|
| 2301 | 2324 | -> [AvailInfo]
|
| 2302 | - -> TcRn ImportLookupReason
|
|
| 2325 | + -> TcRn [ImportLookupReason] -- non-empty
|
|
| 2303 | 2326 | badImportItemErr iface decl_spec ie sub avails = do
|
| 2304 | 2327 | patsyns_enabled <- xoptM LangExt.PatternSynonyms
|
| 2305 | 2328 | expl_ns_enabled <- xoptM LangExt.ExplicitNamespaces
|
| ... | ... | @@ -2307,20 +2330,24 @@ badImportItemErr iface decl_spec ie sub avails = do |
| 2307 | 2330 | hsc_env <- getTopEnv
|
| 2308 | 2331 | let rdr_env = mkGlobalRdrEnv
|
| 2309 | 2332 | $ gresFromAvails hsc_env (Just imp_spec) all_avails
|
| 2310 | - pure (ImportLookupBad (importErrorKind dflags rdr_env expl_ns_enabled) iface decl_spec ie patsyns_enabled)
|
|
| 2333 | + pure [ImportLookupBad k iface decl_spec ie patsyns_enabled | k <- importErrorKind dflags rdr_env expl_ns_enabled ]
|
|
| 2311 | 2334 | where
|
| 2312 | 2335 | importErrorKind dflags rdr_env expl_ns_enabled
|
| 2313 | 2336 | | any checkIfTyCon avails = case sub of
|
| 2314 | - IsNotSubordinate -> BadImportAvailTyCon expl_ns_enabled
|
|
| 2315 | - IsSubordinate {} -> BadImportNotExportedSubordinates unavailableChildren
|
|
| 2316 | - | any checkIfVarName avails = BadImportAvailVar
|
|
| 2317 | - | Just con <- find checkIfDataCon avails = BadImportAvailDataCon (availOccName con)
|
|
| 2318 | - | otherwise = BadImportNotExported suggs
|
|
| 2337 | + IsNotSubordinate -> [BadImportAvailTyCon expl_ns_enabled]
|
|
| 2338 | + IsSubordinateError { subordinate_err_parent = gre
|
|
| 2339 | + , subordinate_err_unavailable = unavailable
|
|
| 2340 | + , subordinate_err_nontype = nontype }
|
|
| 2341 | + -> [BadImportNotExportedSubordinates gre unavailable | notNull unavailable] ++
|
|
| 2342 | + [BadImportNonTypeSubordinates gre nontype | notNull nontype ]
|
|
| 2343 | + | any checkIfVarName avails = [BadImportAvailVar]
|
|
| 2344 | + | Just con <- find checkIfDataCon avails = [BadImportAvailDataCon (availOccName con)]
|
|
| 2345 | + | otherwise = [BadImportNotExported suggs]
|
|
| 2319 | 2346 | where
|
| 2320 | 2347 | suggs = similar_suggs ++ fieldSelectorSuggestions rdr_env rdr
|
| 2321 | 2348 | what_look = case sub of
|
| 2322 | - IsNotSubordinate -> WL_TyCon_or_TermVar
|
|
| 2323 | - IsSubordinate gre ->
|
|
| 2349 | + IsNotSubordinate -> WL_TyCon_or_TermVar
|
|
| 2350 | + IsSubordinateError { subordinate_err_parent = gre } ->
|
|
| 2324 | 2351 | case greInfo gre of
|
| 2325 | 2352 | IAmTyCon ClassFlavour
|
| 2326 | 2353 | -> WL_TyCon_or_TermVar
|
| ... | ... | @@ -2359,9 +2386,6 @@ badImportItemErr iface decl_spec ie sub avails = do |
| 2359 | 2386 | importedFS = occNameFS $ rdrNameOcc rdr
|
| 2360 | 2387 | imp_spec = ImpSpec { is_decl = decl_spec, is_item = ImpAll }
|
| 2361 | 2388 | all_avails = mi_exports iface
|
| 2362 | - unavailableChildren = case ie of
|
|
| 2363 | - IEThingWith _ _ _ ns _ -> map (rdrNameOcc . ieWrappedName . unLoc) ns
|
|
| 2364 | - _ -> panic "importedChildren failed pattern match: no children"
|
|
| 2365 | 2389 | |
| 2366 | 2390 | addDupDeclErr :: NonEmpty GlobalRdrElt -> TcRn ()
|
| 2367 | 2391 | addDupDeclErr gres@(gre :| _)
|
| ... | ... | @@ -3305,6 +3305,7 @@ instance Diagnostic TcRnMessage where |
| 3305 | 3305 | ++ [ImportSuggestion occ $ CouldAddTypeKeyword mod_name]
|
| 3306 | 3306 | BadImportAvailDataCon par -> [ImportSuggestion occ $ ImportDataCon (Just (mod_name, patsyns_enabled)) par]
|
| 3307 | 3307 | BadImportNotExportedSubordinates{} -> noHints
|
| 3308 | + BadImportNonTypeSubordinates{} -> noHints
|
|
| 3308 | 3309 | TcRnImportLookup{}
|
| 3309 | 3310 | -> noHints
|
| 3310 | 3311 | TcRnUnusedImport{}
|
| ... | ... | @@ -5889,15 +5890,30 @@ pprImportLookup = \case |
| 5889 | 5890 | where
|
| 5890 | 5891 | tycon_occ = rdrNameOcc $ ieName ie
|
| 5891 | 5892 | tycon = parenSymOcc tycon_occ (ppr tycon_occ)
|
| 5892 | - BadImportNotExportedSubordinates ns ->
|
|
| 5893 | + BadImportNotExportedSubordinates gre unavailable ->
|
|
| 5893 | 5894 | withContext
|
| 5894 | - [ text "an item called" <+> quotes sub <+> text "is exported, but it does not export any children"
|
|
| 5895 | - , text "(constructors, class methods or field names) called"
|
|
| 5896 | - <+> pprWithCommas (quotes . ppr) ns <> dot
|
|
| 5895 | + [ what <+> text "called" <+> parent_name <+> text "is exported, but it does not export"
|
|
| 5896 | + , text "any" <+> what_children <+> text "called" <+> unavailable_names <> dot
|
|
| 5897 | 5897 | ]
|
| 5898 | 5898 | where
|
| 5899 | - sub_occ = rdrNameOcc $ ieName ie
|
|
| 5900 | - sub = parenSymOcc sub_occ (ppr sub_occ)
|
|
| 5899 | + parent_name = (quotes . pprPrefixOcc . nameOccName . gre_name) gre
|
|
| 5900 | + unavailable_names = pprWithCommas (quotes . ppr) unavailable
|
|
| 5901 | + (what, what_children) = case greInfo gre of
|
|
| 5902 | + IAmTyCon ClassFlavour -> (text "a class", text "class methods or associated types")
|
|
| 5903 | + IAmTyCon _ -> (text "a data type", text "constructors or record fields")
|
|
| 5904 | + _ -> (text "an item", text "children")
|
|
| 5905 | + BadImportNonTypeSubordinates gre nontype ->
|
|
| 5906 | + withContext
|
|
| 5907 | + [ what <+> text "called" <+> parent_name <+> text "is exported,"
|
|
| 5908 | + , sep [ text "but its subordinate" <+> "item" <> plural nontype <+> nontype_names
|
|
| 5909 | + , isOrAre nontype <+> "not in the type namespace." ] ]
|
|
| 5910 | + where
|
|
| 5911 | + parent_name = (quotes . pprPrefixOcc . nameOccName . gre_name) gre
|
|
| 5912 | + nontype_names = pprWithCommas (quotes . pprPrefixOcc . nameOccName . gre_name) nontype
|
|
| 5913 | + what = case greInfo gre of
|
|
| 5914 | + IAmTyCon ClassFlavour -> text "a class"
|
|
| 5915 | + IAmTyCon _ -> text "a data type"
|
|
| 5916 | + _ -> text "an item"
|
|
| 5901 | 5917 | BadImportAvailDataCon dataType_occ ->
|
| 5902 | 5918 | withContext
|
| 5903 | 5919 | [ text "an item called" <+> quotes datacon
|
| ... | ... | @@ -5846,7 +5846,9 @@ data BadImportKind |
| 5846 | 5846 | -- @import Data.Maybe (Just)@ instead of @import Data.Maybe (Maybe(Just))@
|
| 5847 | 5847 | | BadImportAvailDataCon OccName
|
| 5848 | 5848 | -- | The parent does not export the given children.
|
| 5849 | - | BadImportNotExportedSubordinates [OccName]
|
|
| 5849 | + | BadImportNotExportedSubordinates !GlobalRdrElt [FastString]
|
|
| 5850 | + -- | Incorrect @type@ keyword when importing subordinates that aren't types.
|
|
| 5851 | + | BadImportNonTypeSubordinates !GlobalRdrElt [GlobalRdrElt]
|
|
| 5850 | 5852 | -- | Incorrect @type@ keyword when importing something which isn't a type.
|
| 5851 | 5853 | | BadImportAvailVar
|
| 5852 | 5854 | deriving Generic
|
| ... | ... | @@ -756,6 +756,7 @@ type family GhcDiagnosticCode c = n | n -> c where |
| 756 | 756 | GhcDiagnosticCode "BadImportNotExported" = 61689
|
| 757 | 757 | GhcDiagnosticCode "BadImportAvailDataCon" = 35373
|
| 758 | 758 | GhcDiagnosticCode "BadImportNotExportedSubordinates" = 10237
|
| 759 | + GhcDiagnosticCode "BadImportNonTypeSubordinates" = 51433
|
|
| 759 | 760 | GhcDiagnosticCode "BadImportAvailTyCon" = 56449
|
| 760 | 761 | GhcDiagnosticCode "BadImportAvailVar" = 12112
|
| 761 | 762 |
| ... | ... | @@ -82,6 +82,9 @@ Compiler |
| 82 | 82 | :ghc-ticket:`20875`, :ghc-ticket:`21172`, :ghc-ticket:`22257`, :ghc-ticket:`25238`,
|
| 83 | 83 | :ghc-ticket:`25834`.
|
| 84 | 84 | |
| 85 | +- The compiler no longer accepts invalid ``type`` namespace specifiers in
|
|
| 86 | + subordinate import lists (:ghc-ticket:`22581`).
|
|
| 87 | + |
|
| 85 | 88 | - A new flag, :ghc-flag:`-Wuseless-specialisations`, controls warnings emitted when GHC
|
| 86 | 89 | determines that a SPECIALISE pragma would have no effect.
|
| 87 | 90 |
| ... | ... | @@ -34,6 +34,20 @@ disambiguate this case, thus: :: |
| 34 | 34 | module N( f, type (++) ) where
|
| 35 | 35 | data family a ++ b = L a | R b
|
| 36 | 36 | |
| 37 | +It is also possible to use the ``type`` namespace specifier in subordinate
|
|
| 38 | +import and export lists:
|
|
| 39 | +::
|
|
| 40 | + |
|
| 41 | + module N (C(type (#))) where
|
|
| 42 | + class C a b where
|
|
| 43 | + type a # b
|
|
| 44 | + (#) :: a -> b -> (a # b)
|
|
| 45 | + module M where
|
|
| 46 | + import N as T (C(type (#)))
|
|
| 47 | + import N as D (C((#)))
|
|
| 48 | + -- (T.#) is the associated type
|
|
| 49 | + -- (D.#) is the class method
|
|
| 50 | + |
|
| 37 | 51 | The extension :extension:`ExplicitNamespaces` is implied by
|
| 38 | 52 | :extension:`TypeOperators` and (for some reason) by :extension:`TypeFamilies`.
|
| 39 | 53 |
| ... | ... | @@ -3,6 +3,6 @@ RecompExports1_N.hs:3:25: error: [GHC-61689] |
| 3 | 3 | |
| 4 | 4 | RecompExports1_N.hs:3:30: error: [GHC-10237]
|
| 5 | 5 | In the import of ‘RecompExports1_M’:
|
| 6 | - an item called ‘T’ is exported, but it does not export any children
|
|
| 7 | - (constructors, class methods or field names) called ‘Foo’.
|
|
| 6 | + a data type called ‘T’ is exported, but it does not export
|
|
| 7 | + any constructors or record fields called ‘Foo’.
|
|
| 8 | 8 |
| 1 | 1 | RecompExports4_N.hs:3:26: error: [GHC-10237]
|
| 2 | 2 | In the import of ‘RecompExports4_M’:
|
| 3 | - an item called ‘T’ is exported, but it does not export any children
|
|
| 4 | - (constructors, class methods or field names) called ‘fld’.
|
|
| 3 | + a data type called ‘T’ is exported, but it does not export
|
|
| 4 | + any constructors or record fields called ‘fld’.
|
|
| 5 | 5 | |
| 6 | 6 | RecompExports4_N.hs:3:39: error: [GHC-10237]
|
| 7 | 7 | In the import of ‘RecompExports4_M’:
|
| 8 | - an item called ‘C’ is exported, but it does not export any children
|
|
| 9 | - (constructors, class methods or field names) called ‘meth’.
|
|
| 8 | + a class called ‘C’ is exported, but it does not export
|
|
| 9 | + any class methods or associated types called ‘meth’.
|
|
| 10 | 10 |
| 1 | - |
|
| 2 | 1 | T21826.hs:3:29: error: [GHC-56449]
|
| 3 | 2 | In the import of ‘Data.Type.Equality’:
|
| 4 | 3 | an item called ‘(~)’ is exported, but it is a type.
|
| ... | ... | @@ -24,13 +23,13 @@ T21826.hs:5:21: error: [GHC-61689] |
| 24 | 23 | |
| 25 | 24 | T21826.hs:6:21: error: [GHC-10237]
|
| 26 | 25 | In the import of ‘Data.Maybe’:
|
| 27 | - an item called ‘Maybe’ is exported, but it does not export any children
|
|
| 28 | - (constructors, class methods or field names) called ‘Some’.
|
|
| 26 | + a data type called ‘Maybe’ is exported, but it does not export
|
|
| 27 | + any constructors or record fields called ‘Some’.
|
|
| 29 | 28 | |
| 30 | 29 | T21826.hs:7:21: error: [GHC-10237]
|
| 31 | 30 | In the import of ‘Data.Maybe’:
|
| 32 | - an item called ‘Maybe’ is exported, but it does not export any children
|
|
| 33 | - (constructors, class methods or field names) called ‘Some’, ‘Mk’.
|
|
| 31 | + a data type called ‘Maybe’ is exported, but it does not export
|
|
| 32 | + any constructors or record fields called ‘Some’, ‘Mk’.
|
|
| 34 | 33 | |
| 35 | 34 | T21826.hs:8:20: error: [GHC-12112]
|
| 36 | 35 | In the import of ‘Data.List’:
|
| ... | ... | @@ -55,3 +54,4 @@ T21826.hs:13:21: error: [GHC-56449] |
| 55 | 54 | Suggested fix:
|
| 56 | 55 | Add the ‘type’ keyword to the import statement:
|
| 57 | 56 | import Data.Maybe ( type Maybe )
|
| 57 | + |
| 1 | - |
|
| 2 | 1 | mod81.hs:3:16: error: [GHC-10237]
|
| 3 | 2 | In the import of ‘Prelude’:
|
| 4 | - an item called ‘Either’ is exported, but it does not export any children
|
|
| 5 | - (constructors, class methods or field names) called ‘Foo’. |
|
| 3 | + a data type called ‘Either’ is exported, but it does not export
|
|
| 4 | + any constructors or record fields called ‘Foo’.
|
|
| 5 | + |
| 1 | - |
|
| 2 | 1 | mod91.hs:3:16: error: [GHC-10237]
|
| 3 | 2 | In the import of ‘Prelude’:
|
| 4 | - an item called ‘Eq’ is exported, but it does not export any children
|
|
| 5 | - (constructors, class methods or field names) called ‘eq’. |
|
| 3 | + a class called ‘Eq’ is exported, but it does not export
|
|
| 4 | + any class methods or associated types called ‘eq’.
|
|
| 5 | + |
| 1 | +{-# LANGUAGE ExplicitNamespaces #-}
|
|
| 2 | + |
|
| 3 | +module T22581c where
|
|
| 4 | + |
|
| 5 | +import T22581c_helper (K(type T), C(type (#), type Tf, type Df))
|
|
| 6 | + |
|
| 7 | +type T' :: K
|
|
| 8 | +type T' = T
|
|
| 9 | + |
|
| 10 | +type C' a = C a
|
|
| 11 | +type (#.) a b = a # b
|
|
| 12 | +type Tf' a = Tf a
|
|
| 13 | +type Df' a = Df a |
|
| \ No newline at end of file |
| 1 | +{-# LANGUAGE TypeData, TypeFamilies #-}
|
|
| 2 | + |
|
| 3 | +module T22581c_helper (K(T), C((#), Tf, Df)) where
|
|
| 4 | + |
|
| 5 | +type data K = T
|
|
| 6 | + |
|
| 7 | +class C a where
|
|
| 8 | + type a # b
|
|
| 9 | + type Tf a
|
|
| 10 | + data Df a |
|
| \ No newline at end of file |
| 1 | +:set -XExplicitNamespaces
|
|
| 2 | +import Data.Functor.Product (Product(type Pair)) |
| 1 | +<interactive>:2:30: error: [GHC-51433]
|
|
| 2 | + In the import of ‘Data.Functor.Product’:
|
|
| 3 | + a data type called ‘Product’ is exported,
|
|
| 4 | + but its subordinate item ‘Pair’ is not in the type namespace.
|
|
| 5 | + |
| 1 | +{-# LANGUAGE TypeFamilies, DataKinds #-}
|
|
| 2 | + |
|
| 3 | +module T25991a where
|
|
| 4 | + |
|
| 5 | +import T25991a_helper as T (C(type (#)))
|
|
| 6 | +import T25991a_helper as D (C((#)))
|
|
| 7 | + |
|
| 8 | +type S a b = a T.# b
|
|
| 9 | +f a b = a D.# b |
|
| \ No newline at end of file |
| 1 | +{-# LANGUAGE TypeFamilies #-}
|
|
| 2 | + |
|
| 3 | +module T25991a_helper (C(..)) where
|
|
| 4 | + |
|
| 5 | +class C a b where
|
|
| 6 | + type a # b
|
|
| 7 | + (#) :: a -> b -> () |
| ... | ... | @@ -229,4 +229,7 @@ test('T14032d', normal, compile, ['']) |
| 229 | 229 | test('T24621_normal', normal, compile, [''])
|
| 230 | 230 | test('T24621_th', req_th, compile, [''])
|
| 231 | 231 | test('T24732', normal, compile_and_run, ['-package "base(Prelude, Text.Printf as P\')"'])
|
| 232 | -test('T25182', [extra_files(['ReExportTuples.hs'])], multimod_compile, ['T25182', '-v0']) |
|
| \ No newline at end of file | ||
| 232 | +test('T25182', [extra_files(['ReExportTuples.hs'])], multimod_compile, ['T25182', '-v0'])
|
|
| 233 | +test('T22581c', [extra_files(['T22581c_helper.hs'])], multimod_compile, ['T22581c', '-v0'])
|
|
| 234 | +test('T22581d', combined_output, ghci_script, ['T22581d.script'])
|
|
| 235 | +test('T25991a', [extra_files(['T25991a_helper.hs'])], multimod_compile, ['T25991a', '-v0']) |
| 1 | +{-# LANGUAGE ExplicitNamespaces #-}
|
|
| 2 | + |
|
| 3 | +module T22581a where
|
|
| 4 | + |
|
| 5 | +import T22581a_helper (T(type MkT))
|
|
| 6 | + |
|
| 7 | +t :: T
|
|
| 8 | +t = MkT |
| 1 | +T22581a.hs:5:24: error: [GHC-51433]
|
|
| 2 | + In the import of ‘T22581a_helper’:
|
|
| 3 | + a data type called ‘T’ is exported,
|
|
| 4 | + but its subordinate item ‘MkT’ is not in the type namespace.
|
|
| 5 | + |
| 1 | +module T22581a_helper (T(MkT)) where
|
|
| 2 | + |
|
| 3 | +data T = MkT |
| 1 | +{-# LANGUAGE ExplicitNamespaces #-}
|
|
| 2 | + |
|
| 3 | +module T22581b where
|
|
| 4 | + |
|
| 5 | +import T22581b_helper (T(type MkT1, MkT2, MkT3, unT))
|
|
| 6 | + |
| 1 | +T22581b.hs:5:24: error: [GHC-51433]
|
|
| 2 | + In the import of ‘T22581b_helper’:
|
|
| 3 | + a data type called ‘T’ is exported,
|
|
| 4 | + but its subordinate item ‘MkT1’ is not in the type namespace.
|
|
| 5 | + |
|
| 6 | +T22581b.hs:5:24: error: [GHC-10237]
|
|
| 7 | + In the import of ‘T22581b_helper’:
|
|
| 8 | + a data type called ‘T’ is exported, but it does not export
|
|
| 9 | + any constructors or record fields called ‘MkT3’, ‘unT’.
|
|
| 10 | + |
| 1 | +module T22581b_helper (T(MkT1, MkT2)) where
|
|
| 2 | + |
|
| 3 | +data T = MkT1 | MkT2 |
| 1 | +{-# LANGUAGE TypeFamilies, DataKinds #-}
|
|
| 2 | + |
|
| 3 | +module T25991b1 where
|
|
| 4 | + |
|
| 5 | +import T25991b_helper (C((#)))
|
|
| 6 | + |
|
| 7 | +type S a b = a # b |
|
| \ No newline at end of file |
| 1 | +{-# LANGUAGE TypeFamilies, DataKinds #-}
|
|
| 2 | + |
|
| 3 | +module T25991b2 where
|
|
| 4 | + |
|
| 5 | +import T25991b_helper (C(type (#)))
|
|
| 6 | + |
|
| 7 | +f a b = a # b |
|
| \ No newline at end of file |
| 1 | +{-# LANGUAGE TypeFamilies #-}
|
|
| 2 | + |
|
| 3 | +module T25991b_helper (C(..)) where
|
|
| 4 | + |
|
| 5 | +class C a b where
|
|
| 6 | + type a # b
|
|
| 7 | + (#) :: a -> b -> () |
| 1 | - |
|
| 2 | 1 | T9006.hs:3:16: error: [GHC-10237]
|
| 3 | 2 | In the import of ‘T9006a’:
|
| 4 | - an item called ‘T’ is exported, but it does not export any children
|
|
| 5 | - (constructors, class methods or field names) called ‘T’. |
|
| 3 | + a data type called ‘T’ is exported, but it does not export
|
|
| 4 | + any constructors or record fields called ‘T’.
|
|
| 5 | + |
| ... | ... | @@ -237,3 +237,7 @@ test('T25877', [extra_files(['T25877_aux.hs'])], multimod_compile_fail, ['T25877 |
| 237 | 237 | test('T23501_fail', normal, compile_fail, [''])
|
| 238 | 238 | test('T23501_fail_ext', normal, compile_fail, [''])
|
| 239 | 239 | test('T25437', normal, compile_fail, [''])
|
| 240 | +test('T22581a', [extra_files(['T22581a_helper.hs'])], multimod_compile_fail, ['T22581a', '-v0'])
|
|
| 241 | +test('T22581b', [extra_files(['T22581b_helper.hs'])], multimod_compile_fail, ['T22581b', '-v0'])
|
|
| 242 | +test('T25991b1', [extra_files(['T25991b_helper.hs'])], multimod_compile_fail, ['T25991b1', '-v0'])
|
|
| 243 | +test('T25991b2', [extra_files(['T25991b_helper.hs'])], multimod_compile_fail, ['T25991b2', '-v0']) |