[commit: ghc] wip/nfs-locking: Add copyDirectory to Rules.Actions. (63bbebf)
git at git.haskell.org
git at git.haskell.org
Fri Oct 27 00:47:23 UTC 2017
Repository : ssh://git@git.haskell.org/ghc
On branch : wip/nfs-locking
Link : http://ghc.haskell.org/trac/ghc/changeset/63bbebfdd0920959ed33d0bd8ffdf75cfb3640ac/ghc
>---------------------------------------------------------------
commit 63bbebfdd0920959ed33d0bd8ffdf75cfb3640ac
Author: Andrey Mokhov <andrey.mokhov at gmail.com>
Date: Sun Feb 7 01:13:05 2016 +0000
Add copyDirectory to Rules.Actions.
See #98.
>---------------------------------------------------------------
63bbebfdd0920959ed33d0bd8ffdf75cfb3640ac
src/Rules/Actions.hs | 10 ++++++++--
1 file changed, 8 insertions(+), 2 deletions(-)
diff --git a/src/Rules/Actions.hs b/src/Rules/Actions.hs
index daa4c5e..9275207 100644
--- a/src/Rules/Actions.hs
+++ b/src/Rules/Actions.hs
@@ -1,8 +1,8 @@
{-# LANGUAGE RecordWildCards #-}
module Rules.Actions (
build, buildWithResources, copyFile, createDirectory, removeDirectory,
- moveDirectory, fixFile, runConfigure, runMake, runMakeVerbose, applyPatch,
- renderLibrary, renderProgram, runBuilder, makeExecutable
+ copyDirectory, moveDirectory, applyPatch, fixFile, runConfigure, runMake,
+ runMakeVerbose, renderLibrary, renderProgram, runBuilder, makeExecutable
) where
import qualified System.Directory as IO
@@ -82,6 +82,12 @@ removeDirectory dir = do
removeDirectoryIfExists dir
-- Note, the source directory is untracked
+copyDirectory :: FilePath -> FilePath -> Action ()
+copyDirectory source target = do
+ putProgressInfo $ renderAction "Copy directory" source target
+ quietly $ cmd (EchoStdout False) ["cp", "-r", source, target]
+
+-- Note, the source directory is untracked
moveDirectory :: FilePath -> FilePath -> Action ()
moveDirectory source target = do
putProgressInfo $ renderAction "Move directory" source target
More information about the ghc-commits
mailing list