2 % (c) The University of Glasgow, 2000-2006
4 \section[Finder]{Module Finder}
16 addHomeModuleToFinder,
20 findObjectLinkableMaybe,
33 import PrelNames ( gHC_PRIM )
34 import DynFlags ( DynFlags(..), isOneShot, GhcMode(..) )
38 import Maybes ( expectJust )
40 import Distribution.Package hiding (PackageId)
41 import Data.IORef ( IORef, writeIORef, readIORef, modifyIORef )
43 import System.Directory
44 import System.FilePath
47 import System.Time ( ClockTime )
50 type FileExt = String -- Filename extension
51 type BaseName = String -- Basename of file
53 -- -----------------------------------------------------------------------------
56 -- The Finder provides a thin filesystem abstraction to the rest of
57 -- the compiler. For a given module, it can tell you where the
58 -- source, interface, and object files for that module live.
60 -- It does *not* know which particular package a module lives in. Use
61 -- Packages.lookupModuleInAllPackages for that.
63 -- -----------------------------------------------------------------------------
66 -- remove all the home modules from the cache; package modules are
67 -- assumed to not move around during a session.
68 flushFinderCaches :: HscEnv -> IO ()
69 flushFinderCaches hsc_env = do
70 writeIORef fc_ref emptyUFM
71 flushModLocationCache this_pkg mlc_ref
73 this_pkg = thisPackage (hsc_dflags hsc_env)
74 fc_ref = hsc_FC hsc_env
75 mlc_ref = hsc_MLC hsc_env
77 flushModLocationCache :: PackageId -> IORef ModLocationCache -> IO ()
78 flushModLocationCache this_pkg ref = do
80 writeIORef ref $! filterFM is_ext fm
82 where is_ext mod _ | modulePackageId mod /= this_pkg = True
85 addToFinderCache :: IORef FinderCache -> ModuleName -> FindResult -> IO ()
86 addToFinderCache ref key val = modifyIORef ref $ \c -> addToUFM c key val
88 addToModLocationCache :: IORef ModLocationCache -> Module -> ModLocation -> IO ()
89 addToModLocationCache ref key val = modifyIORef ref $ \c -> addToFM c key val
91 removeFromFinderCache :: IORef FinderCache -> ModuleName -> IO ()
92 removeFromFinderCache ref key = modifyIORef ref $ \c -> delFromUFM c key
94 removeFromModLocationCache :: IORef ModLocationCache -> Module -> IO ()
95 removeFromModLocationCache ref key = modifyIORef ref $ \c -> delFromFM c key
97 lookupFinderCache :: IORef FinderCache -> ModuleName -> IO (Maybe FindResult)
98 lookupFinderCache ref key = do
100 return $! lookupUFM c key
102 lookupModLocationCache :: IORef ModLocationCache -> Module
103 -> IO (Maybe ModLocation)
104 lookupModLocationCache ref key = do
106 return $! lookupFM c key
108 -- -----------------------------------------------------------------------------
109 -- The two external entry points
111 -- | Locate a module that was imported by the user. We have the
112 -- module's name, and possibly a package name. Without a package
113 -- name, this function will use the search path and the known exposed
114 -- packages to find the module, if a package is specified then only
115 -- that package is searched for the module.
117 findImportedModule :: HscEnv -> ModuleName -> Maybe FastString -> IO FindResult
118 findImportedModule hsc_env mod_name mb_pkg =
120 Nothing -> unqual_import
121 Just pkg | pkg == fsLit "this" -> home_import -- "this" is special
122 | otherwise -> pkg_import
124 home_import = findHomeModule hsc_env mod_name
126 pkg_import = findExposedPackageModule hsc_env mod_name mb_pkg
128 unqual_import = home_import
130 findExposedPackageModule hsc_env mod_name Nothing
132 -- | Locate a specific 'Module'. The purpose of this function is to
133 -- create a 'ModLocation' for a given 'Module', that is to find out
134 -- where the files associated with this module live. It is used when
135 -- reading the interface for a module mentioned by another interface,
136 -- for example (a "system import").
138 findExactModule :: HscEnv -> Module -> IO FindResult
139 findExactModule hsc_env mod =
140 let dflags = hsc_dflags hsc_env in
141 if modulePackageId mod == thisPackage dflags
142 then findHomeModule hsc_env (moduleName mod)
143 else findPackageModule hsc_env mod
145 -- -----------------------------------------------------------------------------
148 orIfNotFound :: IO FindResult -> IO FindResult -> IO FindResult
149 this `orIfNotFound` or_this = do
152 NotFound places1 _mb_pkg1 mod_hiddens1 pkg_hiddens1 -> do
155 NotFound places2 mb_pkg2 mod_hiddens2 pkg_hiddens2 ->
156 return (NotFound (places1 ++ places2)
157 mb_pkg2 -- snd arg is the package search
158 (mod_hiddens1 ++ mod_hiddens2)
159 (pkg_hiddens1 ++ pkg_hiddens2))
160 _other -> return res2
164 homeSearchCache :: HscEnv -> ModuleName -> IO FindResult -> IO FindResult
165 homeSearchCache hsc_env mod_name do_this = do
166 m <- lookupFinderCache (hsc_FC hsc_env) mod_name
168 Just result -> return result
171 addToFinderCache (hsc_FC hsc_env) mod_name result
173 Found loc mod -> addToModLocationCache (hsc_MLC hsc_env) mod loc
177 findExposedPackageModule :: HscEnv -> ModuleName -> Maybe FastString
179 findExposedPackageModule hsc_env mod_name mb_pkg
180 -- not found in any package:
181 | null found_exposed = return (NotFound [] Nothing mod_hiddens pkg_hiddens)
182 -- found in just one exposed package:
183 | [(pkg_conf, _)] <- found_exposed
184 = let pkgid = mkPackageId (package pkg_conf) in
185 findPackageModule_ hsc_env (mkModule pkgid mod_name) pkg_conf
187 = return (FoundMultiple (map (mkPackageId.package.fst) found_exposed))
189 dflags = hsc_dflags hsc_env
190 found = lookupModuleInAllPackages dflags mod_name
192 for_this_pkg = filter ((`matches` mb_pkg) . fst) found
194 found_exposed = [ (pkg_conf,exposed_mod)
195 | x@(pkg_conf,exposed_mod) <- for_this_pkg,
198 is_exposed (pkg_conf,exposed_mod) = exposed pkg_conf && exposed_mod
200 mod_hiddens = [ mkPackageId (package pkg_conf)
201 | (pkg_conf,False) <- found ]
203 pkg_hiddens = [ mkPackageId (package pkg_conf)
204 | (pkg_conf,_) <- found, not (exposed pkg_conf) ]
206 _pkg_conf `matches` Nothing = True
207 pkg_conf `matches` Just pkg =
208 case packageName pkg_conf of
209 PackageName n -> pkg == mkFastString n
212 modLocationCache :: HscEnv -> Module -> IO FindResult -> IO FindResult
213 modLocationCache hsc_env mod do_this = do
214 mb_loc <- lookupModLocationCache mlc mod
216 Just loc -> return (Found loc mod)
220 Found loc mod -> addToModLocationCache (hsc_MLC hsc_env) mod loc
224 mlc = hsc_MLC hsc_env
226 addHomeModuleToFinder :: HscEnv -> ModuleName -> ModLocation -> IO Module
227 addHomeModuleToFinder hsc_env mod_name loc = do
228 let mod = mkModule (thisPackage (hsc_dflags hsc_env)) mod_name
229 addToFinderCache (hsc_FC hsc_env) mod_name (Found loc mod)
230 addToModLocationCache (hsc_MLC hsc_env) mod loc
233 uncacheModule :: HscEnv -> ModuleName -> IO ()
234 uncacheModule hsc_env mod = do
235 let this_pkg = thisPackage (hsc_dflags hsc_env)
236 removeFromFinderCache (hsc_FC hsc_env) mod
237 removeFromModLocationCache (hsc_MLC hsc_env) (mkModule this_pkg mod)
239 -- -----------------------------------------------------------------------------
240 -- The internal workers
242 -- | Search for a module in the home package only.
243 findHomeModule :: HscEnv -> ModuleName -> IO FindResult
244 findHomeModule hsc_env mod_name =
245 homeSearchCache hsc_env mod_name $
247 dflags = hsc_dflags hsc_env
248 home_path = importPaths dflags
250 mod = mkModule (thisPackage dflags) mod_name
253 [ ("hs", mkHomeModLocationSearched dflags mod_name "hs")
254 , ("lhs", mkHomeModLocationSearched dflags mod_name "lhs")
257 hi_exts = [ (hisuf, mkHiOnlyModLocation dflags hisuf)
258 , (addBootSuffix hisuf, mkHiOnlyModLocation dflags hisuf)
261 -- In compilation manager modes, we look for source files in the home
262 -- package because we can compile these automatically. In one-shot
263 -- compilation mode we look for .hi and .hi-boot files only.
264 exts | isOneShot (ghcMode dflags) = hi_exts
265 | otherwise = source_exts
268 -- special case for GHC.Prim; we won't find it in the filesystem.
269 -- This is important only when compiling the base package (where GHC.Prim
270 -- is a home module).
272 then return (Found (error "GHC.Prim ModLocation") mod)
275 searchPathExts home_path mod exts
278 -- | Search for a module in external packages only.
279 findPackageModule :: HscEnv -> Module -> IO FindResult
280 findPackageModule hsc_env mod = do
282 dflags = hsc_dflags hsc_env
283 pkg_id = modulePackageId mod
284 pkg_map = pkgIdMap (pkgState dflags)
286 case lookupPackage pkg_map pkg_id of
287 Nothing -> return (NoPackage pkg_id)
288 Just pkg_conf -> findPackageModule_ hsc_env mod pkg_conf
290 findPackageModule_ :: HscEnv -> Module -> PackageConfig -> IO FindResult
291 findPackageModule_ hsc_env mod pkg_conf =
292 modLocationCache hsc_env mod $
294 -- special case for GHC.Prim; we won't find it in the filesystem.
296 then return (Found (error "GHC.Prim ModLocation") mod)
300 dflags = hsc_dflags hsc_env
301 tag = buildTag dflags
303 -- hi-suffix for packages depends on the build tag.
304 package_hisuf | null tag = "hi"
305 | otherwise = tag ++ "_hi"
307 mk_hi_loc = mkHiOnlyModLocation dflags package_hisuf
309 import_dirs = importDirs pkg_conf
310 -- we never look for a .hi-boot file in an external package;
311 -- .hi-boot files only make sense for the home package.
314 [one] | MkDepend <- ghcMode dflags -> do
315 -- there's only one place that this .hi file can be, so
316 -- don't bother looking for it.
317 let basename = moduleNameSlashes (moduleName mod)
318 loc <- mk_hi_loc one basename
319 return (Found loc mod)
321 searchPathExts import_dirs mod [(package_hisuf, mk_hi_loc)]
323 -- -----------------------------------------------------------------------------
324 -- General path searching
327 :: [FilePath] -- paths to search
328 -> Module -- module name
331 FilePath -> BaseName -> IO ModLocation -- action
336 searchPathExts paths mod exts
337 = do result <- search to_search
339 hPutStrLn stderr (showSDoc $
340 vcat [text "Search" <+> ppr mod <+> sep (map (text. fst) exts)
341 , nest 2 (vcat (map text paths))
343 Succeeded (loc, p) -> text "Found" <+> ppr loc
344 Failed fs -> text "not found"])
349 basename = moduleNameSlashes (moduleName mod)
351 to_search :: [(FilePath, IO ModLocation)]
352 to_search = [ (file, fn path basename)
355 let base | path == "." = basename
356 | otherwise = path </> basename
360 search [] = return (NotFound (map fst to_search) (Just (modulePackageId mod))
362 search ((file, mk_result) : rest) = do
363 b <- doesFileExist file
365 then do { loc <- mk_result; return (Found loc mod) }
368 mkHomeModLocationSearched :: DynFlags -> ModuleName -> FileExt
369 -> FilePath -> BaseName -> IO ModLocation
370 mkHomeModLocationSearched dflags mod suff path basename = do
371 mkHomeModLocation2 dflags mod (path </> basename) suff
373 -- -----------------------------------------------------------------------------
374 -- Constructing a home module location
376 -- This is where we construct the ModLocation for a module in the home
377 -- package, for which we have a source file. It is called from three
380 -- (a) Here in the finder, when we are searching for a module to import,
381 -- using the search path (-i option).
383 -- (b) The compilation manager, when constructing the ModLocation for
384 -- a "root" module (a source file named explicitly on the command line
385 -- or in a :load command in GHCi).
387 -- (c) The driver in one-shot mode, when we need to construct a
388 -- ModLocation for a source file named on the command-line.
393 -- The name of the module
396 -- (a): The search path component where the source file was found.
400 -- (a): (moduleNameSlashes mod)
401 -- (b) and (c): The filename of the source file, minus its extension
404 -- The filename extension of the source file (usually "hs" or "lhs").
406 mkHomeModLocation :: DynFlags -> ModuleName -> FilePath -> IO ModLocation
407 mkHomeModLocation dflags mod src_filename = do
408 let (basename,extension) = splitExtension src_filename
409 mkHomeModLocation2 dflags mod basename extension
411 mkHomeModLocation2 :: DynFlags
413 -> FilePath -- Of source module, without suffix
416 mkHomeModLocation2 dflags mod src_basename ext = do
417 let mod_basename = moduleNameSlashes mod
419 obj_fn <- mkObjPath dflags src_basename mod_basename
420 hi_fn <- mkHiPath dflags src_basename mod_basename
422 return (ModLocation{ ml_hs_file = Just (src_basename <.> ext),
424 ml_obj_file = obj_fn })
426 mkHiOnlyModLocation :: DynFlags -> Suffix -> FilePath -> String
428 mkHiOnlyModLocation dflags hisuf path basename
429 = do let full_basename = path </> basename
430 obj_fn <- mkObjPath dflags full_basename basename
431 return ModLocation{ ml_hs_file = Nothing,
432 ml_hi_file = full_basename <.> hisuf,
433 -- Remove the .hi-boot suffix from
434 -- hi_file, if it had one. We always
435 -- want the name of the real .hi file
436 -- in the ml_hi_file field.
440 -- | Constructs the filename of a .o file for a given source file.
441 -- Does /not/ check whether the .o file exists
444 -> FilePath -- the filename of the source file, minus the extension
445 -> String -- the module name with dots replaced by slashes
447 mkObjPath dflags basename mod_basename
449 odir = objectDir dflags
450 osuf = objectSuf dflags
452 obj_basename | Just dir <- odir = dir </> mod_basename
453 | otherwise = basename
455 return (obj_basename <.> osuf)
457 -- | Constructs the filename of a .hi file for a given source file.
458 -- Does /not/ check whether the .hi file exists
461 -> FilePath -- the filename of the source file, minus the extension
462 -> String -- the module name with dots replaced by slashes
464 mkHiPath dflags basename mod_basename
469 hi_basename | Just dir <- hidir = dir </> mod_basename
470 | otherwise = basename
472 return (hi_basename <.> hisuf)
475 -- -----------------------------------------------------------------------------
476 -- Filenames of the stub files
478 -- We don't have to store these in ModLocations, because they can be derived
479 -- from other available information, and they're only rarely needed.
485 -> (FilePath,FilePath,FilePath)
487 mkStubPaths dflags mod location
489 stubdir = stubDir dflags
491 mod_basename = moduleNameSlashes mod
492 src_basename = dropExtension $ expectJust "mkStubPaths"
493 (ml_hs_file location)
496 | Just dir <- stubdir = dir </> mod_basename
497 | otherwise = src_basename
499 stub_basename = stub_basename0 ++ "_stub"
501 obj = ml_obj_file location
502 osuf = objectSuf dflags
503 stub_obj_base = dropTail (length osuf + 1) obj ++ "_stub"
504 -- NB. not takeFileName, see #3093
506 (stub_basename <.> "c",
507 stub_basename <.> "h",
508 stub_obj_base <.> objectSuf dflags)
510 -- -----------------------------------------------------------------------------
511 -- findLinkable isn't related to the other stuff in here,
512 -- but there's no other obvious place for it
514 findObjectLinkableMaybe :: Module -> ModLocation -> IO (Maybe Linkable)
515 findObjectLinkableMaybe mod locn
516 = do let obj_fn = ml_obj_file locn
517 maybe_obj_time <- modificationTimeIfExists obj_fn
518 case maybe_obj_time of
519 Nothing -> return Nothing
520 Just obj_time -> liftM Just (findObjectLinkable mod obj_fn obj_time)
522 -- Make an object linkable when we know the object file exists, and we know
523 -- its modification time.
524 findObjectLinkable :: Module -> FilePath -> ClockTime -> IO Linkable
525 findObjectLinkable mod obj_fn obj_time = do
526 let stub_fn = (dropExtension obj_fn ++ "_stub") <.> "o"
527 stub_exist <- doesFileExist stub_fn
529 then return (LM obj_time mod [DotO obj_fn, DotO stub_fn])
530 else return (LM obj_time mod [DotO obj_fn])
532 -- -----------------------------------------------------------------------------
535 cannotFindModule :: DynFlags -> ModuleName -> FindResult -> SDoc
536 cannotFindModule = cantFindErr (sLit "Could not find module")
538 cannotFindInterface :: DynFlags -> ModuleName -> FindResult -> SDoc
539 cannotFindInterface = cantFindErr (sLit "Failed to load interface for")
541 cantFindErr :: LitString -> DynFlags -> ModuleName -> FindResult -> SDoc
542 cantFindErr cannot_find _dflags mod_name (FoundMultiple pkgs)
543 = hang (ptext cannot_find <+> quotes (ppr mod_name) <> colon) 2 (
544 sep [ptext (sLit "it was found in multiple packages:"),
545 hsep (map (text.packageIdString) pkgs)]
547 cantFindErr cannot_find dflags mod_name find_result
548 = hang (ptext cannot_find <+> quotes (ppr mod_name) <> colon)
552 = case find_result of
554 -> ptext (sLit "no package matching") <+> quotes (ppr pkg) <+>
555 ptext (sLit "was found")
557 NotFound files mb_pkg mod_hiddens pkg_hiddens
558 | Just pkg <- mb_pkg, pkg /= thisPackage dflags
559 -> not_found_in_package pkg files
561 | null files && null mod_hiddens && null pkg_hiddens
562 -> ptext (sLit "it is not a module in the current program, or in any known package.")
565 -> vcat (map pkg_hidden pkg_hiddens) $$
566 vcat (map mod_hidden mod_hiddens) $$
569 NotFoundInPackage pkg
570 -> ptext (sLit "it is not in package") <+> quotes (ppr pkg)
572 _ -> panic "cantFindErr"
574 build_tag = buildTag dflags
576 not_found_in_package pkg files
579 build = if build_tag == "p" then "profiling"
580 else "\"" ++ build_tag ++ "\""
582 ptext (sLit "Perhaps you haven't installed the ") <> text build <>
583 ptext (sLit " libraries for package ") <> quotes (ppr pkg) <> char '?' $$
587 = ptext (sLit "There are files missing in the ") <> quotes (ppr pkg) <>
588 ptext (sLit " package,") $$
589 ptext (sLit "try running 'ghc-pkg check'.") $$
594 | verbosity dflags < 3 =
595 ptext (sLit "Use -v to see a list of the files searched for.")
597 hang (ptext (sLit "locations searched:")) 2 $ vcat (map text files)
600 ptext (sLit "it is a member of the hidden package") <+> quotes (ppr pkg)
603 ptext (sLit "it is a hidden module in the package") <+> quotes (ppr pkg)