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