[project @ 2002-10-17 14:26:16 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     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     hiBootExt,          -- :: String
18     hiBootVerExt,       -- :: String
19
20   ) where
21
22 #include "HsVersions.h"
23
24 import Module
25 import UniqFM           ( filterUFM )
26 import Packages         ( PackageConfig(..) )
27 import DriverState
28 import DriverUtil       ( split_longest_prefix )
29 import FastString
30 import Config
31 import Util
32
33 import DATA_IOREF       ( IORef, writeIORef, readIORef )
34
35 import List
36 import Directory
37 import IO
38 import Monad
39
40 -- -----------------------------------------------------------------------------
41 -- The Finder
42
43 -- The Finder provides a thin filesystem abstraction to the rest of the
44 -- compiler.  For a given module, it knows (a) whether the module lives
45 -- in the home package or in another package, so it can make a Module
46 -- from a ModuleName, and (b) where the source, interface, and object
47 -- files for a module live.
48 -- 
49 -- It does *not* know which particular package a module lives in, because
50 -- that information is only contained in the interface file.
51
52 initFinder :: [PackageConfig] -> IO ()
53 initFinder pkgs = return ()
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 (Maybe (Module, ModLocation))
91 findModule name = do
92   r <- lookupFinderCache name
93   case r of
94    Just result -> return (Just result)
95    Nothing -> do  
96        j <- maybeHomeModule name
97        case j of
98          Just home_module -> return (Just home_module)
99          Nothing          -> findPackageMod name
100
101 findPackageModule :: ModuleName -> IO (Maybe (Module, ModLocation))
102 findPackageModule name = do
103   r <- lookupFinderCache name
104   case r of
105    Just result -> return (Just result)
106    Nothing     -> findPackageMod name
107
108 hiBootExt = "hi-boot"
109 hiBootVerExt = "hi-boot-" ++ cHscIfaceFileVersion
110
111 maybeHomeModule :: ModuleName -> IO (Maybe (Module, ModLocation))
112 maybeHomeModule mod_name = do
113    home_path <- readIORef v_Import_paths
114    hisuf     <- readIORef v_Hi_suf
115    mode      <- readIORef v_GhcMode
116
117    let
118      source_exts = 
119       [ ("hs",   mkHomeModLocation mod_name False)
120       , ("lhs",  mkHomeModLocation mod_name False)
121       ]
122      
123      hi_exts = [ (hisuf,  mkHiOnlyModLocation hisuf mod_name) ]
124      
125      boot_exts =
126        [ (hiBootVerExt, mkHiOnlyModLocation hisuf mod_name)
127        , (hiBootExt,    mkHiOnlyModLocation hisuf mod_name)
128        ]
129      
130         -- In compilation manager modes, we look for source files in the home
131         -- package because we can compile these automatically.  In one-shot
132         -- compilation mode we look for .hi and .hi-boot files only.
133         --
134         -- When generating dependencies, we're interested in either category.
135         --
136      exts
137          | mode == DoMkDependHS   = hi_exts ++ source_exts ++ boot_exts
138          | isCompManagerMode mode = source_exts
139          | otherwise {-one-shot-} = hi_exts ++ boot_exts
140
141    searchPathExts home_path mod_name exts
142         
143 -- -----------------------------------------------------------------------------
144 -- Looking for a package module
145
146 findPackageMod :: ModuleName -> IO (Maybe (Module, ModLocation))
147 findPackageMod mod_name = do
148   mode     <- readIORef v_GhcMode
149   imp_dirs <- getPackageImportPath -- including the 'auto' ones
150
151    -- hi-suffix for packages depends on the build tag.
152   package_hisuf <-
153         do tag <- readIORef v_Build_tag
154            if null tag
155                 then return "hi"
156                 else return (tag ++ "_hi")
157
158   let
159      hi_exts =
160         [ (package_hisuf, mkPackageModLocation package_hisuf mod_name) ]
161
162      source_exts = 
163        [ ("hs",   mkPackageModLocation package_hisuf mod_name)
164        , ("lhs",  mkPackageModLocation package_hisuf mod_name)
165        ]
166      
167      -- mkdependHS needs to look for source files in packages too, so
168      -- that we can make dependencies between package before they have
169      -- been built.
170      exts 
171       | mode == DoMkDependHS = hi_exts ++ source_exts
172       | otherwise = hi_exts
173
174       -- we never look for a .hi-boot file in an external package;
175       -- .hi-boot files only make sense for the home package.
176   searchPathExts imp_dirs mod_name exts
177
178 -- -----------------------------------------------------------------------------
179 -- General path searching
180
181 searchPathExts
182   :: [FilePath]         -- paths to search
183   -> ModuleName         -- module name
184   -> [ (
185         String,                                         -- suffix
186         String -> String -> String -> IO (Module, ModLocation)  -- action
187        )
188      ] 
189   -> IO (Maybe (Module, ModLocation))
190
191 searchPathExts path mod_name exts = search path
192   where
193     mod_str = moduleNameUserString mod_name
194     basename = map (\c -> if c == '.' then '/' else c) mod_str
195
196     search [] = return Nothing
197     search (p:ps) = loop exts
198       where     
199         base | p == "."  = basename
200              | otherwise = p ++ '/':basename
201
202         loop [] = search ps
203         loop ((ext,fn):exts) = do
204             let file = base ++ '.':ext
205             b <- doesFileExist file
206             if b then Just `liftM` fn p basename ext
207                  else loop exts
208
209 -- -----------------------------------------------------------------------------
210 -- Building ModLocations
211
212 mkHiOnlyModLocation hisuf mod_name path basename extension = do
213   addToFinderCache mod_name result
214   return result
215  where
216   result = ( mkHomeModule mod_name, hiOnlyModLocation path basename hisuf )
217
218 mkPackageModLocation hisuf mod_name path basename _extension = do
219   addToFinderCache mod_name result
220   return result
221  where
222   result = ( mkPackageModule mod_name, hiOnlyModLocation path basename hisuf )
223
224 hiOnlyModLocation path basename hisuf =
225       ModLocation{ ml_hspp_file = Nothing,
226                   ml_hs_file   = Nothing,
227                     -- remove the .hi-boot suffix from hi_file, if it
228                     -- had one.  We always want the name of the real
229                     -- .hi file in the ml_hi_file field.
230                   ml_hi_file   = path ++ '/':basename ++ '.':hisuf,
231                   ml_obj_file  = Nothing
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    odir   <- readIORef v_Output_dir
278    osuf   <- readIORef v_Object_suf
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         -- the object filename
298        obj_path | Just d <- odir = d
299                 | otherwise      = path
300        obj_fn = obj_path ++ '/':basename ++ '.':osuf
301
302   
303        result = ( mkHomeModule mod_name,
304                   ModLocation{ ml_hspp_file = Nothing,
305                                ml_hs_file   = Just source_fn,
306                                ml_hi_file   = hi_fn,
307                                ml_obj_file  = Just obj_fn,
308                        })
309
310    addToFinderCache mod_name result
311    return result
312 \end{code}