X-Git-Url: http://git.megacz.com/?a=blobdiff_plain;f=compiler%2Fmain%2FFinder.lhs;h=6b6c52f6adf753bea40fbda1f80b6efd9fe31592;hb=f14f1daa67546643b49902c56829d13ec641f21c;hp=4c6ae292985e7350d8a98446e3cf610367565406;hpb=c735a21acf3e478df36f630cf224dcb3755db485;p=ghc-hetmet.git diff --git a/compiler/main/Finder.lhs b/compiler/main/Finder.lhs index 4c6ae29..6b6c52f 100644 --- a/compiler/main/Finder.lhs +++ b/compiler/main/Finder.lhs @@ -10,6 +10,7 @@ module Finder ( findImportedModule, findExactModule, findHomeModule, + findExposedPackageModule, mkHomeModLocation, mkHomeModLocation2, mkHiOnlyModLocation, @@ -31,18 +32,17 @@ import Packages import FastString import Util import PrelNames ( gHC_PRIM ) -import DynFlags ( DynFlags(..), isOneShot, GhcMode(..) ) +import DynFlags import Outputable -import FiniteMap -import LazyUniqFM +import UniqFM import Maybes ( expectJust ) +import Exception ( evaluate ) +import Distribution.Text import Distribution.Package hiding (PackageId) -import Data.IORef ( IORef, writeIORef, readIORef, modifyIORef ) -import Data.List +import Data.IORef ( IORef, writeIORef, readIORef, atomicModifyIORef ) import System.Directory import System.FilePath -import System.IO import Control.Monad import System.Time ( ClockTime ) @@ -67,6 +67,7 @@ type BaseName = String -- Basename of file -- assumed to not move around during a session. flushFinderCaches :: HscEnv -> IO () flushFinderCaches hsc_env = do + -- Ideally the update to both caches be a single atomic operation. writeIORef fc_ref emptyUFM flushModLocationCache this_pkg mlc_ref where @@ -76,23 +77,27 @@ flushFinderCaches hsc_env = do flushModLocationCache :: PackageId -> IORef ModLocationCache -> IO () flushModLocationCache this_pkg ref = do - fm <- readIORef ref - writeIORef ref $! filterFM is_ext fm + atomicModifyIORef ref $ \fm -> (filterModuleEnv is_ext fm, ()) + _ <- evaluate =<< readIORef ref return () where is_ext mod _ | modulePackageId mod /= this_pkg = True | otherwise = False addToFinderCache :: IORef FinderCache -> ModuleName -> FindResult -> IO () -addToFinderCache ref key val = modifyIORef ref $ \c -> addToUFM c key val +addToFinderCache ref key val = + atomicModifyIORef ref $ \c -> (addToUFM c key val, ()) addToModLocationCache :: IORef ModLocationCache -> Module -> ModLocation -> IO () -addToModLocationCache ref key val = modifyIORef ref $ \c -> addToFM c key val +addToModLocationCache ref key val = + atomicModifyIORef ref $ \c -> (extendModuleEnv c key val, ()) removeFromFinderCache :: IORef FinderCache -> ModuleName -> IO () -removeFromFinderCache ref key = modifyIORef ref $ \c -> delFromUFM c key +removeFromFinderCache ref key = + atomicModifyIORef ref $ \c -> (delFromUFM c key, ()) removeFromModLocationCache :: IORef ModLocationCache -> Module -> IO () -removeFromModLocationCache ref key = modifyIORef ref $ \c -> delFromFM c key +removeFromModLocationCache ref key = + atomicModifyIORef ref $ \c -> (delModuleEnv c key, ()) lookupFinderCache :: IORef FinderCache -> ModuleName -> IO (Maybe FindResult) lookupFinderCache ref key = do @@ -103,7 +108,7 @@ lookupModLocationCache :: IORef ModLocationCache -> Module -> IO (Maybe ModLocation) lookupModLocationCache ref key = do c <- readIORef ref - return $! lookupFM c key + return $! lookupModuleEnv c key -- ----------------------------------------------------------------------------- -- The two external entry points @@ -126,7 +131,7 @@ findImportedModule hsc_env mod_name mb_pkg = pkg_import = findExposedPackageModule hsc_env mod_name mb_pkg unqual_import = home_import - `orIfNotFound` + `orIfNotFound` findExposedPackageModule hsc_env mod_name Nothing -- | Locate a specific 'Module'. The purpose of this function is to @@ -146,14 +151,21 @@ findExactModule hsc_env mod = -- Helpers orIfNotFound :: IO FindResult -> IO FindResult -> IO FindResult -this `orIfNotFound` or_this = do +orIfNotFound this or_this = do res <- this case res of - NotFound here _ -> do - res2 <- or_this - case res2 of - NotFound or_here pkg -> return (NotFound (here ++ or_here) pkg) - _other -> return res2 + NotFound { fr_paths = paths1, fr_mods_hidden = mh1 + , fr_pkgs_hidden = ph1, 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 } + -> 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_suggestions = s1 ++ s2 }) + _other -> return res2 _other -> return res @@ -174,35 +186,38 @@ findExposedPackageModule :: HscEnv -> ModuleName -> Maybe FastString -> IO FindResult findExposedPackageModule hsc_env mod_name mb_pkg -- not found in any package: - | null found = return (NotFound [] Nothing) - -- found in just one exposed package: - | [(pkg_conf, _)] <- found_exposed - = let pkgid = mkPackageId (package pkg_conf) in - findPackageModule_ hsc_env (mkModule pkgid mod_name) pkg_conf - -- not found in any exposed package, report how it was hidden: - | null found_exposed, ((pkg_conf, exposed_mod):_) <- found - = let pkgid = mkPackageId (package pkg_conf) in - if not (exposed_mod) - then return (ModuleHidden pkgid) - else return (PackageHidden pkgid) - | otherwise - = return (FoundMultiple (map (mkPackageId.package.fst) found_exposed)) - where - dflags = hsc_dflags hsc_env - found = lookupModuleInAllPackages dflags mod_name - - found_exposed = [ (pkg_conf,exposed_mod) - | x@(pkg_conf,exposed_mod) <- found, - is_exposed x, - pkg_conf `matches` mb_pkg ] - - is_exposed (pkg_conf,exposed_mod) = exposed pkg_conf && exposed_mod - - _pkg_conf `matches` Nothing = True - pkg_conf `matches` Just pkg = - case packageName pkg_conf of - PackageName n -> pkg == mkFastString n - + = case lookupModuleWithSuggestions (hsc_dflags hsc_env) mod_name of + Left suggest -> return (NotFound { fr_paths = [], fr_pkg = Nothing + , fr_pkgs_hidden = [], fr_mods_hidden = [] + , fr_suggestions = suggest }) + Right found + | null found_exposed -- Found, but with no exposed copies + -> return (NotFound { fr_paths = [], fr_pkg = Nothing + , fr_pkgs_hidden = mod_hiddens, fr_mods_hidden = pkg_hiddens + , fr_suggestions = [] }) + + | [(pkg_conf,_)] <- found_exposed -- Found uniquely + -> let pkgid = packageConfigId pkg_conf in + findPackageModule_ hsc_env (mkModule pkgid mod_name) pkg_conf + + | otherwise -- Found in more than one place + -> return (FoundMultiple (map (packageConfigId.fst) found_exposed)) + where + for_this_pkg = case mb_pkg of + Nothing -> found + Just p -> filter ((`matches` p) . fst) found + found_exposed = filter is_exposed for_this_pkg + is_exposed (pkg_conf,exposed_mod) = exposed pkg_conf && exposed_mod + + mod_hiddens = [ packageConfigId pkg_conf + | (pkg_conf,False) <- found ] + + pkg_hiddens = [ packageConfigId pkg_conf + | (pkg_conf,_) <- found, not (exposed pkg_conf) ] + + pkg_conf `matches` pkg + = case packageName pkg_conf of + PackageName n -> pkg == mkFastString n modLocationCache :: HscEnv -> Module -> IO FindResult -> IO FindResult modLocationCache hsc_env mod do_this = do @@ -298,24 +313,22 @@ findPackageModule_ hsc_env mod pkg_conf = -- hi-suffix for packages depends on the build tag. package_hisuf | null tag = "hi" | otherwise = tag ++ "_hi" - hi_exts = - [ (package_hisuf, mkHiOnlyModLocation dflags package_hisuf) ] - source_exts = - [ ("hs", mkHiOnlyModLocation dflags package_hisuf) - , ("lhs", mkHiOnlyModLocation dflags package_hisuf) - ] - - -- mkdependHS needs to look for source files in packages too, so - -- that we can make dependencies between package before they have - -- been built. - exts - | MkDepend <- ghcMode dflags = hi_exts ++ source_exts - | otherwise = hi_exts + mk_hi_loc = mkHiOnlyModLocation dflags package_hisuf + + import_dirs = importDirs pkg_conf -- we never look for a .hi-boot file in an external package; -- .hi-boot files only make sense for the home package. in - searchPathExts (importDirs pkg_conf) mod exts + case import_dirs of + [one] | MkDepend <- ghcMode dflags -> do + -- there's only one place that this .hi file can be, so + -- don't bother looking for it. + let basename = moduleNameSlashes (moduleName mod) + loc <- mk_hi_loc one basename + return (Found loc mod) + _otherwise -> + searchPathExts import_dirs mod [(package_hisuf, mk_hi_loc)] -- ----------------------------------------------------------------------------- -- General path searching @@ -354,7 +367,11 @@ searchPathExts paths mod exts file = base <.> ext ] - search [] = return (NotFound (map fst to_search) (Just (modulePackageId mod))) + search [] = return (NotFound { fr_paths = map fst to_search + , fr_pkg = Just (modulePackageId mod) + , fr_mods_hidden = [], fr_pkgs_hidden = [] + , fr_suggestions = [] }) + search ((file, mk_result) : rest) = do b <- doesFileExist file if b @@ -494,23 +511,14 @@ mkStubPaths dflags mod location stub_basename = stub_basename0 ++ "_stub" - -- this is the filename we're going to use when - -- \#including the stub_h file from the .hc file. - -- Without -stubdir, we just #include the basename - -- (eg. for a module A.B, we #include "B_stub.h"), - -- relying on the fact that we add an implicit -I flag - -- for the directory in which the source file resides - -- (see DriverPipeline.hs). With -stubdir, we - -- \#include "A/B.h", assuming that the user has added - -- -I along with -stubdir . - include_basename - | Just _ <- stubdir = mod_basename - | otherwise = takeFileName src_basename + obj = ml_obj_file location + osuf = objectSuf dflags + stub_obj_base = dropTail (length osuf + 1) obj ++ "_stub" + -- NB. not takeFileName, see #3093 in (stub_basename <.> "c", stub_basename <.> "h", - (include_basename ++ "_stub") <.> "h") - -- the _stub.o filename is derived from the ml_obj_file. + stub_obj_base <.> objectSuf dflags) -- ----------------------------------------------------------------------------- -- findLinkable isn't related to the other stuff in here, @@ -539,59 +547,90 @@ findObjectLinkable mod obj_fn obj_time = do cannotFindModule :: DynFlags -> ModuleName -> FindResult -> SDoc cannotFindModule = cantFindErr (sLit "Could not find module") + (sLit "Ambiguous module name") cannotFindInterface :: DynFlags -> ModuleName -> FindResult -> SDoc cannotFindInterface = cantFindErr (sLit "Failed to load interface for") + (sLit "Ambiguous interface for") -cantFindErr :: LitString -> DynFlags -> ModuleName -> FindResult -> SDoc -cantFindErr cannot_find _dflags mod_name (FoundMultiple pkgs) - = hang (ptext cannot_find <+> quotes (ppr mod_name) <> colon) 2 ( +cantFindErr :: LitString -> LitString -> DynFlags -> ModuleName -> FindResult + -> SDoc +cantFindErr _ multiple_found _ mod_name (FoundMultiple pkgs) + = hang (ptext multiple_found <+> quotes (ppr mod_name) <> colon) 2 ( sep [ptext (sLit "it was found in multiple packages:"), hsep (map (text.packageIdString) pkgs)] ) -cantFindErr cannot_find dflags mod_name find_result +cantFindErr cannot_find _ dflags mod_name find_result = hang (ptext cannot_find <+> quotes (ppr mod_name) <> colon) 2 more_info where more_info = case find_result of - PackageHidden pkg - -> ptext (sLit "it is a member of package") <+> ppr pkg <> comma - <+> ptext (sLit "which is hidden") - - ModuleHidden pkg - -> ptext (sLit "it is hidden") <+> parens (ptext (sLit "in package") - <+> ppr pkg) - NoPackage pkg - -> ptext (sLit "no package matching") <+> ppr pkg <+> + -> ptext (sLit "no package matching") <+> quotes (ppr pkg) <+> ptext (sLit "was found") - NotFound files mb_pkg - | null files - -> ptext (sLit "it is not a module in the current program, or in any known package.") - | Just pkg <- mb_pkg, pkg /= thisPackage dflags, build_tag /= "" - -> let - build = if build_tag == "p" then "profiling" - else "\"" ++ build_tag ++ "\"" - in - ptext (sLit "Perhaps you haven't installed the ") <> text build <> - ptext (sLit " libraries for package ") <> ppr pkg <> char '?' $$ - not_found files + NotFound { fr_paths = files, fr_pkg = mb_pkg + , fr_mods_hidden = mod_hiddens, fr_pkgs_hidden = pkg_hiddens + , fr_suggestions = suggest } + | Just pkg <- mb_pkg, pkg /= thisPackage dflags + -> not_found_in_package pkg files - | otherwise - -> not_found files + | null files && null mod_hiddens && null pkg_hiddens + -> vcat [ ptext (sLit "it is not a module in the current program, or in any known package.") + , pp_suggestions suggest ] - NotFoundInPackage pkg - -> ptext (sLit "it is not in package") <+> ppr pkg + | otherwise + -> vcat (map pkg_hidden pkg_hiddens) $$ + vcat (map mod_hidden mod_hiddens) $$ + tried_these files - _ -> panic "cantFindErr" + _ -> panic "cantFindErr" build_tag = buildTag dflags - not_found files - | verbosity dflags < 3 - = ptext (sLit "Use -v to see a list of the files searched for.") - | otherwise - = hang (ptext (sLit "locations searched:")) 2 (vcat (map text files)) + not_found_in_package pkg files + | build_tag /= "" + = let + build = if build_tag == "p" then "profiling" + else "\"" ++ build_tag ++ "\"" + in + ptext (sLit "Perhaps you haven't installed the ") <> text build <> + ptext (sLit " libraries for package ") <> quotes (ppr pkg) <> char '?' $$ + tried_these files + + | otherwise + = ptext (sLit "There are files missing in the ") <> quotes (ppr pkg) <> + ptext (sLit " package,") $$ + ptext (sLit "try running 'ghc-pkg check'.") $$ + tried_these files + + tried_these files + | null files = empty + | verbosity dflags < 3 = + ptext (sLit "Use -v to see a list of the files searched for.") + | otherwise = + hang (ptext (sLit "locations searched:")) 2 $ vcat (map text files) + + pkg_hidden pkg = + ptext (sLit "It is a member of the hidden package") <+> quotes (ppr pkg) + <> dot $$ cabal_pkg_hidden_hint pkg + cabal_pkg_hidden_hint pkg + | dopt Opt_BuildingCabalPackage dflags + = case simpleParse (packageIdString pkg) of + Just pid -> + ptext (sLit "Perhaps you need to add") <+> + quotes (text (display (pkgName pid))) <+> + ptext (sLit "to the build-depends in your .cabal file.") + Nothing -> empty + | otherwise = empty + + mod_hidden pkg = + ptext (sLit "it is a hidden module in the package") <+> quotes (ppr pkg) + + pp_suggestions sugs + | null sugs = empty + | otherwise = ptext (sLit "Perhaps you meant") <+> vcat (map pp sugs) + where + pp mod = ppr mod <+> parens (ptext (sLit "package") <+> ppr (modulePackageId mod)) \end{code}