{-# LANGUAGE CPP #-} ----------------------------------------------------------------------------- -- | -- Module : Windll -- Copyright : (c) Tamar Christina 2009 - 2010 -- License : BSD3 -- -- Maintainer : tamar@zhox.com -- Stability : experimental -- Portability : portable -- -- Module to do dependency tracing so that all source files can be -- traversed and all data structures resolved -- ----------------------------------------------------------------------------- module WinDll.Utils.DepScanner where import WinDll.Session.Hs2lib import WinDll.Utils.Feedback import GHC import GHC.Paths ( libdir ) import DynFlags import System.Environment import System.Directory import System.FilePath ( replaceExtension ) -- | This module is self contained, So it can be used on it's own. main :: IO () main = do args <- getArgs when (not $ null args) $ do deps <- getDeps (head args) putStrLn (unwords deps) -- | Trace the sessions dependencies traceDeps :: Exec () traceDeps = do session <- get let file = mainFile session path = absPath session file' = replaceExtension path ".o" inform _normal $ "Tracing dependencies of file '" ++ file ++ "'" exists <- liftIO $ doesFileExist path when (not exists) $ do die $ "File does not exist '" ++ file ++ "'" inform _detail ("Reading file '" ++ file ++ "'") deps <- liftIO (getDeps file) let payload = (workingset session) { dependencies = deps } put $ session { workingset = payload } after <- liftIO $ doesFileExist file' when exists $ do liftIO $ removeFile file' inform _detail "Dependencies traced." inform _detail ("Dependencies are: " ++ unwords deps) -- | Get the depencies of the supplied file as a list of strings getDeps :: String -> IO [String] getDeps file = fmap (fmap (moduleNameString . ms_mod_name)) (getGraph file) -- | Get the module dependency graph of the given file getGraph :: String -> IO ModuleGraph getGraph file = #if __GLASGOW_HASKELL__ >= 706 defaultErrorHandler defaultFatalMessager defaultFlushOut $ do #elif __GLASGOW_HASKELL__ >= 702 defaultErrorHandler defaultLogAction $ do #else defaultErrorHandler defaultDynFlags $ do #endif runGhc (Just libdir) $ do dflags <- getSessionDynFlags setSessionDynFlags $ dflags { ghcMode = MkDepend , ghcLink = NoLink } target <- guessTarget file Nothing setTargets [target] load LoadAllTargets getModuleGraph