X-Git-Url: http://git.megacz.com/?a=blobdiff_plain;f=ghc%2Fcompiler%2Fmain%2FDriverMkDepend.hs;h=f01faf31c6c3bc61753c9591ad585651074c501a;hb=5ec161b9994b21d94a1d494ea6a7e5c360075cd0;hp=bfe1a6a50fc086445475b274810b4514f957cf73;hpb=06575d67c6e85ee746d96c77dab9e40edfb4f7ee;p=ghc-hetmet.git diff --git a/ghc/compiler/main/DriverMkDepend.hs b/ghc/compiler/main/DriverMkDepend.hs index bfe1a6a..f01faf3 100644 --- a/ghc/compiler/main/DriverMkDepend.hs +++ b/ghc/compiler/main/DriverMkDepend.hs @@ -1,5 +1,5 @@ ----------------------------------------------------------------------------- --- $Id: DriverMkDepend.hs,v 1.25 2002/10/17 14:26:18 simonmar Exp $ +-- $Id: DriverMkDepend.hs,v 1.30 2003/07/18 13:18:07 simonmar Exp $ -- -- GHC Driver -- @@ -11,14 +11,16 @@ module DriverMkDepend where #include "HsVersions.h" +import GetImports ( getImports ) import DriverState -import DriverUtil ( add, softGetDirectoryContents, replaceFilenameSuffix ) +import DriverUtil import DriverFlags import SysTools ( newTempName ) import qualified SysTools import Module ( ModuleName, ModLocation(..), moduleNameUserString, isHomeModule ) -import Finder ( findModule, hiBootExt, hiBootVerExt ) +import Finder ( findModule, hiBootExt, hiBootVerExt, + mkHomeModLocation ) import Util ( global ) import Panic @@ -128,6 +130,68 @@ beginMkDependHS = do return () +doMkDependHSPhase basename suff input_fn + = do src <- readFile input_fn + let (import_sources, import_normals, mod_name) = getImports src + let orig_fn = basename ++ '.':suff + (_, location') <- mkHomeModLocation mod_name orig_fn + + -- take -ohi into account if present + ohi <- readIORef v_Output_hi + let location | Just fn <- ohi = location'{ ml_hi_file = fn } + | otherwise = location' + + deps_sources <- mapM (findDependency True orig_fn) import_sources + deps_normals <- mapM (findDependency False orig_fn) import_normals + let deps = deps_sources ++ deps_normals + + osuf <- readIORef v_Object_suf + extra_suffixes <- readIORef v_Dep_suffixes + let suffixes = map (++ ('_':osuf)) extra_suffixes + obj_file = ml_obj_file location + objs = obj_file : map (replaceFilenameSuffix obj_file) suffixes + + -- Handle for file that accumulates dependencies + hdl <- readIORef v_Dep_tmp_hdl + + -- std dependency of the object(s) on the source file + hPutStrLn hdl (unwords (map escapeSpaces objs) ++ " : " ++ + escapeSpaces (basename ++ '.':suff)) + + let genDep (dep, False {- not an hi file -}) = + hPutStrLn hdl (unwords (map escapeSpaces objs) ++ " : " ++ + escapeSpaces dep) + genDep (dep, True {- is an hi file -}) = do + hisuf <- readIORef v_Hi_suf + let dep_base = remove_suffix '.' dep + deps = (dep_base ++ hisuf) + : map (\suf -> dep_base ++ suf ++ '_':hisuf) extra_suffixes + -- length objs should be == length deps + sequence_ (zipWith (\o d -> hPutStrLn hdl (escapeSpaces o ++ " : " ++ escapeSpaces d)) objs deps) + + sequence_ (map genDep [ d | Just d <- deps ]) + return location + +-- add the lines to dep_makefile: + -- always: + -- this.o : this.hs + + -- if the dependency is on something other than a .hi file: + -- this.o this.p_o ... : dep + -- otherwise + -- if the import is {-# SOURCE #-} + -- this.o this.p_o ... : dep.hi-boot[-$vers] + + -- else + -- this.o ... : dep.hi + -- this.p_o ... : dep.p_hi + -- ... + + -- (where .o is $osuf, and the other suffixes come from + -- the cmdline -s options). + + + endMkDependHS :: IO () endMkDependHS = do makefile <- readIORef v_Dep_makefile @@ -173,7 +237,7 @@ findDependency is_source src imp = do else do r <- findModule imp case r of - Just (mod,loc) + Right (mod,loc) -- not in this package: we don't need a dependency | not (isHomeModule mod) && not include_prelude -> return Nothing @@ -189,15 +253,15 @@ findDependency is_source src imp = do boot_hi_file = replaceFilenameSuffix hi_file hiBootExt boot_ver_hi_file = replaceFilenameSuffix hi_file hiBootVerExt in do - b <- doesFileExist boot_hi_file + b <- doesFileExist boot_ver_hi_file if b - then return (Just (boot_hi_file, not is_source)) + then return (Just (boot_ver_hi_file, not is_source)) else do - b <- doesFileExist boot_ver_hi_file + b <- doesFileExist boot_hi_file if b - then return (Just (boot_ver_hi_file, not is_source)) + then return (Just (boot_hi_file, not is_source)) else return (Just (hi_file, not is_source)) - Nothing -> throwDyn (ProgramError + Left _ -> throwDyn (ProgramError (src ++ ": " ++ "can't locate import `" ++ imp_mod ++ "'" ++ if is_source then " (SOURCE import)" else ""))