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