[commit: ghc] wip/nfs-locking: Minor revision (5e1d004)

git at git.haskell.org git at git.haskell.org
Fri Oct 27 01:22:11 UTC 2017


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

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

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

commit 5e1d004c4d92f9847f6d96e38c27815429239fea
Author: Andrey Mokhov <andrey.mokhov at gmail.com>
Date:   Sun Aug 6 01:24:06 2017 +0100

    Minor revision


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

5e1d004c4d92f9847f6d96e38c27815429239fea
 src/Hadrian/Oracles/ArgsHash.hs | 9 +++++----
 src/Util.hs                     | 2 +-
 2 files changed, 6 insertions(+), 5 deletions(-)

diff --git a/src/Hadrian/Oracles/ArgsHash.hs b/src/Hadrian/Oracles/ArgsHash.hs
index 0eba6c2..80a170d 100644
--- a/src/Hadrian/Oracles/ArgsHash.hs
+++ b/src/Hadrian/Oracles/ArgsHash.hs
@@ -1,6 +1,6 @@
 {-# LANGUAGE GeneralizedNewtypeDeriving #-}
 module Hadrian.Oracles.ArgsHash (
-    TrackArgument, trackAllArguments, checkArgsHash, argsHashOracle
+    TrackArgument, trackAllArguments, trackArgsHash, argsHashOracle
     ) where
 
 import Control.Monad
@@ -34,13 +34,14 @@ newtype ArgsHashKey c b = ArgsHashKey (Target c b)
 -- in the Shake database. This optimisation is normally harmless, because
 -- argument list constructors are assumed not to examine target sources, but
 -- only append them to argument lists where appropriate.
-checkArgsHash :: (ShakeValue c, ShakeValue b) => Target c b -> Action ()
-checkArgsHash t = do
+trackArgsHash :: (ShakeValue c, ShakeValue b) => Target c b -> Action ()
+trackArgsHash t = do
     let hashedInputs  = [ show $ hash (inputs t) ]
         hashedTarget = target (context t) (builder t) hashedInputs (outputs t)
     void (askOracle $ ArgsHashKey hashedTarget :: Action Int)
 
--- | Oracle for storing per-target argument list hashes.
+-- | This oracle stores per-target argument list hashes in the Shake database,
+-- allowing the user to track them between builds using 'trackArgsHash' queries.
 argsHashOracle :: (ShakeValue c, ShakeValue b) => TrackArgument c b -> Args c b -> Rules ()
 argsHashOracle trackArgument args = void $
     addOracle $ \(ArgsHashKey target) -> do
diff --git a/src/Util.hs b/src/Util.hs
index ed535fe..c4b888d 100644
--- a/src/Util.hs
+++ b/src/Util.hs
@@ -51,7 +51,7 @@ customBuild rs opts target = do
     argList <- interpret target getArgs
     verbose <- interpret target verboseCommands
     let quietlyUnlessVerbose = if verbose then withVerbosity Loud else quietly
-    checkArgsHash target -- Rerun the rule if the hash of argList has changed.
+    trackArgsHash target -- Rerun the rule if the hash of argList has changed.
     withResources rs $ do
         putInfo target
         quietlyUnlessVerbose $ case targetBuilder of



More information about the ghc-commits mailing list