[commit: ghc] wip/nfs-locking: Refactor Data and Register build rules (7ebb204)

git at git.haskell.org git at git.haskell.org
Fri Oct 27 00:45:45 UTC 2017


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

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

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

commit 7ebb2045222d9c800d523ed93e32680d8b07fc10
Author: Andrey Mokhov <andrey.mokhov at gmail.com>
Date:   Sun Nov 27 01:48:25 2016 +0000

    Refactor Data and Register build rules


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

7ebb2045222d9c800d523ed93e32680d8b07fc10
 src/Rules/Data.hs               | 21 ++++++++++++++++++++-
 src/Rules/Register.hs           | 39 ++++-----------------------------------
 src/Settings/Builders/GhcPkg.hs |  2 +-
 src/Settings/Packages/Rts.hs    |  2 +-
 src/Settings/Path.hs            |  6 +++---
 5 files changed, 29 insertions(+), 41 deletions(-)

diff --git a/src/Rules/Data.hs b/src/Rules/Data.hs
index e16f03b..1314cc4 100644
--- a/src/Rules/Data.hs
+++ b/src/Rules/Data.hs
@@ -9,6 +9,7 @@ import Oracles.Dependencies
 import Oracles.Path
 import Rules.Generate
 import Rules.Libffi
+import Settings.Packages.Rts
 import Settings.Path
 import Target
 import UserSettings
@@ -17,7 +18,8 @@ import Util
 -- | Build @package-data.mk@ by using ghc-cabal utility to process .cabal files.
 buildPackageData :: Context -> Rules ()
 buildPackageData context at Context {..} = do
-    let cabalFile = pkgCabalFile package
+    let path      = buildPath context
+        cabalFile = pkgCabalFile package
         configure = pkgPath package -/- "configure"
         dataFile  = pkgDataFile context
 
@@ -35,6 +37,23 @@ buildPackageData context at Context {..} = do
         build $ Target context GhcCabal [cabalFile] [mk]
         postProcessPackageData context mk
 
+    pkgInplaceConfig context %> \conf -> do
+        need [dataFile] -- ghc-cabal builds inplace package configuration file
+        if package == rts
+        then do
+            need [rtsConfIn]
+            build $ Target context HsCpp [rtsConfIn] [conf]
+            fixFile conf $ unlines
+                         . map
+                         ( replace "\"\"" ""
+                         . replace "rts/dist/build" rtsBuildPath
+                         . replace "includes/dist-derivedconstants/header" generatedPath )
+                         . lines
+        else do
+            top <- topDirectory
+            let oldPath = top -/- path </> "build"
+            fixFile conf $ unlines . map (replace oldPath path) . lines
+
     -- TODO: PROGNAME was $(CrossCompilePrefix)hp2ps.
     priority 2.0 $ do
         when (package `elem` [hp2ps, rts, touchy, unlit]) $ dataFile %>
diff --git a/src/Rules/Register.hs b/src/Rules/Register.hs
index b7e12d1..19ce0e3 100644
--- a/src/Rules/Register.hs
+++ b/src/Rules/Register.hs
@@ -4,9 +4,6 @@ import Base
 import Context
 import Expression
 import GHC
-import Oracles.Path
-import Rules.Libffi
-import Settings.Packages.Rts
 import Settings.Path
 import Target
 import UserSettings
@@ -16,40 +13,12 @@ import Util
 -- by running the @ghc-pkg@ utility.
 registerPackage :: [(Resource, Int)] -> Context -> Rules ()
 registerPackage rs context at Context {..} = when (stage <= Stage1) $ do
-    let dir = packageDbDirectory stage
+    let confIn = pkgInplaceConfig context
+        dir    = packageDbDirectory stage
 
     matchVersionedFilePath (dir -/- pkgNameString package) "conf" ?> \conf -> do
-        -- This produces inplace-pkg-config. TODO: Add explicit tracking.
-        need [pkgDataFile context]
-
-        -- Post-process inplace-pkg-config.
-        top <- topDirectory
-        let path      = buildPath context
-            pkgConfig = inplacePkgConfig context
-            oldPath   = top -/- path </> "build"
-
-        fixFile pkgConfig $ unlines . map (replace oldPath path) . lines
-
-        buildWithResources rs $ Target context (GhcPkg stage) [pkgConfig] [conf]
-
-    when (package == rts && stage == Stage1) $ do
-        packageDbDirectory Stage1 -/- "rts.conf" %> \conf -> do
-            need [rtsConf]
-            buildWithResources rs $ Target context (GhcPkg stage) [rtsConf] [conf]
-
-        rtsConf %> \_ -> do
-            need [pkgDataFile rtsContext, rtsConfIn]
-            build $ Target context HsCpp [rtsConfIn] [rtsConf]
-
-            let fixRtsConf = unlines
-                           . map
-                           ( replace "\"\"" ""
-                           . replace "rts/dist/build" rtsBuildPath
-                           . replace "includes/dist-derivedconstants/header" generatedPath )
-                           . filter (not . null)
-                           . lines
-
-            fixFile rtsConf fixRtsConf
+        need [confIn]
+        buildWithResources rs $ Target context (GhcPkg stage) [confIn] [conf]
 
     when (package == ghc) $ packageDbStamp stage %> \stamp -> do
         removeDirectory dir
diff --git a/src/Settings/Builders/GhcPkg.hs b/src/Settings/Builders/GhcPkg.hs
index 5156d71..15d5249 100644
--- a/src/Settings/Builders/GhcPkg.hs
+++ b/src/Settings/Builders/GhcPkg.hs
@@ -18,4 +18,4 @@ updateArgs = notM initPredicate ? do
             , arg "--force"
             , verbosity < Chatty ? arg "-v0"
             , bootPackageDatabaseArgs
-            , arg . inplacePkgConfig =<< getContext ]
+            , arg . pkgInplaceConfig =<< getContext ]
diff --git a/src/Settings/Packages/Rts.hs b/src/Settings/Packages/Rts.hs
index 40b85e4..e7c3a60 100644
--- a/src/Settings/Packages/Rts.hs
+++ b/src/Settings/Packages/Rts.hs
@@ -18,7 +18,7 @@ rtsConfIn :: FilePath
 rtsConfIn = pkgPath rts -/- "package.conf.in"
 
 rtsConf :: FilePath
-rtsConf = inplacePkgConfig rtsContext
+rtsConf = pkgInplaceConfig rtsContext
 
 rtsLibffiLibraryName :: Action FilePath
 rtsLibffiLibraryName = do
diff --git a/src/Settings/Path.hs b/src/Settings/Path.hs
index cbe1612..934a0ec 100644
--- a/src/Settings/Path.hs
+++ b/src/Settings/Path.hs
@@ -4,7 +4,7 @@ module Settings.Path (
     gmpBuildInfoPath, generatedPath, libffiBuildPath, shakeFilesPath,
     pkgConfFile, packageDbDirectory, packageDbStamp, bootPackageConstraints,
     packageDependencies, objectPath, programInplacePath, programInplaceLibPath,
-    installPath, autogenPath, inplacePkgConfig
+    installPath, autogenPath, pkgInplaceConfig
     ) where
 
 import Base
@@ -61,8 +61,8 @@ autogenPath context at Context {..}
     autogen dir = buildPath context -/- dir -/- "autogen"
 
 -- | Path to inplace package configuration of a given 'Context'.
-inplacePkgConfig :: Context -> FilePath
-inplacePkgConfig context = buildPath context -/- "inplace-pkg-config"
+pkgInplaceConfig :: Context -> FilePath
+pkgInplaceConfig context = buildPath context -/- "inplace-pkg-config"
 
 -- | Path to the @package-data.mk@ of a given 'Context'.
 pkgDataFile :: Context -> FilePath



More information about the ghc-commits mailing list