X-Git-Url: http://git.megacz.com/?p=ghc-hetmet.git;a=blobdiff_plain;f=compiler%2Fmain%2FDriverMkDepend.hs;h=1694aba9b87577cca5778647948d7582a861d4e2;hp=7451cef95e552866ffc0803600439c9313eb8d42;hb=d0faaa6fa0cecd23c5670fd199e9206275313666;hpb=87a00632efef6891ea67e095fd6d3490a274d83c diff --git a/compiler/main/DriverMkDepend.hs b/compiler/main/DriverMkDepend.hs index 7451cef..1694aba 100644 --- a/compiler/main/DriverMkDepend.hs +++ b/compiler/main/DriverMkDepend.hs @@ -16,9 +16,8 @@ module DriverMkDepend ( #include "HsVersions.h" import qualified GHC -import GHC ( ModSummary(..), GhcMonad ) +import GhcMonad import HsSyn ( ImportDecl(..) ) -import PrelNames import DynFlags import Util import HscTypes @@ -35,7 +34,6 @@ import FastString import Exception import ErrUtils -import MonadUtils ( liftIO ) import System.Directory import System.FilePath @@ -72,7 +70,8 @@ doMkDependHS srcs = do -- Prcess them one by one, dumping results into makefile -- and complaining about cycles hsc_env <- getSession - mapM (liftIO . processDeps dflags hsc_env excl_mods (mkd_tmp_hdl files)) sorted + root <- liftIO getCurrentDirectory + mapM_ (liftIO . processDeps dflags hsc_env excl_mods root (mkd_tmp_hdl files)) sorted -- If -ddump-mod-cycles, show cycles in the module graph liftIO $ dumpModCycles dflags mod_summaries @@ -158,6 +157,7 @@ beginMkDependHS dflags = do processDeps :: DynFlags -> HscEnv -> [ModuleName] + -> FilePath -> Handle -- Write dependencies to here -> SCC ModSummary -> IO () @@ -176,11 +176,11 @@ processDeps :: DynFlags -- -- For {-# SOURCE #-} imports the "hi" will be "hi-boot". -processDeps _ _ _ _ (CyclicSCC nodes) +processDeps _ _ _ _ _ (CyclicSCC nodes) = -- There shouldn't be any cycles; report them ghcError (ProgramError (showSDoc $ GHC.cyclicModuleErr nodes)) -processDeps dflags hsc_env excl_mods hdl (AcyclicSCC node) +processDeps dflags hsc_env excl_mods root hdl (AcyclicSCC node) = do { let extra_suffixes = depSuffixes dflags include_pkg_deps = depIncludePkgDeps dflags src_file = msHsFilePath node @@ -194,7 +194,7 @@ processDeps dflags hsc_env excl_mods hdl (AcyclicSCC node) Nothing -> return () ; Just hi_file -> do { let hi_files = insertSuffixes hi_file extra_suffixes - write_dep (obj,hi) = writeDependency hdl [obj] hi + write_dep (obj,hi) = writeDependency root hdl [obj] hi -- Add one dependency for each suffix; -- e.g. A.o : B.hi @@ -204,7 +204,7 @@ processDeps dflags hsc_env excl_mods hdl (AcyclicSCC node) -- Emit std dependency of the object(s) on the source file -- Something like A.o : A.hs - ; writeDependency hdl obj_files src_file + ; writeDependency root hdl obj_files src_file -- Emit a dependency for each import @@ -216,9 +216,6 @@ processDeps dflags hsc_env excl_mods hdl (AcyclicSCC node) ; do_imps True (ms_srcimps node) ; do_imps False (ms_imps node) - - ; when (dopt Opt_ImplicitPrelude (ms_hspp_opts node)) $ - do_imp noSrcSpan False Nothing pRELUDE_NAME } @@ -248,12 +245,18 @@ findDependency hsc_env srcloc pkg imp is_boot include_pkg_deps } ----------------------------- -writeDependency :: Handle -> [FilePath] -> FilePath -> IO () --- (writeDependency h [t1,t2] dep) writes to handle h the dependency +writeDependency :: FilePath -> Handle -> [FilePath] -> FilePath -> IO () +-- (writeDependency r h [t1,t2] dep) writes to handle h the dependency -- t1 t2 : dep -writeDependency hdl targets dep - = hPutStrLn hdl (unwords (map forOutput targets) ++ " : " ++ forOutput dep) - where forOutput = escapeSpaces . reslash Forwards . normalise +writeDependency root hdl targets dep + = do let -- We need to avoid making deps on + -- c:/foo/... + -- on cygwin as make gets confused by the : + -- Making relative deps avoids some instances of this. + dep' = makeRelative root dep + forOutput = escapeSpaces . reslash Forwards . normalise + output = unwords (map forOutput targets) ++ " : " ++ forOutput dep' + hPutStrLn hdl output ----------------------------- insertSuffixes @@ -344,7 +347,7 @@ dumpModCycles dflags mod_summaries cycles = [ c | CyclicSCC c <- GHC.topSortModuleGraph True mod_summaries Nothing ] pp_cycles = vcat [ (ptext (sLit "---------- Cycle") <+> int n <+> ptext (sLit "----------")) - $$ pprCycle c $$ text "" + $$ pprCycle c $$ blankLine | (n,c) <- [1..] `zip` cycles ] pprCycle :: [ModSummary] -> SDoc