[commit: ghc] wip/nfs-locking: Move parseMakefile from dependenciesOracle to Rules.Dependencies (for better performance) (8fe9fa6)

git at git.haskell.org git at git.haskell.org
Thu Oct 26 23:46:21 UTC 2017


Repository : ssh://git@git.haskell.org/ghc

On branch  : wip/nfs-locking
Link       : http://ghc.haskell.org/trac/ghc/changeset/8fe9fa6dc0fb9b18ca11c34a8f6282a19344e9c1/ghc

>---------------------------------------------------------------

commit 8fe9fa6dc0fb9b18ca11c34a8f6282a19344e9c1
Author: Andrey Mokhov <andrey.mokhov at gmail.com>
Date:   Fri Dec 25 01:19:50 2015 +0000

    Move parseMakefile from dependenciesOracle to Rules.Dependencies (for better performance)


>---------------------------------------------------------------

8fe9fa6dc0fb9b18ca11c34a8f6282a19344e9c1
 src/Oracles/Dependencies.hs |  7 ++-----
 src/Rules/Dependencies.hs   | 19 +++++++++++++------
 2 files changed, 15 insertions(+), 11 deletions(-)

diff --git a/src/Oracles/Dependencies.hs b/src/Oracles/Dependencies.hs
index c27c2cc..8895758 100644
--- a/src/Oracles/Dependencies.hs
+++ b/src/Oracles/Dependencies.hs
@@ -31,11 +31,8 @@ dependenciesOracle :: Rules ()
 dependenciesOracle = do
     deps <- newCache $ \file -> do
         putOracle $ "Reading dependencies from " ++ file ++ "..."
-        contents <- parseMakefile <$> readFile' file
-        return . Map.fromList . map (bimap unifyPath (map unifyPath))
-                              . map (bimap head concat . unzip)
-                              . groupBy ((==) `on` fst)
-                              . sortBy (compare `on` fst) $ contents
+        contents <- map words <$> readFileLines file
+        return . Map.fromList $ map (\(x:xs) -> (x, xs)) contents
 
     _ <- addOracle $ \(DependenciesKey (file, obj)) -> Map.lookup obj <$> deps file
     return ()
diff --git a/src/Rules/Dependencies.hs b/src/Rules/Dependencies.hs
index 47e6c6d..907c4d3 100644
--- a/src/Rules/Dependencies.hs
+++ b/src/Rules/Dependencies.hs
@@ -21,7 +21,7 @@ buildPackageDependencies _ target @ (PartialTarget stage pkg) =
             need [srcFile]
             build $ fullTarget target (GccM stage) [srcFile] [out]
 
-        hDepFile %> \file -> do
+        hDepFile %> \out -> do
             srcs <- interpretPartial target getPackageSources
             when (pkg == compiler) $ need [platformH]
             -- TODO: very ugly and fragile; use gcc -MM instead?
@@ -43,14 +43,21 @@ buildPackageDependencies _ target @ (PartialTarget stage pkg) =
                    , "primop-vector-tys.hs-incl" ]
             need $ srcs ++ extraDeps
             if srcs == []
-            then writeFileChanged file ""
-            else build $ fullTarget target (GhcM stage) srcs [file]
-            removeFileIfExists $ file <.> "bak"
+            then writeFileChanged out ""
+            else build $ fullTarget target (GhcM stage) srcs [out]
+            removeFileIfExists $ out <.> "bak"
 
-        (buildPath -/- ".dependencies") %> \file -> do
+        (buildPath -/- ".dependencies") %> \out -> do
             cSrcs <- pkgDataList $ CSrcs path
             let cDepFiles = [ buildPath -/- src <.> "deps" | src <- cSrcs ]
             need $ hDepFile : cDepFiles -- need all for more parallelism
             cDeps <- fmap concat $ mapM readFile' cDepFiles
             hDeps <- readFile' hDepFile
-            writeFileChanged file $ cDeps ++ hDeps
+            let result = unlines
+                       . map (\(src, deps) -> unwords $ src : deps)
+                       . map (bimap unifyPath (map unifyPath))
+                       . map (bimap head concat . unzip)
+                       . groupBy ((==) `on` fst)
+                       . sortBy (compare `on` fst)
+                       . parseMakefile $ cDeps ++ hDeps
+            writeFileChanged out result



More information about the ghc-commits mailing list