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