[commit: ghc] wip/nfs-locking: Add removeDirectory to Rules/Actions, seems to fit (db11fb0)

git at git.haskell.org git at git.haskell.org
Thu Oct 26 23:50:55 UTC 2017


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

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

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

commit db11fb04e50c4cc46a2e3286adf0b67acbc82b47
Author: Neil Mitchell <ndmitchell at gmail.com>
Date:   Tue Jan 12 22:33:21 2016 +0000

    Add removeDirectory to Rules/Actions, seems to fit


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

db11fb04e50c4cc46a2e3286adf0b67acbc82b47
 src/Rules/Actions.hs | 7 ++++++-
 1 file changed, 6 insertions(+), 1 deletion(-)

diff --git a/src/Rules/Actions.hs b/src/Rules/Actions.hs
index 0600d82..a968160 100644
--- a/src/Rules/Actions.hs
+++ b/src/Rules/Actions.hs
@@ -1,6 +1,6 @@
 {-# LANGUAGE RecordWildCards #-}
 module Rules.Actions (
-    build, buildWithResources, copyFile, createDirectory, moveDirectory,
+    build, buildWithResources, copyFile, createDirectory, removeDirectory, moveDirectory,
     fixFile, runConfigure, runMake, runBuilder, makeExecutable
     ) where
 
@@ -74,6 +74,11 @@ createDirectory dir = do
     putBuild $ "| Create directory " ++ dir
     liftIO $ IO.createDirectoryIfMissing True dir
 
+removeDirectory :: FilePath -> Action ()
+removeDirectory dir = do
+    putBuild $ "| Remove directory " ++ dir
+    liftIO $ IO.removeDirectoryRecursive dir
+
 -- Note, the source directory is untracked
 moveDirectory :: FilePath -> FilePath -> Action ()
 moveDirectory source target = do



More information about the ghc-commits mailing list