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