[project @ 2001-04-30 09:40: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     findModule,         -- :: ModuleName -> IO (Maybe (Module, ModuleLocation))
10     mkHomeModuleLocn,   -- :: ModuleName -> String -> FilePath 
11                         --      -> IO ModuleLocation
12     emptyHomeDirCache   -- :: IO ()
13   ) where
14
15 #include "HsVersions.h"
16
17 import HscTypes         ( ModuleLocation(..) )
18 import CmStaticInfo
19 import DriverPhases
20 import DriverState
21 import DriverUtil
22 import Module
23 import FiniteMap
24 import Util
25 import Panic            ( panic )
26 import Config
27
28 import IOExts
29 import Directory
30 import List
31 import IO
32 import Monad
33 import Outputable
34 \end{code}
35
36 The Finder provides a thin filesystem abstraction to the rest of the
37 compiler.  For a given module, it knows (a) which package the module
38 lives in, so it can make a Module from a ModuleName, and (b) where the
39 source, interface, and object files for a module live.
40
41 \begin{code}
42
43 -- v_PkgDirCache caches contents of package directories, never expunged
44 GLOBAL_VAR(v_PkgDirCache, panic "no pkg cache!", 
45            FiniteMap String (PackageName, FilePath))
46
47 -- v_HomeDirCache caches contents of home directories, 
48 -- expunged whenever we create a new finder.
49 GLOBAL_VAR(v_HomeDirCache, Nothing, Maybe (FiniteMap String FilePath))
50
51
52 initFinder :: [PackageConfig] -> IO ()
53 initFinder pkgs 
54   = do  {       -- expunge our home cache
55         ; writeIORef v_HomeDirCache Nothing
56                 -- lazilly fill in the package cache
57         ; writeIORef v_PkgDirCache (unsafePerformIO (newPkgCache pkgs))
58         }
59
60 emptyHomeDirCache :: IO ()
61 emptyHomeDirCache
62    = writeIORef v_HomeDirCache Nothing
63
64 findModule :: ModuleName -> IO (Maybe (Module, ModuleLocation))
65 findModule name
66   = do  { j <- maybeHomeModule name
67         ; case j of
68             Just home_module -> return (Just home_module)
69             Nothing          -> maybePackageModule name
70         }
71
72 maybeHomeModule :: ModuleName -> IO (Maybe (Module, ModuleLocation))
73 maybeHomeModule mod_name = do
74    home_cache <- readIORef v_HomeDirCache
75
76    home_map <- 
77      case home_cache of
78         Nothing -> do
79            -- populate the home dir cache, using the import path (the import 
80            -- path is changed by -i flags on the command line, and defaults 
81            -- to ["."]).
82            home_imports <- readIORef v_Import_paths
83            let extendFM fm path = do
84                    contents <- softGetDirectoryContents path
85                    let clean_contents = filter isUsefulFile contents
86                    return (addListToFM fm (zip clean_contents (repeat path)))
87            home_map <- foldM extendFM emptyFM (reverse home_imports)
88            writeIORef v_HomeDirCache (Just home_map)
89            return home_map
90
91         Just home_map -> return home_map
92
93    let basename = moduleNameUserString mod_name 
94        hs  = basename ++ ".hs"
95        lhs = basename ++ ".lhs"
96
97    case lookupFM home_map hs of {
98           -- special case to avoid getting "./foo.hs" all the time
99         Just "."  -> mkHomeModuleLocn mod_name basename hs;
100         Just path -> mkHomeModuleLocn mod_name 
101                         (path ++ '/':basename) (path ++ '/':hs);
102         Nothing ->
103
104    case lookupFM home_map lhs of {
105           -- special case to avoid getting "./foo.hs" all the time
106         Just "."  -> mkHomeModuleLocn mod_name basename lhs;
107         Just path ->  mkHomeModuleLocn mod_name
108                         (path ++ '/':basename) (path ++ '/':lhs);
109         Nothing -> do
110
111    -- can't find a source file anywhere, check for a lone .hi file.
112    hisuf <- readIORef v_Hi_suf
113    let hi = basename ++ '.':hisuf
114    case lookupFM home_map hi of {
115         Just path ->  mkHomeModuleLocn mod_name
116                         (path ++ '/':basename) (path ++ '/':hs);
117         Nothing -> do
118
119    -- last chance: .hi-boot-<ver> and .hi-boot
120    let hi_boot = basename ++ ".hi-boot"
121    let hi_boot_ver = basename ++ ".hi-boot-" ++ cHscIfaceFileVersion
122    case lookupFM home_map hi_boot_ver of {
123         Just path ->  mkHomeModuleLocn mod_name
124                         (path ++ '/':basename) (path ++ '/':hs);
125         Nothing -> do
126    case lookupFM home_map hi_boot of {
127         Just path ->  mkHomeModuleLocn mod_name 
128                         (path ++ '/':basename) (path ++ '/':hs);
129         Nothing -> return Nothing
130    }}}}}
131
132
133 -- The .hi file always follows the module name, whereas the object
134 -- file may follow the name of the source file in the case where the
135 -- two differ (see summariseFile in compMan/CompManager.lhs).
136
137 mkHomeModuleLocn mod_name basename source_fn = do
138
139    hisuf  <- readIORef v_Hi_suf
140    let hifile = getdir basename ++ '/':moduleNameUserString mod_name 
141                                 ++ '.':hisuf
142
143    -- figure out the .o file name.  It also lives in the same dir
144    -- as the source, but can be overriden by a -odir flag.
145    o_file <- odir_ify (basename ++ '.':phaseInputExt Ln) >>= osuf_ify
146
147    return (Just (mkHomeModule mod_name,
148                  ModuleLocation{
149                     ml_hspp_file = Nothing,
150                     ml_hs_file   = Just source_fn,
151                     ml_hi_file   = Just hifile,
152                     ml_obj_file  = Just o_file
153                  }
154         ))
155
156
157 newPkgCache :: [PackageConfig] -> IO (FiniteMap String (PackageName, FilePath))
158 newPkgCache pkgs = do
159     let extendFM fm pkg = do
160             let dirs = import_dirs pkg
161                 pkg_name = _PK_ (name pkg)
162             let addDir fm dir = do
163                     contents <- softGetDirectoryContents dir
164                     return (addListToFM fm (zip contents 
165                                                (repeat (pkg_name,dir))))
166             foldM addDir fm dirs
167     
168     pkg_map <- foldM extendFM emptyFM pkgs
169     return pkg_map
170
171
172 maybePackageModule :: ModuleName -> IO (Maybe (Module, ModuleLocation))
173 maybePackageModule mod_name = do
174   pkg_cache <- readIORef v_PkgDirCache
175
176   -- hi-suffix for packages depends on the build tag.
177   package_hisuf <-
178         do tag <- readIORef v_Build_tag
179            if null tag
180                 then return "hi"
181                 else return (tag ++ "_hi")
182
183   let basename = moduleNameUserString mod_name
184       hi = basename ++ '.':package_hisuf
185
186   case lookupFM pkg_cache hi of
187         Nothing -> return Nothing
188         Just (pkg_name,path) -> 
189             return (Just (mkModule mod_name pkg_name,
190                           ModuleLocation{ 
191                                 ml_hspp_file = Nothing,
192                                 ml_hs_file   = Nothing,
193                                 ml_hi_file   = Just (path ++ '/':hi),
194                                 ml_obj_file  = Nothing
195                            }
196                    ))
197
198 isUsefulFile fn
199    = let suffix = (reverse . takeWhile (/= '.') . reverse) fn
200      in  suffix `elem` ["hi", "hs", "lhs", "hi-boot", "hi-boot-5"]
201 \end{code}