[commit: ghc] wip/nfs-locking: Decouple buildPackageData and registerPackage rules. (9129e8b)
git at git.haskell.org
git at git.haskell.org
Fri Oct 27 00:46:40 UTC 2017
Repository : ssh://git@git.haskell.org/ghc
On branch : wip/nfs-locking
Link : http://ghc.haskell.org/trac/ghc/changeset/9129e8bc158dab081094554abc4dcbef3f8b2a5f/ghc
>---------------------------------------------------------------
commit 9129e8bc158dab081094554abc4dcbef3f8b2a5f
Author: Andrey Mokhov <andrey.mokhov at gmail.com>
Date: Wed Feb 3 00:39:32 2016 +0000
Decouple buildPackageData and registerPackage rules.
See #200.
>---------------------------------------------------------------
9129e8bc158dab081094554abc4dcbef3f8b2a5f
shaking-up-ghc.cabal | 1 +
src/Rules/Data.hs | 26 ++++----------------------
src/Rules/Documentation.hs | 3 ++-
src/Rules/Package.hs | 30 ++++++++++++++++--------------
src/Rules/Register.hs | 39 +++++++++++++++++++++++++++++++++++++++
5 files changed, 62 insertions(+), 37 deletions(-)
diff --git a/shaking-up-ghc.cabal b/shaking-up-ghc.cabal
index f00c7c6..0807ff3 100644
--- a/shaking-up-ghc.cabal
+++ b/shaking-up-ghc.cabal
@@ -62,6 +62,7 @@ executable ghc-shake
, Rules.Package
, Rules.Perl
, Rules.Program
+ , Rules.Register
, Rules.Resources
, Rules.Wrappers.Ghc
, Rules.Wrappers.GhcPkg
diff --git a/src/Rules/Data.hs b/src/Rules/Data.hs
index fbe22db..f2e3d43 100644
--- a/src/Rules/Data.hs
+++ b/src/Rules/Data.hs
@@ -6,7 +6,6 @@ import Base
import Expression
import GHC
import Oracles
-import Predicates (registerPackage)
import Rules.Actions
import Rules.Generate
import Rules.Libffi
@@ -29,14 +28,14 @@ buildPackageData rs target @ (PartialTarget stage pkg) = do
orderOnly $ generatedDependencies stage pkg
-- GhcCabal may run the configure script, so we depend on it
- -- We don't know who built the configure script from configure.ac
whenM (doesFileExist $ configure <.> "ac") $ need [configure]
- -- We configure packages in the order of their dependencies
+ -- Before we configure a package its dependencies need to be registered
deps <- packageDeps pkg
pkgs <- interpretPartial target getPackages
let depPkgs = matchPackageNames (sort pkgs) deps
- orderOnly $ map (pkgDataFile stage) depPkgs
+ depConfs <- traverse (pkgConfFile stage) depPkgs
+ orderOnly depConfs
-- TODO: get rid of this, see #113
let inTreeMk = oldPath -/- takeFileName dataFile
@@ -52,23 +51,6 @@ buildPackageData rs target @ (PartialTarget stage pkg) = do
forM_ autogenFiles $ \file -> do
copyFile (oldPath -/- file) (targetPath stage pkg -/- file)
- -- ghc-pkg produces inplace-pkg-config when run on packages with
- -- library components only
- when (isLibrary pkg) .
- whenM (interpretPartial target registerPackage) $ do
-
- -- Post-process inplace-pkg-config. TODO: remove, see #113, #148
- let fixPkgConf = unlines
- . map (replace oldPath (targetPath stage pkg)
- . replace (replaceSeparators '\\' $ oldPath)
- (targetPath stage pkg) )
- . lines
-
- fixFile (oldPath -/- "inplace-pkg-config") fixPkgConf
-
- buildWithResources [(resGhcPkg rs, 1)] $
- fullTarget target (GhcPkg stage) [cabalFile] []
-
postProcessPackageData stage pkg dataFile
-- TODO: PROGNAME was $(CrossCompilePrefix)hp2ps
@@ -141,7 +123,7 @@ buildPackageData rs target @ (PartialTarget stage pkg) = do
[ "C_SRCS = "
++ unwords (cSrcs ++ cmmSrcs ++ sSrcs ++ extraSrcs)
, "CC_OPTS = " ++ unwords includes
- , "COMPONENT_ID = " ++ "rts" ]
+ , "COMPONENT_ID = rts" ]
writeFileChanged mk contents
putSuccess $ "| Successfully generated '" ++ mk ++ "'."
diff --git a/src/Rules/Documentation.hs b/src/Rules/Documentation.hs
index cb74952..e235bfc 100644
--- a/src/Rules/Documentation.hs
+++ b/src/Rules/Documentation.hs
@@ -26,7 +26,8 @@ buildPackageDocumentation _ target @ (PartialTarget stage pkg) =
-- HsColour sources
whenM (specified HsColour) $ do
- need [cabalFile, pkgDataFile stage pkg ]
+ pkgConf <- pkgConfFile stage pkg
+ need [ cabalFile, pkgConf ] -- TODO: check if need pkgConf
build $ fullTarget target GhcCabalHsColour [cabalFile] []
-- Build Haddock documentation
diff --git a/src/Rules/Package.hs b/src/Rules/Package.hs
index 7a7d854..28fe635 100644
--- a/src/Rules/Package.hs
+++ b/src/Rules/Package.hs
@@ -1,22 +1,24 @@
module Rules.Package (buildPackage) where
import Base
-import Rules.Compile
-import Rules.Data
-import Rules.Dependencies
-import Rules.Documentation
-import Rules.Generate
-import Rules.Library
-import Rules.Program
+import qualified Rules.Compile
+import qualified Rules.Data
+import qualified Rules.Dependencies
+import qualified Rules.Documentation
+import qualified Rules.Generate
+import qualified Rules.Library
+import qualified Rules.Program
+import qualified Rules.Register
import Rules.Resources
import Target
buildPackage :: Resources -> PartialTarget -> Rules ()
buildPackage = mconcat
- [ buildPackageData
- , buildPackageDependencies
- , generatePackageCode
- , compilePackage
- , buildPackageLibrary
- , buildPackageDocumentation
- , buildProgram ]
+ [ Rules.Compile.compilePackage
+ , Rules.Data.buildPackageData
+ , Rules.Dependencies.buildPackageDependencies
+ , Rules.Documentation.buildPackageDocumentation
+ , Rules.Generate.generatePackageCode
+ , Rules.Library.buildPackageLibrary
+ , Rules.Program.buildProgram
+ , Rules.Register.registerPackage ]
diff --git a/src/Rules/Register.hs b/src/Rules/Register.hs
new file mode 100644
index 0000000..8c3ec73
--- /dev/null
+++ b/src/Rules/Register.hs
@@ -0,0 +1,39 @@
+module Rules.Register (registerPackage) where
+
+import Data.Char
+
+import Base
+import Expression
+import GHC
+import Rules.Actions
+import Rules.Resources
+import Settings
+
+-- matchPkgConf :: FilePath -> Bool
+-- matchPkgConf file =
+
+-- Build package-data.mk by using GhcCabal to process pkgCabal file
+registerPackage :: Resources -> PartialTarget -> Rules ()
+registerPackage rs target @ (PartialTarget stage pkg) = do
+ let oldPath = pkgPath pkg -/- targetDirectory stage pkg -- TODO: remove, #113
+ pkgConf = packageDbDirectory stage -/- pkgNameString pkg
+ match f = case stripPrefix (pkgConf ++ "-") f of
+ Nothing -> False
+ Just suf -> dropWhile (\c -> isDigit c || c == '.') suf == "conf"
+
+ when (stage <= Stage1) $ match ?> \_ -> do
+ -- This produces pkgConfig. TODO: Add explicit tracking
+ need [pkgDataFile stage pkg]
+
+ -- Post-process inplace-pkg-config. TODO: remove, see #113, #148
+ let pkgConfig = oldPath -/- "inplace-pkg-config"
+ fixPkgConf = unlines
+ . map (replace oldPath (targetPath stage pkg)
+ . replace (replaceSeparators '\\' $ oldPath)
+ (targetPath stage pkg) )
+ . lines
+
+ fixFile pkgConfig fixPkgConf
+
+ buildWithResources [(resGhcPkg rs, 1)] $
+ fullTarget target (GhcPkg stage) [pkgConfig] []
More information about the ghc-commits
mailing list