[project @ 2001-06-26 16:30:50 by rrt]
[ghc-hetmet.git] / ghc / compiler / main / DriverMkDepend.hs
index e22a1da..e218044 100644 (file)
@@ -1,5 +1,5 @@
 -----------------------------------------------------------------------------
--- $Id: DriverMkDepend.hs,v 1.7 2000/12/12 14:35:08 simonmar Exp $
+-- $Id: DriverMkDepend.hs,v 1.13 2001/06/26 16:30:50 rrt Exp $
 --
 -- GHC Driver
 --
@@ -14,7 +14,8 @@ module DriverMkDepend where
 import DriverState
 import DriverUtil
 import DriverFlags
-import TmpFiles
+import SysTools                ( newTempName )
+import qualified SysTools
 import Module
 import Config
 import Util
@@ -35,6 +36,7 @@ import Maybe
 GLOBAL_VAR(v_Dep_makefile,             "Makefile", String);
 GLOBAL_VAR(v_Dep_include_prelude,      False, Bool);
 GLOBAL_VAR(v_Dep_ignore_dirs,          [], [String]);
+GLOBAL_VAR(v_Dep_exclude_mods,          [], [String]);
 GLOBAL_VAR(v_Dep_suffixes,             [], [String]);
 GLOBAL_VAR(v_Dep_warnings,             True, Bool);
 
@@ -56,6 +58,9 @@ dep_opts = [
    (  "-include-prelude",      NoArg (writeIORef v_Dep_include_prelude True) ),
    (  "X",                     Prefix (addToDirList v_Dep_ignore_dirs) ),
    (  "-exclude-directory=",   Prefix (addToDirList v_Dep_ignore_dirs) )
+--   (  "-exclude-module=",       Prefix (add v_Dep_exclude_mods) )
+--   (  "x",                      Prefix (add v_Dep_exclude_mods) )
+   
  ]
 
 beginMkDependHS :: IO ()
@@ -113,8 +118,8 @@ beginMkDependHS = do
        -- reference.
   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
+  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)
@@ -141,7 +146,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,21 +159,20 @@ endMkDependHS = do
 
   hClose tmp_hdl  -- make sure it's flushed
 
-       -- create a backup of the original makefile
-  when (isJust makefile_hdl) $
-     runSomething ("Backing up " ++ makefile)
-       (unwords [ "cp", makefile, makefile++".bak" ])
+       -- 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
-  runSomething "Installing new makefile"
-       (unwords [ "cp", tmp_file, makefile ])
+       -- Copy the new makefile in place
+  SysTools.copy "Installing new makefile" tmp_file makefile
 
 
-findDependency :: Bool -> String -> ModuleName -> IO (Maybe (String, Bool))
-findDependency is_source mod imp = do
+findDependency :: Bool -> FilePath -> ModuleName -> IO (Maybe (String, Bool))
+findDependency is_source src imp = do
    dir_contents <- readIORef v_Dep_dir_contents
    ignore_dirs  <- readIORef v_Dep_ignore_dirs
-   hisuf <- readIORef v_Hi_suf
+   excl_mods    <- readIORef v_Dep_exclude_mods
+   hisuf        <- readIORef v_Hi_suf
 
    let
      imp_mod      = moduleNameUserString imp
@@ -181,9 +185,8 @@ findDependency is_source mod imp = do
      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 [] = throwDyn (ProgramError (src ++ ": " ++ "can't find one of the following: " ++
+                                     unwords (map (\d -> '`': d ++ "'") deps)))
      search ((dir, contents) : dirs)
           | null present = search dirs
           | otherwise = 
@@ -199,5 +202,7 @@ findDependency is_source mod imp = do
                dep     = head present
  
    -- in
-   search dir_contents
-
+   if imp_mod `elem` excl_mods then
+      return Nothing
+    else
+      search dir_contents