24936ec27eca8092e61f20eb0e45e3afbefc138c
[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
10     findModule,         -- :: ModuleName 
11                         --   -> IO (Either [FilePath] (Module, ModLocation))
12
13     findPackageModule,  -- :: ModuleName
14                         --   -> IO (Either [FilePath] (Module, ModLocation))
15
16     mkHomeModLocation,  -- :: ModuleName -> FilePath -> IO ModLocation
17
18     findLinkable,       -- :: ModuleName -> ModLocation -> IO (Maybe Linkable)
19
20     hiBootExt,          -- :: String
21     hiBootVerExt,       -- :: String
22
23   ) where
24
25 #include "HsVersions.h"
26
27 import Module
28 import UniqFM           ( filterUFM )
29 import HscTypes         ( Linkable(..), Unlinked(..) )
30 import DriverState
31 import DriverUtil
32 import FastString
33 import Config
34 import Util
35
36 import DATA_IOREF       ( IORef, writeIORef, readIORef )
37
38 import List
39 import Directory
40 import IO
41 import Monad
42
43 -- -----------------------------------------------------------------------------
44 -- The Finder
45
46 -- The Finder provides a thin filesystem abstraction to the rest of the
47 -- compiler.  For a given module, it knows (a) whether the module lives
48 -- in the home package or in another package, so it can make a Module
49 -- from a ModuleName, and (b) where the source, interface, and object
50 -- files for a module live.
51 -- 
52 -- It does *not* know which particular package a module lives in, because
53 -- that information is only contained in the interface file.
54
55 -- -----------------------------------------------------------------------------
56 -- The finder's cache
57
58 GLOBAL_VAR(finder_cache, emptyModuleEnv, ModuleEnv (Module,ModLocation))
59
60 -- remove all the home modules from the cache; package modules are
61 -- assumed to not move around during a session.
62 flushFinderCache :: IO ()
63 flushFinderCache = do
64   fm <- readIORef finder_cache
65   writeIORef finder_cache (filterUFM (not . isHomeModule . fst) fm)
66
67 addToFinderCache :: ModuleName -> (Module,ModLocation) -> IO ()
68 addToFinderCache mod_name stuff = do
69   fm <- readIORef finder_cache
70   writeIORef finder_cache (extendModuleEnvByName fm mod_name stuff)
71
72 lookupFinderCache :: ModuleName -> IO (Maybe (Module,ModLocation))
73 lookupFinderCache mod_name = do
74   fm <- readIORef finder_cache
75   return $! lookupModuleEnvByName fm mod_name
76
77 -- -----------------------------------------------------------------------------
78 -- Locating modules
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 -- Returns: 
91 --      Right (Module, ModLocation)   if the module was found
92 --      Left [FilePath]               if the module was not found, and here
93 --                                      is a list of all the places we looked
94 findModule :: ModuleName -> IO (Either [FilePath] (Module, ModLocation))
95 findModule name = do
96   r <- lookupFinderCache name
97   case r of
98    Just result -> return (Right result)
99    Nothing -> do  
100        j <- maybeHomeModule name
101        case j of
102          Right home_module -> return (Right home_module)
103          Left home_files   -> do
104             r <- findPackageMod name
105             case r of
106                 Right pkg_module -> return (Right pkg_module)
107                 Left pkg_files   -> return (Left (home_files ++ pkg_files))
108
109 findPackageModule :: ModuleName -> IO (Either [FilePath] (Module, ModLocation))
110 findPackageModule name = do
111   r <- lookupFinderCache name
112   case r of
113    Just result -> return (Right result)
114    Nothing     -> findPackageMod name
115
116 hiBootExt = "hi-boot"
117 hiBootVerExt = "hi-boot-" ++ cHscIfaceFileVersion
118
119 maybeHomeModule :: ModuleName -> IO (Either [FilePath] (Module, ModLocation))
120 maybeHomeModule mod_name = do
121    home_path <- readIORef v_Import_paths
122    hisuf     <- readIORef v_Hi_suf
123    mode      <- readIORef v_GhcMode
124
125    let
126      source_exts = 
127       [ ("hs",   mkHomeModLocationSearched mod_name)
128       , ("lhs",  mkHomeModLocationSearched mod_name)
129       ]
130      
131      hi_exts = [ (hisuf,  mkHiOnlyModLocation hisuf mod_name) ]
132      
133      boot_exts =
134        [ (hiBootVerExt, mkHiOnlyModLocation hisuf mod_name)
135        , (hiBootExt,    mkHiOnlyModLocation hisuf mod_name)
136        ]
137
138         -- In compilation manager modes, we look for source files in the home
139         -- package because we can compile these automatically.  In one-shot
140         -- compilation mode we look for .hi and .hi-boot files only.
141         --
142         -- When generating dependencies, we're interested in either category.
143         --
144      exts
145          | mode == DoMkDependHS   = hi_exts ++ source_exts ++ boot_exts
146          | isCompManagerMode mode = source_exts
147          | otherwise {-one-shot-} = hi_exts ++ boot_exts
148
149    searchPathExts home_path mod_name exts
150         
151 -- -----------------------------------------------------------------------------
152 -- Looking for a package module
153
154 findPackageMod :: ModuleName -> IO (Either [FilePath] (Module, ModLocation))
155 findPackageMod mod_name = do
156   mode     <- readIORef v_GhcMode
157   imp_dirs <- getPackageImportPath -- including the 'auto' ones
158
159    -- hi-suffix for packages depends on the build tag.
160   package_hisuf <-
161         do tag <- readIORef v_Build_tag
162            if null tag
163                 then return "hi"
164                 else return (tag ++ "_hi")
165
166   let
167      hi_exts =
168         [ (package_hisuf, mkPackageModLocation package_hisuf mod_name) ]
169
170      source_exts = 
171        [ ("hs",   mkPackageModLocation package_hisuf mod_name)
172        , ("lhs",  mkPackageModLocation package_hisuf mod_name)
173        ]
174      
175      -- mkdependHS needs to look for source files in packages too, so
176      -- that we can make dependencies between package before they have
177      -- been built.
178      exts 
179       | mode == DoMkDependHS = hi_exts ++ source_exts
180       | otherwise = hi_exts
181
182       -- we never look for a .hi-boot file in an external package;
183       -- .hi-boot files only make sense for the home package.
184   searchPathExts imp_dirs mod_name exts
185
186 -- -----------------------------------------------------------------------------
187 -- General path searching
188
189 searchPathExts
190   :: [FilePath]         -- paths to search
191   -> ModuleName         -- module name
192   -> [ (
193         String,                                         -- suffix
194         String -> String -> String -> IO (Module, ModLocation)  -- action
195        )
196      ] 
197   -> IO (Either [FilePath] (Module, ModLocation))
198
199 searchPathExts path mod_name exts = search to_search
200   where
201     basename = dots_to_slashes (moduleNameUserString mod_name)
202
203     to_search :: [(FilePath, IO (Module,ModLocation))]
204     to_search = [ (file, fn p basename ext)
205                 | p <- path, 
206                   (ext,fn) <- exts,
207                   let base | p == "."  = basename
208                            | otherwise = p ++ '/':basename
209                       file = base ++ '.':ext
210                 ]
211
212     search [] = return (Left (map fst to_search))
213     search ((file, result) : rest) = do
214       b <- doesFileExist file
215       if b 
216         then Right `liftM` result
217         else search rest
218
219 -- -----------------------------------------------------------------------------
220 -- Building ModLocations
221
222 mkHiOnlyModLocation hisuf mod_name path basename _ext = do
223   -- basename == dots_to_slashes (moduleNameUserString mod_name)
224   loc <- hiOnlyModLocation path basename hisuf
225   let result = (mkHomeModule mod_name, loc)
226   addToFinderCache mod_name result
227   return result
228
229 mkPackageModLocation hisuf mod_name path basename _ext = do
230   -- basename == dots_to_slashes (moduleNameUserString mod_name)
231   loc <- hiOnlyModLocation path basename hisuf
232   let result = (mkPackageModule mod_name, loc)
233   addToFinderCache mod_name result
234   return result
235
236 hiOnlyModLocation path basename hisuf 
237  = do let full_basename = path++'/':basename
238       obj_fn <- mkObjPath full_basename basename
239       return ModLocation{ ml_hspp_file = Nothing,
240                              ml_hs_file   = Nothing,
241                              ml_hi_file   = full_basename ++ '.':hisuf,
242                                 -- Remove the .hi-boot suffix from
243                                 -- hi_file, if it had one.  We always
244                                 -- want the name of the real .hi file
245                                 -- in the ml_hi_file field.
246                              ml_obj_file  = obj_fn
247                   }
248
249 -- -----------------------------------------------------------------------------
250 -- Constructing a home module location
251
252 -- This is where we construct the ModLocation for a module in the home
253 -- package, for which we have a source file.  It is called from three
254 -- places:
255 --
256 --  (a) Here in the finder, when we are searching for a module to import,
257 --      using the search path (-i option).
258 --
259 --  (b) The compilation manager, when constructing the ModLocation for
260 --      a "root" module (a source file named explicitly on the command line
261 --      or in a :load command in GHCi).
262 --
263 --  (c) The driver in one-shot mode, when we need to construct a
264 --      ModLocation for a source file named on the command-line.
265 --
266 -- Parameters are:
267 --
268 -- mod_name
269 --      The name of the module
270 --
271 -- path
272 --      (a): The search path component where the source file was found.
273 --      (b) and (c): "."
274 --
275 -- src_basename
276 --      (a): dots_to_slashes (moduleNameUserString mod_name)
277 --      (b) and (c): The filename of the source file, minus its extension
278 --
279 -- ext
280 --      The filename extension of the source file (usually "hs" or "lhs").
281
282 mkHomeModLocation mod_name src_filename = do
283    let (basename,extension) = splitFilename src_filename
284    mkHomeModLocation' mod_name basename extension
285
286 mkHomeModLocationSearched mod_name path basename ext =
287    mkHomeModLocation' mod_name (path ++ '/':basename) ext
288
289 mkHomeModLocation' mod_name src_basename ext = do
290    let mod_basename = dots_to_slashes (moduleNameUserString mod_name)
291
292    obj_fn <- mkObjPath src_basename mod_basename
293    hi_fn  <- mkHiPath  src_basename mod_basename
294
295    let result = ( mkHomeModule mod_name,
296                    ModLocation{ ml_hspp_file = Nothing,
297                                 ml_hs_file   = Just (src_basename ++ '.':ext),
298                                 ml_hi_file   = hi_fn,
299                                 ml_obj_file  = obj_fn
300                        })
301
302    addToFinderCache mod_name result
303    return result
304
305 -- | Constructs the filename of a .o file for a given source file.
306 -- Does /not/ check whether the .o file exists
307 mkObjPath
308   :: FilePath           -- the filename of the source file, minus the extension
309   -> String             -- the module name with dots replaced by slashes
310   -> IO FilePath
311 mkObjPath basename mod_basename
312   = do  odir   <- readIORef v_Output_dir
313         osuf   <- readIORef v_Object_suf
314
315         let obj_basename | Just dir <- odir = dir ++ '/':mod_basename
316                          | otherwise        = basename
317
318         return (obj_basename ++ '.':osuf)
319
320 -- | Constructs the filename of a .hi file for a given source file.
321 -- Does /not/ check whether the .hi file exists
322 mkHiPath
323   :: FilePath           -- the filename of the source file, minus the extension
324   -> String             -- the module name with dots replaced by slashes
325   -> IO FilePath
326 mkHiPath basename mod_basename
327   = do  hidir   <- readIORef v_Hi_dir
328         hisuf   <- readIORef v_Hi_suf
329
330         let hi_basename | Just dir <- hidir = dir ++ '/':mod_basename
331                         | otherwise         = basename
332
333         return (hi_basename ++ '.':hisuf)
334
335 -- -----------------------------------------------------------------------------
336 -- findLinkable isn't related to the other stuff in here, 
337 -- but there's no other obvious place for it
338
339 findLinkable :: ModuleName -> ModLocation -> IO (Maybe Linkable)
340 findLinkable mod locn
341    = do let obj_fn = ml_obj_file locn
342         obj_exist <- doesFileExist obj_fn
343         if not obj_exist 
344          then return Nothing 
345          else 
346          do let stub_fn = case splitFilename3 obj_fn of
347                              (dir, base, ext) -> dir ++ "/" ++ base ++ "_stub.o"
348             stub_exist <- doesFileExist stub_fn
349             obj_time <- getModificationTime obj_fn
350             if stub_exist
351              then return (Just (LM obj_time mod [DotO obj_fn, DotO stub_fn]))
352              else return (Just (LM obj_time mod [DotO obj_fn]))
353
354 -- -----------------------------------------------------------------------------
355 -- Utils
356
357 dots_to_slashes = map (\c -> if c == '.' then '/' else c)
358
359 \end{code}