[commit: ghc] wip/nfs-locking: Optimise ArgsHash oracle improving zero build time. (486a3e5)

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


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

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

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

commit 486a3e58a9c323f651f733508492efe9a3e768d0
Author: Andrey Mokhov <andrey.mokhov at gmail.com>
Date:   Mon Aug 10 01:40:17 2015 +0100

    Optimise ArgsHash oracle improving zero build time.


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

486a3e58a9c323f651f733508492efe9a3e768d0
 src/Oracles/ArgsHash.hs | 13 ++++++++-----
 src/Rules/Actions.hs    |  4 +---
 2 files changed, 9 insertions(+), 8 deletions(-)

diff --git a/src/Oracles/ArgsHash.hs b/src/Oracles/ArgsHash.hs
index ca0aa6c..f67f8c4 100644
--- a/src/Oracles/ArgsHash.hs
+++ b/src/Oracles/ArgsHash.hs
@@ -1,23 +1,26 @@
 {-# LANGUAGE DeriveDataTypeable, GeneralizedNewtypeDeriving #-}
 
 module Oracles.ArgsHash (
-    askArgsHash, argsHashOracle
+    checkArgsHash, argsHashOracle
     ) where
 
 import Base
+import Target
 import Expression
 import Settings.Args
 import Control.Applicative
 
-newtype ArgsHashKey = ArgsHashKey FullTarget
-    deriving (Show, Typeable, Eq, Hashable, Binary, NFData)
+newtype ArgsHashKey = ArgsHashKey Target
+    deriving (Show, Eq, Typeable, Binary, Hashable, NFData)
 
 -- This is an action that given a full target determines the corresponding
 -- argument list and computes its hash. The resulting value is tracked in a
 -- Shake oracle, hence initiating rebuilts when the hash is changed (a hash
 -- change indicates changes in the build system).
-askArgsHash :: FullTarget -> Action Int
-askArgsHash = askOracle . ArgsHashKey
+checkArgsHash :: FullTarget -> Action ()
+checkArgsHash target = do
+    tmp <- askOracle . ArgsHashKey $ target { sources = ["src"] } :: Action Int
+    return ()
 
 -- Oracle for storing per-target argument list hashes
 argsHashOracle :: Rules ()
diff --git a/src/Rules/Actions.hs b/src/Rules/Actions.hs
index 062a5d5..2f9ebc6 100644
--- a/src/Rules/Actions.hs
+++ b/src/Rules/Actions.hs
@@ -19,13 +19,11 @@ import Settings.Builders.Ar
 buildWithResources :: [(Resource, Int)] -> FullTarget -> Action ()
 buildWithResources rs target = do
     let builder = Target.builder target
-        deps    = Target.dependencies target
     needBuilder builder
-    -- need deps -- TODO: think if needs could be done here
     path    <- builderPath builder
     argList <- interpret target getArgs
     -- The line below forces the rule to be rerun if the args hash has changed
-    argsHash <- askArgsHash target
+    checkArgsHash target
     withResources rs $ do
         putBuild $ "/--------\n" ++ "| Running "
                  ++ show builder ++ " with arguments:"



More information about the ghc-commits mailing list