[project @ 2004-11-12 13:35:55 by simonpj]
[ghc-hetmet.git] / ghc / compiler / main / DriverMkDepend.hs
index 769d9a2..b376102 100644 (file)
@@ -1,5 +1,5 @@
 -----------------------------------------------------------------------------
--- $Id: DriverMkDepend.hs,v 1.28 2003/06/04 15:47:58 simonmar Exp $
+-- $Id: DriverMkDepend.hs,v 1.33 2004/09/30 10:37:10 simonpj Exp $
 --
 -- GHC Driver
 --
@@ -7,7 +7,9 @@
 --
 -----------------------------------------------------------------------------
 
-module DriverMkDepend where
+module DriverMkDepend (
+       doMkDependHSPhase, beginMkDependHS, endMkDependHS
+  ) where
 
 #include "HsVersions.h"
 
@@ -19,8 +21,9 @@ import SysTools               ( newTempName )
 import qualified SysTools
 import Module          ( ModuleName, ModLocation(..),
                          moduleNameUserString, isHomeModule )
-import Finder          ( findModule, hiBootExt, hiBootVerExt )
-import Util             ( global )
+import Finder          ( findModule, hiBootExt, hiBootVerExt,
+                         mkHomeModLocation )
+import Util             ( global, maybePrefixMatch )
 import Panic
 
 import DATA_IOREF      ( IORef, readIORef, writeIORef )
@@ -131,19 +134,24 @@ beginMkDependHS = do
 
 doMkDependHSPhase basename suff input_fn
  = do src <- readFile input_fn
-      let (import_sources, import_normals, _) = getImports src
+      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 = osuf : map (++ ('_':osuf)) extra_suffixes
-          ofiles = map (\suf -> basename ++ '.':suf) suffixes
-
-      objs <- mapM odir_ify ofiles
+      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
@@ -157,14 +165,30 @@ doMkDependHSPhase basename suff input_fn
                            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
+            let 
+               -- In order to construct hi files with alternate suffixes, we
+               -- now have to find the "basename" of the hi file.  This is
+               -- difficult because we can't just split the hi filename
+               -- at the last dot - the hisuf might have dots in it.  So we
+               -- check whether the hi filename ends in hisuf, and if it does,
+               -- we strip off hisuf, otherwise we strip everything after the
+               -- last dot.
+               dep_base 
+                  | Just rest <- maybePrefixMatch rev_hisuf rev_dep
+                  = reverse rest
+                  | otherwise
+                  = remove_suffix '.' dep
+                 where
+                       rev_hisuf = reverse hisuf
+                       rev_dep   = reverse dep
+
+               deps = dep : 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
+      return location
 
 -- add the lines to dep_makefile:
           -- always: