b376102e8c6fe95298cc71a26c1c0bf9147a34c9
[ghc-hetmet.git] / ghc / compiler / main / DriverMkDepend.hs
1 -----------------------------------------------------------------------------
2 -- $Id: DriverMkDepend.hs,v 1.33 2004/09/30 10:37:10 simonpj Exp $
3 --
4 -- GHC Driver
5 --
6 -- (c) Simon Marlow 2000
7 --
8 -----------------------------------------------------------------------------
9
10 module DriverMkDepend (
11         doMkDependHSPhase, beginMkDependHS, endMkDependHS
12   ) where
13
14 #include "HsVersions.h"
15
16 import GetImports       ( getImports )
17 import DriverState      
18 import DriverUtil
19 import DriverFlags
20 import SysTools         ( newTempName )
21 import qualified SysTools
22 import Module           ( ModuleName, ModLocation(..),
23                           moduleNameUserString, isHomeModule )
24 import Finder           ( findModule, hiBootExt, hiBootVerExt,
25                           mkHomeModLocation )
26 import Util             ( global, maybePrefixMatch )
27 import Panic
28
29 import DATA_IOREF       ( IORef, readIORef, writeIORef )
30 import EXCEPTION
31
32 import Directory
33 import IO
34 import Monad            ( when )
35 import Maybe            ( isJust )
36
37 #if __GLASGOW_HASKELL__ <= 408
38 import Panic            ( catchJust, ioErrors )
39 #endif
40
41 -------------------------------------------------------------------------------
42 -- mkdependHS
43
44         -- flags
45 GLOBAL_VAR(v_Dep_makefile,              "Makefile", String);
46 GLOBAL_VAR(v_Dep_include_prelude,       False, Bool);
47 GLOBAL_VAR(v_Dep_exclude_mods,          ["GHC.Prim"], [String]);
48 GLOBAL_VAR(v_Dep_suffixes,              [], [String]);
49 GLOBAL_VAR(v_Dep_warnings,              True, Bool);
50
51         -- global vars
52 GLOBAL_VAR(v_Dep_makefile_hdl,  error "dep_makefile_hdl", Maybe Handle);
53 GLOBAL_VAR(v_Dep_tmp_file,      error "dep_tmp_file", String);
54 GLOBAL_VAR(v_Dep_tmp_hdl,       error "dep_tmp_hdl", Handle);
55 GLOBAL_VAR(v_Dep_dir_contents,  error "dep_dir_contents", [(String,[String])]);
56
57 depStartMarker = "# DO NOT DELETE: Beginning of Haskell dependencies"
58 depEndMarker   = "# DO NOT DELETE: End of Haskell dependencies"
59
60 -- for compatibility with the old mkDependHS, we accept options of the form
61 -- -optdep-f -optdep.depend, etc.
62 dep_opts = 
63    [ (  "s",                    SepArg (add v_Dep_suffixes) )
64    , (  "f",                    SepArg (writeIORef v_Dep_makefile) )
65    , (  "w",                    NoArg (writeIORef v_Dep_warnings False) )
66    , (  "-include-prelude",     NoArg (writeIORef v_Dep_include_prelude True) )
67    , (  "-exclude-module=",       Prefix (add v_Dep_exclude_mods) )
68    , (  "x",                      Prefix (add v_Dep_exclude_mods) )
69    ]
70
71 beginMkDependHS :: IO ()
72 beginMkDependHS = do
73
74         -- slurp in the mkdependHS-style options
75   flags <- getStaticOpts v_Opt_dep
76   _ <- processArgs dep_opts flags []
77
78         -- open a new temp file in which to stuff the dependency info
79         -- as we go along.
80   dep_file <- newTempName "dep"
81   writeIORef v_Dep_tmp_file dep_file
82   tmp_hdl <- openFile dep_file WriteMode
83   writeIORef v_Dep_tmp_hdl tmp_hdl
84
85         -- open the makefile
86   makefile <- readIORef v_Dep_makefile
87   exists <- doesFileExist makefile
88   if not exists
89         then do 
90            writeIORef v_Dep_makefile_hdl Nothing
91            return ()
92
93         else do
94            makefile_hdl <- openFile makefile ReadMode
95            writeIORef v_Dep_makefile_hdl (Just makefile_hdl)
96
97                 -- slurp through until we get the magic start string,
98                 -- copying the contents into dep_makefile
99            let slurp = do
100                 l <- hGetLine makefile_hdl
101                 if (l == depStartMarker)
102                         then return ()
103                         else do hPutStrLn tmp_hdl l; slurp
104          
105                 -- slurp through until we get the magic end marker,
106                 -- throwing away the contents
107            let chuck = do
108                 l <- hGetLine makefile_hdl
109                 if (l == depEndMarker)
110                         then return ()
111                         else chuck
112          
113            catchJust ioErrors slurp 
114                 (\e -> if isEOFError e then return () else ioError e)
115            catchJust ioErrors chuck
116                 (\e -> if isEOFError e then return () else ioError e)
117
118
119         -- write the magic marker into the tmp file
120   hPutStrLn tmp_hdl depStartMarker
121
122         -- cache the contents of all the import directories, for future
123         -- reference.
124   import_dirs <- readIORef v_Import_paths
125   pkg_import_dirs <- getPackageImportPath
126   import_dir_contents <- mapM softGetDirectoryContents import_dirs
127   pkg_import_dir_contents <- mapM softGetDirectoryContents pkg_import_dirs
128   writeIORef v_Dep_dir_contents 
129         (zip import_dirs import_dir_contents ++
130          zip pkg_import_dirs pkg_import_dir_contents)
131
132   return ()
133
134
135 doMkDependHSPhase basename suff input_fn
136  = do src <- readFile input_fn
137       let (import_sources, import_normals, mod_name) = getImports src
138       let orig_fn = basename ++ '.':suff
139       (_, location') <- mkHomeModLocation mod_name orig_fn
140
141       -- take -ohi into account if present
142       ohi <- readIORef v_Output_hi
143       let location | Just fn <- ohi = location'{ ml_hi_file = fn }
144                    | otherwise      = location'
145
146       deps_sources <- mapM (findDependency True  orig_fn) import_sources
147       deps_normals <- mapM (findDependency False orig_fn) import_normals
148       let deps = deps_sources ++ deps_normals
149
150       osuf <- readIORef v_Object_suf
151       extra_suffixes <- readIORef v_Dep_suffixes
152       let suffixes = map (++ ('_':osuf)) extra_suffixes
153           obj_file = ml_obj_file location
154           objs = obj_file : map (replaceFilenameSuffix obj_file) suffixes
155
156         -- Handle for file that accumulates dependencies 
157       hdl <- readIORef v_Dep_tmp_hdl
158
159         -- std dependency of the object(s) on the source file
160       hPutStrLn hdl (unwords (map escapeSpaces objs) ++ " : " ++
161                      escapeSpaces (basename ++ '.':suff))
162
163       let genDep (dep, False {- not an hi file -}) = 
164              hPutStrLn hdl (unwords (map escapeSpaces objs) ++ " : " ++
165                             escapeSpaces dep)
166           genDep (dep, True  {- is an hi file -}) = do
167              hisuf <- readIORef v_Hi_suf
168              let 
169                 -- In order to construct hi files with alternate suffixes, we
170                 -- now have to find the "basename" of the hi file.  This is
171                 -- difficult because we can't just split the hi filename
172                 -- at the last dot - the hisuf might have dots in it.  So we
173                 -- check whether the hi filename ends in hisuf, and if it does,
174                 -- we strip off hisuf, otherwise we strip everything after the
175                 -- last dot.
176                 dep_base 
177                    | Just rest <- maybePrefixMatch rev_hisuf rev_dep
178                    = reverse rest
179                    | otherwise
180                    = remove_suffix '.' dep
181                   where
182                         rev_hisuf = reverse hisuf
183                         rev_dep   = reverse dep
184
185                 deps = dep : map (\suf -> dep_base ++ suf ++ '_':hisuf) 
186                                 extra_suffixes
187                   -- length objs should be == length deps
188              sequence_ (zipWith (\o d -> hPutStrLn hdl (escapeSpaces o ++ " : " ++ escapeSpaces d)) objs deps)
189
190       sequence_ (map genDep [ d | Just d <- deps ])
191       return location
192
193 -- add the lines to dep_makefile:
194            -- always:
195                    -- this.o : this.hs
196
197            -- if the dependency is on something other than a .hi file:
198                    -- this.o this.p_o ... : dep
199            -- otherwise
200                    -- if the import is {-# SOURCE #-}
201                            -- this.o this.p_o ... : dep.hi-boot[-$vers]
202                            
203                    -- else
204                            -- this.o ...   : dep.hi
205                            -- this.p_o ... : dep.p_hi
206                            -- ...
207    
208            -- (where .o is $osuf, and the other suffixes come from
209            -- the cmdline -s options).
210    
211
212
213 endMkDependHS :: IO ()
214 endMkDependHS = do
215   makefile     <- readIORef v_Dep_makefile
216   makefile_hdl <- readIORef v_Dep_makefile_hdl
217   tmp_file     <- readIORef v_Dep_tmp_file
218   tmp_hdl      <- readIORef v_Dep_tmp_hdl
219
220         -- write the magic marker into the tmp file
221   hPutStrLn tmp_hdl depEndMarker
222
223   case makefile_hdl of
224      Nothing  -> return ()
225      Just hdl -> do
226
227           -- slurp the rest of the original makefile and copy it into the output
228         let slurp = do
229                 l <- hGetLine hdl
230                 hPutStrLn tmp_hdl l
231                 slurp
232          
233         catchJust ioErrors slurp 
234                 (\e -> if isEOFError e then return () else ioError e)
235
236         hClose hdl
237
238   hClose tmp_hdl  -- make sure it's flushed
239
240         -- Create a backup of the original makefile
241   when (isJust makefile_hdl)
242        (SysTools.copy ("Backing up " ++ makefile) makefile (makefile++".bak"))
243
244         -- Copy the new makefile in place
245   SysTools.copy "Installing new makefile" tmp_file makefile
246
247
248 findDependency :: Bool -> FilePath -> ModuleName -> IO (Maybe (String, Bool))
249 findDependency is_source src imp = do
250    excl_mods <- readIORef v_Dep_exclude_mods
251    include_prelude <- readIORef v_Dep_include_prelude
252    let imp_mod = moduleNameUserString imp
253    if imp_mod `elem` excl_mods 
254       then return Nothing
255       else do
256         r <- findModule imp
257         case r of 
258            Right (mod,loc)
259                 -- not in this package: we don't need a dependency
260                 | not (isHomeModule mod) && not include_prelude
261                 -> return Nothing
262
263                 -- normal import: just depend on the .hi file
264                 | not is_source
265                 -> return (Just (ml_hi_file loc, not is_source))
266
267                 -- if it's a source import, we want to generate a dependency
268                 -- on the .hi-boot file, not the .hi file
269                 | otherwise
270                 -> let hi_file = ml_hi_file loc
271                        boot_hi_file = replaceFilenameSuffix hi_file hiBootExt 
272                        boot_ver_hi_file = replaceFilenameSuffix hi_file hiBootVerExt 
273                    in do
274                    b <- doesFileExist boot_ver_hi_file
275                    if b 
276                      then return (Just (boot_ver_hi_file, not is_source))
277                      else do
278                         b <- doesFileExist boot_hi_file
279                         if b 
280                            then return (Just (boot_hi_file, not is_source))
281                            else return (Just (hi_file, not is_source))
282
283            Left _ -> throwDyn (ProgramError 
284                 (src ++ ": " ++ "can't locate import `" ++ imp_mod ++ "'" ++
285                  if is_source then " (SOURCE import)" else ""))