6173853af552958b4e8ab51a14a4e15ee8614156
[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     FindResult(..),
10     findModule,                 -- :: ModuleName -> Bool -> IO FindResult
11     findPackageModule,          -- :: ModuleName -> Bool -> IO FindResult
12     mkHomeModLocation,          -- :: ModuleName -> FilePath -> IO ModLocation
13     mkHomeModLocation2,         -- :: ModuleName -> FilePath -> String -> IO ModLocation
14     addHomeModuleToFinder,      -- :: Module -> ModLocation -> IO ()
15
16     findLinkable,       -- :: ModuleName -> ModLocation -> IO (Maybe Linkable)
17
18     cantFindError,      -- :: DynFlags -> Module -> FindResult -> SDoc
19   ) where
20
21 #include "HsVersions.h"
22
23 import Module
24 import UniqFM           ( filterUFM )
25 import HscTypes         ( Linkable(..), Unlinked(..) )
26 import Packages
27 import DriverState
28 import DriverUtil
29 import FastString
30 import Util
31 import CmdLineOpts      ( DynFlags(..) )
32 import Outputable
33
34 import DATA_IOREF       ( IORef, writeIORef, readIORef )
35
36 import Data.List
37 import System.Directory
38 import System.IO
39 import Control.Monad
40 import Maybes           ( MaybeErr(..) )
41 import Data.Maybe       ( isNothing )
42
43
44 type FileExt = String   -- Filename extension
45 type BaseName = String  -- Basename of file
46
47 -- -----------------------------------------------------------------------------
48 -- The Finder
49
50 -- The Finder provides a thin filesystem abstraction to the rest of
51 -- the compiler.  For a given module, it can tell you where the
52 -- source, interface, and object files for that module live.
53 -- 
54 -- It does *not* know which particular package a module lives in.  Use
55 -- Packages.moduleToPackageConfig for that.
56
57 -- -----------------------------------------------------------------------------
58 -- The finder's cache
59
60 GLOBAL_VAR(finder_cache, emptyModuleEnv, ModuleEnv FinderCacheEntry)
61
62 type FinderCacheEntry = (ModLocation, Maybe (PackageConfig,Bool))
63
64 -- remove all the home modules from the cache; package modules are
65 -- assumed to not move around during a session.
66 flushFinderCache :: IO ()
67 flushFinderCache = do
68   fm <- readIORef finder_cache
69   writeIORef finder_cache (filterUFM (\(loc,m) -> isNothing m) fm)
70
71 addToFinderCache :: Module -> FinderCacheEntry -> IO ()
72 addToFinderCache mod_name entry = do
73   fm <- readIORef finder_cache
74   writeIORef finder_cache (extendModuleEnv fm mod_name entry)
75
76 lookupFinderCache :: Module -> IO (Maybe FinderCacheEntry)
77 lookupFinderCache mod_name = do
78   fm <- readIORef finder_cache
79   return $! lookupModuleEnv fm mod_name
80
81 -- -----------------------------------------------------------------------------
82 -- Locating modules
83
84 -- This is the main interface to the finder, which maps ModuleNames to
85 -- Modules and ModLocations.
86 --
87 -- The Module contains one crucial bit of information about a module:
88 -- whether it lives in the current ("home") package or not (see Module
89 -- for more details).
90 --
91 -- The ModLocation contains the names of all the files associated with
92 -- that module: its source file, .hi file, object file, etc.
93
94 data FindResult
95   = Found ModLocation PackageIdH
96         -- the module was found
97   | PackageHidden PackageId
98         -- for an explicit source import: the package containing the module is
99         -- not exposed.
100   | ModuleHidden  PackageId
101         -- for an explicit source import: the package containing the module is
102         -- exposed, but the module itself is hidden.
103   | NotFound [FilePath]
104         -- the module was not found, the specified places were searched.
105
106 type LocalFindResult = MaybeErr [FilePath] FinderCacheEntry
107         -- LocalFindResult is used for internal functions which 
108         -- return a more informative type; it's munged into
109         -- the external FindResult by 'cached'
110
111 cached :: (DynFlags -> Module -> IO LocalFindResult)
112        -> DynFlags -> Module -> Bool -> IO FindResult
113 cached wrapped_fn dflags name explicit 
114   = do  {       -- First try the cache
115           mb_entry <- lookupFinderCache name
116         ; case mb_entry of {
117             Just old_entry -> return (found old_entry) ;
118             Nothing    -> do
119
120         {       -- Now try the wrapped function
121           mb_entry <- wrapped_fn dflags name
122         ; case mb_entry of
123             Failed paths        -> return (NotFound paths)
124             Succeeded new_entry -> do { addToFinderCache name new_entry
125                                       ; return (found new_entry) }
126         }}} 
127   where
128         -- We've found the module, so the remaining question is
129         -- whether it's visible or not
130     found :: FinderCacheEntry -> FindResult
131     found (loc, Nothing)                = Found loc HomePackage
132     found (loc, Just (pkg, exposed_mod))
133         | explicit && not exposed_mod   = ModuleHidden pkg_name
134         | explicit && not (exposed pkg) = PackageHidden pkg_name
135         | otherwise                     = Found loc (ExtPackage (mkPackageId (package pkg)))
136         where
137           pkg_name = packageConfigId pkg
138
139 addHomeModuleToFinder :: Module -> ModLocation -> IO ()
140 addHomeModuleToFinder mod loc = addToFinderCache mod (loc, Nothing)
141
142
143 -- -----------------------------------------------------------------------------
144 --      The two external entry points
145
146
147 findModule :: DynFlags -> Module -> Bool -> IO FindResult
148 findModule = cached findModule' 
149   
150 findPackageModule :: DynFlags -> Module -> Bool -> IO FindResult
151 findPackageModule = cached findPackageModule'
152
153 -- -----------------------------------------------------------------------------
154 --      The internal workers
155
156 findModule' :: DynFlags -> Module -> IO LocalFindResult
157 -- Find home or package module
158 findModule' dflags name = do
159     r <- findPackageModule' dflags name
160     case r of
161         Failed pkg_files -> do
162            j <- findHomeModule' dflags name
163            case j of
164                 Failed home_files -> 
165                         return (Failed (home_files ++ pkg_files))
166                 other_result
167                         -> return other_result
168         other_result
169                 -> return other_result
170
171 findHomeModule' :: DynFlags -> Module -> IO LocalFindResult
172 findHomeModule' dflags mod = do
173    let home_path = importPaths dflags
174    hisuf     <- readIORef v_Hi_suf
175    mode      <- readIORef v_GhcMode
176
177    let
178      source_exts = 
179       [ ("hs",   mkHomeModLocationSearched mod "hs")
180       , ("lhs",  mkHomeModLocationSearched mod "lhs")
181       ]
182      
183      hi_exts = [ (hisuf,                mkHiOnlyModLocation hisuf)
184                , (addBootSuffix hisuf,  mkHiOnlyModLocation hisuf)
185                ]
186      
187         -- In compilation manager modes, we look for source files in the home
188         -- package because we can compile these automatically.  In one-shot
189         -- compilation mode we look for .hi and .hi-boot files only.
190      exts
191          | DoMkDependHS <- mode   = source_exts
192          | isCompManagerMode mode = source_exts
193          | otherwise {-one-shot-} = hi_exts
194
195    searchPathExts home_path mod exts
196         
197 findPackageModule' :: DynFlags -> Module -> IO LocalFindResult
198 findPackageModule' dflags mod 
199   = case moduleToPackageConfig dflags mod of
200         Nothing       -> return (Failed [])
201         Just pkg_info -> findPackageIface mod pkg_info
202
203 findPackageIface :: Module -> (PackageConfig,Bool) -> IO LocalFindResult
204 findPackageIface mod pkg_info@(pkg_conf, _) = do
205   mode <- readIORef v_GhcMode
206   tag  <- readIORef v_Build_tag
207   let
208            -- hi-suffix for packages depends on the build tag.
209      package_hisuf | null tag  = "hi"
210                    | otherwise = tag ++ "_hi"
211      hi_exts =
212         [ (package_hisuf, 
213             mkPackageModLocation pkg_info package_hisuf) ]
214
215      source_exts = 
216        [ ("hs",   mkPackageModLocation pkg_info package_hisuf)
217        , ("lhs",  mkPackageModLocation pkg_info package_hisuf)
218        ]
219
220      -- mkdependHS needs to look for source files in packages too, so
221      -- that we can make dependencies between package before they have
222      -- been built.
223      exts 
224       | DoMkDependHS <- mode = hi_exts ++ source_exts
225       | otherwise            = hi_exts
226       -- we never look for a .hi-boot file in an external package;
227       -- .hi-boot files only make sense for the home package.
228
229   searchPathExts (importDirs pkg_conf) mod exts
230
231 -- -----------------------------------------------------------------------------
232 -- General path searching
233
234 searchPathExts
235   :: [FilePath]         -- paths to search
236   -> Module             -- module name
237   -> [ (
238         FileExt,                                     -- suffix
239         FilePath -> BaseName -> IO FinderCacheEntry  -- action
240        )
241      ] 
242   -> IO LocalFindResult
243
244 searchPathExts paths mod exts 
245    = do result <- search to_search
246 {-
247         hPutStrLn stderr (showSDoc $
248                 vcat [text "Search" <+> ppr mod <+> sep (map (text. fst) exts)
249                     , nest 2 (vcat (map text paths))
250                     , case result of
251                         Succeeded (loc, p) -> text "Found" <+> ppr loc
252                         Failed fs          -> text "not found"])
253 -}      
254         return result
255
256   where
257     basename = dots_to_slashes (moduleUserString mod)
258
259     to_search :: [(FilePath, IO FinderCacheEntry)]
260     to_search = [ (file, fn path basename)
261                 | path <- paths, 
262                   (ext,fn) <- exts,
263                   let base | path == "." = basename
264                            | otherwise   = path ++ '/':basename
265                       file = base ++ '.':ext
266                 ]
267
268     search [] = return (Failed (map fst to_search))
269     search ((file, mk_result) : rest) = do
270       b <- doesFileExist file
271       if b 
272         then do { res <- mk_result; return (Succeeded res) }
273         else search rest
274
275 mkHomeModLocationSearched :: Module -> FileExt
276                           -> FilePath -> BaseName -> IO FinderCacheEntry
277 mkHomeModLocationSearched mod suff path basename = do
278    loc <- mkHomeModLocation2 mod (path ++ '/':basename) suff
279    return (loc, Nothing)
280
281 mkHiOnlyModLocation :: FileExt -> FilePath -> BaseName -> IO FinderCacheEntry
282 mkHiOnlyModLocation hisuf path basename = do
283   loc <- hiOnlyModLocation path basename hisuf
284   return (loc, Nothing)
285
286 mkPackageModLocation :: (PackageConfig, Bool) -> FileExt
287                      -> FilePath -> BaseName -> IO FinderCacheEntry
288 mkPackageModLocation pkg_info hisuf path basename = do
289   loc <- hiOnlyModLocation path basename hisuf
290   return (loc, Just pkg_info)
291
292 -- -----------------------------------------------------------------------------
293 -- Constructing a home module location
294
295 -- This is where we construct the ModLocation for a module in the home
296 -- package, for which we have a source file.  It is called from three
297 -- places:
298 --
299 --  (a) Here in the finder, when we are searching for a module to import,
300 --      using the search path (-i option).
301 --
302 --  (b) The compilation manager, when constructing the ModLocation for
303 --      a "root" module (a source file named explicitly on the command line
304 --      or in a :load command in GHCi).
305 --
306 --  (c) The driver in one-shot mode, when we need to construct a
307 --      ModLocation for a source file named on the command-line.
308 --
309 -- Parameters are:
310 --
311 -- mod
312 --      The name of the module
313 --
314 -- path
315 --      (a): The search path component where the source file was found.
316 --      (b) and (c): "."
317 --
318 -- src_basename
319 --      (a): dots_to_slashes (moduleNameUserString mod)
320 --      (b) and (c): The filename of the source file, minus its extension
321 --
322 -- ext
323 --      The filename extension of the source file (usually "hs" or "lhs").
324
325 mkHomeModLocation :: Module -> FilePath -> IO ModLocation
326 mkHomeModLocation mod src_filename = do
327    let (basename,extension) = splitFilename src_filename
328    mkHomeModLocation2 mod basename extension
329
330 mkHomeModLocation2 :: Module    
331                    -> FilePath  -- Of source module, without suffix
332                    -> String    -- Suffix
333                    -> IO ModLocation
334 mkHomeModLocation2 mod src_basename ext = do
335    let mod_basename = dots_to_slashes (moduleUserString mod)
336
337    obj_fn <- mkObjPath src_basename mod_basename
338    hi_fn  <- mkHiPath  src_basename mod_basename
339
340    return (ModLocation{ ml_hs_file   = Just (src_basename ++ '.':ext),
341                         ml_hi_file   = hi_fn,
342                         ml_obj_file  = obj_fn })
343
344 hiOnlyModLocation :: FilePath -> String -> Suffix -> IO ModLocation
345 hiOnlyModLocation path basename hisuf 
346  = do let full_basename = path++'/':basename
347       obj_fn <- mkObjPath full_basename basename
348       return ModLocation{    ml_hs_file   = Nothing,
349                              ml_hi_file   = full_basename ++ '.':hisuf,
350                                 -- Remove the .hi-boot suffix from
351                                 -- hi_file, if it had one.  We always
352                                 -- want the name of the real .hi file
353                                 -- in the ml_hi_file field.
354                              ml_obj_file  = obj_fn
355                   }
356
357 -- | Constructs the filename of a .o file for a given source file.
358 -- Does /not/ check whether the .o file exists
359 mkObjPath
360   :: FilePath           -- the filename of the source file, minus the extension
361   -> String             -- the module name with dots replaced by slashes
362   -> IO FilePath
363 mkObjPath basename mod_basename
364   = do  odir   <- readIORef v_Output_dir
365         osuf   <- readIORef v_Object_suf
366
367         let obj_basename | Just dir <- odir = dir ++ '/':mod_basename
368                          | otherwise        = basename
369
370         return (obj_basename ++ '.':osuf)
371
372 -- | Constructs the filename of a .hi file for a given source file.
373 -- Does /not/ check whether the .hi file exists
374 mkHiPath
375   :: FilePath           -- the filename of the source file, minus the extension
376   -> String             -- the module name with dots replaced by slashes
377   -> IO FilePath
378 mkHiPath basename mod_basename
379   = do  hidir   <- readIORef v_Hi_dir
380         hisuf   <- readIORef v_Hi_suf
381
382         let hi_basename | Just dir <- hidir = dir ++ '/':mod_basename
383                         | otherwise         = basename
384
385         return (hi_basename ++ '.':hisuf)
386
387
388 -- -----------------------------------------------------------------------------
389 -- findLinkable isn't related to the other stuff in here, 
390 -- but there's no other obvious place for it
391
392 findLinkable :: Module -> ModLocation -> IO (Maybe Linkable)
393 findLinkable mod locn
394    = do let obj_fn = ml_obj_file locn
395         obj_exist <- doesFileExist obj_fn
396         if not obj_exist 
397          then return Nothing 
398          else 
399          do let stub_fn = case splitFilename3 obj_fn of
400                              (dir, base, ext) -> dir ++ "/" ++ base ++ "_stub.o"
401             stub_exist <- doesFileExist stub_fn
402             obj_time <- getModificationTime obj_fn
403             if stub_exist
404              then return (Just (LM obj_time mod [DotO obj_fn, DotO stub_fn]))
405              else return (Just (LM obj_time mod [DotO obj_fn]))
406
407 -- -----------------------------------------------------------------------------
408 -- Utils
409
410 dots_to_slashes = map (\c -> if c == '.' then '/' else c)
411
412
413 -- -----------------------------------------------------------------------------
414 -- Error messages
415
416 cantFindError :: DynFlags -> Module -> FindResult -> SDoc
417 cantFindError dflags mod_name find_result
418   = hang (ptext SLIT("Could not find module") <+> quotes (ppr mod_name) <> colon)
419        2 more_info
420   where
421     more_info
422       = case find_result of
423             PackageHidden pkg 
424                 -> ptext SLIT("it is a member of package") <+> ppr pkg <> comma
425                    <+> ptext SLIT("which is hidden")
426
427             ModuleHidden pkg
428                 -> ptext SLIT("it is hidden") <+> parens (ptext SLIT("in package")
429                    <+> ppr pkg)
430
431             NotFound files
432                 | verbosity dflags < 3 
433                 -> ptext SLIT("use -v to see a list of the files searched for")
434                 | otherwise 
435                 -> hang (ptext SLIT("locations searched:")) 
436                       2 (vcat (map text files))
437
438             Found _ _ -> panic "cantFindErr"
439 \end{code}