f161d6408740d010dc1af72ba0666bd0df708e47
[ghc-hetmet.git] / ghc / compiler / main / DriverMkDepend.hs
1 -----------------------------------------------------------------------------
2 --
3 -- Makefile Dependency Generation
4 --
5 -- (c) The University of Glasgow 2005
6 --
7 -----------------------------------------------------------------------------
8
9 module DriverMkDepend (
10         doMkDependHS
11   ) where
12
13 #include "HsVersions.h"
14
15 import qualified GHC
16 import GHC              ( Session, ModSummary(..) )
17 import DynFlags         ( DynFlags( verbosity, opt_dep ), getOpts )
18 import Util             ( escapeSpaces, splitFilename, joinFileExt )
19 import HscTypes         ( HscEnv, IsBootInterface, msObjFilePath, msHsFilePath )
20 import Packages         ( PackageIdH(..) )
21 import SysTools         ( newTempName )
22 import qualified SysTools
23 import Module           ( Module, ModLocation(..), mkModule, moduleUserString,
24                           addBootSuffix_maybe )
25 import Digraph          ( SCC(..) )
26 import Finder           ( findModule, FindResult(..) )
27 import Util             ( global, consIORef )
28 import Outputable
29 import Panic
30 import SrcLoc           ( unLoc )
31 import CmdLineParser
32
33 import DATA_IOREF       ( IORef, readIORef, writeIORef )
34 import EXCEPTION
35
36 import Directory
37 import IO
38 import Monad            ( when )
39 import Maybe            ( isJust )
40
41 #if __GLASGOW_HASKELL__ <= 408
42 import Panic            ( catchJust, ioErrors )
43 #endif
44 import ErrUtils         ( debugTraceMsg )
45
46 -----------------------------------------------------------------
47 --
48 --              The main function
49 --
50 -----------------------------------------------------------------
51
52 doMkDependHS :: Session -> [FilePath] -> IO ()
53 doMkDependHS session srcs
54   = do  {       -- Initialisation
55           dflags <- GHC.getSessionDynFlags session
56         ; files <- beginMkDependHS dflags
57
58                 -- Do the downsweep to find all the modules
59         ; targets <- mapM (\s -> GHC.guessTarget s Nothing) srcs
60         ; GHC.setTargets session targets
61         ; excl_mods <- readIORef v_Dep_exclude_mods
62         ; GHC.depanal session excl_mods
63         ; mod_summaries <- GHC.getModuleGraph session
64
65                 -- Sort into dependency order
66                 -- There should be no cycles
67         ; let sorted = GHC.topSortModuleGraph False mod_summaries Nothing
68
69                 -- Print out the dependencies if wanted
70         ; debugTraceMsg dflags 2 (showSDoc (text "Module dependencies" $$ ppr sorted))
71                 
72                 -- Prcess them one by one, dumping results into makefile
73                 -- and complaining about cycles
74         ; mapM (processDeps session excl_mods (mkd_tmp_hdl files)) sorted
75
76                 -- Tidy up
77         ; endMkDependHS dflags files }
78
79 -----------------------------------------------------------------
80 --
81 --              beginMkDependHs
82 --      Create a temporary file, 
83 --      find the Makefile, 
84 --      slurp through it, etc
85 --
86 -----------------------------------------------------------------
87
88 data MkDepFiles 
89   = MkDep { mkd_make_file :: FilePath,          -- Name of the makefile
90             mkd_make_hdl  :: Maybe Handle,      -- Handle for the open makefile 
91             mkd_tmp_file  :: FilePath,          -- Name of the temporary file
92             mkd_tmp_hdl   :: Handle }           -- Handle of the open temporary file
93
94 beginMkDependHS :: DynFlags -> IO MkDepFiles
95         
96 beginMkDependHS dflags = do
97         -- slurp in the mkdependHS-style options
98   let flags = getOpts dflags opt_dep
99   _ <- processArgs dep_opts flags
100
101         -- open a new temp file in which to stuff the dependency info
102         -- as we go along.
103   tmp_file <- newTempName dflags "dep"
104   tmp_hdl <- openFile tmp_file WriteMode
105
106         -- open the makefile
107   makefile <- readIORef v_Dep_makefile
108   exists <- doesFileExist makefile
109   mb_make_hdl <- 
110         if not exists
111         then return Nothing
112         else do
113            makefile_hdl <- openFile makefile ReadMode
114
115                 -- slurp through until we get the magic start string,
116                 -- copying the contents into dep_makefile
117            let slurp = do
118                 l <- hGetLine makefile_hdl
119                 if (l == depStartMarker)
120                         then return ()
121                         else do hPutStrLn tmp_hdl l; slurp
122          
123                 -- slurp through until we get the magic end marker,
124                 -- throwing away the contents
125            let chuck = do
126                 l <- hGetLine makefile_hdl
127                 if (l == depEndMarker)
128                         then return ()
129                         else chuck
130          
131            catchJust ioErrors slurp 
132                 (\e -> if isEOFError e then return () else ioError e)
133            catchJust ioErrors chuck
134                 (\e -> if isEOFError e then return () else ioError e)
135
136            return (Just makefile_hdl)
137
138
139         -- write the magic marker into the tmp file
140   hPutStrLn tmp_hdl depStartMarker
141
142   return (MkDep { mkd_make_file = makefile, mkd_make_hdl = mb_make_hdl, 
143                   mkd_tmp_file  = tmp_file, mkd_tmp_hdl  = tmp_hdl})
144
145
146 -----------------------------------------------------------------
147 --
148 --              processDeps
149 --
150 -----------------------------------------------------------------
151
152 processDeps :: Session
153             -> [Module]
154             -> Handle           -- Write dependencies to here
155             -> SCC ModSummary
156             -> IO ()
157 -- Write suitable dependencies to handle
158 -- Always:
159 --                      this.o : this.hs
160 --
161 -- If the dependency is on something other than a .hi file:
162 --                      this.o this.p_o ... : dep
163 -- otherwise
164 --                      this.o ...   : dep.hi
165 --                      this.p_o ... : dep.p_hi
166 --                      ...
167 -- (where .o is $osuf, and the other suffixes come from
168 -- the cmdline -s options).
169 --
170 -- For {-# SOURCE #-} imports the "hi" will be "hi-boot".
171
172 processDeps session excl_mods hdl (CyclicSCC nodes)
173   =     -- There shouldn't be any cycles; report them   
174     throwDyn (ProgramError (showSDoc $ GHC.cyclicModuleErr nodes))
175
176 processDeps session excl_mods hdl (AcyclicSCC node)
177   = do  { extra_suffixes   <- readIORef v_Dep_suffixes
178         ; hsc_env <- GHC.sessionHscEnv session
179         ; include_pkg_deps <- readIORef v_Dep_include_pkg_deps
180         ; let src_file  = msHsFilePath node
181               obj_file  = msObjFilePath node
182               obj_files = insertSuffixes obj_file extra_suffixes
183
184               do_imp is_boot imp_mod
185                 = do { mb_hi <- findDependency hsc_env src_file imp_mod 
186                                                is_boot include_pkg_deps
187                      ; case mb_hi of {
188                            Nothing      -> return () ;
189                            Just hi_file -> do
190                      { let hi_files = insertSuffixes hi_file extra_suffixes
191                            write_dep (obj,hi) = writeDependency hdl [obj] hi
192
193                         -- Add one dependency for each suffix; 
194                         -- e.g.         A.o   : B.hi
195                         --              A.x_o : B.x_hi
196                      ; mapM_ write_dep (obj_files `zip` hi_files) }}}
197
198              
199                 -- Emit std dependency of the object(s) on the source file
200                 -- Something like       A.o : A.hs
201         ; writeDependency hdl obj_files src_file
202
203                 -- Emit a dependency for each import
204
205         -- SOURCE imports
206         ; mapM_ (do_imp True)  
207                 (filter (`notElem` excl_mods) (map unLoc (ms_srcimps node)))
208
209         -- regular imports
210         ; mapM_ (do_imp False)
211                 (filter (`notElem` excl_mods) (map unLoc (ms_imps node)))
212         }
213
214
215 findDependency  :: HscEnv
216                 -> FilePath             -- Importing module: used only for error msg
217                 -> Module               -- Imported module
218                 -> IsBootInterface      -- Source import
219                 -> Bool                 -- Record dependency on package modules
220                 -> IO (Maybe FilePath)  -- Interface file file
221 findDependency hsc_env src imp is_boot include_pkg_deps
222   = do  {       -- Find the module; this will be fast because
223                 -- we've done it once during downsweep
224           r <- findModule hsc_env imp True {-explicit-}
225         ; case r of 
226             Found loc pkg
227                 -- Not in this package: we don't need a dependency
228                 | ExtPackage _ <- pkg, not include_pkg_deps
229                 -> return Nothing
230
231                 -- Home package: just depend on the .hi or hi-boot file
232                 | otherwise
233                 -> return (Just (addBootSuffix_maybe is_boot (ml_hi_file loc)))
234
235             _ -> panic "findDependency"
236         }
237
238 -----------------------------
239 writeDependency :: Handle -> [FilePath] -> FilePath -> IO ()
240 -- (writeDependency h [t1,t2] dep) writes to handle h the dependency
241 --      t1 t2 : dep
242 writeDependency hdl targets dep
243   = hPutStrLn hdl (unwords (map escapeSpaces targets) ++ " : "
244                    ++ escapeSpaces dep)
245
246 -----------------------------
247 insertSuffixes  
248         :: FilePath     -- Original filename;   e.g. "foo.o"
249         -> [String]     -- Extra suffices       e.g. ["x","y"]
250         -> [FilePath]   -- Zapped filenames     e.g. ["foo.o", "foo.x_o", "foo.y_o"]
251         -- Note that that the extra bit gets inserted *before* the old suffix
252         -- We assume the old suffix contains no dots, so we can strip it with removeSuffix
253
254         -- NOTE: we used to have this comment
255                 -- In order to construct hi files with alternate suffixes, we
256                 -- now have to find the "basename" of the hi file.  This is
257                 -- difficult because we can't just split the hi filename
258                 -- at the last dot - the hisuf might have dots in it.  So we
259                 -- check whether the hi filename ends in hisuf, and if it does,
260                 -- we strip off hisuf, otherwise we strip everything after the
261                 -- last dot.
262         -- But I'm not sure we care about hisufs with dots in them. 
263         -- Lots of other things will break first!
264
265 insertSuffixes file_name extras
266   = file_name : [ basename `joinFileExt` (extra ++ "_" ++ suffix) | extra <- extras ]
267   where
268     (basename, suffix) = splitFilename file_name
269
270
271 -----------------------------------------------------------------
272 --
273 --              endMkDependHs
274 --      Complete the makefile, close the tmp file etc
275 --
276 -----------------------------------------------------------------
277
278 endMkDependHS :: DynFlags -> MkDepFiles -> IO ()
279
280 endMkDependHS dflags 
281    (MkDep { mkd_make_file = makefile, mkd_make_hdl =  makefile_hdl,
282             mkd_tmp_file  = tmp_file, mkd_tmp_hdl  =  tmp_hdl }) 
283   = do
284   -- write the magic marker into the tmp file
285   hPutStrLn tmp_hdl depEndMarker
286
287   case makefile_hdl of
288      Nothing  -> return ()
289      Just hdl -> do
290
291           -- slurp the rest of the original makefile and copy it into the output
292         let slurp = do
293                 l <- hGetLine hdl
294                 hPutStrLn tmp_hdl l
295                 slurp
296          
297         catchJust ioErrors slurp 
298                 (\e -> if isEOFError e then return () else ioError e)
299
300         hClose hdl
301
302   hClose tmp_hdl  -- make sure it's flushed
303
304         -- Create a backup of the original makefile
305   when (isJust makefile_hdl)
306        (SysTools.copy dflags ("Backing up " ++ makefile) 
307           makefile (makefile++".bak"))
308
309         -- Copy the new makefile in place
310   SysTools.copy dflags "Installing new makefile" tmp_file makefile
311
312
313 -----------------------------------------------------------------
314 --
315 --              Flags
316 --
317 -----------------------------------------------------------------
318
319         -- Flags
320 GLOBAL_VAR(v_Dep_makefile,              "Makefile", String);
321 GLOBAL_VAR(v_Dep_include_pkg_deps,      False, Bool);
322 GLOBAL_VAR(v_Dep_exclude_mods,          [], [Module]);
323 GLOBAL_VAR(v_Dep_suffixes,              [], [String]);
324 GLOBAL_VAR(v_Dep_warnings,              True, Bool);
325
326 depStartMarker = "# DO NOT DELETE: Beginning of Haskell dependencies"
327 depEndMarker   = "# DO NOT DELETE: End of Haskell dependencies"
328
329 -- for compatibility with the old mkDependHS, we accept options of the form
330 -- -optdep-f -optdep.depend, etc.
331 dep_opts = 
332    [ (  "s",                    SepArg (consIORef v_Dep_suffixes) )
333    , (  "f",                    SepArg (writeIORef v_Dep_makefile) )
334    , (  "w",                    NoArg (writeIORef v_Dep_warnings False) )
335    , (  "-include-prelude",     NoArg (writeIORef v_Dep_include_pkg_deps True) )
336    , (  "-include-pkg-deps",    NoArg (writeIORef v_Dep_include_pkg_deps True) )
337    , (  "-exclude-module=",     Prefix (consIORef v_Dep_exclude_mods . mkModule) )
338    , (  "x",                    Prefix (consIORef v_Dep_exclude_mods . mkModule) )
339    ]