[project @ 2003-06-04 15:47:58 by simonmar]
[ghc-hetmet.git] / ghc / compiler / main / DriverMkDepend.hs
index 607ba78..769d9a2 100644 (file)
@@ -1,5 +1,5 @@
 -----------------------------------------------------------------------------
--- $Id: DriverMkDepend.hs,v 1.23 2002/09/18 10:51:01 simonmar Exp $
+-- $Id: DriverMkDepend.hs,v 1.28 2003/06/04 15:47:58 simonmar Exp $
 --
 -- GHC Driver
 --
@@ -11,18 +11,19 @@ module DriverMkDepend where
 
 #include "HsVersions.h"
 
+import GetImports      ( getImports )
 import DriverState      
-import DriverUtil       ( add, softGetDirectoryContents )
+import DriverUtil
 import DriverFlags
 import SysTools                ( newTempName )
 import qualified SysTools
 import Module          ( ModuleName, ModLocation(..),
                          moduleNameUserString, isHomeModule )
-import Finder          ( findModuleDep )
+import Finder          ( findModule, hiBootExt, hiBootVerExt )
 import Util             ( global )
 import Panic
 
-import DATA_IOREF      ( IORef, newIORef, readIORef, writeIORef )
+import DATA_IOREF      ( IORef, readIORef, writeIORef )
 import EXCEPTION
 
 import Directory
@@ -128,6 +129,63 @@ beginMkDependHS = do
   return ()
 
 
+doMkDependHSPhase basename suff input_fn
+ = do src <- readFile input_fn
+      let (import_sources, import_normals, _) = getImports src
+      let orig_fn = basename ++ '.':suff
+      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 = osuf : map (++ ('_':osuf)) extra_suffixes
+          ofiles = map (\suf -> basename ++ '.':suf) suffixes
+
+      objs <- mapM odir_ify ofiles
+
+       -- 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 True
+
+-- 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
@@ -171,13 +229,33 @@ findDependency is_source src imp = do
    if imp_mod `elem` excl_mods 
       then return Nothing
       else do
-       r <- findModuleDep imp is_source
+       r <- findModule imp
        case r of 
-          Just (mod,loc)
-               | isHomeModule mod || include_prelude
+          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
-               -> return Nothing
-          Nothing -> throwDyn (ProgramError 
+               -> 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 ""))