[project @ 2005-05-17 10:51:04 by simonmar]
[ghc-hetmet.git] / ghc / compiler / main / Finder.lhs
1 %
2 % (c) The University of Glasgow, 2000
3 %
4 \section[Finder]{Module Finder}
5
6 \begin{code}
7 module Finder (
8     flushFinderCache,   -- :: IO ()
9     FindResult(..),
10     findModule,                 -- :: ModuleName -> Bool -> IO FindResult
11     findPackageModule,          -- :: ModuleName -> Bool -> IO FindResult
12     mkHomeModLocation,          -- :: ModuleName -> FilePath -> IO ModLocation
13     mkHomeModLocation2,         -- :: ModuleName -> FilePath -> String -> IO ModLocation
14     addHomeModuleToFinder,      -- :: HscEnv -> Module -> ModLocation -> IO ()
15
16     findObjectLinkableMaybe,
17     findObjectLinkable,
18
19     cantFindError,      -- :: DynFlags -> Module -> FindResult -> SDoc
20   ) where
21
22 #include "HsVersions.h"
23
24 import Module
25 import UniqFM           ( filterUFM )
26 import HscTypes
27 import Packages
28 import FastString
29 import Util
30 import DynFlags         ( DynFlags(..), isOneShot, GhcMode(..) )
31 import Outputable
32
33 import DATA_IOREF       ( IORef, writeIORef, readIORef )
34
35 import Data.List
36 import System.Directory
37 import System.IO
38 import Control.Monad
39 import Maybes           ( MaybeErr(..) )
40 import Data.Maybe       ( isNothing )
41 import Time             ( ClockTime )
42
43
44 type FileExt = String   -- Filename extension
45 type BaseName = String  -- Basename of file
46
47 -- -----------------------------------------------------------------------------
48 -- The Finder
49
50 -- The Finder provides a thin filesystem abstraction to the rest of
51 -- the compiler.  For a given module, it can tell you where the
52 -- source, interface, and object files for that module live.
53
54 -- It does *not* know which particular package a module lives in.  Use
55 -- Packages.moduleToPackageConfig for that.
56
57 -- -----------------------------------------------------------------------------
58 -- The finder's cache
59
60 -- remove all the home modules from the cache; package modules are
61 -- assumed to not move around during a session.
62 flushFinderCache :: IORef FinderCache -> IO ()
63 flushFinderCache finder_cache = do
64   fm <- readIORef finder_cache
65   writeIORef finder_cache $! filterUFM (\(loc,m) -> isNothing m) fm
66
67 addToFinderCache :: IORef FinderCache -> Module -> FinderCacheEntry -> IO ()
68 addToFinderCache finder_cache mod_name entry = do
69   fm <- readIORef finder_cache
70   writeIORef finder_cache $! extendModuleEnv fm mod_name entry
71
72 lookupFinderCache :: IORef FinderCache -> Module -> IO (Maybe FinderCacheEntry)
73 lookupFinderCache finder_cache mod_name = do
74   fm <- readIORef finder_cache
75   return $! lookupModuleEnv fm mod_name
76
77 -- -----------------------------------------------------------------------------
78 -- The two external entry points
79
80 -- This is the main interface to the finder, which maps ModuleNames to
81 -- Modules and ModLocations.
82 --
83 -- The Module contains one crucial bit of information about a module:
84 -- whether it lives in the current ("home") package or not (see Module
85 -- for more details).
86 --
87 -- The ModLocation contains the names of all the files associated with
88 -- that module: its source file, .hi file, object file, etc.
89
90 data FindResult
91   = Found ModLocation PackageIdH
92         -- the module was found
93   | FoundMultiple ModLocation PackageId
94         -- *error*: both a home module and a package module
95   | PackageHidden PackageId
96         -- for an explicit source import: the package containing the module is
97         -- not exposed.
98   | ModuleHidden  PackageId
99         -- for an explicit source import: the package containing the module is
100         -- exposed, but the module itself is hidden.
101   | NotFound [FilePath]
102         -- the module was not found, the specified places were searched.
103
104 findModule :: HscEnv -> Module -> Bool -> IO FindResult
105 findModule = findModule' True
106   
107 findPackageModule :: HscEnv -> Module -> Bool -> IO FindResult
108 findPackageModule = findModule' False
109
110
111 type LocalFindResult = MaybeErr [FilePath] FinderCacheEntry
112         -- LocalFindResult is used for internal functions which 
113         -- return a more informative type; it's munged into
114         -- the external FindResult by 'cached'
115
116 findModule' :: Bool -> HscEnv -> Module -> Bool -> IO FindResult
117 findModule' home_allowed hsc_env name explicit 
118   = do  -- First try the cache
119   mb_entry <- lookupFinderCache cache name
120   case mb_entry of
121      Just old_entry -> return $! found old_entry
122      Nothing        -> not_cached
123
124  where
125   cache  = hsc_FC hsc_env
126   dflags = hsc_dflags hsc_env
127
128         -- We've found the module, so the remaining question is
129         -- whether it's visible or not
130   found :: FinderCacheEntry -> FindResult
131   found (loc, Nothing)
132         | home_allowed  = Found loc HomePackage
133         | otherwise     = NotFound []
134   found (loc, Just (pkg, exposed_mod))
135         | explicit && not exposed_mod   = ModuleHidden pkg_name
136         | explicit && not (exposed pkg) = PackageHidden pkg_name
137         | otherwise = 
138                 Found loc (ExtPackage (mkPackageId (package pkg)))
139         where
140           pkg_name = packageConfigId pkg
141
142   found_new entry = do
143         addToFinderCache cache name entry
144         return $! found entry
145
146   not_cached
147         | not home_allowed = do
148             j <- findPackageModule' dflags name
149             case j of
150                Failed paths    -> return (NotFound paths)
151                Succeeded entry -> found_new entry
152
153         | home_allowed && explicit = do
154                 -- for an explict home import, we try looking for
155                 -- both a package module and a home module, and report
156                 -- a FoundMultiple if we find both.
157             j <- findHomeModule' dflags name
158             case j of
159                 Failed home_files -> do
160                     r <- findPackageModule' dflags name
161                     case r of
162                         Failed pkg_files ->
163                                 return (NotFound (home_files ++ pkg_files))
164                         Succeeded entry -> 
165                                 found_new entry
166                 Succeeded entry@(loc,_) -> do
167                     r <- findPackageModule' dflags name
168                     case r of
169                         Failed pkg_files -> found_new entry
170                         Succeeded (_,Just (pkg,_)) -> 
171                                 return (FoundMultiple loc (packageConfigId pkg))
172                         Succeeded _ -> 
173                                 panic "findModule: shouldn't happen"
174
175                 -- implicit home imports: check for package modules first,
176                 -- because that's the quickest (doesn't involve filesystem
177                 -- operations).
178         | home_allowed && not explicit = do
179             r <- findPackageModule' dflags name
180             case r of
181                 Failed pkg_files -> do
182                     j <- findHomeModule' dflags name
183                     case j of
184                         Failed home_files ->
185                                 return (NotFound (home_files ++ pkg_files))
186                         Succeeded entry ->
187                                 found_new entry
188                 Succeeded entry ->
189                     found_new entry
190
191
192 addHomeModuleToFinder :: HscEnv -> Module -> ModLocation -> IO ()
193 addHomeModuleToFinder hsc_env mod loc 
194   = addToFinderCache (hsc_FC hsc_env) mod (loc, Nothing)
195
196
197 -- -----------------------------------------------------------------------------
198 --      The internal workers
199
200 findHomeModule' :: DynFlags -> Module -> IO LocalFindResult
201 findHomeModule' dflags mod = do
202    let home_path = importPaths dflags
203        hisuf = hiSuf dflags
204
205    let
206      source_exts = 
207       [ ("hs",   mkHomeModLocationSearched dflags mod "hs")
208       , ("lhs",  mkHomeModLocationSearched dflags  mod "lhs")
209       ]
210      
211      hi_exts = [ (hisuf,                mkHiOnlyModLocation dflags hisuf)
212                , (addBootSuffix hisuf,  mkHiOnlyModLocation dflags hisuf)
213                ]
214      
215         -- In compilation manager modes, we look for source files in the home
216         -- package because we can compile these automatically.  In one-shot
217         -- compilation mode we look for .hi and .hi-boot files only.
218      exts | isOneShot (ghcMode dflags) = hi_exts
219           | otherwise                  = source_exts
220
221    searchPathExts home_path mod exts
222         
223 findPackageModule' :: DynFlags -> Module -> IO LocalFindResult
224 findPackageModule' dflags mod 
225   = case moduleToPackageConfig dflags mod of
226         Nothing       -> return (Failed [])
227         Just pkg_info -> findPackageIface dflags mod pkg_info
228
229 findPackageIface :: DynFlags -> Module -> (PackageConfig,Bool) -> IO LocalFindResult
230 findPackageIface dflags mod pkg_info@(pkg_conf, _) = do
231   let
232      tag = buildTag dflags
233
234            -- hi-suffix for packages depends on the build tag.
235      package_hisuf | null tag  = "hi"
236                    | otherwise = tag ++ "_hi"
237      hi_exts =
238         [ (package_hisuf, 
239             mkPackageModLocation dflags pkg_info package_hisuf) ]
240
241      source_exts = 
242        [ ("hs",   mkPackageModLocation dflags pkg_info package_hisuf)
243        , ("lhs",  mkPackageModLocation dflags pkg_info package_hisuf)
244        ]
245
246      -- mkdependHS needs to look for source files in packages too, so
247      -- that we can make dependencies between package before they have
248      -- been built.
249      exts 
250       | MkDepend <- ghcMode dflags = hi_exts ++ source_exts
251       | otherwise                  = hi_exts
252       -- we never look for a .hi-boot file in an external package;
253       -- .hi-boot files only make sense for the home package.
254
255   searchPathExts (importDirs pkg_conf) mod exts
256
257 -- -----------------------------------------------------------------------------
258 -- General path searching
259
260 searchPathExts
261   :: [FilePath]         -- paths to search
262   -> Module             -- module name
263   -> [ (
264         FileExt,                                     -- suffix
265         FilePath -> BaseName -> IO FinderCacheEntry  -- action
266        )
267      ] 
268   -> IO LocalFindResult
269
270 searchPathExts paths mod exts 
271    = do result <- search to_search
272 {-
273         hPutStrLn stderr (showSDoc $
274                 vcat [text "Search" <+> ppr mod <+> sep (map (text. fst) exts)
275                     , nest 2 (vcat (map text paths))
276                     , case result of
277                         Succeeded (loc, p) -> text "Found" <+> ppr loc
278                         Failed fs          -> text "not found"])
279 -}      
280         return result
281
282   where
283     basename = dots_to_slashes (moduleUserString mod)
284
285     to_search :: [(FilePath, IO FinderCacheEntry)]
286     to_search = [ (file, fn path basename)
287                 | path <- paths, 
288                   (ext,fn) <- exts,
289                   let base | path == "." = basename
290                            | otherwise   = path `joinFileName` basename
291                       file = base `joinFileExt` ext
292                 ]
293
294     search [] = return (Failed (map fst to_search))
295     search ((file, mk_result) : rest) = do
296       b <- doesFileExist file
297       if b 
298         then do { res <- mk_result; return (Succeeded res) }
299         else search rest
300
301 mkHomeModLocationSearched :: DynFlags -> Module -> FileExt
302                           -> FilePath -> BaseName -> IO FinderCacheEntry
303 mkHomeModLocationSearched dflags mod suff path basename = do
304    loc <- mkHomeModLocation2 dflags mod (path `joinFileName` basename) suff
305    return (loc, Nothing)
306
307 mkHiOnlyModLocation :: DynFlags -> FileExt -> FilePath -> BaseName
308                     -> IO FinderCacheEntry
309 mkHiOnlyModLocation dflags hisuf path basename = do
310   loc <- hiOnlyModLocation dflags path basename hisuf
311   return (loc, Nothing)
312
313 mkPackageModLocation :: DynFlags -> (PackageConfig, Bool) -> FileExt
314                      -> FilePath -> BaseName -> IO FinderCacheEntry
315 mkPackageModLocation dflags pkg_info hisuf path basename = do
316   loc <- hiOnlyModLocation dflags path basename hisuf
317   return (loc, Just pkg_info)
318
319 -- -----------------------------------------------------------------------------
320 -- Constructing a home module location
321
322 -- This is where we construct the ModLocation for a module in the home
323 -- package, for which we have a source file.  It is called from three
324 -- places:
325 --
326 --  (a) Here in the finder, when we are searching for a module to import,
327 --      using the search path (-i option).
328 --
329 --  (b) The compilation manager, when constructing the ModLocation for
330 --      a "root" module (a source file named explicitly on the command line
331 --      or in a :load command in GHCi).
332 --
333 --  (c) The driver in one-shot mode, when we need to construct a
334 --      ModLocation for a source file named on the command-line.
335 --
336 -- Parameters are:
337 --
338 -- mod
339 --      The name of the module
340 --
341 -- path
342 --      (a): The search path component where the source file was found.
343 --      (b) and (c): "."
344 --
345 -- src_basename
346 --      (a): dots_to_slashes (moduleNameUserString mod)
347 --      (b) and (c): The filename of the source file, minus its extension
348 --
349 -- ext
350 --      The filename extension of the source file (usually "hs" or "lhs").
351
352 mkHomeModLocation :: DynFlags -> Module -> FilePath -> IO ModLocation
353 mkHomeModLocation dflags mod src_filename = do
354    let (basename,extension) = splitFilename src_filename
355    mkHomeModLocation2 dflags mod basename extension
356
357 mkHomeModLocation2 :: DynFlags
358                    -> Module    
359                    -> FilePath  -- Of source module, without suffix
360                    -> String    -- Suffix
361                    -> IO ModLocation
362 mkHomeModLocation2 dflags mod src_basename ext = do
363    let mod_basename = dots_to_slashes (moduleUserString mod)
364
365    obj_fn <- mkObjPath dflags src_basename mod_basename
366    hi_fn  <- mkHiPath  dflags src_basename mod_basename
367
368    return (ModLocation{ ml_hs_file   = Just (src_basename `joinFileExt` ext),
369                         ml_hi_file   = hi_fn,
370                         ml_obj_file  = obj_fn })
371
372 hiOnlyModLocation :: DynFlags -> FilePath -> String -> Suffix -> IO ModLocation
373 hiOnlyModLocation dflags path basename hisuf 
374  = do let full_basename = path `joinFileName` basename
375       obj_fn <- mkObjPath dflags full_basename basename
376       return ModLocation{    ml_hs_file   = Nothing,
377                              ml_hi_file   = full_basename  `joinFileExt` hisuf,
378                                 -- Remove the .hi-boot suffix from
379                                 -- hi_file, if it had one.  We always
380                                 -- want the name of the real .hi file
381                                 -- in the ml_hi_file field.
382                              ml_obj_file  = obj_fn
383                   }
384
385 -- | Constructs the filename of a .o file for a given source file.
386 -- Does /not/ check whether the .o file exists
387 mkObjPath
388   :: DynFlags
389   -> FilePath           -- the filename of the source file, minus the extension
390   -> String             -- the module name with dots replaced by slashes
391   -> IO FilePath
392 mkObjPath dflags basename mod_basename
393   = do  let
394                 odir = outputDir dflags
395                 osuf = objectSuf dflags
396         
397                 obj_basename | Just dir <- odir = dir `joinFileName` mod_basename
398                              | otherwise        = basename
399
400         return (obj_basename `joinFileExt` osuf)
401
402 -- | Constructs the filename of a .hi file for a given source file.
403 -- Does /not/ check whether the .hi file exists
404 mkHiPath
405   :: DynFlags
406   -> FilePath           -- the filename of the source file, minus the extension
407   -> String             -- the module name with dots replaced by slashes
408   -> IO FilePath
409 mkHiPath dflags basename mod_basename
410   = do  let
411                 hidir = hiDir dflags
412                 hisuf = hiSuf dflags
413
414                 hi_basename | Just dir <- hidir = dir `joinFileName` mod_basename
415                             | otherwise         = basename
416
417         return (hi_basename `joinFileExt` hisuf)
418
419
420 -- -----------------------------------------------------------------------------
421 -- findLinkable isn't related to the other stuff in here, 
422 -- but there's no other obvious place for it
423
424 findObjectLinkableMaybe :: Module -> ModLocation -> IO (Maybe Linkable)
425 findObjectLinkableMaybe mod locn
426    = do let obj_fn = ml_obj_file locn
427         maybe_obj_time <- modificationTimeIfExists obj_fn
428         case maybe_obj_time of
429           Nothing -> return Nothing
430           Just obj_time -> liftM Just (findObjectLinkable mod obj_fn obj_time)
431
432 -- Make an object linkable when we know the object file exists, and we know
433 -- its modification time.
434 findObjectLinkable :: Module -> FilePath -> ClockTime -> IO Linkable
435 findObjectLinkable mod obj_fn obj_time = do
436   let stub_fn = case splitFilename3 obj_fn of
437                         (dir, base, ext) -> dir ++ "/" ++ base ++ "_stub.o"
438   stub_exist <- doesFileExist stub_fn
439   if stub_exist
440         then return (LM obj_time mod [DotO obj_fn, DotO stub_fn])
441         else return (LM obj_time mod [DotO obj_fn])
442
443 -- -----------------------------------------------------------------------------
444 -- Utils
445
446 dots_to_slashes = map (\c -> if c == '.' then '/' else c)
447
448
449 -- -----------------------------------------------------------------------------
450 -- Error messages
451
452 cantFindError :: DynFlags -> Module -> FindResult -> SDoc
453 cantFindError dflags mod_name (FoundMultiple loc pkg)
454   = hang (ptext SLIT("Cannot import") <+> quotes (ppr mod_name) <> colon) 2 (
455        sep [ptext SLIT("it was found in both") <+>
456                 (case ml_hs_file loc of Nothing -> ptext SLIT("<unkonwn file>")
457                                         Just f  -> text f),
458             ptext SLIT("and package") <+> ppr pkg <> char '.'] $$
459        ptext SLIT("Possible fix: -ignore-package") <+> ppr pkg
460     )
461 cantFindError dflags mod_name find_result
462   = hang (ptext SLIT("Could not find module") <+> quotes (ppr mod_name) <> colon)
463        2 more_info
464   where
465     more_info
466       = case find_result of
467             PackageHidden pkg 
468                 -> ptext SLIT("it is a member of package") <+> ppr pkg <> comma
469                    <+> ptext SLIT("which is hidden")
470
471             ModuleHidden pkg
472                 -> ptext SLIT("it is hidden") <+> parens (ptext SLIT("in package")
473                    <+> ppr pkg)
474
475             NotFound files
476                 | null files
477                 -> ptext SLIT("it is not a module in the current program, or in any known package.")
478                 | verbosity dflags < 3 
479                 -> ptext SLIT("use -v to see a list of the files searched for")
480                 | otherwise 
481                 -> hang (ptext SLIT("locations searched:")) 
482                       2 (vcat (map text files))
483
484             Found _ _ -> panic "cantFindErr"
485 \end{code}