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