module DriverMkDepend (
doMkDependHS
) where
#include "HsVersions.h"
import qualified GHC
import GhcMonad
import HsSyn ( ImportDecl(..) )
import DynFlags
import Util
import HscTypes
import SysTools ( newTempName )
import qualified SysTools
import Module
import Digraph ( SCC(..) )
import Finder
import Outputable
import Panic
import SrcLoc
import Data.List
import FastString
import Exception
import ErrUtils
import System.Directory
import System.FilePath
import System.IO
import System.IO.Error ( isEOFError )
import Control.Monad ( when )
import Data.Maybe ( isJust )
doMkDependHS :: GhcMonad m => [FilePath] -> m ()
doMkDependHS srcs = do
dflags0 <- GHC.getSessionDynFlags
let dflags = dflags0 {
ways = [],
buildTag = mkBuildTag [],
hiSuf = "hi",
objectSuf = "o"
}
_ <- GHC.setSessionDynFlags dflags
when (null (depSuffixes dflags)) $ liftIO $
throwGhcExceptionIO (ProgramError "You must specify at least one -dep-suffix")
files <- liftIO $ beginMkDependHS dflags
targets <- mapM (\s -> GHC.guessTarget s Nothing) srcs
GHC.setTargets targets
let excl_mods = depExcludeMods dflags
mod_summaries <- GHC.depanal excl_mods True
let sorted = GHC.topSortModuleGraph False mod_summaries Nothing
liftIO $ debugTraceMsg dflags 2 (text "Module dependencies" $$ ppr sorted)
hsc_env <- getSession
root <- liftIO getCurrentDirectory
mapM_ (liftIO . processDeps dflags hsc_env excl_mods root (mkd_tmp_hdl files)) sorted
liftIO $ dumpModCycles dflags mod_summaries
liftIO $ endMkDependHS dflags files
data MkDepFiles
= MkDep { mkd_make_file :: FilePath,
mkd_make_hdl :: Maybe Handle,
mkd_tmp_file :: FilePath,
mkd_tmp_hdl :: Handle }
beginMkDependHS :: DynFlags -> IO MkDepFiles
beginMkDependHS dflags = do
tmp_file <- newTempName dflags "dep"
tmp_hdl <- openFile tmp_file WriteMode
let makefile = depMakefile dflags
exists <- doesFileExist makefile
mb_make_hdl <-
if not exists
then return Nothing
else do
makefile_hdl <- openFile makefile ReadMode
let slurp = do
l <- hGetLine makefile_hdl
if (l == depStartMarker)
then return ()
else do hPutStrLn tmp_hdl l; slurp
let chuck = do
l <- hGetLine makefile_hdl
if (l == depEndMarker)
then return ()
else chuck
catchIO slurp
(\e -> if isEOFError e then return () else ioError e)
catchIO chuck
(\e -> if isEOFError e then return () else ioError e)
return (Just makefile_hdl)
hPutStrLn tmp_hdl depStartMarker
return (MkDep { mkd_make_file = makefile, mkd_make_hdl = mb_make_hdl,
mkd_tmp_file = tmp_file, mkd_tmp_hdl = tmp_hdl})
processDeps :: DynFlags
-> HscEnv
-> [ModuleName]
-> FilePath
-> Handle
-> SCC ModSummary
-> IO ()
processDeps dflags _ _ _ _ (CyclicSCC nodes)
=
throwGhcExceptionIO (ProgramError (showSDoc dflags $ GHC.cyclicModuleErr nodes))
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
obj_file = msObjFilePath node
obj_files = insertSuffixes obj_file extra_suffixes
do_imp loc is_boot pkg_qual imp_mod
= do { mb_hi <- findDependency hsc_env loc pkg_qual imp_mod
is_boot include_pkg_deps
; case mb_hi of {
Nothing -> return () ;
Just hi_file -> do
{ let hi_files = insertSuffixes hi_file extra_suffixes
write_dep (obj,hi) = writeDependency root hdl [obj] hi
; mapM_ write_dep (obj_files `zip` hi_files) }}}
; writeDependency root hdl obj_files src_file
; let do_imps is_boot idecls = sequence_
[ do_imp loc is_boot (ideclPkgQual i) mod
| L loc i <- idecls,
let mod = unLoc (ideclName i),
mod `notElem` excl_mods ]
; do_imps True (ms_srcimps node)
; do_imps False (ms_imps node)
}
findDependency :: HscEnv
-> SrcSpan
-> Maybe FastString
-> ModuleName
-> IsBootInterface
-> Bool
-> IO (Maybe FilePath)
findDependency hsc_env srcloc pkg imp is_boot include_pkg_deps
= do {
r <- findImportedModule hsc_env imp pkg
; case r of
Found loc _
| isJust (ml_hs_file loc) || include_pkg_deps
-> return (Just (addBootSuffix_maybe is_boot (ml_hi_file loc)))
| otherwise
-> return Nothing
fail ->
let dflags = hsc_dflags hsc_env
in throwOneError $ mkPlainErrMsg dflags srcloc $
cannotFindModule dflags imp fail
}
writeDependency :: FilePath -> Handle -> [FilePath] -> FilePath -> IO ()
writeDependency root hdl targets dep
= do let
dep' = makeRelative root dep
forOutput = escapeSpaces . reslash Forwards . normalise
output = unwords (map forOutput targets) ++ " : " ++ forOutput dep'
hPutStrLn hdl output
insertSuffixes
:: FilePath
-> [String]
-> [FilePath]
insertSuffixes file_name extras
= [ basename <.> (extra ++ suffix) | extra <- extras ]
where
(basename, suffix) = case splitExtension file_name of
(b, s) -> (b, drop 1 s)
endMkDependHS :: DynFlags -> MkDepFiles -> IO ()
endMkDependHS dflags
(MkDep { mkd_make_file = makefile, mkd_make_hdl = makefile_hdl,
mkd_tmp_file = tmp_file, mkd_tmp_hdl = tmp_hdl })
= do
hPutStrLn tmp_hdl depEndMarker
case makefile_hdl of
Nothing -> return ()
Just hdl -> do
let slurp = do
l <- hGetLine hdl
hPutStrLn tmp_hdl l
slurp
catchIO slurp
(\e -> if isEOFError e then return () else ioError e)
hClose hdl
hClose tmp_hdl
when (isJust makefile_hdl)
(SysTools.copy dflags ("Backing up " ++ makefile)
makefile (makefile++".bak"))
SysTools.copy dflags "Installing new makefile" tmp_file makefile
dumpModCycles :: DynFlags -> [ModSummary] -> IO ()
dumpModCycles dflags mod_summaries
| not (dopt Opt_D_dump_mod_cycles dflags)
= return ()
| null cycles
= putMsg dflags (ptext (sLit "No module cycles"))
| otherwise
= putMsg dflags (hang (ptext (sLit "Module cycles found:")) 2 pp_cycles)
where
cycles :: [[ModSummary]]
cycles = [ c | CyclicSCC c <- GHC.topSortModuleGraph True mod_summaries Nothing ]
pp_cycles = vcat [ (ptext (sLit "---------- Cycle") <+> int n <+> ptext (sLit "----------"))
$$ pprCycle c $$ blankLine
| (n,c) <- [1..] `zip` cycles ]
pprCycle :: [ModSummary] -> SDoc
pprCycle summaries = pp_group (CyclicSCC summaries)
where
cycle_mods :: [ModuleName]
cycle_mods = map (moduleName . ms_mod) summaries
pp_group (AcyclicSCC ms) = pp_ms ms
pp_group (CyclicSCC mss)
= ASSERT( not (null boot_only) )
pp_ms loop_breaker $$ vcat (map pp_group groups)
where
(boot_only, others) = partition is_boot_only mss
is_boot_only ms = not (any in_group (map (ideclName.unLoc) (ms_imps ms)))
in_group (L _ m) = m `elem` group_mods
group_mods = map (moduleName . ms_mod) mss
loop_breaker = head boot_only
all_others = tail boot_only ++ others
groups = GHC.topSortModuleGraph True all_others Nothing
pp_ms summary = text mod_str <> text (take (20 length mod_str) (repeat ' '))
<+> (pp_imps empty (map (ideclName.unLoc) (ms_imps summary)) $$
pp_imps (ptext (sLit "{-# SOURCE #-}")) (map (ideclName.unLoc) (ms_srcimps summary)))
where
mod_str = moduleNameString (moduleName (ms_mod summary))
pp_imps :: SDoc -> [Located ModuleName] -> SDoc
pp_imps _ [] = empty
pp_imps what lms
= case [m | L _ m <- lms, m `elem` cycle_mods] of
[] -> empty
ms -> what <+> ptext (sLit "imports") <+>
pprWithCommas ppr ms
depStartMarker, depEndMarker :: String
depStartMarker = "# DO NOT DELETE: Beginning of Haskell dependencies"
depEndMarker = "# DO NOT DELETE: End of Haskell dependencies"