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