X-Git-Url: http://git.megacz.com/?a=blobdiff_plain;f=ghc%2Fcompiler%2Fmain%2FDriverMkDepend.hs;h=f01faf31c6c3bc61753c9591ad585651074c501a;hb=2d532e45924dfdb5b5157caf4d3fc3541497d86c;hp=2f455065d077a3b64ecbd9183d7132f7dcc86e15;hpb=dbb27b50948726c09fae681bca921ba3c00d859b;p=ghc-hetmet.git diff --git a/ghc/compiler/main/DriverMkDepend.hs b/ghc/compiler/main/DriverMkDepend.hs index 2f45506..f01faf3 100644 --- a/ghc/compiler/main/DriverMkDepend.hs +++ b/ghc/compiler/main/DriverMkDepend.hs @@ -1,5 +1,5 @@ ----------------------------------------------------------------------------- --- $Id: DriverMkDepend.hs,v 1.2 2000/10/17 13:22:10 simonmar Exp $ +-- $Id: DriverMkDepend.hs,v 1.30 2003/07/18 13:18:07 simonmar Exp $ -- -- GHC Driver -- @@ -11,78 +11,86 @@ module DriverMkDepend where #include "HsVersions.h" -import CmSummarise -- for mkdependHS stuff -import DriverState +import GetImports ( getImports ) +import DriverState import DriverUtil import DriverFlags -import TmpFiles -import Module -import Config -import Util - -import IOExts -import Exception +import SysTools ( newTempName ) +import qualified SysTools +import Module ( ModuleName, ModLocation(..), + moduleNameUserString, isHomeModule ) +import Finder ( findModule, hiBootExt, hiBootVerExt, + mkHomeModLocation ) +import Util ( global ) +import Panic + +import DATA_IOREF ( IORef, readIORef, writeIORef ) +import EXCEPTION import Directory import IO -import Monad -import Maybe +import Monad ( when ) +import Maybe ( isJust ) + +#if __GLASGOW_HASKELL__ <= 408 +import Panic ( catchJust, ioErrors ) +#endif ------------------------------------------------------------------------------- -- mkdependHS -- flags -GLOBAL_VAR(dep_makefile, "Makefile", String); -GLOBAL_VAR(dep_include_prelude, False, Bool); -GLOBAL_VAR(dep_ignore_dirs, [], [String]); -GLOBAL_VAR(dep_suffixes, [], [String]); -GLOBAL_VAR(dep_warnings, True, Bool); +GLOBAL_VAR(v_Dep_makefile, "Makefile", String); +GLOBAL_VAR(v_Dep_include_prelude, False, Bool); +GLOBAL_VAR(v_Dep_exclude_mods, ["GHC.Prim"], [String]); +GLOBAL_VAR(v_Dep_suffixes, [], [String]); +GLOBAL_VAR(v_Dep_warnings, True, Bool); -- global vars -GLOBAL_VAR(dep_makefile_hdl, error "dep_makefile_hdl", Maybe Handle); -GLOBAL_VAR(dep_tmp_file, error "dep_tmp_file", String); -GLOBAL_VAR(dep_tmp_hdl, error "dep_tmp_hdl", Handle); -GLOBAL_VAR(dep_dir_contents, error "dep_dir_contents", [(String,[String])]); +GLOBAL_VAR(v_Dep_makefile_hdl, error "dep_makefile_hdl", Maybe Handle); +GLOBAL_VAR(v_Dep_tmp_file, error "dep_tmp_file", String); +GLOBAL_VAR(v_Dep_tmp_hdl, error "dep_tmp_hdl", Handle); +GLOBAL_VAR(v_Dep_dir_contents, error "dep_dir_contents", [(String,[String])]); depStartMarker = "# DO NOT DELETE: Beginning of Haskell dependencies" depEndMarker = "# DO NOT DELETE: End of Haskell dependencies" -- for compatibility with the old mkDependHS, we accept options of the form -- -optdep-f -optdep.depend, etc. -dep_opts = [ - ( "s", SepArg (add dep_suffixes) ), - ( "f", SepArg (writeIORef dep_makefile) ), - ( "w", NoArg (writeIORef dep_warnings False) ), - ( "-include-prelude", NoArg (writeIORef dep_include_prelude True) ), - ( "X", Prefix (addToDirList dep_ignore_dirs) ), - ( "-exclude-directory=", Prefix (addToDirList dep_ignore_dirs) ) - ] +dep_opts = + [ ( "s", SepArg (add v_Dep_suffixes) ) + , ( "f", SepArg (writeIORef v_Dep_makefile) ) + , ( "w", NoArg (writeIORef v_Dep_warnings False) ) + , ( "-include-prelude", NoArg (writeIORef v_Dep_include_prelude True) ) + , ( "-exclude-module=", Prefix (add v_Dep_exclude_mods) ) + , ( "x", Prefix (add v_Dep_exclude_mods) ) + ] beginMkDependHS :: IO () beginMkDependHS = do -- slurp in the mkdependHS-style options - flags <- getStaticOpts opt_dep + flags <- getStaticOpts v_Opt_dep _ <- processArgs dep_opts flags [] -- open a new temp file in which to stuff the dependency info -- as we go along. dep_file <- newTempName "dep" - writeIORef dep_tmp_file dep_file + writeIORef v_Dep_tmp_file dep_file tmp_hdl <- openFile dep_file WriteMode - writeIORef dep_tmp_hdl tmp_hdl + writeIORef v_Dep_tmp_hdl tmp_hdl -- open the makefile - makefile <- readIORef dep_makefile + makefile <- readIORef v_Dep_makefile exists <- doesFileExist makefile if not exists then do - writeIORef dep_makefile_hdl Nothing + writeIORef v_Dep_makefile_hdl Nothing return () else do makefile_hdl <- openFile makefile ReadMode - writeIORef dep_makefile_hdl (Just makefile_hdl) + writeIORef v_Dep_makefile_hdl (Just makefile_hdl) -- slurp through until we get the magic start string, -- copying the contents into dep_makefile @@ -111,28 +119,85 @@ beginMkDependHS = do -- cache the contents of all the import directories, for future -- reference. - import_dirs <- readIORef import_paths + import_dirs <- readIORef v_Import_paths pkg_import_dirs <- getPackageImportPath - import_dir_contents <- mapM getDirectoryContents import_dirs - pkg_import_dir_contents <- mapM getDirectoryContents pkg_import_dirs - writeIORef dep_dir_contents + import_dir_contents <- mapM softGetDirectoryContents import_dirs + pkg_import_dir_contents <- mapM softGetDirectoryContents pkg_import_dirs + writeIORef v_Dep_dir_contents (zip import_dirs import_dir_contents ++ zip pkg_import_dirs pkg_import_dir_contents) - -- ignore packages unless --include-prelude is on - include_prelude <- readIORef dep_include_prelude - when (not include_prelude) $ - mapM_ (add dep_ignore_dirs) pkg_import_dirs - 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 dep_makefile - makefile_hdl <- readIORef dep_makefile_hdl - tmp_file <- readIORef dep_tmp_file - tmp_hdl <- readIORef dep_tmp_hdl + makefile <- readIORef v_Dep_makefile + makefile_hdl <- readIORef v_Dep_makefile_hdl + tmp_file <- readIORef v_Dep_tmp_file + tmp_hdl <- readIORef v_Dep_tmp_hdl -- write the magic marker into the tmp file hPutStrLn tmp_hdl depEndMarker @@ -141,7 +206,7 @@ endMkDependHS = do Nothing -> return () Just hdl -> do - -- slurp the rest of the orignal makefile and copy it into the output + -- slurp the rest of the original makefile and copy it into the output let slurp = do l <- hGetLine hdl hPutStrLn tmp_hdl l @@ -154,54 +219,49 @@ endMkDependHS = do hClose tmp_hdl -- make sure it's flushed - -- create a backup of the original makefile - when (isJust makefile_hdl) $ - run_something ("Backing up " ++ makefile) - (unwords [ "cp", makefile, makefile++".bak" ]) - - -- copy the new makefile in place - run_something "Installing new makefile" - (unwords [ "cp", tmp_file, makefile ]) - - -findDependency :: String -> ModImport -> IO (Maybe (String, Bool)) -findDependency mod imp = do - dir_contents <- readIORef dep_dir_contents - ignore_dirs <- readIORef dep_ignore_dirs - hisuf <- readIORef hi_suf - - let - (imp_mod, is_source) = - case imp of - MINormal str -> (moduleNameString str, False) - MISource str -> (moduleNameString str, True ) - - imp_hi = imp_mod ++ '.':hisuf - imp_hiboot = imp_mod ++ ".hi-boot" - imp_hiboot_v = imp_mod ++ ".hi-boot-" ++ cHscIfaceFileVersion - imp_hs = imp_mod ++ ".hs" - imp_lhs = imp_mod ++ ".lhs" - - deps | is_source = [ imp_hiboot_v, imp_hiboot, imp_hs, imp_lhs ] - | otherwise = [ imp_hi, imp_hs, imp_lhs ] - - search [] = throwDyn (OtherError ("can't find one of the following: " ++ - unwords (map (\d -> '`': d ++ "'") deps) ++ - " (imported from `" ++ mod ++ "')")) - search ((dir, contents) : dirs) - | null present = search dirs - | otherwise = - if dir `elem` ignore_dirs - then return Nothing - else if is_source - then if dep /= imp_hiboot_v - then return (Just (dir++'/':imp_hiboot, False)) - else return (Just (dir++'/':dep, False)) - else return (Just (dir++'/':imp_hi, not is_source)) - where - present = filter (`elem` contents) deps - dep = head present - - -- in - search dir_contents - + -- Create a backup of the original makefile + when (isJust makefile_hdl) + (SysTools.copy ("Backing up " ++ makefile) makefile (makefile++".bak")) + + -- Copy the new makefile in place + SysTools.copy "Installing new makefile" tmp_file makefile + + +findDependency :: Bool -> FilePath -> ModuleName -> IO (Maybe (String, Bool)) +findDependency is_source src imp = do + excl_mods <- readIORef v_Dep_exclude_mods + include_prelude <- readIORef v_Dep_include_prelude + let imp_mod = moduleNameUserString imp + if imp_mod `elem` excl_mods + then return Nothing + else do + r <- findModule imp + case r of + Right (mod,loc) + -- not in this package: we don't need a dependency + | not (isHomeModule mod) && not include_prelude + -> return Nothing + + -- normal import: just depend on the .hi file + | not is_source + -> return (Just (ml_hi_file loc, not is_source)) + + -- if it's a source import, we want to generate a dependency + -- on the .hi-boot file, not the .hi file + | otherwise + -> let hi_file = ml_hi_file loc + boot_hi_file = replaceFilenameSuffix hi_file hiBootExt + boot_ver_hi_file = replaceFilenameSuffix hi_file hiBootVerExt + in do + b <- doesFileExist boot_ver_hi_file + if b + then return (Just (boot_ver_hi_file, not is_source)) + else do + b <- doesFileExist boot_hi_file + if b + then return (Just (boot_hi_file, not is_source)) + else return (Just (hi_file, not is_source)) + + Left _ -> throwDyn (ProgramError + (src ++ ": " ++ "can't locate import `" ++ imp_mod ++ "'" ++ + if is_source then " (SOURCE import)" else ""))