X-Git-Url: http://git.megacz.com/?p=ghc-hetmet.git;a=blobdiff_plain;f=compiler%2Fmain%2FFinder.lhs;h=cc19e317cde7825115da0cccf5abe0e8efb9d30f;hp=56929ce24b2bf73e1b2c299ffb807847483274e5;hb=703ca1542c8e0983cc9d8eebce6e9f3dd3fd71e2;hpb=2b37fb7a1809e4d0aec3db33a9c8a215b00a869b diff --git a/compiler/main/Finder.lhs b/compiler/main/Finder.lhs index 56929ce..cc19e31 100644 --- a/compiler/main/Finder.lhs +++ b/compiler/main/Finder.lhs @@ -10,8 +10,10 @@ module Finder ( findImportedModule, findExactModule, findHomeModule, + findExposedPackageModule, mkHomeModLocation, mkHomeModLocation2, + mkHiOnlyModLocation, addHomeModuleToFinder, uncacheModule, mkStubPaths, @@ -21,9 +23,8 @@ module Finder ( cannotFindModule, cannotFindInterface, - ) where -#include "HsVersions.h" + ) where import Module import HscTypes @@ -34,13 +35,13 @@ import PrelNames ( gHC_PRIM ) import DynFlags ( DynFlags(..), isOneShot, GhcMode(..) ) import Outputable import FiniteMap -import UniqFM +import LazyUniqFM import Maybes ( expectJust ) +import Distribution.Package hiding (PackageId) import Data.IORef ( IORef, writeIORef, readIORef, modifyIORef ) -import Data.List import System.Directory -import System.IO +import System.FilePath import Control.Monad import System.Time ( ClockTime ) @@ -80,16 +81,25 @@ flushModLocationCache this_pkg ref = do 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 + +addToModLocationCache :: IORef ModLocationCache -> Module -> ModLocation -> IO () addToModLocationCache ref key val = modifyIORef ref $ \c -> addToFM c key val +removeFromFinderCache :: IORef FinderCache -> ModuleName -> IO () removeFromFinderCache ref key = modifyIORef ref $ \c -> delFromUFM c key + +removeFromModLocationCache :: IORef ModLocationCache -> Module -> IO () removeFromModLocationCache ref key = modifyIORef ref $ \c -> delFromFM c key +lookupFinderCache :: IORef FinderCache -> ModuleName -> IO (Maybe FindResult) lookupFinderCache ref key = do c <- readIORef ref return $! lookupUFM c key +lookupModLocationCache :: IORef ModLocationCache -> Module + -> IO (Maybe ModLocation) lookupModLocationCache ref key = do c <- readIORef ref return $! lookupFM c key @@ -103,27 +113,20 @@ lookupModLocationCache ref key = do -- packages to find the module, if a package is specified then only -- that package is searched for the module. -findImportedModule :: HscEnv -> ModuleName -> Maybe PackageId -> IO FindResult -findImportedModule hsc_env mod_name mb_pkgid = - case mb_pkgid of - Nothing -> unqual_import - Just pkg | pkg == this_pkg -> home_import - | otherwise -> pkg_import pkg +findImportedModule :: HscEnv -> ModuleName -> Maybe FastString -> IO FindResult +findImportedModule hsc_env mod_name mb_pkg = + case mb_pkg of + Nothing -> unqual_import + Just pkg | pkg == fsLit "this" -> home_import -- "this" is special + | otherwise -> pkg_import where - dflags = hsc_dflags hsc_env - this_pkg = thisPackage dflags - - home_import = findHomeModule hsc_env mod_name + home_import = findHomeModule hsc_env mod_name - pkg_import pkg = findPackageModule hsc_env (mkModule pkg mod_name) - -- ToDo: this isn't quite right, the module we want - -- might actually be in another package, but re-exposed - -- ToDo: should return NotFoundInPackage if - -- the module isn't exposed by the package. + pkg_import = findExposedPackageModule hsc_env mod_name mb_pkg - unqual_import = home_import + unqual_import = home_import `orIfNotFound` - findExposedPackageModule hsc_env mod_name + findExposedPackageModule hsc_env mod_name Nothing -- | Locate a specific 'Module'. The purpose of this function is to -- create a 'ModLocation' for a given 'Module', that is to find out @@ -141,13 +144,18 @@ findExactModule hsc_env mod = -- ----------------------------------------------------------------------------- -- Helpers +orIfNotFound :: IO FindResult -> IO FindResult -> IO FindResult this `orIfNotFound` or_this = do res <- this case res of - NotFound here _ -> do + NotFound places1 _mb_pkg1 mod_hiddens1 pkg_hiddens1 -> do res2 <- or_this case res2 of - NotFound or_here pkg -> return (NotFound (here ++ or_here) pkg) + NotFound places2 mb_pkg2 mod_hiddens2 pkg_hiddens2 -> + return (NotFound (places1 ++ places2) + mb_pkg2 -- snd arg is the package search + (mod_hiddens1 ++ mod_hiddens2) + (pkg_hiddens1 ++ pkg_hiddens2)) _other -> return res2 _other -> return res @@ -165,28 +173,40 @@ homeSearchCache hsc_env mod_name do_this = do _other -> return () return result -findExposedPackageModule :: HscEnv -> ModuleName -> IO FindResult -findExposedPackageModule hsc_env mod_name +findExposedPackageModule :: HscEnv -> ModuleName -> Maybe FastString + -> IO FindResult +findExposedPackageModule hsc_env mod_name mb_pkg -- not found in any package: - | null found = return (NotFound [] Nothing) + | null found_exposed = return (NotFound [] Nothing mod_hiddens pkg_hiddens) -- 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 = filter is_exposed found + + for_this_pkg = filter ((`matches` mb_pkg) . fst) found + + found_exposed = [ (pkg_conf,exposed_mod) + | x@(pkg_conf,exposed_mod) <- for_this_pkg, + is_exposed x ] + is_exposed (pkg_conf,exposed_mod) = exposed pkg_conf && exposed_mod + mod_hiddens = [ mkPackageId (package pkg_conf) + | (pkg_conf,False) <- found ] + + pkg_hiddens = [ mkPackageId (package pkg_conf) + | (pkg_conf,_) <- found, not (exposed pkg_conf) ] + + _pkg_conf `matches` Nothing = True + pkg_conf `matches` Just 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 @@ -266,6 +286,7 @@ findPackageModule hsc_env mod = do Nothing -> return (NoPackage pkg_id) Just pkg_conf -> findPackageModule_ hsc_env mod pkg_conf +findPackageModule_ :: HscEnv -> Module -> PackageConfig -> IO FindResult findPackageModule_ hsc_env mod pkg_conf = modLocationCache hsc_env mod $ @@ -281,24 +302,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 @@ -326,18 +345,19 @@ searchPathExts paths mod exts return result where - basename = dots_to_slashes (moduleNameString (moduleName mod)) + basename = moduleNameSlashes (moduleName mod) to_search :: [(FilePath, IO ModLocation)] to_search = [ (file, fn path basename) | path <- paths, (ext,fn) <- exts, let base | path == "." = basename - | otherwise = path `joinFileName` basename - file = base `joinFileExt` ext + | otherwise = path basename + file = base <.> ext ] - search [] = return (NotFound (map fst to_search) (Just (modulePackageId mod))) + search [] = return (NotFound (map fst to_search) (Just (modulePackageId mod)) + [] []) search ((file, mk_result) : rest) = do b <- doesFileExist file if b @@ -347,7 +367,7 @@ searchPathExts paths mod exts mkHomeModLocationSearched :: DynFlags -> ModuleName -> FileExt -> FilePath -> BaseName -> IO ModLocation mkHomeModLocationSearched dflags mod suff path basename = do - mkHomeModLocation2 dflags mod (path `joinFileName` basename) suff + mkHomeModLocation2 dflags mod (path basename) suff -- ----------------------------------------------------------------------------- -- Constructing a home module location @@ -376,7 +396,7 @@ mkHomeModLocationSearched dflags mod suff path basename = do -- (b) and (c): "." -- -- src_basename --- (a): dots_to_slashes (moduleNameUserString mod) +-- (a): (moduleNameSlashes mod) -- (b) and (c): The filename of the source file, minus its extension -- -- ext @@ -384,7 +404,7 @@ mkHomeModLocationSearched dflags mod suff path basename = do mkHomeModLocation :: DynFlags -> ModuleName -> FilePath -> IO ModLocation mkHomeModLocation dflags mod src_filename = do - let (basename,extension) = splitFilename src_filename + let (basename,extension) = splitExtension src_filename mkHomeModLocation2 dflags mod basename extension mkHomeModLocation2 :: DynFlags @@ -393,22 +413,22 @@ mkHomeModLocation2 :: DynFlags -> String -- Suffix -> IO ModLocation mkHomeModLocation2 dflags mod src_basename ext = do - let mod_basename = dots_to_slashes (moduleNameString mod) + let mod_basename = moduleNameSlashes mod obj_fn <- mkObjPath dflags src_basename mod_basename hi_fn <- mkHiPath dflags src_basename mod_basename - return (ModLocation{ ml_hs_file = Just (src_basename `joinFileExt` ext), + return (ModLocation{ ml_hs_file = Just (src_basename <.> ext), ml_hi_file = hi_fn, ml_obj_file = obj_fn }) mkHiOnlyModLocation :: DynFlags -> Suffix -> FilePath -> String -> IO ModLocation mkHiOnlyModLocation dflags hisuf path basename - = do let full_basename = path `joinFileName` basename + = do let full_basename = path basename obj_fn <- mkObjPath dflags full_basename basename return ModLocation{ ml_hs_file = Nothing, - ml_hi_file = full_basename `joinFileExt` hisuf, + ml_hi_file = full_basename <.> hisuf, -- Remove the .hi-boot suffix from -- hi_file, if it had one. We always -- want the name of the real .hi file @@ -428,10 +448,10 @@ mkObjPath dflags basename mod_basename odir = objectDir dflags osuf = objectSuf dflags - obj_basename | Just dir <- odir = dir `joinFileName` mod_basename + obj_basename | Just dir <- odir = dir mod_basename | otherwise = basename - return (obj_basename `joinFileExt` osuf) + return (obj_basename <.> osuf) -- | Constructs the filename of a .hi file for a given source file. -- Does /not/ check whether the .hi file exists @@ -445,10 +465,10 @@ mkHiPath dflags basename mod_basename hidir = hiDir dflags hisuf = hiSuf dflags - hi_basename | Just dir <- hidir = dir `joinFileName` mod_basename + hi_basename | Just dir <- hidir = dir mod_basename | otherwise = basename - return (hi_basename `joinFileExt` hisuf) + return (hi_basename <.> hisuf) -- ----------------------------------------------------------------------------- @@ -461,25 +481,30 @@ mkStubPaths :: DynFlags -> ModuleName -> ModLocation - -> (FilePath,FilePath) + -> (FilePath,FilePath,FilePath) mkStubPaths dflags mod location = let - stubdir = stubDir dflags + stubdir = stubDir dflags + + mod_basename = moduleNameSlashes mod + src_basename = dropExtension $ expectJust "mkStubPaths" + (ml_hs_file location) - mod_basename = dots_to_slashes (moduleNameString mod) - src_basename = basenameOf (expectJust "mkStubPaths" - (ml_hs_file location)) + stub_basename0 + | Just dir <- stubdir = dir mod_basename + | otherwise = src_basename - stub_basename0 - | Just dir <- stubdir = dir `joinFileName` mod_basename - | otherwise = src_basename + stub_basename = stub_basename0 ++ "_stub" - stub_basename = stub_basename0 ++ "_stub" + 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 `joinFileExt` "c", - stub_basename `joinFileExt` "h") - -- the _stub.o filename is derived from the ml_obj_file. + (stub_basename <.> "c", + stub_basename <.> "h", + stub_obj_base <.> objectSuf dflags) -- ----------------------------------------------------------------------------- -- findLinkable isn't related to the other stuff in here, @@ -497,76 +522,85 @@ findObjectLinkableMaybe mod locn -- its modification time. findObjectLinkable :: Module -> FilePath -> ClockTime -> IO Linkable findObjectLinkable mod obj_fn obj_time = do - let stub_fn = case splitFilename3 obj_fn of - (dir, base, ext) -> dir ++ "/" ++ base ++ "_stub.o" + let stub_fn = (dropExtension obj_fn ++ "_stub") <.> "o" stub_exist <- doesFileExist stub_fn if stub_exist then return (LM obj_time mod [DotO obj_fn, DotO stub_fn]) else return (LM obj_time mod [DotO obj_fn]) -- ----------------------------------------------------------------------------- --- Utils - -dots_to_slashes = map (\c -> if c == '.' then '/' else c) - - --- ----------------------------------------------------------------------------- -- Error messages cannotFindModule :: DynFlags -> ModuleName -> FindResult -> SDoc -cannotFindModule = cantFindErr SLIT("Could not find module") +cannotFindModule = cantFindErr (sLit "Could not find module") + (sLit "Ambiguous module name") cannotFindInterface :: DynFlags -> ModuleName -> FindResult -> SDoc -cannotFindInterface = cantFindErr SLIT("Failed to load interface for") - -cantFindErr cannot_find dflags mod_name (FoundMultiple pkgs) - = hang (ptext cannot_find <+> quotes (ppr mod_name) <> colon) 2 ( - sep [ptext SLIT("it was found in multiple packages:"), +cannotFindInterface = cantFindErr (sLit "Failed to load interface for") + (sLit "Ambiguous interface for") + +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") + NoPackage pkg + -> ptext (sLit "no package matching") <+> quotes (ppr pkg) <+> + ptext (sLit "was found") - ModuleHidden pkg - -> ptext SLIT("it is hidden") <+> parens (ptext SLIT("in package") - <+> ppr pkg) + NotFound files mb_pkg mod_hiddens pkg_hiddens + | Just pkg <- mb_pkg, pkg /= thisPackage dflags + -> not_found_in_package pkg files - NoPackage pkg - -> ptext SLIT("no package matching") <+> 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 + | null files && null mod_hiddens && null pkg_hiddens + -> ptext (sLit "it is not a module in the current program, or in any known package.") | otherwise - -> not_found files + -> vcat (map pkg_hidden pkg_hiddens) $$ + vcat (map mod_hidden mod_hiddens) $$ + tried_these files NotFoundInPackage pkg - -> ptext SLIT("it is not in package") <+> ppr pkg + -> ptext (sLit "it is not in package") <+> quotes (ppr pkg) _ -> 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) + + mod_hidden pkg = + ptext (sLit "it is a hidden module in the package") <+> quotes (ppr pkg) \end{code}