[commit: ghc] wip/nfs-locking: Fix setup-config dependency (#334) (6d46b39)

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


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

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

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

commit 6d46b39a971e8b833b5ffd8f0666c3361fd79bc0
Author: Zhen Zhang <izgzhen at gmail.com>
Date:   Mon Jul 3 04:05:13 2017 +0800

    Fix setup-config dependency (#334)


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

6d46b39a971e8b833b5ffd8f0666c3361fd79bc0
 src/Rules.hs         | 2 ++
 src/Rules/Data.hs    | 6 ++++--
 src/Rules/Install.hs | 3 ++-
 src/Settings/Path.hs | 8 +++++++-
 4 files changed, 15 insertions(+), 4 deletions(-)

diff --git a/src/Rules.hs b/src/Rules.hs
index 6e9f5d7..e5835c0 100644
--- a/src/Rules.hs
+++ b/src/Rules.hs
@@ -39,6 +39,8 @@ buildLib stage pkg = do
     when (pkg `elem` activePackages) $
         if isLibrary pkg
         then do -- build a library
+            when (nonCabalContext context) $
+                need [pkgSetupConfigFile context]
             ways <- interpretInContext context getLibraryWays
             libs <- mapM (pkgLibraryFile . Context stage pkg) ways
             docs <- interpretInContext context $ buildHaddock flavour
diff --git a/src/Rules/Data.hs b/src/Rules/Data.hs
index 0538f6c..0c19b2a 100644
--- a/src/Rules/Data.hs
+++ b/src/Rules/Data.hs
@@ -20,8 +20,9 @@ buildPackageData context at Context {..} = do
         cabalFile = pkgCabalFile package
         configure = pkgPath package -/- "configure"
         dataFile  = pkgDataFile context
+        setupConfigFile = pkgSetupConfigFile context
 
-    dataFile %> \mk -> do
+    [dataFile, setupConfigFile] &%> \(mk:setupConfig:_) -> do
         -- Make sure all generated dependencies are in place before proceeding.
         orderOnly =<< interpretInContext context generatedDependencies
 
@@ -32,7 +33,7 @@ buildPackageData context at Context {..} = do
         need =<< mapM pkgConfFile =<< contextDependencies context
 
         need [cabalFile]
-        build $ Target context GhcCabal [cabalFile] [mk]
+        build $ Target context GhcCabal [cabalFile] [mk, setupConfig]
         postProcessPackageData context mk
 
     pkgInplaceConfig context %> \conf -> do
@@ -107,6 +108,7 @@ packageCmmSources pkg
 -- For example, @libraries/deepseq/dist-install_VERSION = 1.4.0.0@
 -- is replaced by @VERSION = 1.4.0.0 at .
 -- Reason: Shake's built-in makefile parser doesn't recognise slashes
+-- TODO (izgzhen): should fix DEP_LIB_REL_DIRS_SEARCHPATH
 postProcessPackageData :: Context -> FilePath -> Action ()
 postProcessPackageData context at Context {..} file = do
     top     <- topDirectory
diff --git a/src/Rules/Install.hs b/src/Rules/Install.hs
index 3499b26..e7c6d41 100644
--- a/src/Rules/Install.hs
+++ b/src/Rules/Install.hs
@@ -18,7 +18,7 @@ import Oracles.Config.Setting
 import Oracles.PackageData
 import Oracles.Path
 
-import qualified System.Directory.Extra as IO
+import qualified System.Directory as IO
 
 {- | Install the built binaries etc. to the @destDir ++ prefix at .
 
@@ -133,6 +133,7 @@ withLatestBuildStage pkg m = do
 installPackageConf :: Action ()
 installPackageConf = do
     let context = vanillaContext Stage0 rts
+    liftIO $ IO.createDirectoryIfMissing True (takeDirectory pkgConfInstallPath)
     build $ Target context HsCpp [ pkgPath rts -/- "package.conf.in" ]
                                  [ pkgConfInstallPath <.> "raw" ]
     Stdout out <- cmd ("grep" :: String) [ "-v", "^#pragma GCC"
diff --git a/src/Settings/Path.hs b/src/Settings/Path.hs
index 240f992..8814620 100644
--- a/src/Settings/Path.hs
+++ b/src/Settings/Path.hs
@@ -5,7 +5,8 @@ module Settings.Path (
     rtsContext, rtsBuildPath, rtsConfIn, shakeFilesPath,inplacePackageDbDirectory,
     pkgConfFile, packageDbStamp, bootPackageConstraints, packageDependencies,
     objectPath, inplaceBinPath, inplaceLibBinPath, inplaceLibPath,
-    installPath, autogenPath, pkgInplaceConfig, ghcSplitPath, stripCmdPath
+    installPath, autogenPath, pkgInplaceConfig, ghcSplitPath, stripCmdPath,
+    pkgSetupConfigFile
     ) where
 
 import Base
@@ -74,6 +75,11 @@ pkgInplaceConfig context = buildPath context -/- "inplace-pkg-config"
 pkgDataFile :: Context -> FilePath
 pkgDataFile context = buildPath context -/- "package-data.mk"
 
+
+-- | Path to the @setup-config@ of a given 'Context'.
+pkgSetupConfigFile :: Context -> FilePath
+pkgSetupConfigFile context = buildPath context -/- "setup-config"
+
 -- | Path to the haddock file of a given 'Context', e.g.:
 -- "_build/stage1/libraries/array/doc/html/array/array.haddock".
 pkgHaddockFile :: Context -> FilePath



More information about the ghc-commits mailing list