Skip to content
Snippets Groups Projects
Commit 44f1582e authored by Edward Z. Yang's avatar Edward Z. Yang
Browse files

Remove optimized package lookup, simplifying code.


Summary:
A while back when I was refactoring the package code, I tried to solve
a performance problem by introducing a fastpath for module lookups.  Well,
it turned out the performance problem was unrelated, but I kept the optimization
because it seemed vaguely useful.

In this commit, I remove the optimization because I don't really think it's
buying us much and it increased code complexity.

ToDo: Inline mkModuleToPkgConfGeneric into mkModuleToPkgConfAll

Signed-off-by: default avatarEdward Z. Yang <ezyang@cs.stanford.edu>

Test Plan: validate

Reviewers: simonpj, austin

Reviewed By: austin

Subscribers: thomie, carter

Differential Revision: https://phabricator.haskell.org/D434
parent 74a6a8a9
No related branches found
No related tags found
No related merge requests found
...@@ -210,17 +210,6 @@ originEmpty :: ModuleOrigin -> Bool ...@@ -210,17 +210,6 @@ originEmpty :: ModuleOrigin -> Bool
originEmpty (ModOrigin Nothing [] [] False) = True originEmpty (ModOrigin Nothing [] [] False) = True
originEmpty _ = False originEmpty _ = False
-- | When we do a plain lookup (e.g. for an import), initially, all we want
-- to know is if we can find it or not (and if we do and it's a reexport,
-- what the real name is). If the find fails, we'll want to investigate more
-- to give a good error message.
data SimpleModuleConf =
SModConf Module PackageConfig ModuleOrigin
| SModConfAmbiguous
-- | 'UniqFM' map from 'ModuleName'
type ModuleNameMap = UniqFM
-- | 'UniqFM' map from 'PackageKey' -- | 'UniqFM' map from 'PackageKey'
type PackageKeyMap = UniqFM type PackageKeyMap = UniqFM
...@@ -252,10 +241,6 @@ data PackageState = PackageState { ...@@ -252,10 +241,6 @@ data PackageState = PackageState {
-- is always mentioned before the packages it depends on. -- is always mentioned before the packages it depends on.
preloadPackages :: [PackageKey], preloadPackages :: [PackageKey],
-- | This is a simplified map from 'ModuleName' to original 'Module' and
-- package configuration providing it.
moduleToPkgConf :: ModuleNameMap SimpleModuleConf,
-- | This is a full map from 'ModuleName' to all modules which may possibly -- | This is a full map from 'ModuleName' to all modules which may possibly
-- be providing it. These providers may be hidden (but we'll still want -- be providing it. These providers may be hidden (but we'll still want
-- to report them in error messages), or it may be an ambiguous import. -- to report them in error messages), or it may be an ambiguous import.
...@@ -996,7 +981,6 @@ mkPackageState dflags pkgs0 preload0 this_package = do ...@@ -996,7 +981,6 @@ mkPackageState dflags pkgs0 preload0 this_package = do
let pstate = PackageState{ let pstate = PackageState{
preloadPackages = dep_preload, preloadPackages = dep_preload,
pkgIdMap = pkg_db, pkgIdMap = pkg_db,
moduleToPkgConf = mkModuleToPkgConf dflags pkg_db ipid_map vis_map,
moduleToPkgConfAll = mkModuleToPkgConfAll dflags pkg_db ipid_map vis_map, moduleToPkgConfAll = mkModuleToPkgConfAll dflags pkg_db ipid_map vis_map,
installedPackageIdMap = ipid_map installedPackageIdMap = ipid_map
} }
...@@ -1070,29 +1054,6 @@ mkModuleToPkgConfGeneric emptyMap sing setOrigins addListTo ...@@ -1070,29 +1054,6 @@ mkModuleToPkgConfGeneric emptyMap sing setOrigins addListTo
exposed_mods = exposedModules pkg exposed_mods = exposedModules pkg
hidden_mods = hiddenModules pkg hidden_mods = hiddenModules pkg
-- | This is a quick and efficient module map, which only contains an entry
-- if it is specified unambiguously.
mkModuleToPkgConf
:: DynFlags
-> PackageConfigMap
-> InstalledPackageIdMap
-> VisibilityMap
-> ModuleNameMap SimpleModuleConf
mkModuleToPkgConf =
mkModuleToPkgConfGeneric emptyMap sing setOrigins addListTo
where emptyMap = emptyUFM
sing pk m pkg = SModConf (mkModule pk m) pkg
-- NB: don't put hidden entries in the map, they're not valid!
addListTo m xs = addListToUFM_C merge m (filter isVisible xs)
isVisible (_, SModConf _ _ o) = originVisible o
isVisible (_, SModConfAmbiguous) = False
merge (SModConf m pkg o) (SModConf m' _ o')
| m == m' = SModConf m pkg (o `mappend` o')
| otherwise = SModConfAmbiguous
merge _ _ = SModConfAmbiguous
setOrigins (SModConf m pkg _) os = SModConf m pkg os
setOrigins SModConfAmbiguous _ = SModConfAmbiguous
-- | This is a slow and complete map, which includes information about -- | This is a slow and complete map, which includes information about
-- everything, including hidden modules -- everything, including hidden modules
mkModuleToPkgConfAll mkModuleToPkgConfAll
...@@ -1240,17 +1201,11 @@ lookupModuleWithSuggestions :: DynFlags ...@@ -1240,17 +1201,11 @@ lookupModuleWithSuggestions :: DynFlags
-> Maybe FastString -> Maybe FastString
-> LookupResult -> LookupResult
lookupModuleWithSuggestions dflags m mb_pn lookupModuleWithSuggestions dflags m mb_pn
= case lookupUFM (moduleToPkgConf pkg_state) m of = case Map.lookup m (moduleToPkgConfAll pkg_state) of
Just (SModConf m pkg o) | matches mb_pn pkg o ->
ASSERT( originVisible o ) LookupFound m pkg
_ -> case Map.lookup m (moduleToPkgConfAll pkg_state) of
Nothing -> LookupNotFound suggestions Nothing -> LookupNotFound suggestions
Just xs -> Just xs ->
case foldl' classify ([],[],[]) (Map.toList xs) of case foldl' classify ([],[],[]) (Map.toList xs) of
([], [], []) -> LookupNotFound suggestions ([], [], []) -> LookupNotFound suggestions
-- NB: Yes, we have to check this case too, since package qualified
-- imports could cause the main lookup to fail due to ambiguity,
-- but the second lookup to succeed.
(_, _, [(m, _)]) -> LookupFound m (mod_pkg m) (_, _, [(m, _)]) -> LookupFound m (mod_pkg m)
(_, _, exposed@(_:_)) -> LookupMultiple exposed (_, _, exposed@(_:_)) -> LookupMultiple exposed
(hidden_pkg, hidden_mod, []) -> LookupHidden hidden_pkg hidden_mod (hidden_pkg, hidden_mod, []) -> LookupHidden hidden_pkg hidden_mod
...@@ -1268,9 +1223,6 @@ lookupModuleWithSuggestions dflags m mb_pn ...@@ -1268,9 +1223,6 @@ lookupModuleWithSuggestions dflags m mb_pn
pkg_state = pkgState dflags pkg_state = pkgState dflags
mod_pkg = pkg_lookup . modulePackageKey mod_pkg = pkg_lookup . modulePackageKey
matches Nothing _ _ = True -- shortcut for efficiency
matches mb_pn pkg o = originVisible (filterOrigin mb_pn pkg o)
-- Filters out origins which are not associated with the given package -- Filters out origins which are not associated with the given package
-- qualifier. No-op if there is no package qualifier. Test if this -- qualifier. No-op if there is no package qualifier. Test if this
-- excluded all origins with 'originEmpty'. -- excluded all origins with 'originEmpty'.
......
0% Loading or .
You are about to add 0 people to the discussion. Proceed with caution.
Finish editing this message first!
Please register or to comment