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