[project @ 2002-08-29 15:44:11 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     findModuleDep,      -- :: ModuleName -> Bool -> IO (Maybe (Module, ModuleLocation))
11     findPackageModule,  -- :: ModuleName -> IO (Maybe (Module, ModuleLocation))
12     mkHomeModuleLocn,   -- :: ModuleName -> String -> FilePath 
13                         --      -> IO ModuleLocation
14     emptyHomeDirCache,  -- :: IO ()
15     flushPackageCache   -- :: [PackageConfig] -> IO ()
16   ) where
17
18 #include "HsVersions.h"
19
20 import HscTypes         ( ModuleLocation(..) )
21 import Packages         ( PackageConfig(..) )
22 import DriverPhases
23 import DriverState
24 import DriverUtil
25 import Module
26 import FastString
27 import Config
28
29 import DATA_IOREF       ( readIORef )
30
31 import List
32 import Directory
33 import IO
34 import Monad
35 \end{code}
36
37 The Finder provides a thin filesystem abstraction to the rest of the
38 compiler.  For a given module, it knows (a) whether the module lives
39 in the home package or in another package, so it can make a Module
40 from a ModuleName, and (b) where the source, interface, and object
41 files for a module live.
42
43 It does *not* know which particular package a module lives in, because
44 that information is only contained in the interface file.
45
46 \begin{code}
47 initFinder :: [PackageConfig] -> IO ()
48 initFinder pkgs = return ()
49
50 -- empty, and lazilly fill in the package cache
51 flushPackageCache :: [PackageConfig] -> IO ()
52 flushPackageCache pkgs = return ()
53
54 emptyHomeDirCache :: IO ()
55 emptyHomeDirCache = return ()
56
57 findModule :: ModuleName -> IO (Maybe (Module, ModuleLocation))
58 findModule name = findModuleDep name False
59
60 findModuleDep :: ModuleName -> Bool -> IO (Maybe (Module, ModuleLocation))
61 findModuleDep name is_source
62   = do  { j <- maybeHomeModule name is_source
63         ; case j of
64             Just home_module -> return (Just home_module)
65             Nothing          -> findPackageMod name False is_source
66         }
67
68 maybeHomeModule :: ModuleName -> Bool -> IO (Maybe (Module, ModuleLocation))
69 maybeHomeModule mod_name is_source = do
70    home_path <- readIORef v_Import_paths
71    hisuf     <- readIORef v_Hi_suf
72    mode      <- readIORef v_GhcMode
73
74    let mod_str  = moduleNameUserString mod_name 
75        basename = map (\c -> if c == '.' then '/' else c) mod_str
76        
77         -- In compilation manager modes, we look for source files in the home
78         -- package because we can compile these automatically.  In one-shot
79         -- compilation mode we look for .hi files only.
80         --
81         -- When generating dependencies, we're interested in either category.
82         --
83        source_exts = 
84              [ ("hs",   \ fName path -> mkHomeModuleLocn mod_name path fName)
85              , ("lhs",  \ fName path -> mkHomeModuleLocn mod_name path fName)
86              ]
87        hi_exts = [ (hisuf,  \ fName path -> mkHiOnlyModuleLocn mod_name fName) ]
88
89        std_exts
90          | mode == DoMkDependHS   = hi_exts ++ source_exts
91          | isCompManagerMode mode = source_exts
92          | otherwise              = hi_exts
93
94         -- last chance: .hi-boot-<ver> and .hi-boot
95        hi_boot_ver = "hi-boot-" ++ cHscIfaceFileVersion
96
97        boot_exts = 
98         [ (hi_boot_ver, \ fName path -> mkHiOnlyModuleLocn mod_name fName)
99         , ("hi-boot",   \ fName path -> mkHiOnlyModuleLocn mod_name fName)
100         ]
101
102    searchPathExts home_path basename
103         (if is_source then boot_exts else (std_exts ++ boot_exts))
104                         -- for SOURCE imports, check the hi-boot extensions
105                         -- before the source/iface ones, to avoid
106                         -- creating circ Makefile deps.
107         
108
109 mkHiOnlyModuleLocn mod_name hi_file =
110  return
111    ( mkHomeModule mod_name
112    , ModuleLocation{ ml_hspp_file = Nothing
113                    , ml_hs_file   = Nothing
114                    , ml_hi_file   = hi_file
115                    , ml_obj_file  = Nothing
116                    }
117    )
118
119 -- The .hi file always follows the module name, whereas the object
120 -- file may follow the name of the source file in the case where the
121 -- two differ (see summariseFile in compMan/CompManager.lhs).
122
123 mkHomeModuleLocn mod_name 
124         basename                -- everything but the extension
125         source_fn               -- full path to the source (required)
126   = do
127
128    hisuf  <- readIORef v_Hi_suf
129    hidir  <- readIORef v_Hi_dir
130
131    -- take the *last* component of the module name (if a hierarchical name),
132    -- and append it to the directory to get the .hi file name.
133    let (_,mod_str) = split_longest_prefix (moduleNameUserString mod_name) (=='.')
134        hi_filename = mod_str ++ '.':hisuf
135        hi_path | Just d <- hidir = d
136                | otherwise       = getdir basename
137        hi = hi_path ++ '/':hi_filename
138
139    -- figure out the .o file name.  It also lives in the same dir
140    -- as the source, but can be overriden by a -odir flag.
141    o_file <- odir_ify (basename ++ '.':phaseInputExt Ln) >>= osuf_ify
142
143    return (mkHomeModule mod_name,
144            ModuleLocation{ ml_hspp_file = Nothing
145                          , ml_hs_file   = Just source_fn
146                          , ml_hi_file   = hi
147                          , ml_obj_file  = Just o_file
148                          })
149
150 findPackageMod :: ModuleName
151                -> Bool
152                -> Bool
153                -> IO (Maybe (Module, ModuleLocation))
154 findPackageMod mod_name hiOnly is_source = do
155   pkgs <- getPackageInfo
156
157    -- hi-suffix for packages depends on the build tag.
158   package_hisuf <-
159         do tag <- readIORef v_Build_tag
160            if null tag
161                 then return "hi"
162                 else return (tag ++ "_hi")
163   let imp_dirs = concatMap import_dirs pkgs
164       mod_str  = moduleNameUserString mod_name 
165       basename = map (\c -> if c == '.' then '/' else c) mod_str
166
167       retPackageModule mod_name mbFName path =
168         return ( mkPackageModule mod_name
169                , ModuleLocation{ ml_hspp_file = Nothing
170                                , ml_hs_file   = mbFName
171                                , ml_hi_file   = path ++ '.':package_hisuf
172                                , ml_obj_file  = Nothing
173                                })
174
175        -- last chance: .hi-boot-<ver> and .hi-boot
176       hi_boot_ver = "hi-boot-" ++ cHscIfaceFileVersion
177
178       boot_exts = 
179         [ (hi_boot_ver, \ fName path -> mkHiOnlyModuleLocn mod_name fName)
180         , ("hi-boot",   \ fName path -> mkHiOnlyModuleLocn mod_name fName)
181         ]
182
183   searchPathExts
184         imp_dirs basename
185         (if is_source then boot_exts else       
186           ((package_hisuf,\ fName path -> retPackageModule mod_name Nothing path) :
187            (if hiOnly then [] else
188              [ ("hs",  \ fName path -> retPackageModule mod_name (Just fName) path)
189              , ("lhs", \ fName path -> retPackageModule mod_name (Just fName) path)
190              ])))
191  where
192
193 findPackageModule :: ModuleName -> IO (Maybe (Module, ModuleLocation))
194 findPackageModule mod_name = findPackageMod mod_name True False
195
196 searchPathExts :: [FilePath]
197                -> String
198                -> [(String, FilePath -> String -> IO (Module, ModuleLocation))] 
199                -> IO (Maybe (Module, ModuleLocation))
200 searchPathExts path basename exts = search path
201   where
202     search [] = return Nothing
203     search (p:ps) = loop exts
204       where     
205         base | p == "."  = basename
206              | otherwise = p ++ '/':basename
207
208         loop [] = search ps
209         loop ((ext,fn):exts) = do
210             let file = base ++ '.':ext
211             b <- doesFileExist file
212             if b then Just `liftM` fn file base
213                  else loop exts
214 \end{code}