[commit: ghc] wip/nfs-locking: Fix parallel invocations of DeriveConstants builder. (9178de2)

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


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

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

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

commit 9178de2bd2483148777975b5bab48d96ce2884ad
Author: Andrey Mokhov <andrey.mokhov at gmail.com>
Date:   Mon Jan 11 16:06:21 2016 +0000

    Fix parallel invocations of DeriveConstants builder.
    
    See #137.


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

9178de2bd2483148777975b5bab48d96ce2884ad
 src/Rules/Generate.hs                    |  9 ++++++---
 src/Settings/Builders/DeriveConstants.hs | 14 +++++---------
 2 files changed, 11 insertions(+), 12 deletions(-)

diff --git a/src/Rules/Generate.hs b/src/Rules/Generate.hs
index 4fd7da6..025f1ee 100644
--- a/src/Rules/Generate.hs
+++ b/src/Rules/Generate.hs
@@ -19,7 +19,6 @@ import Rules.Gmp
 import Rules.Libffi
 import Rules.Resources (Resources)
 import Settings
-import Settings.Builders.DeriveConstants
 
 installTargets :: [FilePath]
 installTargets = [ "inplace/lib/template-hsc.h"
@@ -53,6 +52,9 @@ ghcPrimDependencies stage = ((targetPath stage ghcPrim -/- "build") -/-) <$>
        [ "GHC/PrimopWrappers.hs"
        , "autogen/GHC/Prim.hs" ]
 
+derivedConstantsPath :: FilePath
+derivedConstantsPath = "includes/dist-derivedconstants/header"
+
 derivedConstantsDependencies :: [FilePath]
 derivedConstantsDependencies = installTargets ++ fmap (derivedConstantsPath -/-)
     [ "DerivedConstants.h"
@@ -178,9 +180,10 @@ generateRules = do
         generate ghcSplit emptyTarget generateGhcSplit
         makeExecutable ghcSplit
 
-    -- TODO: simplify
+    -- TODO: simplify, get rid of fake rts target
     derivedConstantsPath ++ "//*" %> \file -> do
-        build $ fullTarget (PartialTarget Stage1 rts) DeriveConstants [] [file]
+        withTempDir $ \dir -> build $
+            fullTarget (PartialTarget Stage1 rts) DeriveConstants [] [file, dir]
 
   where
     file <~ gen = file %> \out -> generate out emptyTarget gen
diff --git a/src/Settings/Builders/DeriveConstants.hs b/src/Settings/Builders/DeriveConstants.hs
index 6f4828a..fb578f5 100644
--- a/src/Settings/Builders/DeriveConstants.hs
+++ b/src/Settings/Builders/DeriveConstants.hs
@@ -1,6 +1,4 @@
-module Settings.Builders.DeriveConstants (
-    derivedConstantsPath, deriveConstantsBuilderArgs
-    ) where
+module Settings.Builders.DeriveConstants (deriveConstantsBuilderArgs) where
 
 import Base
 import Expression
@@ -9,21 +7,19 @@ import Oracles.Config.Setting
 import Predicates (builder, file)
 import Settings.Builders.Common
 
-derivedConstantsPath :: FilePath
-derivedConstantsPath = "includes/dist-derivedconstants/header"
-
 -- TODO: do we need to support `includes_CC_OPTS += -DDYNAMIC_BY_DEFAULT`?
 deriveConstantsBuilderArgs :: Args
 deriveConstantsBuilderArgs = builder DeriveConstants ? do
-    cFlags <- fromDiffExpr includeCcArgs
+    cFlags            <- fromDiffExpr includeCcArgs
+    [output, tempDir] <- getOutputs
     mconcat
         [ file "//DerivedConstants.h"             ? arg "--gen-header"
         , file "//GHCConstantsHaskellType.hs"     ? arg "--gen-haskell-type"
         , file "//platformConstants"              ? arg "--gen-haskell-value"
         , file "//GHCConstantsHaskellWrappers.hs" ? arg "--gen-haskell-wrappers"
         , file "//GHCConstantsHaskellExports.hs"  ? arg "--gen-haskell-exports"
-        , arg "-o", arg =<< getOutput
-        , arg "--tmpdir", arg derivedConstantsPath
+        , arg "-o", arg output
+        , arg "--tmpdir", arg tempDir
         , arg "--gcc-program", arg =<< getBuilderPath (Gcc Stage1)
         , append . concat $ map (\a -> ["--gcc-flag", a]) cFlags
         , arg "--nm-program", arg =<< getBuilderPath Nm



More information about the ghc-commits mailing list