summaryrefslogtreecommitdiff
path: root/Utility/Directory.hs
diff options
context:
space:
mode:
Diffstat (limited to 'Utility/Directory.hs')
-rw-r--r--Utility/Directory.hs81
1 files changed, 13 insertions, 68 deletions
diff --git a/Utility/Directory.hs b/Utility/Directory.hs
index e2c6a94..a5c023f 100644
--- a/Utility/Directory.hs
+++ b/Utility/Directory.hs
@@ -1,11 +1,12 @@
{- directory traversal and manipulation
-
- - Copyright 2011-2014 Joey Hess <id@joeyh.name>
+ - Copyright 2011-2020 Joey Hess <id@joeyh.name>
-
- License: BSD-2-clause
-}
{-# LANGUAGE CPP #-}
+{-# LANGUAGE LambdaCase #-}
{-# OPTIONS_GHC -fno-warn-tabs #-}
module Utility.Directory (
@@ -13,25 +14,19 @@ module Utility.Directory (
module Utility.SystemDirectory
) where
-import System.IO.Error
import Control.Monad
import System.FilePath
-import System.PosixCompat.Files
+import System.PosixCompat.Files (isDirectory, isSymbolicLink)
import Control.Applicative
import System.IO.Unsafe (unsafeInterleaveIO)
import Data.Maybe
import Prelude
-#ifndef mingw32_HOST_OS
-import Utility.SafeCommand
-import Control.Monad.IfElse
-#endif
-
import Utility.SystemDirectory
-import Utility.Tmp
import Utility.Exception
import Utility.Monad
-import Utility.Applicative
+import Utility.FileSystemEncoding
+import qualified Utility.RawFilePath as R
dirCruft :: FilePath -> Bool
dirCruft "." = True
@@ -71,7 +66,7 @@ dirContentsRecursiveSkipping skipdir followsubdirsymlinks topdir = go [topdir]
| otherwise = do
let skip = collect (entry:files) dirs' entries
let recurse = collect files (entry:dirs') entries
- ms <- catchMaybeIO $ getSymbolicLinkStatus entry
+ ms <- catchMaybeIO $ R.getSymbolicLinkStatus (toRawFilePath entry)
case ms of
(Just s)
| isDirectory s -> recurse
@@ -93,64 +88,14 @@ dirTreeRecursiveSkipping skipdir topdir = go [] [topdir]
| skipdir (takeFileName dir) = go c dirs
| otherwise = unsafeInterleaveIO $ do
subdirs <- go []
- =<< filterM (isDirectory <$$> getSymbolicLinkStatus)
+ =<< filterM isdir
=<< catchDefaultIO [] (dirContents dir)
go (subdirs++dir:c) dirs
+ isdir p = isDirectory <$> R.getSymbolicLinkStatus (toRawFilePath p)
-{- Moves one filename to another.
- - First tries a rename, but falls back to moving across devices if needed. -}
-moveFile :: FilePath -> FilePath -> IO ()
-moveFile src dest = tryIO (rename src dest) >>= onrename
- where
- onrename (Right _) = noop
- onrename (Left e)
- | isPermissionError e = rethrow
- | isDoesNotExistError e = rethrow
- | otherwise = viaTmp mv dest ""
- where
- rethrow = throwM e
-
- mv tmp _ = do
- -- copyFile is likely not as optimised as
- -- the mv command, so we'll use the command.
- --
- -- But, while Windows has a "mv", it does not seem very
- -- reliable, so use copyFile there.
-#ifndef mingw32_HOST_OS
- -- If dest is a directory, mv would move the file
- -- into it, which is not desired.
- whenM (isdir dest) rethrow
- ok <- boolSystem "mv" [Param "-f", Param src, Param tmp]
- let e' = e
-#else
- r <- tryIO $ copyFile src tmp
- let (ok, e') = case r of
- Left err -> (False, err)
- Right _ -> (True, e)
-#endif
- unless ok $ do
- -- delete any partial
- _ <- tryIO $ removeFile tmp
- throwM e'
-
-#ifndef mingw32_HOST_OS
- isdir f = do
- r <- tryIO $ getFileStatus f
- case r of
- (Left _) -> return False
- (Right s) -> return $ isDirectory s
-#endif
-
-{- Removes a file, which may or may not exist, and does not have to
- - be a regular file.
+{- Use with an action that removes something, which may or may not exist.
-
- - Note that an exception is thrown if the file exists but
- - cannot be removed. -}
-nukeFile :: FilePath -> IO ()
-nukeFile file = void $ tryWhenExists go
- where
-#ifndef mingw32_HOST_OS
- go = removeLink file
-#else
- go = removeFile file
-#endif
+ - If an exception is thrown due to it not existing, it is ignored.
+ -}
+removeWhenExistsWith :: (a -> IO ()) -> a -> IO ()
+removeWhenExistsWith f a = void $ tryWhenExists $ f a