[commit: ghc] wip/nfs-locking: Rename (run, terseRun) to (verboseRun, run). (9e247b0)
git at git.haskell.org
git at git.haskell.org
Thu Oct 26 23:08:16 UTC 2017
Repository : ssh://git@git.haskell.org/ghc
On branch : wip/nfs-locking
Link : http://ghc.haskell.org/trac/ghc/changeset/9e247b0618357bdca4b0218de19e2eb7f9f23b63/ghc
>---------------------------------------------------------------
commit 9e247b0618357bdca4b0218de19e2eb7f9f23b63
Author: Andrey Mokhov <andrey.mokhov at gmail.com>
Date: Sun Jan 18 12:50:13 2015 +0000
Rename (run, terseRun) to (verboseRun, run).
>---------------------------------------------------------------
9e247b0618357bdca4b0218de19e2eb7f9f23b63
src/Oracles/Builder.hs | 15 ++++++---------
src/Package/Compile.hs | 4 ++--
src/Package/Data.hs | 4 ++--
src/Package/Dependencies.hs | 9 ++-------
src/Package/Library.hs | 4 ++--
5 files changed, 14 insertions(+), 22 deletions(-)
diff --git a/src/Oracles/Builder.hs b/src/Oracles/Builder.hs
index 1dcc797..e52cc58 100644
--- a/src/Oracles/Builder.hs
+++ b/src/Oracles/Builder.hs
@@ -2,7 +2,7 @@
module Oracles.Builder (
Builder (..),
- with, run, terseRun, specified
+ with, run, verboseRun, specified
) where
import Data.Char
@@ -94,9 +94,8 @@ with builder = do
return [key ++ exe]
-- Run the builder with a given collection of arguments
--- Raises an error if the builder is not uniquely specified in config files
-run :: ShowArgs a => Builder -> a -> Action ()
-run builder as = do
+verboseRun :: ShowArgs a => Builder -> a -> Action ()
+verboseRun builder as = do
needBuilder builder
exe <- showArg builder
args <- showArgs as
@@ -104,17 +103,15 @@ run builder as = do
-- Run the builder with a given collection of arguments printing out a
-- terse commentary with only 'interesting' info for the builder.
--- Raises an error if the builder is not uniquely specified in config files
--- TODO: make this a default 'run', rename current 'run' to verboseRun
-terseRun :: ShowArgs a => Builder -> a -> Action ()
-terseRun builder as = do
+run :: ShowArgs a => Builder -> a -> Action ()
+run builder as = do
args <- showArgs as
putColoured White $ "/--------\n" ++
"| Running " ++ show builder ++ " with arguments:"
mapM_ (putColoured White . ("| " ++)) $
interestingInfo builder args
putColoured White $ "\\--------"
- quietly $ run builder as
+ quietly $ verboseRun builder as
interestingInfo :: Builder -> [String] -> [String]
interestingInfo builder ss = case builder of
diff --git a/src/Package/Compile.hs b/src/Package/Compile.hs
index 1155117..e0080f9 100644
--- a/src/Package/Compile.hs
+++ b/src/Package/Compile.hs
@@ -66,9 +66,9 @@ buildRule pkg @ (Package name path _) todo @ (stage, dist, _) =
-- Build using appropriate compiler
need $ hDeps ++ cDeps
when (not $ null hSrcs)
- $ terseRun (Ghc stage) $ ghcArgs pkg todo way hSrcs obj
+ $ run (Ghc stage) $ ghcArgs pkg todo way hSrcs obj
when (not $ null cSrcs)
- $ terseRun (Gcc stage) $ gccArgs pkg todo cSrcs obj
+ $ run (Gcc stage) $ gccArgs pkg todo cSrcs obj
argListRule :: Package -> TodoItem -> Rules ()
argListRule pkg todo @ (stage, _, settings) =
diff --git a/src/Package/Data.hs b/src/Package/Data.hs
index a3f0936..91f0b2d 100644
--- a/src/Package/Data.hs
+++ b/src/Package/Data.hs
@@ -124,9 +124,9 @@ buildRule pkg @ (Package name path _) todo @ (stage, dist, settings) =
] &%> \_ -> do
need [argListPath argListDir pkg stage, cabal]
when (doesFileExist $ configure <.> "ac") $ need [configure]
- terseRun GhcCabal $ cabalArgs pkg todo
+ run GhcCabal $ cabalArgs pkg todo
when (registerPackage settings) $
- terseRun (GhcPkg stage) $ ghcPkgArgs pkg todo
+ run (GhcPkg stage) $ ghcPkgArgs pkg todo
postProcessPackageData $ pathDist </> "package-data.mk"
argListRule :: Package -> TodoItem -> Rules ()
diff --git a/src/Package/Dependencies.hs b/src/Package/Dependencies.hs
index 31c8d92..d1a8a14 100644
--- a/src/Package/Dependencies.hs
+++ b/src/Package/Dependencies.hs
@@ -63,12 +63,7 @@ buildRule pkg @ (Package name path _) todo @ (stage, dist, settings) = do
(buildDir </> "haskell.deps") %> \out -> do
need [argListPath argListDir pkg stage]
- terseRun (Ghc stage) $ ghcArgs pkg todo
- -- Avoid rebuilding dependecies of out if it hasn't changed:
- -- Note: cannot use copyFileChanged as it depends on the source file
- --deps <- liftIO $ readFile $ out <.> "new"
- --writeFileChanged out deps
- --liftIO $ removeFiles "." [out <.> "new"]
+ run (Ghc stage) $ ghcArgs pkg todo
(buildDir </> "c.deps") %> \out -> do
need [argListPath argListDir pkg stage]
@@ -76,7 +71,7 @@ buildRule pkg @ (Package name path _) todo @ (stage, dist, settings) = do
deps <- fmap concat $ forM srcs $ \src -> do
let srcPath = path </> src
depFile = buildDir </> takeFileName src <.> "deps"
- terseRun (Gcc stage) $ gccArgs srcPath pkg todo
+ run (Gcc stage) $ gccArgs srcPath pkg todo
liftIO $ readFile depFile
writeFileChanged out deps
liftIO $ removeFiles buildDir ["*.c.deps"]
diff --git a/src/Package/Library.hs b/src/Package/Library.hs
index 2b82260..e5fa0b8 100644
--- a/src/Package/Library.hs
+++ b/src/Package/Library.hs
@@ -25,7 +25,7 @@ arRule pkg @ (Package _ path _) todo @ (stage, dist, _) =
-- Splitting argument list into chunks as otherwise Ar chokes up
maxChunk <- argSizeLimit
forM_ (chunksOfSize maxChunk $ libHsObjs ++ cObjs) $ \os -> do
- terseRun Ar $ arArgs os $ toStandard out
+ run Ar $ arArgs os $ toStandard out
ldArgs :: Package -> TodoItem -> FilePath -> Args
ldArgs (Package _ path _) (stage, dist, _) result = do
@@ -45,7 +45,7 @@ ldRule pkg @ (Package name path _) todo @ (stage, dist, _) =
in
priority 2 $ (buildDir </> "*.o") %> \out -> do
need [argListPath argListDir pkg stage]
- terseRun Ld $ ldArgs pkg todo $ toStandard out
+ run Ld $ ldArgs pkg todo $ toStandard out
synopsis <- dropWhileEnd isPunctuation <$> showArg (Synopsis pathDist)
putColoured Green $ "/--------\n| Successfully built package "
++ name ++ " (stage " ++ show stage ++ ")."
More information about the ghc-commits
mailing list