[commit: ghc] wip/nfs-locking: Use orderOnly dependencies for generated headers, see #48 (e7f3ae8)

git at git.haskell.org git at git.haskell.org
Thu Oct 26 23:31:37 UTC 2017


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

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

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

commit e7f3ae8418552a145dc192ff5127d2e84bf1fa76
Author: Andrey Mokhov <andrey.mokhov at gmail.com>
Date:   Mon Dec 28 03:03:26 2015 +0000

    Use orderOnly dependencies for generated headers, see #48


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

e7f3ae8418552a145dc192ff5127d2e84bf1fa76
 src/Rules/Dependencies.hs | 27 +++------------------
 src/Rules/Generate.hs     | 62 +++++++++++++++++++++++++++++++++--------------
 2 files changed, 47 insertions(+), 42 deletions(-)

diff --git a/src/Rules/Dependencies.hs b/src/Rules/Dependencies.hs
index 197fa64..dc43071 100644
--- a/src/Rules/Dependencies.hs
+++ b/src/Rules/Dependencies.hs
@@ -1,7 +1,6 @@
 module Rules.Dependencies (buildPackageDependencies) where
 
 import Expression
-import GHC
 import Oracles
 import Rules.Actions
 import Rules.Generate
@@ -14,37 +13,17 @@ buildPackageDependencies _ target @ (PartialTarget stage pkg) =
         buildPath = path -/- "build"
         dropBuild = (pkgPath pkg ++) . drop (length buildPath)
         hDepFile  = buildPath -/- ".hs-dependencies"
-        platformH = targetPath stage compiler -/- "ghc_boot_platform.h"
     in do
         (buildPath <//> "*.c.deps") %> \out -> do
             let srcFile = dropBuild . dropExtension $ out
-            when (pkg == compiler) . need $ platformH : includesDependencies
-            when (pkg == hp2ps) . need $ ["includes/ghcautoconf.h", "includes/ghcplatform.h"]
+            orderOnly $ generatedDependencies stage pkg
             need [srcFile]
             build $ fullTarget target (GccM stage) [srcFile] [out]
 
         hDepFile %> \out -> do
             srcs <- interpretPartial target getPackageSources
-            when (pkg == compiler) . need $ platformH : includesDependencies
-            when (pkg == hp2ps) . need $ ["includes/ghcautoconf.h", "includes/ghcplatform.h"]
-            -- TODO: very ugly and fragile; use gcc -MM instead?
-            let extraDeps = if pkg /= compiler then [] else fmap (buildPath -/-)
-                   [ "primop-vector-uniques.hs-incl"
-                   , "primop-data-decl.hs-incl"
-                   , "primop-tag.hs-incl"
-                   , "primop-list.hs-incl"
-                   , "primop-strictness.hs-incl"
-                   , "primop-fixity.hs-incl"
-                   , "primop-primop-info.hs-incl"
-                   , "primop-out-of-line.hs-incl"
-                   , "primop-has-side-effects.hs-incl"
-                   , "primop-can-fail.hs-incl"
-                   , "primop-code-size.hs-incl"
-                   , "primop-commutable.hs-incl"
-                   , "primop-vector-tys-exports.hs-incl"
-                   , "primop-vector-tycons.hs-incl"
-                   , "primop-vector-tys.hs-incl" ]
-            need $ srcs ++ extraDeps
+            orderOnly $ generatedDependencies stage pkg
+            need srcs
             if srcs == []
             then writeFileChanged out ""
             else build $ fullTarget target (GhcM stage) srcs [out]
diff --git a/src/Rules/Generate.hs b/src/Rules/Generate.hs
index bc0089c..c7d13d6 100644
--- a/src/Rules/Generate.hs
+++ b/src/Rules/Generate.hs
@@ -1,6 +1,6 @@
 module Rules.Generate (
     generatePackageCode, generateRules,
-    derivedConstantsPath, includesDependencies
+    derivedConstantsPath, generatedDependencies
     ) where
 
 import Expression
@@ -19,18 +19,47 @@ import Settings
 primopsSource :: FilePath
 primopsSource = "compiler/prelude/primops.txt.pp"
 
+primopsTxt :: Stage -> FilePath
+primopsTxt stage = targetPath stage compiler -/- "build/primops.txt"
+
+platformH :: Stage -> FilePath
+platformH stage = targetPath stage compiler -/- "ghc_boot_platform.h"
+
 derivedConstantsPath :: FilePath
 derivedConstantsPath = "includes/dist-derivedconstants/header"
 
 -- TODO: can we drop COMPILER_INCLUDES_DEPS += $(includes_GHCCONSTANTS)?
-includesDependencies :: [FilePath]
-includesDependencies =
-    [ "includes/ghcautoconf.h"
-    , "includes/ghcplatform.h"
-    , derivedConstantsPath -/- "DerivedConstants.h"
-    , derivedConstantsPath -/- "GHCConstantsHaskellType.hs"
-    , derivedConstantsPath -/- "GHCConstantsHaskellWrappers.hs"
-    , derivedConstantsPath -/- "GHCConstantsHaskellExports.hs" ]
+generatedDependencies :: Stage -> Package -> [FilePath]
+generatedDependencies stage pkg
+    | pkg == hp2ps    = [ "includes/ghcautoconf.h"
+                        , "includes/ghcplatform.h" ]
+    | pkg == compiler = let buildPath = targetPath stage compiler -/- "build"
+                        in
+                        [ "includes/ghcautoconf.h"
+                        , "includes/ghcplatform.h"
+                        , derivedConstantsPath -/- "DerivedConstants.h"
+                        , derivedConstantsPath -/- "GHCConstantsHaskellType.hs"
+                        , derivedConstantsPath -/- "GHCConstantsHaskellWrappers.hs"
+                        , derivedConstantsPath -/- "GHCConstantsHaskellExports.hs"
+                        , platformH stage ]
+                        ++
+                        fmap (buildPath -/-)
+                        [ "primop-vector-uniques.hs-incl"
+                        , "primop-data-decl.hs-incl"
+                        , "primop-tag.hs-incl"
+                        , "primop-list.hs-incl"
+                        , "primop-strictness.hs-incl"
+                        , "primop-fixity.hs-incl"
+                        , "primop-primop-info.hs-incl"
+                        , "primop-out-of-line.hs-incl"
+                        , "primop-has-side-effects.hs-incl"
+                        , "primop-can-fail.hs-incl"
+                        , "primop-code-size.hs-incl"
+                        , "primop-commutable.hs-incl"
+                        , "primop-vector-tys-exports.hs-incl"
+                        , "primop-vector-tycons.hs-incl"
+                        , "primop-vector-tys.hs-incl" ]
+    | otherwise = []
 
 -- The following generators and corresponding source extensions are supported:
 knownGenerators :: [ (Builder, String) ]
@@ -52,10 +81,7 @@ generate file target expr = do
 
 generatePackageCode :: Resources -> PartialTarget -> Rules ()
 generatePackageCode _ target @ (PartialTarget stage pkg) =
-    let path        = targetPath stage pkg
-        buildPath   = path -/- "build"
-        primopsTxt  = targetPath stage compiler -/- "build/primops.txt"
-        platformH   = targetPath stage compiler -/- "ghc_boot_platform.h"
+    let buildPath   = targetPath stage pkg -/- "build"
         generated f = (buildPath ++ "//*.hs") ?== f && not ("//autogen/*" ?== f)
         file <~ gen = generate file target gen
     in do
@@ -74,8 +100,8 @@ generatePackageCode _ target @ (PartialTarget stage pkg) =
                 copyFileChanged srcBoot $ file -<.> "hs-boot"
 
         -- TODO: needing platformH is ugly and fragile
-        when (pkg == compiler) $ primopsTxt %> \file -> do
-            need [platformH, primopsSource]
+        when (pkg == compiler) $ primopsTxt stage %> \file -> do
+            need [platformH stage, primopsSource]
             build $ fullTarget target HsCpp [primopsSource] [file]
 
         -- TODO: why different folders for generated files?
@@ -83,8 +109,8 @@ generatePackageCode _ target @ (PartialTarget stage pkg) =
             [ "GHC/PrimopWrappers.hs"
             , "autogen/GHC/Prim.hs"
             , "*.hs-incl" ] |%> \file -> do
-                need [primopsTxt]
-                build $ fullTarget target GenPrimopCode [primopsTxt] [file]
+                need [primopsTxt stage]
+                build $ fullTarget target GenPrimopCode [primopsTxt stage] [file]
 
         priority 2.0 $ do
             when (pkg == compiler && stage == Stage1) $
@@ -94,7 +120,7 @@ generatePackageCode _ target @ (PartialTarget stage pkg) =
             when (pkg == compiler) $ buildPath -/- "Config.hs" %> \file -> do
                 file <~ generateConfigHs
 
-            when (pkg == compiler) $ platformH %> \file -> do
+            when (pkg == compiler) $ platformH stage %> \file -> do
                 file <~ generateGhcBootPlatformH
 
             when (pkg == ghcPkg) $ buildPath -/- "Version.hs" %> \file -> do



More information about the ghc-commits mailing list