[commit: ghc] wip/nfs-locking: Don't track -jN arguments passed to Make (b096f1e)

git at git.haskell.org git at git.haskell.org
Fri Oct 27 00:23:32 UTC 2017


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

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

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

commit b096f1e48ba8df3e1636c8671ec867fc6b636c29
Author: Andrey Mokhov <andrey.mokhov at gmail.com>
Date:   Wed Oct 5 13:28:28 2016 +0100

    Don't track -jN arguments passed to Make
    
    See #289.


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

b096f1e48ba8df3e1636c8671ec867fc6b636c29
 src/Builder.hs          | 13 +++++++++++--
 src/Oracles/ArgsHash.hs |  6 +++++-
 2 files changed, 16 insertions(+), 3 deletions(-)

diff --git a/src/Builder.hs b/src/Builder.hs
index 1974eff..704947d 100644
--- a/src/Builder.hs
+++ b/src/Builder.hs
@@ -1,10 +1,11 @@
 {-# LANGUAGE DeriveGeneric, LambdaCase #-}
 module Builder (
-    CcMode (..), GhcMode (..), Builder (..),
-    builderPath, getBuilderPath, builderEnvironment, specified, needBuilder
+    CcMode (..), GhcMode (..), Builder (..), builderPath, getBuilderPath,
+    builderEnvironment, specified, trackedArgument, needBuilder
     ) where
 
 import Control.Monad.Trans.Reader
+import Data.Char
 import GHC.Generics (Generic)
 
 import Base
@@ -149,6 +150,14 @@ builderEnvironment variable builder = do
 specified :: Builder -> Action Bool
 specified = fmap (not . null) . builderPath
 
+-- | Some arguments do not affect build results and therefore do not need to be
+-- tracked by the build system. A notable example is "-jN" that controls Make's
+-- parallelism. Given a 'Builder' and an argument, this function should return
+-- 'True' only if the argument needs to be tracked.
+trackedArgument :: Builder -> String -> Bool
+trackedArgument (Make _) ('-' : 'j' : xs) = not $ all isDigit xs
+trackedArgument _        _                = True
+
 -- | Make sure a Builder exists on the given path and rebuild it if out of date.
 needBuilder :: Builder -> Action ()
 needBuilder = \case
diff --git a/src/Oracles/ArgsHash.hs b/src/Oracles/ArgsHash.hs
index 660edd9..f9cec24 100644
--- a/src/Oracles/ArgsHash.hs
+++ b/src/Oracles/ArgsHash.hs
@@ -2,6 +2,7 @@
 module Oracles.ArgsHash (checkArgsHash, argsHashOracle) where
 
 import Base
+import Builder
 import Expression
 import Settings
 import Target
@@ -28,4 +29,7 @@ checkArgsHash target = do
 -- | Oracle for storing per-target argument list hashes.
 argsHashOracle :: Rules ()
 argsHashOracle = void $
-    addOracle $ \(ArgsHashKey target) -> hash <$> interpret target getArgs
+    addOracle $ \(ArgsHashKey target) -> do
+    	argList <- interpret target getArgs
+    	let trackedArgList = filter (trackedArgument $ builder target) argList
+    	return $ hash trackedArgList



More information about the ghc-commits mailing list