[project @ 2003-07-18 13:18:06 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 -> 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 findModule :: ModuleName -> IO (Either [FilePath] (Module, ModLocation))
91 findModule name = do
92   r <- lookupFinderCache name
93   case r of
94    Just result -> return (Right result)
95    Nothing -> do  
96        j <- maybeHomeModule name
97        case j of
98          Right home_module -> return (Right home_module)
99          Left home_files   -> do
100             r <- findPackageMod name
101             case r of
102                 Right pkg_module -> return (Right pkg_module)
103                 Left pkg_files   -> return (Left (home_files ++ pkg_files))
104
105 findPackageModule :: ModuleName -> IO (Either [FilePath] (Module, ModLocation))
106 findPackageModule name = do
107   r <- lookupFinderCache name
108   case r of
109    Just result -> return (Right result)
110    Nothing     -> findPackageMod name
111
112 hiBootExt = "hi-boot"
113 hiBootVerExt = "hi-boot-" ++ cHscIfaceFileVersion
114
115 maybeHomeModule :: ModuleName -> IO (Either [FilePath] (Module, ModLocation))
116 maybeHomeModule mod_name = do
117    home_path <- readIORef v_Import_paths
118    hisuf     <- readIORef v_Hi_suf
119    mode      <- readIORef v_GhcMode
120
121    let
122      source_exts = 
123       [ ("hs",   mkHomeModLocationSearched mod_name)
124       , ("lhs",  mkHomeModLocationSearched mod_name)
125       ]
126      
127      hi_exts = [ (hisuf,  mkHiOnlyModLocation hisuf mod_name) ]
128      
129      boot_exts =
130        [ (hiBootVerExt, mkHiOnlyModLocation hisuf mod_name)
131        , (hiBootExt,    mkHiOnlyModLocation hisuf mod_name)
132        ]
133
134         -- In compilation manager modes, we look for source files in the home
135         -- package because we can compile these automatically.  In one-shot
136         -- compilation mode we look for .hi and .hi-boot files only.
137         --
138         -- When generating dependencies, we're interested in either category.
139         --
140      exts
141          | mode == DoMkDependHS   = hi_exts ++ source_exts ++ boot_exts
142          | isCompManagerMode mode = source_exts
143          | otherwise {-one-shot-} = hi_exts ++ boot_exts
144
145    searchPathExts home_path mod_name exts
146         
147 -- -----------------------------------------------------------------------------
148 -- Looking for a package module
149
150 findPackageMod :: ModuleName -> IO (Either [FilePath] (Module, ModLocation))
151 findPackageMod mod_name = do
152   mode     <- readIORef v_GhcMode
153   imp_dirs <- getPackageImportPath -- including the 'auto' ones
154
155    -- hi-suffix for packages depends on the build tag.
156   package_hisuf <-
157         do tag <- readIORef v_Build_tag
158            if null tag
159                 then return "hi"
160                 else return (tag ++ "_hi")
161
162   let
163      hi_exts =
164         [ (package_hisuf, mkPackageModLocation package_hisuf mod_name) ]
165
166      source_exts = 
167        [ ("hs",   mkPackageModLocation package_hisuf mod_name)
168        , ("lhs",  mkPackageModLocation package_hisuf mod_name)
169        ]
170      
171      -- mkdependHS needs to look for source files in packages too, so
172      -- that we can make dependencies between package before they have
173      -- been built.
174      exts 
175       | mode == DoMkDependHS = hi_exts ++ source_exts
176       | otherwise = hi_exts
177
178       -- we never look for a .hi-boot file in an external package;
179       -- .hi-boot files only make sense for the home package.
180   searchPathExts imp_dirs mod_name exts
181
182 -- -----------------------------------------------------------------------------
183 -- General path searching
184
185 searchPathExts
186   :: [FilePath]         -- paths to search
187   -> ModuleName         -- module name
188   -> [ (
189         String,                                         -- suffix
190         String -> String -> String -> IO (Module, ModLocation)  -- action
191        )
192      ] 
193   -> IO (Either [FilePath] (Module, ModLocation))
194
195 searchPathExts path mod_name exts = search to_search
196   where
197     basename = dots_to_slashes (moduleNameUserString mod_name)
198
199     to_search :: [(FilePath, IO (Module,ModLocation))]
200     to_search = [ (file, fn p basename ext)
201                 | p <- path, 
202                   (ext,fn) <- exts,
203                   let base | p == "."  = basename
204                            | otherwise = p ++ '/':basename
205                       file = base ++ '.':ext
206                 ]
207
208     search [] = return (Left (map fst to_search))
209     search ((file, result) : rest) = do
210       b <- doesFileExist file
211       if b 
212         then Right `liftM` result
213         else search rest
214
215 -- -----------------------------------------------------------------------------
216 -- Building ModLocations
217
218 mkHiOnlyModLocation hisuf mod_name path basename _ext = do
219   -- basename == dots_to_slashes (moduleNameUserString mod_name)
220   loc <- hiOnlyModLocation path basename hisuf
221   let result = (mkHomeModule mod_name, loc)
222   addToFinderCache mod_name result
223   return result
224
225 mkPackageModLocation hisuf mod_name path basename _ext = do
226   -- basename == dots_to_slashes (moduleNameUserString mod_name)
227   loc <- hiOnlyModLocation path basename hisuf
228   let result = (mkPackageModule mod_name, loc)
229   addToFinderCache mod_name result
230   return result
231
232 hiOnlyModLocation path basename hisuf 
233  = do { obj_fn <- mkObjPath path basename ;
234         return (ModLocation{ ml_hspp_file = Nothing,
235                              ml_hs_file   = Nothing,
236                              ml_hi_file   = path ++ '/':basename ++ '.':hisuf,
237                                 -- Remove the .hi-boot suffix from
238                                 -- hi_file, if it had one.  We always
239                                 -- want the name of the real .hi file
240                                 -- in the ml_hi_file field.
241                              ml_obj_file  = obj_fn
242                  })}
243
244 -- -----------------------------------------------------------------------------
245 -- Constructing a home module location
246
247 -- This is where we construct the ModLocation for a module in the home
248 -- package, for which we have a source file.  It is called from three
249 -- places:
250 --
251 --  (a) Here in the finder, when we are searching for a module to import,
252 --      using the search path (-i option).
253 --
254 --  (b) The compilation manager, when constructing the ModLocation for
255 --      a "root" module (a source file named explicitly on the command line
256 --      or in a :load command in GHCi).
257 --
258 --  (c) The driver in one-shot mode, when we need to construct a
259 --      ModLocation for a source file named on the command-line.
260 --
261 -- Parameters are:
262 --
263 -- mod_name
264 --      The name of the module
265 --
266 -- path
267 --      (a): The search path component where the source file was found.
268 --      (b) and (c): "."
269 --
270 -- src_basename
271 --      (a): dots_to_slashes (moduleNameUserString mod_name)
272 --      (b) and (c): The filename of the source file, minus its extension
273 --
274 -- ext
275 --      The filename extension of the source file (usually "hs" or "lhs").
276
277 mkHomeModLocation mod_name src_filename = do
278    let mod_basename = dots_to_slashes (moduleNameUserString mod_name)
279        (basename,extension) = splitFilename src_filename
280
281    case my_prefix_match (reverse mod_basename) (reverse basename) of
282         Just ""   ->
283            mkHomeModLocationSearched mod_name "."  mod_basename extension
284         Just rest -> do
285            let path = reverse (dropWhile (=='/') rest)
286            mkHomeModLocationSearched mod_name path mod_basename extension
287         Nothing   -> do
288           hPutStrLn stderr ("Warning: " ++ src_filename ++
289                                  ": filename and module name do not match")
290           let (dir,basename,ext) = splitFilename3 src_filename
291           mkHomeModLocationSearched mod_name dir basename ext
292
293 mkHomeModLocationSearched mod_name path src_basename ext = do
294    hisuf  <- readIORef v_Hi_suf
295    hidir  <- readIORef v_Hi_dir
296
297    let mod_basename = dots_to_slashes (moduleNameUserString mod_name)
298
299    obj_fn <- mkObjPath path mod_basename
300
301    let  -- hi filename, always follows the module name
302        hi_path | Just d <- hidir = d
303                | otherwise       = path
304
305        hi_fn = hi_path ++ '/':mod_basename ++ '.':hisuf
306
307         -- source filename
308        source_fn = path ++ '/':src_basename ++ '.':ext
309
310        result = ( mkHomeModule mod_name,
311                   ModLocation{ ml_hspp_file = Nothing,
312                                ml_hs_file   = Just source_fn,
313                                ml_hi_file   = hi_fn,
314                                ml_obj_file  = obj_fn,
315                        })
316
317    addToFinderCache mod_name result
318    return result
319
320 mkObjPath :: FilePath -> String -> IO FilePath
321 -- Construct the filename of a .o file.
322 -- Does *not* check whether the .o file exists
323 mkObjPath path basename
324   = do  odir   <- readIORef v_Output_dir
325         osuf   <- readIORef v_Object_suf
326
327         let obj_path | Just d <- odir = d
328                      | otherwise      = path
329
330         return (obj_path ++ '/':basename ++ '.':osuf)
331
332 -- -----------------------------------------------------------------------------
333 -- findLinkable isn't related to the other stuff in here, 
334 -- but there's no other obvious place for it
335
336 findLinkable :: ModuleName -> ModLocation -> IO (Maybe Linkable)
337 findLinkable mod locn
338    = do let obj_fn = ml_obj_file locn
339         obj_exist <- doesFileExist obj_fn
340         if not obj_exist 
341          then return Nothing 
342          else 
343          do let stub_fn = case splitFilename3 obj_fn of
344                              (dir, base, ext) -> dir ++ "/" ++ base ++ "_stub.o"
345             stub_exist <- doesFileExist stub_fn
346             obj_time <- getModificationTime obj_fn
347             if stub_exist
348              then return (Just (LM obj_time mod [DotO obj_fn, DotO stub_fn]))
349              else return (Just (LM obj_time mod [DotO obj_fn]))
350
351 -- -----------------------------------------------------------------------------
352 -- Utils
353
354 dots_to_slashes = map (\c -> if c == '.' then '/' else c)
355
356 \end{code}