[commit: ghc] wip/nfs-locking: Drop laxDependencies. To be replaced by Shake's skip feature. (8d0581e)

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


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

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

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

commit 8d0581ed811c1b180981d4a767e3862e5dd490de
Author: Andrey Mokhov <andrey.mokhov at gmail.com>
Date:   Tue Apr 26 09:44:41 2016 +0100

    Drop laxDependencies. To be replaced by Shake's skip feature.


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

8d0581ed811c1b180981d4a767e3862e5dd490de
 src/Builder.hs                    | 18 ++++--------------
 src/Predicates.hs                 |  1 -
 src/Rules/Actions.hs              |  6 +++---
 src/Rules/Gmp.hs                  |  2 +-
 src/Rules/Libffi.hs               |  2 +-
 src/Rules/Test.hs                 |  6 +++---
 src/Settings/Builders/GhcCabal.hs |  2 +-
 src/Settings/User.hs              |  9 +--------
 8 files changed, 14 insertions(+), 32 deletions(-)

diff --git a/src/Builder.hs b/src/Builder.hs
index 09e4ab9..8f711e0 100644
--- a/src/Builder.hs
+++ b/src/Builder.hs
@@ -141,21 +141,11 @@ getBuilderPath = lift . builderPath
 specified :: Builder -> Action Bool
 specified = fmap (not . null) . builderPath
 
--- TODO: Get rid of laxDependencies -- we no longer need it (use Shake's skip).
--- | Make sure a builder exists on the given path and rebuild it if out of date.
--- If 'laxDependencies' is True then we do not rebuild GHC even if it is out of
--- date (can save a lot of build time when changing GHC).
-needBuilder :: Bool -> Builder -> Action ()
-needBuilder laxDependencies builder = when (isInternal builder) $ do
+-- | Make sure a Builder exists on the given path and rebuild it if out of date.
+needBuilder :: Builder -> Action ()
+needBuilder builder = when (isInternal builder) $ do
     path <- builderPath builder
-    if laxDependencies && allowOrderOnlyDependency builder
-    then orderOnly [path]
-    else need      [path]
-  where
-    allowOrderOnlyDependency :: Builder -> Bool
-    allowOrderOnlyDependency = \case
-        Ghc _ _ -> True
-        _       -> False
+    need [path]
 
 -- Instances for storing in the Shake database
 instance Binary CompilerMode
diff --git a/src/Predicates.hs b/src/Predicates.hs
index 1f87386..0ae18e9 100644
--- a/src/Predicates.hs
+++ b/src/Predicates.hs
@@ -15,7 +15,6 @@ stage s = (s ==) <$> getStage
 package :: Package -> Predicate
 package p = (p ==) <$> getPackage
 
--- TODO: Also add needBuilder, builderPath, etc.
 -- | Is a particular builder being used?
 class BuilderLike a where
     builder :: a -> Predicate
diff --git a/src/Rules/Actions.hs b/src/Rules/Actions.hs
index 3b12249..10bcbd2 100644
--- a/src/Rules/Actions.hs
+++ b/src/Rules/Actions.hs
@@ -24,7 +24,7 @@ import Target
 -- built (that is, track changes in the build system).
 buildWithResources :: [(Resource, Int)] -> Target -> Action ()
 buildWithResources rs target at Target {..} = do
-    needBuilder laxDependencies builder
+    needBuilder builder
     path    <- builderPath builder
     argList <- interpret target getArgs
     verbose <- interpret target verboseCommands
@@ -140,14 +140,14 @@ applyPatch :: FilePath -> FilePath -> Action ()
 applyPatch dir patch = do
     let file = dir -/- patch
     need [file]
-    needBuilder False Patch -- TODO: add a specialised version ~needBuilderFalse?
+    needBuilder Patch
     path <- builderPath Patch
     putBuild $ "| Apply patch " ++ file
     quietly $ cmd Shell (EchoStdout False) [Cwd dir] [path, "-p0 <", patch]
 
 runBuilder :: Builder -> [String] -> Action ()
 runBuilder builder args = do
-    needBuilder laxDependencies builder
+    needBuilder builder
     path <- builderPath builder
     let note = if null args then "" else " (" ++ intercalate ", " args ++ ")"
     putBuild $ "| Run " ++ show builder ++ note
diff --git a/src/Rules/Gmp.hs b/src/Rules/Gmp.hs
index ae73104..99dda79 100644
--- a/src/Rules/Gmp.hs
+++ b/src/Rules/Gmp.hs
@@ -42,7 +42,7 @@ configureEnvironment = do
              , builderEnv "NM" Nm ]
   where
     builderEnv var bld = do
-        needBuilder False bld
+        needBuilder bld
         path <- builderPath bld
         return $ AddEnv var path
 
diff --git a/src/Rules/Libffi.hs b/src/Rules/Libffi.hs
index 18c328b..8dce6d1 100644
--- a/src/Rules/Libffi.hs
+++ b/src/Rules/Libffi.hs
@@ -53,7 +53,7 @@ configureEnvironment = do
              , return . AddEnv "LDFLAGS" $ unwords ldFlags ++ " -w" ]
   where
     builderEnv var bld = do
-        needBuilder False bld
+        needBuilder bld
         path <- builderPath bld
         return $ AddEnv var path
 
diff --git a/src/Rules/Test.hs b/src/Rules/Test.hs
index 0604236..7faf62d 100644
--- a/src/Rules/Test.hs
+++ b/src/Rules/Test.hs
@@ -15,9 +15,9 @@ import Settings.User
 testRules :: Rules ()
 testRules = do
     "validate" ~> do
-        needBuilder False $ Ghc Compile Stage2 -- TODO: get rid of False
-        needBuilder False $ GhcPkg Stage1
-        needBuilder False $ Hpc
+        needBuilder $ Ghc Compile Stage2
+        needBuilder $ GhcPkg Stage1
+        needBuilder Hpc
         runMakeVerbose "testsuite/tests" ["fast"]
 
     "test" ~> do
diff --git a/src/Settings/Builders/GhcCabal.hs b/src/Settings/Builders/GhcCabal.hs
index 1750604..9f6c6e2 100644
--- a/src/Settings/Builders/GhcCabal.hs
+++ b/src/Settings/Builders/GhcCabal.hs
@@ -127,7 +127,7 @@ with :: Builder -> Args
 with b = specified b ? do
     top  <- getTopDirectory
     path <- getBuilderPath b
-    lift $ needBuilder laxDependencies b
+    lift $ needBuilder b
     append [withBuilderKey b ++ top -/- path]
 
 withStaged :: (Stage -> Builder) -> Args
diff --git a/src/Settings/User.hs b/src/Settings/User.hs
index 49a3a1d..b147665 100644
--- a/src/Settings/User.hs
+++ b/src/Settings/User.hs
@@ -2,7 +2,7 @@ module Settings.User (
     buildRootPath, trackBuildSystem, userArgs, userPackages, userLibraryWays,
     userRtsWays, userKnownPackages, integerLibrary, buildHaddock, validating,
     ghciWithDebugger, ghcProfiled, ghcDebugged, dynamicGhcPrograms,
-    laxDependencies, verboseCommands, turnWarningsIntoErrors, splitObjects
+    verboseCommands, turnWarningsIntoErrors, splitObjects
     ) where
 
 import Base
@@ -74,13 +74,6 @@ ghcProfiled = False
 ghcDebugged :: Bool
 ghcDebugged = False
 
--- | When laxDependencies is set to True, dependencies on the GHC executable
--- are turned into order-only dependencies to avoid needless recompilation when
--- making changes to GHC's sources. In certain situations this can lead to build
--- failures, in which case you should reset the flag (at least temporarily).
-laxDependencies :: Bool
-laxDependencies = False
-
 buildHaddock :: Predicate
 buildHaddock = return cmdBuildHaddock
 



More information about the ghc-commits mailing list