diff --git a/compiler/main/Finder.hs b/compiler/main/Finder.hs index 613c0a41dd14723e186a9329736719f9dc15911a..40efcf3523946e22a3ad883c5cf633ce623079e3 100644 --- a/compiler/main/Finder.hs +++ b/compiler/main/Finder.hs @@ -152,15 +152,17 @@ orIfNotFound this or_this = do res <- this case res of NotFound { fr_paths = paths1, fr_mods_hidden = mh1 - , fr_pkgs_hidden = ph1, fr_suggestions = s1 } + , fr_pkgs_hidden = ph1, fr_unusables = u1, fr_suggestions = s1 } -> do res2 <- or_this case res2 of NotFound { fr_paths = paths2, fr_pkg = mb_pkg2, fr_mods_hidden = mh2 - , fr_pkgs_hidden = ph2, fr_suggestions = s2 } + , fr_pkgs_hidden = ph2, fr_unusables = u2 + , fr_suggestions = s2 } -> return (NotFound { fr_paths = paths1 ++ paths2 , fr_pkg = mb_pkg2 -- snd arg is the package search , fr_mods_hidden = mh1 ++ mh2 , fr_pkgs_hidden = ph1 ++ ph2 + , fr_unusables = u1 ++ u2 , fr_suggestions = s1 ++ s2 }) _other -> return res2 _other -> return res @@ -205,6 +207,7 @@ findLookupResult hsc_env r = case r of InstalledNotFound fp _ -> return (NotFound{ fr_paths = fp, fr_pkg = Just (moduleUnitId m) , fr_pkgs_hidden = [] , fr_mods_hidden = [] + , fr_unusables = [] , fr_suggestions = []}) LookupMultiple rs -> return (FoundMultiple rs) @@ -212,11 +215,23 @@ findLookupResult hsc_env r = case r of return (NotFound{ fr_paths = [], fr_pkg = Nothing , fr_pkgs_hidden = map (moduleUnitId.fst) pkg_hiddens , fr_mods_hidden = map (moduleUnitId.fst) mod_hiddens + , fr_unusables = [] , fr_suggestions = [] }) + LookupUnusable unusable -> + let unusables' = map get_unusable unusable + get_unusable (m, ModUnusable r) = (moduleUnitId m, r) + get_unusable (_, r) = + pprPanic "findLookupResult: unexpected origin" (ppr r) + in return (NotFound{ fr_paths = [], fr_pkg = Nothing + , fr_pkgs_hidden = [] + , fr_mods_hidden = [] + , fr_unusables = unusables' + , fr_suggestions = [] }) LookupNotFound suggest -> return (NotFound{ fr_paths = [], fr_pkg = Nothing , fr_pkgs_hidden = [] , fr_mods_hidden = [] + , fr_unusables = [] , fr_suggestions = suggest }) modLocationCache :: HscEnv -> InstalledModule -> IO InstalledFindResult -> IO InstalledFindResult @@ -260,6 +275,7 @@ findHomeModule hsc_env mod_name = do fr_pkg = Just uid, fr_mods_hidden = [], fr_pkgs_hidden = [], + fr_unusables = [], fr_suggestions = [] } where @@ -570,8 +586,19 @@ findObjectLinkable mod obj_fn obj_time = return (LM obj_time mod [DotO obj_fn]) -- Error messages cannotFindModule :: DynFlags -> ModuleName -> FindResult -> SDoc -cannotFindModule = cantFindErr (sLit "Could not find module") - (sLit "Ambiguous module name") +cannotFindModule flags mod res = + cantFindErr (sLit cannotFindMsg) + (sLit "Ambiguous module name") + flags mod res + where + cannotFindMsg = + case res of + NotFound { fr_mods_hidden = hidden_mods + , fr_pkgs_hidden = hidden_pkgs + , fr_unusables = unusables } + | not (null hidden_mods && null hidden_pkgs && null unusables) + -> "Could not load module" + _ -> "Could not find module" cannotFindInterface :: DynFlags -> ModuleName -> InstalledFindResult -> SDoc cannotFindInterface = cantFindInstalledErr (sLit "Failed to load interface for") @@ -598,6 +625,7 @@ cantFindErr _ multiple_found _ mod_name (FoundMultiple mods) pprMod (m, o) = text "it is bound as" <+> ppr m <+> text "by" <+> pprOrigin m o pprOrigin _ ModHidden = panic "cantFindErr: bound by mod hidden" + pprOrigin _ (ModUnusable _) = panic "cantFindErr: bound by mod unusable" pprOrigin m (ModOrigin e res _ f) = sep $ punctuate comma ( if e == Just True then [text "package" <+> ppr (moduleUnitId m)] @@ -619,19 +647,21 @@ cantFindErr cannot_find _ dflags mod_name find_result NotFound { fr_paths = files, fr_pkg = mb_pkg , fr_mods_hidden = mod_hiddens, fr_pkgs_hidden = pkg_hiddens - , fr_suggestions = suggest } + , fr_unusables = unusables, fr_suggestions = suggest } | Just pkg <- mb_pkg, pkg /= thisPackage dflags -> not_found_in_package pkg files | not (null suggest) -> pp_suggestions suggest $$ tried_these files - | null files && null mod_hiddens && null pkg_hiddens + | null files && null mod_hiddens && + null pkg_hiddens && null unusables -> text "It is not a module in the current program, or in any known package." | otherwise -> vcat (map pkg_hidden pkg_hiddens) $$ vcat (map mod_hidden mod_hiddens) $$ + vcat (map unusable unusables) $$ tried_these files _ -> panic "cantFindErr" @@ -674,16 +704,21 @@ cantFindErr cannot_find _ dflags mod_name find_result in text "Perhaps you need to add" <+> quotes (ppr (packageName pkg)) <+> text "to the build-depends in your .cabal file." - | otherwise - = let pkg = expectJust "pkg_hidden" (lookupPackage dflags pkgid) - in text "You can run" <+> - quotes (text ":set -package " <> ppr (packageName pkg)) <+> - text "to expose it." $$ - text "(Note: this unloads all the modules in the current scope.)" + | Just pkg <- lookupPackage dflags pkgid + = text "You can run" <+> + quotes (text ":set -package " <> ppr (packageName pkg)) <+> + text "to expose it." $$ + text "(Note: this unloads all the modules in the current scope.)" + | otherwise = Outputable.empty mod_hidden pkg = text "it is a hidden module in the package" <+> quotes (ppr pkg) + unusable (pkg, reason) + = text "It is a member of the package" + <+> quotes (ppr pkg) + $$ pprReason (text "which is") reason + pp_suggestions :: [ModuleSuggestion] -> SDoc pp_suggestions sugs | null sugs = Outputable.empty @@ -695,6 +730,7 @@ cantFindErr cannot_find _ dflags mod_name find_result -- also has a reexport, prefer that one pp_sugg (SuggestVisible m mod o) = ppr m <+> provenance o where provenance ModHidden = Outputable.empty + provenance (ModUnusable _) = Outputable.empty provenance (ModOrigin{ fromOrigPackage = e, fromExposedReexport = res, fromPackageFlag = f }) @@ -711,6 +747,7 @@ cantFindErr cannot_find _ dflags mod_name find_result | otherwise = Outputable.empty pp_sugg (SuggestHidden m mod o) = ppr m <+> provenance o where provenance ModHidden = Outputable.empty + provenance (ModUnusable _) = Outputable.empty provenance (ModOrigin{ fromOrigPackage = e, fromHiddenReexport = rhs }) | Just False <- e diff --git a/compiler/main/HscTypes.hs b/compiler/main/HscTypes.hs index 89497991981ced2ea2952e9cb723cfbb11c5e239..0ef1487312a895b9786526c83cf2deb5c5334ecf 100644 --- a/compiler/main/HscTypes.hs +++ b/compiler/main/HscTypes.hs @@ -817,6 +817,9 @@ data FindResult , fr_pkgs_hidden :: [UnitId] -- Module is in these packages, -- but the *package* is hidden + -- Modules are in these packages, but it is unusable + , fr_unusables :: [(UnitId, UnusablePackageReason)] + , fr_suggestions :: [ModuleSuggestion] -- Possible mis-spelled modules } diff --git a/compiler/main/Packages.hs b/compiler/main/Packages.hs index 008e9b5da0ac822ae81e6b84c611feadf57e00cd..d9c198a432933cebb0c973ffe5b8c9a21fd4496b 100644 --- a/compiler/main/Packages.hs +++ b/compiler/main/Packages.hs @@ -35,6 +35,8 @@ module Packages ( LookupResult(..), ModuleSuggestion(..), ModuleOrigin(..), + UnusablePackageReason(..), + pprReason, -- * Inspecting the set of packages in scope getPackageIncludePath, @@ -157,6 +159,8 @@ data ModuleOrigin = -- (But maybe the user didn't realize), so we'll still keep track -- of these modules.) ModHidden + -- | Module is unavailable because the package is unusable. + | ModUnusable UnusablePackageReason -- | Module is public, and could have come from some places. | ModOrigin { -- | @Just False@ means that this module is in @@ -176,6 +180,7 @@ data ModuleOrigin = instance Outputable ModuleOrigin where ppr ModHidden = text "hidden module" + ppr (ModUnusable _) = text "unusable module" ppr (ModOrigin e res rhs f) = sep (punctuate comma ( (case e of Nothing -> [] @@ -226,6 +231,7 @@ instance Monoid ModuleOrigin where -- ambiguity, or is it only relevant when we're making suggestions?) originVisible :: ModuleOrigin -> Bool originVisible ModHidden = False +originVisible (ModUnusable _) = False originVisible (ModOrigin b res _ f) = b == Just True || not (null res) || f -- | Are there actually no providers for this module? This will never occur @@ -1136,7 +1142,8 @@ pprReason pref reason = case reason of pref <+> text "unusable due to cyclic dependencies:" $$ nest 2 (hsep (map ppr deps)) IgnoredDependencies deps -> - pref <+> text "unusable due to ignored dependencies:" $$ + pref <+> text ("unusable because the -ignore-package flag was used to " ++ + "ignore at least one of its dependencies:") $$ nest 2 (hsep (map ppr deps)) ShadowedDependencies deps -> pref <+> text "unusable due to shadowed dependencies:" $$ @@ -1548,7 +1555,10 @@ mkPackageState dflags dbs preload0 = do dep_preload <- closeDeps dflags pkg_db (zip (map toInstalledUnitId preload3) (repeat Nothing)) let new_dep_preload = filter (`notElem` preload0) dep_preload - let mod_map = mkModuleToPkgConfAll dflags pkg_db vis_map + let mod_map1 = mkModuleToPkgConfAll dflags pkg_db vis_map + mod_map2 = mkUnusableModuleToPkgConfAll unusable + mod_map = Map.union mod_map1 mod_map2 + when (dopt Opt_D_dump_mod_map dflags) $ printInfoForUser (dflags { pprCols = 200 }) alwaysQualify (pprModuleMap mod_map) @@ -1617,9 +1627,6 @@ mkModuleToPkgConfAll dflags pkg_db vis_map = ] emptyMap = Map.empty - sing pk m _ = Map.singleton (mkModule pk m) - addListTo = foldl' merge - merge m (k, v) = MapStrict.insertWith (Map.unionWith mappend) k v m setOrigins m os = fmap (const os) m extend_modmap modmap uid UnitVisibility { uv_expose_all = b, uv_renamings = rns } @@ -1647,19 +1654,19 @@ mkModuleToPkgConfAll dflags pkg_db vis_map = es :: Bool -> [(ModuleName, Map Module ModuleOrigin)] es e = do (m, exposedReexport) <- exposed_mods - let (pk', m', pkg', origin') = + let (pk', m', origin') = case exposedReexport of - Nothing -> (pk, m, pkg, fromExposedModules e) + Nothing -> (pk, m, fromExposedModules e) Just (Module pk' m') -> let pkg' = pkg_lookup pk' - in (pk', m', pkg', fromReexportedModules e pkg') - return (m, sing pk' m' pkg' origin') + in (pk', m', fromReexportedModules e pkg') + return (m, mkModMap pk' m' origin') esmap :: UniqFM (Map Module ModuleOrigin) esmap = listToUFM (es False) -- parameter here doesn't matter, orig will -- be overwritten - hiddens = [(m, sing pk m pkg ModHidden) | m <- hidden_mods] + hiddens = [(m, mkModMap pk m ModHidden) | m <- hidden_mods] pk = packageConfigId pkg pkg_lookup uid = lookupPackage' (isIndefinite dflags) pkg_db uid @@ -1668,6 +1675,43 @@ mkModuleToPkgConfAll dflags pkg_db vis_map = exposed_mods = exposedModules pkg hidden_mods = hiddenModules pkg +-- | Make a 'ModuleToPkgConfAll' covering a set of unusable packages. +mkUnusableModuleToPkgConfAll :: UnusablePackages -> ModuleToPkgConfAll +mkUnusableModuleToPkgConfAll unusables = + Map.foldl' extend_modmap Map.empty unusables + where + extend_modmap modmap (pkg, reason) = addListTo modmap bindings + where bindings :: [(ModuleName, Map Module ModuleOrigin)] + bindings = exposed ++ hidden + + origin = ModUnusable reason + pkg_id = packageConfigId pkg + + exposed = map get_exposed exposed_mods + hidden = [(m, mkModMap pkg_id m origin) | m <- hidden_mods] + + get_exposed (mod, Just mod') = (mod, Map.singleton mod' origin) + get_exposed (mod, _) = (mod, mkModMap pkg_id mod origin) + + exposed_mods = exposedModules pkg + hidden_mods = hiddenModules pkg + +-- | Add a list of key/value pairs to a nested map. +-- +-- The outer map is processed with 'Data.Map.Strict' to prevent memory leaks +-- when reloading modules in GHCi (see Trac #4029). This ensures that each +-- value is forced before installing into the map. +addListTo :: (Monoid a, Ord k1, Ord k2) + => Map k1 (Map k2 a) + -> [(k1, Map k2 a)] + -> Map k1 (Map k2 a) +addListTo = foldl' merge + where merge m (k, v) = MapStrict.insertWith (Map.unionWith mappend) k v m + +-- | Create a singleton module mapping +mkModMap :: UnitId -> ModuleName -> ModuleOrigin -> Map Module ModuleOrigin +mkModMap pkg mod = Map.singleton (mkModule pkg mod) + -- ----------------------------------------------------------------------------- -- Extracting information from the packages in scope @@ -1815,6 +1859,9 @@ data LookupResult = -- an exact name match. First is due to package hidden, second -- is due to module being hidden | LookupHidden [(Module, ModuleOrigin)] [(Module, ModuleOrigin)] + -- | No modules found, but there were some unusable ones with + -- an exact name match + | LookupUnusable [(Module, ModuleOrigin)] -- | Nothing found, here are some suggested different names | LookupNotFound [ModuleSuggestion] -- suggestions @@ -1846,20 +1893,28 @@ lookupModuleWithSuggestions' dflags mod_map m mb_pn = case Map.lookup m mod_map of Nothing -> LookupNotFound suggestions Just xs -> - case foldl' classify ([],[],[]) (Map.toList xs) of - ([], [], []) -> LookupNotFound suggestions - (_, _, [(m, _)]) -> LookupFound m (mod_pkg m) - (_, _, exposed@(_:_)) -> LookupMultiple exposed - (hidden_pkg, hidden_mod, []) -> LookupHidden hidden_pkg hidden_mod + case foldl' classify ([],[],[], []) (Map.toList xs) of + ([], [], [], []) -> LookupNotFound suggestions + (_, _, _, [(m, _)]) -> LookupFound m (mod_pkg m) + (_, _, _, exposed@(_:_)) -> LookupMultiple exposed + ([], [], unusable@(_:_), []) -> LookupUnusable unusable + (hidden_pkg, hidden_mod, _, []) -> + LookupHidden hidden_pkg hidden_mod where - classify (hidden_pkg, hidden_mod, exposed) (m, origin0) = + classify (hidden_pkg, hidden_mod, unusable, exposed) (m, origin0) = let origin = filterOrigin mb_pn (mod_pkg m) origin0 x = (m, origin) in case origin of - ModHidden -> (hidden_pkg, x:hidden_mod, exposed) - _ | originEmpty origin -> (hidden_pkg, hidden_mod, exposed) - | originVisible origin -> (hidden_pkg, hidden_mod, x:exposed) - | otherwise -> (x:hidden_pkg, hidden_mod, exposed) + ModHidden + -> (hidden_pkg, x:hidden_mod, unusable, exposed) + ModUnusable _ + -> (hidden_pkg, hidden_mod, x:unusable, exposed) + _ | originEmpty origin + -> (hidden_pkg, hidden_mod, unusable, exposed) + | originVisible origin + -> (hidden_pkg, hidden_mod, unusable, x:exposed) + | otherwise + -> (x:hidden_pkg, hidden_mod, unusable, exposed) pkg_lookup p = lookupPackage dflags p `orElse` pprPanic "lookupModuleWithSuggestions" (ppr p <+> ppr m) mod_pkg = pkg_lookup . moduleUnitId @@ -1875,6 +1930,7 @@ lookupModuleWithSuggestions' dflags mod_map m mb_pn filterOrigin (Just pn) pkg o = case o of ModHidden -> if go pkg then ModHidden else mempty + (ModUnusable _) -> if go pkg then o else mempty ModOrigin { fromOrigPackage = e, fromExposedReexport = res, fromHiddenReexport = rhs } -> ModOrigin { diff --git a/testsuite/tests/ghci/should_fail/T15055.stderr b/testsuite/tests/ghci/should_fail/T15055.stderr index daba7c7e5308d6e0e4c385a3b8c6be12d99fac9d..fbf540edfd28ff5e78dd0bf72ade966a76cc16a4 100644 --- a/testsuite/tests/ghci/should_fail/T15055.stderr +++ b/testsuite/tests/ghci/should_fail/T15055.stderr @@ -1,6 +1,6 @@ -<no location info>: - Could not find module ‘GHC’ +<no location info>: error: + Could not load module ‘GHC’ It is a member of the hidden package ‘ghc-8.5’. You can run ‘:set -package ghc’ to expose it. (Note: this unloads all the modules in the current scope.) diff --git a/testsuite/tests/package/T4806.hs b/testsuite/tests/package/T4806.hs new file mode 100644 index 0000000000000000000000000000000000000000..781cfef1ac3f3b6df317bfc8380a1ffbd39b61ed --- /dev/null +++ b/testsuite/tests/package/T4806.hs @@ -0,0 +1 @@ +import Data.Map diff --git a/testsuite/tests/package/T4806.stderr b/testsuite/tests/package/T4806.stderr new file mode 100644 index 0000000000000000000000000000000000000000..6b332fd32b0870b26770fd24588083d0bb18e6e5 --- /dev/null +++ b/testsuite/tests/package/T4806.stderr @@ -0,0 +1,6 @@ + +T4806.hs:1:1: error: + Could not load module ‘Data.Map’ + It is a member of the package ‘containers-0.5.11.0’ + which is ignored due to an -ignore-package flag + Use -v to see a list of the files searched for. diff --git a/testsuite/tests/package/T4806a.hs b/testsuite/tests/package/T4806a.hs new file mode 100644 index 0000000000000000000000000000000000000000..781cfef1ac3f3b6df317bfc8380a1ffbd39b61ed --- /dev/null +++ b/testsuite/tests/package/T4806a.hs @@ -0,0 +1 @@ +import Data.Map diff --git a/testsuite/tests/package/T4806a.stderr b/testsuite/tests/package/T4806a.stderr new file mode 100644 index 0000000000000000000000000000000000000000..36cbb59fbe0d162155b21b2ad529adc4cd48715f --- /dev/null +++ b/testsuite/tests/package/T4806a.stderr @@ -0,0 +1,7 @@ + +T4806a.hs:1:1: error: + Could not load module ‘Data.Map’ + It is a member of the package ‘containers-0.5.11.0’ + which is unusable because the -ignore-package flag was used to ignore at least one of its dependencies: + deepseq-1.4.4.0 + Use -v to see a list of the files searched for. diff --git a/testsuite/tests/package/all.T b/testsuite/tests/package/all.T index 129ae8540cba3137a6a3b9651bbfb1b27b74a9d2..670550e41d5bf099e1d9f08a2fcd1a58c11f4fbf 100644 --- a/testsuite/tests/package/all.T +++ b/testsuite/tests/package/all.T @@ -17,3 +17,6 @@ test('package07e', normalise_version('ghc'), compile_fail, [incr_ghc + inc_ghc + test('package08e', normalise_version('ghc'), compile_fail, [incr_ghc + hide_ghc]) test('package09e', normal, compile_fail, ['-package "containers (Data.Map as M, Data.Set as M)"']) test('package10', normal, compile, ['-hide-all-packages -package "ghc (UniqFM as Prelude)" ']) + +test('T4806', normal, compile_fail, ['-ignore-package containers']) +test('T4806a', normal, compile_fail, ['-ignore-package deepseq']) \ No newline at end of file diff --git a/testsuite/tests/package/package01e.stderr b/testsuite/tests/package/package01e.stderr index e4af6b12277abae0fc14378228fb5f52731bfb6b..7ae545fe6f75eae43922830dd6f349d496a6dd1f 100644 --- a/testsuite/tests/package/package01e.stderr +++ b/testsuite/tests/package/package01e.stderr @@ -1,13 +1,13 @@ package01e.hs:2:1: error: - Could not find module ‘Data.Map’ + Could not load module ‘Data.Map’ It is a member of the hidden package ‘containers-0.5.11.0’. You can run ‘:set -package containers’ to expose it. (Note: this unloads all the modules in the current scope.) Use -v to see a list of the files searched for. package01e.hs:3:1: error: - Could not find module ‘Data.IntMap’ + Could not load module ‘Data.IntMap’ It is a member of the hidden package ‘containers-0.5.11.0’. You can run ‘:set -package containers’ to expose it. (Note: this unloads all the modules in the current scope.) diff --git a/testsuite/tests/package/package06e.stderr b/testsuite/tests/package/package06e.stderr index 1bdbb162b0f831c26cb77d7d51d0908f13cf00ef..40673b844cf9be9ca6d827248d8cc0c9e789e534 100644 --- a/testsuite/tests/package/package06e.stderr +++ b/testsuite/tests/package/package06e.stderr @@ -1,14 +1,14 @@ package06e.hs:2:1: error: - Could not find module ‘HsTypes’ - It is a member of the hidden package ‘ghc-8.1’. + Could not load module ‘HsTypes’ + It is a member of the hidden package ‘ghc-8.5’. You can run ‘:set -package ghc’ to expose it. (Note: this unloads all the modules in the current scope.) Use -v to see a list of the files searched for. package06e.hs:3:1: error: - Could not find module ‘UniqFM’ - It is a member of the hidden package ‘ghc-8.1’. + Could not load module ‘UniqFM’ + It is a member of the hidden package ‘ghc-8.5’. You can run ‘:set -package ghc’ to expose it. (Note: this unloads all the modules in the current scope.) Use -v to see a list of the files searched for. diff --git a/testsuite/tests/package/package07e.stderr b/testsuite/tests/package/package07e.stderr index 9bd53da52cf2a205d2441f33c608f0587792bb7c..132268cb64c41c511dd0636a2e303aec979f078c 100644 --- a/testsuite/tests/package/package07e.stderr +++ b/testsuite/tests/package/package07e.stderr @@ -5,21 +5,21 @@ package07e.hs:2:1: error: Use -v to see a list of the files searched for. package07e.hs:3:1: error: - Could not find module ‘HsTypes’ + Could not load module ‘HsTypes’ It is a member of the hidden package ‘ghc-8.5’. You can run ‘:set -package ghc’ to expose it. (Note: this unloads all the modules in the current scope.) Use -v to see a list of the files searched for. package07e.hs:4:1: error: - Could not find module ‘HsUtils’ + Could not load module ‘HsUtils’ It is a member of the hidden package ‘ghc-8.5’. You can run ‘:set -package ghc’ to expose it. (Note: this unloads all the modules in the current scope.) Use -v to see a list of the files searched for. package07e.hs:5:1: error: - Could not find module ‘UniqFM’ + Could not load module ‘UniqFM’ It is a member of the hidden package ‘ghc-8.5’. You can run ‘:set -package ghc’ to expose it. (Note: this unloads all the modules in the current scope.) diff --git a/testsuite/tests/package/package08e.stderr b/testsuite/tests/package/package08e.stderr index 0e075ddda9e8b8adf7368fae1938a8f98da16064..31b6e762e7a2eccfdd9d6440e4da69cb3301bc1f 100644 --- a/testsuite/tests/package/package08e.stderr +++ b/testsuite/tests/package/package08e.stderr @@ -5,21 +5,21 @@ package08e.hs:2:1: error: Use -v to see a list of the files searched for. package08e.hs:3:1: error: - Could not find module ‘HsTypes’ + Could not load module ‘HsTypes’ It is a member of the hidden package ‘ghc-8.5’. You can run ‘:set -package ghc’ to expose it. (Note: this unloads all the modules in the current scope.) Use -v to see a list of the files searched for. package08e.hs:4:1: error: - Could not find module ‘HsUtils’ + Could not load module ‘HsUtils’ It is a member of the hidden package ‘ghc-8.5’. You can run ‘:set -package ghc’ to expose it. (Note: this unloads all the modules in the current scope.) Use -v to see a list of the files searched for. package08e.hs:5:1: error: - Could not find module ‘UniqFM’ + Could not load module ‘UniqFM’ It is a member of the hidden package ‘ghc-8.5’. You can run ‘:set -package ghc’ to expose it. (Note: this unloads all the modules in the current scope.) diff --git a/testsuite/tests/plugins/T11244.stderr b/testsuite/tests/plugins/T11244.stderr index b5711445b87c57662763e54ffd6f9b8eac024410..0c3b3cf7811b8d160d5ca5e1d851b431e6607aa1 100644 --- a/testsuite/tests/plugins/T11244.stderr +++ b/testsuite/tests/plugins/T11244.stderr @@ -1,4 +1,4 @@ -<command line>: Could not find module ‘RuleDefiningPlugin’ +<command line>: Could not load module ‘RuleDefiningPlugin’ It is a member of the hidden package ‘rule-defining-plugin-0.1’. You can run ‘:set -package rule-defining-plugin’ to expose it. (Note: this unloads all the modules in the current scope.)