X-Git-Url: http://git.megacz.com/?p=ghc-hetmet.git;a=blobdiff_plain;f=compiler%2Fmain%2FFinder.lhs;h=b76bd972e7bbcf4dd67b99f39f75c827f2cc3242;hp=fbde40f6ea261823652d8bd6b4fdc0a93dd6d6bc;hb=d51f42f602bf9a6d1b356c41228a534c88723f65;hpb=0065d5ab628975892cea1ec7303f968c3338cbe1 diff --git a/compiler/main/Finder.lhs b/compiler/main/Finder.lhs index fbde40f..b76bd97 100644 --- a/compiler/main/Finder.lhs +++ b/compiler/main/Finder.lhs @@ -1,46 +1,51 @@ % -% (c) The University of Glasgow, 2000 +% (c) The University of Glasgow, 2000-2006 % \section[Finder]{Module Finder} \begin{code} module Finder ( - flushFinderCache, -- :: IO () + flushFinderCaches, FindResult(..), - findModule, -- :: ModuleName -> Bool -> IO FindResult - findPackageModule, -- :: ModuleName -> Bool -> IO FindResult - mkHomeModLocation, -- :: ModuleName -> FilePath -> IO ModLocation - mkHomeModLocation2, -- :: ModuleName -> FilePath -> String -> IO ModLocation - addHomeModuleToFinder, -- :: HscEnv -> Module -> ModLocation -> IO () - uncacheModule, -- :: HscEnv -> Module -> IO () + findImportedModule, + findExactModule, + findHomeModule, + mkHomeModLocation, + mkHomeModLocation2, + mkHiOnlyModLocation, + addHomeModuleToFinder, + uncacheModule, mkStubPaths, findObjectLinkableMaybe, findObjectLinkable, - cantFindError, -- :: DynFlags -> Module -> FindResult -> SDoc + cannotFindModule, + cannotFindInterface, + ) where #include "HsVersions.h" import Module -import UniqFM ( filterUFM, delFromUFM ) import HscTypes import Packages import FastString import Util +import PrelNames ( gHC_PRIM ) import DynFlags ( DynFlags(..), isOneShot, GhcMode(..) ) import Outputable +import FiniteMap +import LazyUniqFM import Maybes ( expectJust ) -import DATA_IOREF ( IORef, writeIORef, readIORef ) - +import Data.IORef ( IORef, writeIORef, readIORef, modifyIORef ) import Data.List import System.Directory +import System.FilePath import System.IO import Control.Monad -import Data.Maybe ( isNothing ) -import Time ( ClockTime ) +import System.Time ( ClockTime ) type FileExt = String -- Filename extension @@ -61,137 +66,184 @@ type BaseName = String -- Basename of file -- remove all the home modules from the cache; package modules are -- assumed to not move around during a session. -flushFinderCache :: IORef FinderCache -> IO () -flushFinderCache finder_cache = do - fm <- readIORef finder_cache - writeIORef finder_cache $! filterUFM (\(loc,m) -> isNothing m) fm - -addToFinderCache :: IORef FinderCache -> Module -> FinderCacheEntry -> IO () -addToFinderCache finder_cache mod_name entry = do - fm <- readIORef finder_cache - writeIORef finder_cache $! extendModuleEnv fm mod_name entry - -removeFromFinderCache :: IORef FinderCache -> Module -> IO () -removeFromFinderCache finder_cache mod_name = do - fm <- readIORef finder_cache - writeIORef finder_cache $! delFromUFM fm mod_name - -lookupFinderCache :: IORef FinderCache -> Module -> IO (Maybe FinderCacheEntry) -lookupFinderCache finder_cache mod_name = do - fm <- readIORef finder_cache - return $! lookupModuleEnv fm mod_name +flushFinderCaches :: HscEnv -> IO () +flushFinderCaches hsc_env = do + writeIORef fc_ref emptyUFM + flushModLocationCache this_pkg mlc_ref + where + this_pkg = thisPackage (hsc_dflags hsc_env) + fc_ref = hsc_FC hsc_env + mlc_ref = hsc_MLC hsc_env + +flushModLocationCache :: PackageId -> IORef ModLocationCache -> IO () +flushModLocationCache this_pkg ref = do + fm <- readIORef ref + writeIORef ref $! filterFM is_ext fm + 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 + +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 -- ----------------------------------------------------------------------------- -- The two external entry points --- This is the main interface to the finder, which maps ModuleNames to --- Modules and ModLocations. --- --- The Module contains one crucial bit of information about a module: --- whether it lives in the current ("home") package or not (see Module --- for more details). --- --- The ModLocation contains the names of all the files associated with --- that module: its source file, .hi file, object file, etc. - -data FindResult - = Found ModLocation PackageIdH - -- the module was found - | FoundMultiple [PackageId] - -- *error*: both in multiple packages - | PackageHidden PackageId - -- for an explicit source import: the package containing the module is - -- not exposed. - | ModuleHidden PackageId - -- for an explicit source import: the package containing the module is - -- exposed, but the module itself is hidden. - | NotFound [FilePath] - -- the module was not found, the specified places were searched. - -findModule :: HscEnv -> Module -> Bool -> IO FindResult -findModule = findModule' True - -findPackageModule :: HscEnv -> Module -> Bool -> IO FindResult -findPackageModule = findModule' False - - -data LocalFindResult - = Ok FinderCacheEntry - | CantFindAmongst [FilePath] - | MultiplePackages [PackageId] - -findModule' :: Bool -> HscEnv -> Module -> Bool -> IO FindResult -findModule' home_allowed hsc_env name explicit - = do -- First try the cache - mb_entry <- lookupFinderCache cache name - case mb_entry of - Just old_entry -> return $! found old_entry - Nothing -> not_cached +-- | Locate a module that was imported by the user. We have the +-- module's name, and possibly a package name. Without a package +-- name, this function will use the search path and the known exposed +-- 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 + where + dflags = hsc_dflags hsc_env + this_pkg = thisPackage dflags + + 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. + + unqual_import = home_import + `orIfNotFound` + findExposedPackageModule hsc_env mod_name + +-- | Locate a specific 'Module'. The purpose of this function is to +-- create a 'ModLocation' for a given 'Module', that is to find out +-- where the files associated with this module live. It is used when +-- reading the interface for a module mentioned by another interface, +-- for example (a "system import"). + +findExactModule :: HscEnv -> Module -> IO FindResult +findExactModule hsc_env mod = + let dflags = hsc_dflags hsc_env in + if modulePackageId mod == thisPackage dflags + then findHomeModule hsc_env (moduleName mod) + else findPackageModule hsc_env mod - where - cache = hsc_FC hsc_env - dflags = hsc_dflags hsc_env - - -- We've found the module, so the remaining question is - -- whether it's visible or not - found :: FinderCacheEntry -> FindResult - found (loc, Nothing) - | home_allowed = Found loc HomePackage - | otherwise = NotFound [] - found (loc, Just (pkg, exposed_mod)) - | explicit && not exposed_mod = ModuleHidden pkg_name - | explicit && not (exposed pkg) = PackageHidden pkg_name - | otherwise = - Found loc (ExtPackage (mkPackageId (package pkg))) - where - pkg_name = packageConfigId pkg - - found_new entry = do - addToFinderCache cache name entry - return $! found entry - - not_cached - | not home_allowed = do - j <- findPackageModule' dflags name - case j of - Ok entry -> found_new entry - MultiplePackages pkgs -> return (FoundMultiple pkgs) - CantFindAmongst paths -> return (NotFound paths) - - | otherwise = do - j <- findHomeModule' dflags name - case j of - Ok entry -> found_new entry - MultiplePackages pkgs -> return (FoundMultiple pkgs) - CantFindAmongst home_files -> do - r <- findPackageModule' dflags name - case r of - CantFindAmongst pkg_files -> - return (NotFound (home_files ++ pkg_files)) - MultiplePackages pkgs -> - return (FoundMultiple pkgs) - Ok entry -> - found_new entry - -addHomeModuleToFinder :: HscEnv -> Module -> ModLocation -> IO () -addHomeModuleToFinder hsc_env mod loc - = addToFinderCache (hsc_FC hsc_env) mod (loc, Nothing) - -uncacheModule :: HscEnv -> Module -> IO () -uncacheModule hsc_env mod = removeFromFinderCache (hsc_FC hsc_env) mod +-- ----------------------------------------------------------------------------- +-- Helpers + +orIfNotFound :: IO FindResult -> IO FindResult -> IO FindResult +this `orIfNotFound` 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 + _other -> return res + + +homeSearchCache :: HscEnv -> ModuleName -> IO FindResult -> IO FindResult +homeSearchCache hsc_env mod_name do_this = do + m <- lookupFinderCache (hsc_FC hsc_env) mod_name + case m of + Just result -> return result + Nothing -> do + result <- do_this + addToFinderCache (hsc_FC hsc_env) mod_name result + case result of + Found loc mod -> addToModLocationCache (hsc_MLC hsc_env) mod loc + _other -> return () + return result + +findExposedPackageModule :: HscEnv -> ModuleName -> IO FindResult +findExposedPackageModule hsc_env mod_name + -- 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 = filter is_exposed found + is_exposed (pkg_conf,exposed_mod) = exposed pkg_conf && exposed_mod + + +modLocationCache :: HscEnv -> Module -> IO FindResult -> IO FindResult +modLocationCache hsc_env mod do_this = do + mb_loc <- lookupModLocationCache mlc mod + case mb_loc of + Just loc -> return (Found loc mod) + Nothing -> do + result <- do_this + case result of + Found loc mod -> addToModLocationCache (hsc_MLC hsc_env) mod loc + _other -> return () + return result + where + mlc = hsc_MLC hsc_env + +addHomeModuleToFinder :: HscEnv -> ModuleName -> ModLocation -> IO Module +addHomeModuleToFinder hsc_env mod_name loc = do + let mod = mkModule (thisPackage (hsc_dflags hsc_env)) mod_name + addToFinderCache (hsc_FC hsc_env) mod_name (Found loc mod) + addToModLocationCache (hsc_MLC hsc_env) mod loc + return mod + +uncacheModule :: HscEnv -> ModuleName -> IO () +uncacheModule hsc_env mod = do + let this_pkg = thisPackage (hsc_dflags hsc_env) + removeFromFinderCache (hsc_FC hsc_env) mod + removeFromModLocationCache (hsc_MLC hsc_env) (mkModule this_pkg mod) -- ----------------------------------------------------------------------------- -- The internal workers -findHomeModule' :: DynFlags -> Module -> IO LocalFindResult -findHomeModule' dflags mod = do - let home_path = importPaths dflags - hisuf = hiSuf dflags +-- | Search for a module in the home package only. +findHomeModule :: HscEnv -> ModuleName -> IO FindResult +findHomeModule hsc_env mod_name = + homeSearchCache hsc_env mod_name $ + let + dflags = hsc_dflags hsc_env + home_path = importPaths dflags + hisuf = hiSuf dflags + mod = mkModule (thisPackage dflags) mod_name - let source_exts = - [ ("hs", mkHomeModLocationSearched dflags mod "hs") - , ("lhs", mkHomeModLocationSearched dflags mod "lhs") + [ ("hs", mkHomeModLocationSearched dflags mod_name "hs") + , ("lhs", mkHomeModLocationSearched dflags mod_name "lhs") ] hi_exts = [ (hisuf, mkHiOnlyModLocation dflags hisuf) @@ -203,31 +255,52 @@ findHomeModule' dflags mod = do -- compilation mode we look for .hi and .hi-boot files only. exts | isOneShot (ghcMode dflags) = hi_exts | otherwise = source_exts + in + + -- special case for GHC.Prim; we won't find it in the filesystem. + -- This is important only when compiling the base package (where GHC.Prim + -- is a home module). + if mod == gHC_PRIM + then return (Found (error "GHC.Prim ModLocation") mod) + else searchPathExts home_path mod exts - -findPackageModule' :: DynFlags -> Module -> IO LocalFindResult -findPackageModule' dflags mod - = case lookupModuleInAllPackages dflags mod of - [] -> return (CantFindAmongst []) - [pkg_info] -> findPackageIface dflags mod pkg_info - many -> return (MultiplePackages (map (mkPackageId.package.fst) many)) - -findPackageIface :: DynFlags -> Module -> (PackageConfig,Bool) -> IO LocalFindResult -findPackageIface dflags mod pkg_info@(pkg_conf, _) = do + + +-- | Search for a module in external packages only. +findPackageModule :: HscEnv -> Module -> IO FindResult +findPackageModule hsc_env mod = do + let + dflags = hsc_dflags hsc_env + pkg_id = modulePackageId mod + pkg_map = pkgIdMap (pkgState dflags) + -- + case lookupPackage pkg_map pkg_id of + 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 $ + + -- special case for GHC.Prim; we won't find it in the filesystem. + if mod == gHC_PRIM + then return (Found (error "GHC.Prim ModLocation") mod) + else + let + dflags = hsc_dflags hsc_env tag = buildTag dflags -- hi-suffix for packages depends on the build tag. package_hisuf | null tag = "hi" | otherwise = tag ++ "_hi" hi_exts = - [ (package_hisuf, - mkPackageModLocation dflags pkg_info package_hisuf) ] + [ (package_hisuf, mkHiOnlyModLocation dflags package_hisuf) ] source_exts = - [ ("hs", mkPackageModLocation dflags pkg_info package_hisuf) - , ("lhs", mkPackageModLocation dflags pkg_info package_hisuf) + [ ("hs", mkHiOnlyModLocation dflags package_hisuf) + , ("lhs", mkHiOnlyModLocation dflags package_hisuf) ] -- mkdependHS needs to look for source files in packages too, so @@ -238,7 +311,7 @@ findPackageIface dflags mod pkg_info@(pkg_conf, _) = do | otherwise = hi_exts -- 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 -- ----------------------------------------------------------------------------- @@ -248,11 +321,11 @@ searchPathExts :: [FilePath] -- paths to search -> Module -- module name -> [ ( - FileExt, -- suffix - FilePath -> BaseName -> IO FinderCacheEntry -- action + FileExt, -- suffix + FilePath -> BaseName -> IO ModLocation -- action ) ] - -> IO LocalFindResult + -> IO FindResult searchPathExts paths mod exts = do result <- search to_search @@ -267,41 +340,28 @@ searchPathExts paths mod exts return result where - basename = dots_to_slashes (moduleString mod) + basename = moduleNameSlashes (moduleName mod) - to_search :: [(FilePath, IO FinderCacheEntry)] + 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 (CantFindAmongst (map fst to_search)) + search [] = return (NotFound (map fst to_search) (Just (modulePackageId mod))) search ((file, mk_result) : rest) = do b <- doesFileExist file if b - then do { res <- mk_result; return (Ok res) } + then do { loc <- mk_result; return (Found loc mod) } else search rest -mkHomeModLocationSearched :: DynFlags -> Module -> FileExt - -> FilePath -> BaseName -> IO FinderCacheEntry +mkHomeModLocationSearched :: DynFlags -> ModuleName -> FileExt + -> FilePath -> BaseName -> IO ModLocation mkHomeModLocationSearched dflags mod suff path basename = do - loc <- mkHomeModLocation2 dflags mod (path `joinFileName` basename) suff - return (loc, Nothing) - -mkHiOnlyModLocation :: DynFlags -> FileExt -> FilePath -> BaseName - -> IO FinderCacheEntry -mkHiOnlyModLocation dflags hisuf path basename = do - loc <- hiOnlyModLocation dflags path basename hisuf - return (loc, Nothing) - -mkPackageModLocation :: DynFlags -> (PackageConfig, Bool) -> FileExt - -> FilePath -> BaseName -> IO FinderCacheEntry -mkPackageModLocation dflags pkg_info hisuf path basename = do - loc <- hiOnlyModLocation dflags path basename hisuf - return (loc, Just pkg_info) + mkHomeModLocation2 dflags mod (path basename) suff -- ----------------------------------------------------------------------------- -- Constructing a home module location @@ -330,38 +390,39 @@ mkPackageModLocation dflags pkg_info hisuf 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 -- The filename extension of the source file (usually "hs" or "lhs"). -mkHomeModLocation :: DynFlags -> Module -> FilePath -> IO ModLocation +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 - -> Module + -> ModuleName -> FilePath -- Of source module, without suffix -> String -- Suffix -> IO ModLocation mkHomeModLocation2 dflags mod src_basename ext = do - let mod_basename = dots_to_slashes (moduleString 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 }) -hiOnlyModLocation :: DynFlags -> FilePath -> String -> Suffix -> IO ModLocation -hiOnlyModLocation dflags path basename hisuf - = do let full_basename = path `joinFileName` basename +mkHiOnlyModLocation :: DynFlags -> Suffix -> FilePath -> String + -> IO ModLocation +mkHiOnlyModLocation dflags hisuf path 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 @@ -381,10 +442,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 @@ -398,10 +459,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) -- ----------------------------------------------------------------------------- @@ -412,27 +473,41 @@ mkHiPath dflags basename mod_basename mkStubPaths :: DynFlags - -> Module + -> ModuleName -> ModLocation - -> (FilePath,FilePath) + -> (FilePath,FilePath,FilePath) mkStubPaths dflags mod location = let - stubdir = stubDir dflags - - mod_basename = dots_to_slashes (moduleString mod) - src_basename = basenameOf (expectJust "mkStubPaths" - (ml_hs_file location)) - - stub_basename0 - | Just dir <- stubdir = dir `joinFileName` mod_basename - | otherwise = src_basename - - stub_basename = stub_basename0 ++ "_stub" + stubdir = stubDir dflags + + mod_basename = moduleNameSlashes mod + src_basename = dropExtension $ expectJust "mkStubPaths" + (ml_hs_file location) + + stub_basename0 + | Just dir <- stubdir = dir mod_basename + | otherwise = src_basename + + 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 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", + (include_basename ++ "_stub") <.> "h") + -- the _stub.o filename is derived from the ml_obj_file. -- ----------------------------------------------------------------------------- -- findLinkable isn't related to the other stuff in here, @@ -450,30 +525,29 @@ 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") --- ----------------------------------------------------------------------------- --- Error messages +cannotFindInterface :: DynFlags -> ModuleName -> FindResult -> SDoc +cannotFindInterface = cantFindErr SLIT("Failed to load interface for") -cantFindError :: DynFlags -> Module -> FindResult -> SDoc -cantFindError dflags mod_name (FoundMultiple pkgs) - = hang (ptext SLIT("Cannot import") <+> quotes (ppr mod_name) <> colon) 2 ( +cantFindErr :: LitString -> DynFlags -> ModuleName -> FindResult -> SDoc +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:"), hsep (map (text.packageIdString) pkgs)] ) -cantFindError dflags mod_name find_result - = hang (ptext SLIT("Could not find module") <+> quotes (ppr mod_name) <> colon) +cantFindErr cannot_find dflags mod_name find_result + = hang (ptext cannot_find <+> quotes (ppr mod_name) <> colon) 2 more_info where more_info @@ -486,14 +560,35 @@ cantFindError dflags mod_name find_result -> ptext SLIT("it is hidden") <+> parens (ptext SLIT("in package") <+> ppr pkg) - NotFound 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.") - | 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)) + | 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 + + | otherwise + -> not_found files + + NotFoundInPackage pkg + -> ptext SLIT("it is not in package") <+> 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)) \end{code}