module Darcs.Util.File
(
getFileStatus
, doesDirectoryReallyExist
, removeFileMayNotExist
, getRecursiveContents
, getRecursiveContentsFullPath
, copyTree
, fetchFilePS
, fetchFileLazyPS
, gzFetchFilePS
, speculateFileOrUrl
, copyFileOrUrl
, Cachable(..)
, backupByRenaming
, backupByCopying
, withTemp
, withOpenTemp
) where
import Darcs.Prelude
import Darcs.Util.ByteString ( gzReadFilePS )
import Darcs.Util.Exception ( catchall, ifDoesNotExistError )
import Darcs.Util.Global ( defaultRemoteDarcsCmd )
import Darcs.Util.HTTP ( Cachable(..) )
import qualified Darcs.Util.HTTP as HTTP
import Darcs.Util.Path ( FilePathLike, toFilePath )
import Darcs.Util.Ssh ( copySSH )
import Darcs.Util.URL ( isHttpUrl, isSshUrl, isValidLocalPath, splitSshUrl )
import Control.Exception ( IOException, bracket, catch )
import Control.Monad ( forM, unless, when, zipWithM_ )
import qualified Data.ByteString as B ( ByteString, readFile )
import qualified Data.ByteString.Lazy as BL
import Network.URI ( parseURI, uriScheme )
import System.Directory
( copyFile
, createDirectory
, doesDirectoryExist
, doesFileExist
, listDirectory
, removeFile
, renameDirectory
, renameFile
)
import System.FilePath.Posix ( normalise, (</>) )
import System.IO ( Handle, hClose, openBinaryTempFile )
import System.IO.Error ( catchIOError, isDoesNotExistError )
import System.Posix.Files
( FileStatus
, createLink
, getSymbolicLinkStatus
, isDirectory
, isRegularFile
)
getFileStatus :: FilePath -> IO (Maybe FileStatus)
getFileStatus :: String -> IO (Maybe FileStatus)
getFileStatus String
f =
FileStatus -> Maybe FileStatus
forall a. a -> Maybe a
Just (FileStatus -> Maybe FileStatus)
-> IO FileStatus -> IO (Maybe FileStatus)
forall a b. (a -> b) -> IO a -> IO b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
`fmap` String -> IO FileStatus
getSymbolicLinkStatus String
f IO (Maybe FileStatus)
-> (IOError -> IO (Maybe FileStatus)) -> IO (Maybe FileStatus)
forall a. IO a -> (IOError -> IO a) -> IO a
`catchIOError` (\IOError
_-> Maybe FileStatus -> IO (Maybe FileStatus)
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Maybe FileStatus
forall a. Maybe a
Nothing)
doesDirectoryReallyExist :: FilePath -> IO Bool
doesDirectoryReallyExist :: String -> IO Bool
doesDirectoryReallyExist String
f =
Bool -> IO Bool -> IO Bool
forall a. a -> IO a -> IO a
ifDoesNotExistError Bool
False (FileStatus -> Bool
isDirectory (FileStatus -> Bool) -> IO FileStatus -> IO Bool
forall a b. (a -> b) -> IO a -> IO b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
`fmap` String -> IO FileStatus
getSymbolicLinkStatus String
f)
removeFileMayNotExist :: FilePathLike p => p -> IO ()
removeFileMayNotExist :: forall p. FilePathLike p => p -> IO ()
removeFileMayNotExist p
f = () -> IO () -> IO ()
forall a. a -> IO a -> IO a
ifDoesNotExistError () (String -> IO ()
removeFile (String -> IO ()) -> String -> IO ()
forall a b. (a -> b) -> a -> b
$ p -> String
forall a. FilePathLike a => a -> String
toFilePath p
f)
getRecursiveContents :: FilePath -> IO [FilePath]
getRecursiveContents :: String -> IO [String]
getRecursiveContents String
topdir = do
[String]
entries <- String -> IO [String]
listDirectory String
topdir
[[String]]
paths <- [String] -> (String -> IO [String]) -> IO [[String]]
forall (t :: * -> *) (m :: * -> *) a b.
(Traversable t, Monad m) =>
t a -> (a -> m b) -> m (t b)
forM [String]
entries ((String -> IO [String]) -> IO [[String]])
-> (String -> IO [String]) -> IO [[String]]
forall a b. (a -> b) -> a -> b
$ \String
name -> do
let path :: String
path = String
topdir String -> String -> String
</> String
name
Bool
isDir <- String -> IO Bool
doesDirectoryExist String
path
if Bool
isDir
then String -> IO [String]
getRecursiveContents String
path
else [String] -> IO [String]
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return [String
name]
[String] -> IO [String]
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return ([[String]] -> [String]
forall (t :: * -> *) a. Foldable t => t [a] -> [a]
concat [[String]]
paths)
getRecursiveContentsFullPath :: FilePath -> IO [FilePath]
getRecursiveContentsFullPath :: String -> IO [String]
getRecursiveContentsFullPath String
topdir = do
[String]
entries <- String -> IO [String]
listDirectory String
topdir
[[String]]
paths <- [String] -> (String -> IO [String]) -> IO [[String]]
forall (t :: * -> *) (m :: * -> *) a b.
(Traversable t, Monad m) =>
t a -> (a -> m b) -> m (t b)
forM [String]
entries ((String -> IO [String]) -> IO [[String]])
-> (String -> IO [String]) -> IO [[String]]
forall a b. (a -> b) -> a -> b
$ \String
name -> do
let path :: String
path = String
topdir String -> String -> String
</> String
name
Bool
isDir <- String -> IO Bool
doesDirectoryExist String
path
if Bool
isDir
then String -> IO [String]
getRecursiveContentsFullPath String
path
else [String] -> IO [String]
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return [String
path]
[String] -> IO [String]
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return ([[String]] -> [String]
forall (t :: * -> *) a. Foldable t => t [a] -> [a]
concat [[String]]
paths)
copyFileOrUrl :: String
-> String
-> FilePath
-> Cachable
-> IO ()
copyFileOrUrl :: String -> String -> String -> Cachable -> IO ()
copyFileOrUrl String
_ String
fou String
out Cachable
_ | String -> Bool
isValidLocalPath String
fou = String -> String -> IO ()
copyLocal String
fou String
out
copyFileOrUrl String
_ String
fou String
out Cachable
cache | String -> Bool
isHttpUrl String
fou = String -> String -> Cachable -> IO ()
HTTP.copyRemote String
fou String
out Cachable
cache
copyFileOrUrl String
rd String
fou String
out Cachable
_ | String -> Bool
isSshUrl String
fou = String -> SshFilePath -> String -> IO ()
copySSH String
rd (String -> SshFilePath
splitSshUrl String
fou) String
out
copyFileOrUrl String
_ String
fou String
_ Cachable
_ = String -> IO ()
forall a. String -> IO a
forall (m :: * -> *) a. MonadFail m => String -> m a
fail (String -> IO ()) -> String -> IO ()
forall a b. (a -> b) -> a -> b
$ String
"unknown transport protocol: " String -> String -> String
forall a. [a] -> [a] -> [a]
++ String
fou
copyLocal :: String -> FilePath -> IO ()
copyLocal :: String -> String -> IO ()
copyLocal String
fou String
out = String -> String -> IO ()
createLink String
fou String
out IO () -> IO () -> IO ()
forall a. IO a -> IO a -> IO a
`catchall` String -> String -> IO ()
copyFile String
fou String
out
copyTree :: FilePath -> FilePath -> IO ()
copyTree :: String -> String -> IO ()
copyTree String
source String
dest =
do FileStatus
fs <- String -> IO FileStatus
getSymbolicLinkStatus String
source
if FileStatus -> Bool
isDirectory FileStatus
fs then do
[String]
fps <- String -> IO [String]
listDirectory String
source
(String -> String -> IO ()) -> [String] -> [String] -> IO ()
forall (m :: * -> *) a b c.
Applicative m =>
(a -> b -> m c) -> [a] -> [b] -> m ()
zipWithM_ String -> String -> IO ()
copySubTree ((String -> String) -> [String] -> [String]
forall a b. (a -> b) -> [a] -> [b]
map (String
source String -> String -> String
</>) [String]
fps) ((String -> String) -> [String] -> [String]
forall a b. (a -> b) -> [a] -> [b]
map (String
dest String -> String -> String
</>) [String]
fps)
else String -> IO ()
forall a. String -> IO a
forall (m :: * -> *) a. MonadFail m => String -> m a
fail (String
"copyTree: Bad source " String -> String -> String
forall a. [a] -> [a] -> [a]
++ String
source)
IO () -> (IOError -> IO ()) -> IO ()
forall e a. Exception e => IO a -> (e -> IO a) -> IO a
`catch` \(IOError
_ :: IOException) -> String -> IO ()
forall a. String -> IO a
forall (m :: * -> *) a. MonadFail m => String -> m a
fail (String
"copyTree: Bad source " String -> String -> String
forall a. [a] -> [a] -> [a]
++ String
source)
copySubTree :: FilePath -> FilePath -> IO ()
copySubTree :: String -> String -> IO ()
copySubTree String
source String
dest =
do FileStatus
fs <- String -> IO FileStatus
getSymbolicLinkStatus String
source
if FileStatus -> Bool
isDirectory FileStatus
fs then do
String -> IO ()
createDirectory String
dest
[String]
fps <- String -> IO [String]
listDirectory String
source
(String -> String -> IO ()) -> [String] -> [String] -> IO ()
forall (m :: * -> *) a b c.
Applicative m =>
(a -> b -> m c) -> [a] -> [b] -> m ()
zipWithM_ String -> String -> IO ()
copySubTree ((String -> String) -> [String] -> [String]
forall a b. (a -> b) -> [a] -> [b]
map (String
source String -> String -> String
</>) [String]
fps) ((String -> String) -> [String] -> [String]
forall a b. (a -> b) -> [a] -> [b]
map (String
dest String -> String -> String
</>) [String]
fps)
else if FileStatus -> Bool
isRegularFile FileStatus
fs then
String -> String -> IO ()
copyFile String
source String
dest
else String -> IO ()
forall a. String -> IO a
forall (m :: * -> *) a. MonadFail m => String -> m a
fail (String
"copySubTree: Bad source "String -> String -> String
forall a. [a] -> [a] -> [a]
++ String
source)
IO () -> (IOError -> IO ()) -> IO ()
forall e a. Exception e => IO a -> (e -> IO a) -> IO a
`catch` (\IOError
e -> Bool -> IO () -> IO ()
forall (f :: * -> *). Applicative f => Bool -> f () -> f ()
unless (IOError -> Bool
isDoesNotExistError IOError
e) (IO () -> IO ()) -> IO () -> IO ()
forall a b. (a -> b) -> a -> b
$ IOError -> IO ()
forall a. IOError -> IO a
ioError IOError
e)
backupByRenaming :: FilePath -> IO ()
backupByRenaming :: String -> IO ()
backupByRenaming = (String -> String -> IO ()) -> String -> IO ()
backupBy String -> String -> IO ()
rename
where rename :: String -> String -> IO ()
rename String
x String
y = do
Bool
isD <- String -> IO Bool
doesDirectoryExist String
x
if Bool
isD then String -> String -> IO ()
renameDirectory String
x String
y else String -> String -> IO ()
renameFile String
x String
y
backupByCopying :: FilePath -> IO ()
backupByCopying :: String -> IO ()
backupByCopying = (String -> String -> IO ()) -> String -> IO ()
backupBy String -> String -> IO ()
copy
where
copy :: String -> String -> IO ()
copy String
x String
y = do
Bool
isD <- String -> IO Bool
doesDirectoryExist String
x
if Bool
isD then do String -> IO ()
createDirectory String
y
String -> String -> IO ()
copyTree (String -> String
normalise String
x) (String -> String
normalise String
y)
else String -> String -> IO ()
copyFile String
x String
y
backupBy :: (FilePath -> FilePath -> IO ()) -> FilePath -> IO ()
backupBy :: (String -> String -> IO ()) -> String -> IO ()
backupBy String -> String -> IO ()
backup String
f =
do Bool
hasBF <- String -> IO Bool
doesFileExist String
f
Bool
hasBD <- String -> IO Bool
doesDirectoryExist String
f
Bool -> IO () -> IO ()
forall (f :: * -> *). Applicative f => Bool -> f () -> f ()
when (Bool
hasBF Bool -> Bool -> Bool
|| Bool
hasBD) (IO () -> IO ()) -> IO () -> IO ()
forall a b. (a -> b) -> a -> b
$ Int -> IO ()
helper Int
0
where
helper :: Int -> IO ()
helper :: Int -> IO ()
helper Int
i = do Bool
existsF <- String -> IO Bool
doesFileExist String
next
Bool
existsD <- String -> IO Bool
doesDirectoryExist String
next
if Bool
existsF Bool -> Bool -> Bool
|| Bool
existsD
then Int -> IO ()
helper (Int
i Int -> Int -> Int
forall a. Num a => a -> a -> a
+ Int
1)
else do String -> IO ()
putStrLn (String -> IO ()) -> String -> IO ()
forall a b. (a -> b) -> a -> b
$ String
"Backing up " String -> String -> String
forall a. [a] -> [a] -> [a]
++ String
f String -> String -> String
forall a. [a] -> [a] -> [a]
++ String
"(" String -> String -> String
forall a. [a] -> [a] -> [a]
++ String
suffix String -> String -> String
forall a. [a] -> [a] -> [a]
++ String
")"
String -> String -> IO ()
backup String
f String
next
where next :: String
next = String
f String -> String -> String
forall a. [a] -> [a] -> [a]
++ String
suffix
suffix :: String
suffix = String
".~" String -> String -> String
forall a. [a] -> [a] -> [a]
++ Int -> String
forall a. Show a => a -> String
show Int
i String -> String -> String
forall a. [a] -> [a] -> [a]
++ String
"~"
copyAndReadFile :: (FilePath -> IO a) -> String -> Cachable -> IO a
copyAndReadFile :: forall a. (String -> IO a) -> String -> Cachable -> IO a
copyAndReadFile String -> IO a
readfn String
fou Cachable
_ | String -> Bool
isValidLocalPath String
fou = String -> IO a
readfn String
fou
copyAndReadFile String -> IO a
readfn String
fou Cachable
cache = (String -> IO a) -> IO a
forall a. (String -> IO a) -> IO a
withTemp ((String -> IO a) -> IO a) -> (String -> IO a) -> IO a
forall a b. (a -> b) -> a -> b
$ \String
t -> do
String -> String -> String -> Cachable -> IO ()
copyFileOrUrl String
defaultRemoteDarcsCmd String
fou String
t Cachable
cache
String -> IO a
readfn String
t
fetchFilePS :: String -> Cachable -> IO B.ByteString
fetchFilePS :: String -> Cachable -> IO ByteString
fetchFilePS = (String -> IO ByteString) -> String -> Cachable -> IO ByteString
forall a. (String -> IO a) -> String -> Cachable -> IO a
copyAndReadFile String -> IO ByteString
B.readFile
fetchFileLazyPS :: String -> Cachable -> IO BL.ByteString
fetchFileLazyPS :: String -> Cachable -> IO ByteString
fetchFileLazyPS String
x Cachable
c =
case String -> Maybe URI
parseURI String
x of
Just URI
x'
| let s :: String
s = URI -> String
uriScheme URI
x'
, String
s String -> String -> Bool
forall a. Eq a => a -> a -> Bool
== String
"http:" Bool -> Bool -> Bool
|| String
s String -> String -> Bool
forall a. Eq a => a -> a -> Bool
== String
"https:" -> String -> Cachable -> IO ByteString
HTTP.copyRemoteLazy String
x Cachable
c
Maybe URI
_ -> (String -> IO ByteString) -> String -> Cachable -> IO ByteString
forall a. (String -> IO a) -> String -> Cachable -> IO a
copyAndReadFile String -> IO ByteString
BL.readFile String
x Cachable
c
gzFetchFilePS :: String -> Cachable -> IO B.ByteString
gzFetchFilePS :: String -> Cachable -> IO ByteString
gzFetchFilePS = (String -> IO ByteString) -> String -> Cachable -> IO ByteString
forall a. (String -> IO a) -> String -> Cachable -> IO a
copyAndReadFile String -> IO ByteString
gzReadFilePS
speculateFileOrUrl :: String -> FilePath -> IO ()
speculateFileOrUrl :: String -> String -> IO ()
speculateFileOrUrl String
fou String
out
| String -> Bool
isHttpUrl String
fou = String -> String -> IO ()
HTTP.speculateRemote String
fou String
out
| Bool
otherwise = () -> IO ()
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return ()
withTemp :: (FilePath -> IO a) -> IO a
withTemp :: forall a. (String -> IO a) -> IO a
withTemp = IO String -> (String -> IO ()) -> (String -> IO a) -> IO a
forall a b c. IO a -> (a -> IO b) -> (a -> IO c) -> IO c
bracket IO String
get_empty_file String -> IO ()
forall p. FilePathLike p => p -> IO ()
removeFileMayNotExist
where
get_empty_file :: IO String
get_empty_file = do
(String
f, Handle
h) <- String -> String -> IO (String, Handle)
openBinaryTempFile String
"." String
"darcs"
Handle -> IO ()
hClose Handle
h IO () -> IO () -> IO ()
forall a. IO a -> IO a -> IO a
`catchall` () -> IO ()
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return ()
String -> IO String
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return String
f
withOpenTemp :: ((Handle, FilePath) -> IO a) -> IO a
withOpenTemp :: forall a. ((Handle, String) -> IO a) -> IO a
withOpenTemp = IO (Handle, String)
-> ((Handle, String) -> IO ())
-> ((Handle, String) -> IO a)
-> IO a
forall a b c. IO a -> (a -> IO b) -> (a -> IO c) -> IO c
bracket IO (Handle, String)
get_empty_file (Handle, String) -> IO ()
forall {p}. FilePathLike p => (Handle, p) -> IO ()
cleanup
where
cleanup :: (Handle, p) -> IO ()
cleanup (Handle
h, p
f) = do
Handle -> IO ()
hClose Handle
h IO () -> IO () -> IO ()
forall a. IO a -> IO a -> IO a
`catchall` () -> IO ()
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return ()
p -> IO ()
forall p. FilePathLike p => p -> IO ()
removeFileMayNotExist p
f
get_empty_file :: IO (Handle, String)
get_empty_file = (String, Handle) -> (Handle, String)
forall {b} {a}. (b, a) -> (a, b)
swap ((String, Handle) -> (Handle, String))
-> IO (String, Handle) -> IO (Handle, String)
forall a b. (a -> b) -> IO a -> IO b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
`fmap` String -> String -> IO (String, Handle)
openBinaryTempFile String
"." String
"darcs"
swap :: (b, a) -> (a, b)
swap (b
a, a
b) = (a
b, b
a)