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