[project @ 2004-11-26 16:19:45 by simonmar]
[ghc-hetmet.git] / ghc / compiler / main / DriverMkDepend.hs
index 5a2f629..dda568f 100644 (file)
@@ -1,5 +1,5 @@
 -----------------------------------------------------------------------------
--- $Id: DriverMkDepend.hs,v 1.17 2002/02/05 14:42:08 simonpj Exp $
+-- $Id: DriverMkDepend.hs,v 1.34 2004/11/26 16:20:52 simonmar Exp $
 --
 -- GHC Driver
 --
@@ -7,29 +7,37 @@
 --
 -----------------------------------------------------------------------------
 
-module DriverMkDepend where
+module DriverMkDepend (
+       doMkDependHSPhase, beginMkDependHS, endMkDependHS
+  ) where
 
 #include "HsVersions.h"
 
-import DriverState
+import HscTypes                ( IfacePackage(..) )
+import GetImports      ( getImports )
+import CmdLineOpts     ( DynFlags )
+import DriverState      
 import DriverUtil
 import DriverFlags
 import SysTools                ( newTempName )
 import qualified SysTools
-import Module
-import Module          ( isHomeModule )
-import Finder          ( findModuleDep )
-import HscTypes                ( ModuleLocation(..) )
-import Util
+import Module          ( Module, ModLocation(..), moduleUserString)
+import Finder          ( findModule, hiBootExt, hiBootVerExt,
+                         mkHomeModLocation, FindResult(..) )
+import Util             ( global, maybePrefixMatch )
 import Panic
 
-import IOExts
-import Exception
+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
@@ -37,7 +45,7 @@ import Maybe
        -- flags
 GLOBAL_VAR(v_Dep_makefile,             "Makefile", String);
 GLOBAL_VAR(v_Dep_include_prelude,      False, Bool);
-GLOBAL_VAR(v_Dep_exclude_mods,          [], [String]);
+GLOBAL_VAR(v_Dep_exclude_mods,          ["GHC.Prim"], [String]);
 GLOBAL_VAR(v_Dep_suffixes,             [], [String]);
 GLOBAL_VAR(v_Dep_warnings,             True, Bool);
 
@@ -45,7 +53,6 @@ GLOBAL_VAR(v_Dep_warnings,            True, Bool);
 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"
@@ -112,21 +119,89 @@ beginMkDependHS = do
        -- write the magic marker into the tmp file
   hPutStrLn tmp_hdl depStartMarker
 
-       -- cache the contents of all the import directories, for future
-       -- reference.
-  import_dirs <- readIORef v_Import_paths
-  pkg_import_dirs <- getPackageImportPath
-  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)
-
   return ()
 
 
-endMkDependHS :: IO ()
-endMkDependHS = do
+doMkDependHSPhase dflags 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 dflags True  orig_fn) import_sources
+      deps_normals <- mapM (findDependency dflags 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 
+               -- 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 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 :: DynFlags -> IO ()
+endMkDependHS dflags = do
   makefile     <- readIORef v_Dep_makefile
   makefile_hdl <- readIORef v_Dep_makefile_hdl
   tmp_file     <- readIORef v_Dep_tmp_file
@@ -154,26 +229,48 @@ endMkDependHS = do
 
        -- Create a backup of the original makefile
   when (isJust makefile_hdl)
-       (SysTools.copy ("Backing up " ++ makefile) makefile (makefile++".bak"))
+       (SysTools.copy dflags ("Backing up " ++ makefile) 
+               makefile (makefile++".bak"))
 
        -- Copy the new makefile in place
-  SysTools.copy "Installing new makefile" tmp_file makefile
+  SysTools.copy dflags "Installing new makefile" tmp_file makefile
 
 
-findDependency :: Bool -> FilePath -> ModuleName -> IO (Maybe (String, Bool))
-findDependency is_source src imp = do
+findDependency :: DynFlags -> Bool -> FilePath -> Module -> IO (Maybe (String, Bool))
+findDependency dflags is_source src imp = do
    excl_mods <- readIORef v_Dep_exclude_mods
    include_prelude <- readIORef v_Dep_include_prelude
-   let imp_mod = moduleNameUserString imp
+   let imp_mod = moduleUserString imp
    if imp_mod `elem` excl_mods 
       then return Nothing
       else do
-       r <- findModuleDep imp is_source
+       r <- findModule dflags imp True{-explicit-}
        case r of 
-          Just (mod,loc)
-               | isHomeModule mod || include_prelude
-               -> return (Just (ml_hi_file loc, not is_source))
-               | otherwise 
+          Found loc pkg
+               -- not in this package: we don't need a dependency
+               | ExternalPackage _ <- pkg, not include_prelude
                -> return Nothing
-          Nothing -> throwDyn (ProgramError 
-               (src ++ ": " ++ "can't locate import `" ++ imp_mod ++ "'"))
+
+               -- 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))
+
+          _ -> throwDyn (ProgramError 
+               (src ++ ": " ++ "can't locate import `" ++ imp_mod ++ "'" ++
+                if is_source then " (SOURCE import)" else ""))