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