git-annex/Utility/Directory.hs

223 lines
6.9 KiB
Haskell
Raw Normal View History

{- directory traversal and manipulation
-
2020-03-05 17:56:39 +00:00
- Copyright 2011-2020 Joey Hess <id@joeyh.name>
-
- License: BSD-2-clause
-}
{-# LANGUAGE CPP #-}
2020-03-05 17:56:39 +00:00
{-# LANGUAGE LambdaCase #-}
{-# OPTIONS_GHC -fno-warn-tabs #-}
module Utility.Directory (
module Utility.Directory,
module Utility.SystemDirectory
) where
import System.IO.Error
2011-12-09 05:57:13 +00:00
import Control.Monad
2012-03-11 22:12:36 +00:00
import System.FilePath
import System.PosixCompat.Files
2012-03-11 22:12:36 +00:00
import Control.Applicative
2012-05-31 23:25:33 +00:00
import System.IO.Unsafe (unsafeInterleaveIO)
2020-03-05 17:56:39 +00:00
import System.IO.Error
import Data.Maybe
import Prelude
#ifndef mingw32_HOST_OS
2015-08-03 19:54:29 +00:00
import Utility.SafeCommand
import Control.Monad.IfElse
#endif
import Utility.SystemDirectory
2020-03-05 17:56:39 +00:00
import Utility.Path
2013-05-12 23:19:28 +00:00
import Utility.Tmp
import Utility.Exception
2012-04-22 03:32:33 +00:00
import Utility.Monad
import Utility.Applicative
2020-03-05 17:56:39 +00:00
import Utility.PartialPrelude
2012-05-31 23:25:33 +00:00
dirCruft :: FilePath -> Bool
dirCruft "." = True
dirCruft ".." = True
dirCruft _ = False
2012-03-11 22:12:36 +00:00
{- Lists the contents of a directory.
- Unlike getDirectoryContents, paths are not relative to the directory. -}
dirContents :: FilePath -> IO [FilePath]
2012-05-31 23:25:33 +00:00
dirContents d = map (d </>) . filter (not . dirCruft) <$> getDirectoryContents d
2012-06-18 16:53:57 +00:00
{- Gets files in a directory, and then its subdirectories, recursively,
- and lazily.
-
- Does not follow symlinks to other subdirectories.
-
- When the directory does not exist, no exception is thrown,
- instead, [] is returned. -}
2012-05-31 23:25:33 +00:00
dirContentsRecursive :: FilePath -> IO [FilePath]
2014-04-26 23:25:05 +00:00
dirContentsRecursive = dirContentsRecursiveSkipping (const False) True
2012-05-31 23:25:33 +00:00
2013-10-07 17:03:05 +00:00
{- Skips directories whose basenames match the skipdir. -}
dirContentsRecursiveSkipping :: (FilePath -> Bool) -> Bool -> FilePath -> IO [FilePath]
dirContentsRecursiveSkipping skipdir followsubdirsymlinks topdir = go [topdir]
2012-12-13 04:24:19 +00:00
where
go [] = return []
2013-10-05 19:36:09 +00:00
go (dir:dirs)
2013-10-07 17:03:05 +00:00
| skipdir (takeFileName dir) = go dirs
2013-10-05 19:36:09 +00:00
| otherwise = unsafeInterleaveIO $ do
(files, dirs') <- collect [] []
=<< catchDefaultIO [] (dirContents dir)
files' <- go (dirs' ++ dirs)
return (files ++ files')
2012-12-13 04:24:19 +00:00
collect files dirs' [] = return (reverse files, reverse dirs')
collect files dirs' (entry:entries)
| dirCruft entry = collect files dirs' entries
| otherwise = do
2013-12-18 19:20:26 +00:00
let skip = collect (entry:files) dirs' entries
let recurse = collect files (entry:dirs') entries
ms <- catchMaybeIO $ getSymbolicLinkStatus entry
case ms of
2013-12-18 19:20:26 +00:00
(Just s)
| isDirectory s -> recurse
| isSymbolicLink s && followsubdirsymlinks ->
ifM (doesDirectoryExist entry)
( recurse
, skip
)
_ -> skip
2012-03-11 22:12:36 +00:00
{- Gets the directory tree from a point, recursively and lazily,
- with leaf directories **first**, skipping any whose basenames
- match the skipdir. Does not follow symlinks. -}
dirTreeRecursiveSkipping :: (FilePath -> Bool) -> FilePath -> IO [FilePath]
dirTreeRecursiveSkipping skipdir topdir = go [] [topdir]
where
go c [] = return c
go c (dir:dirs)
| skipdir (takeFileName dir) = go c dirs
| otherwise = unsafeInterleaveIO $ do
subdirs <- go []
=<< filterM (isDirectory <$$> getSymbolicLinkStatus)
=<< catchDefaultIO [] (dirContents dir)
go (subdirs++dir:c) dirs
{- 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
2012-12-13 04:24:19 +00:00
where
onrename (Right _) = noop
onrename (Left e)
| isPermissionError e = rethrow
| isDoesNotExistError e = rethrow
| otherwise = viaTmp mv dest ""
2012-12-13 04:24:19 +00:00
where
rethrow = throwM e
2012-12-13 04:24:19 +00:00
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
2012-12-13 04:24:19 +00:00
ok <- boolSystem "mv" [Param "-f", Param src, Param tmp]
let e' = e
#else
r <- tryIO $ copyFile src tmp
let (ok, e') = case r of
2015-08-03 19:54:29 +00:00
Left err -> (False, err)
Right _ -> (True, e)
#endif
2012-12-13 04:24:19 +00:00
unless ok $ do
-- delete any partial
_ <- tryIO $ removeFile tmp
throwM e'
2012-12-13 04:24:19 +00:00
2015-12-28 17:05:08 +00:00
#ifndef mingw32_HOST_OS
2012-12-13 04:24:19 +00:00
isdir f = do
r <- tryIO $ getFileStatus f
case r of
(Left _) -> return False
(Right s) -> return $ isDirectory s
2015-12-28 17:05:08 +00:00
#endif
Clean up handling of git directory and git worktree. Baked into the code was an assumption that a repository's git directory could be determined by adding ".git" to its work tree (or nothing for bare repos). That fails when core.worktree, or GIT_DIR and GIT_WORK_TREE are used to separate the two. This was attacked at the type level, by storing the gitdir and worktree separately, so Nothing for the worktree means a bare repo. A complication arose because we don't learn where a repository is bare until its configuration is read. So another Location type handles repositories that have not had their config read yet. I am not entirely happy with this being a Location type, rather than representing them entirely separate from the Git type. The new code is not worse than the old, but better types could enforce more safety. Added support for core.worktree. Overriding it with -c isn't supported because it's not really clear what to do if a git repo's config is read, is not bare, and is then overridden to bare. What is the right git directory in this case? I will worry about this if/when someone has a use case for overriding core.worktree with -c. (See Git.Config.updateLocation) Also removed and renamed some functions like gitDir and workTree that misused git's terminology. One minor regression is known: git annex add in a bare repository does not print a nice error message, but runs git ls-files in a way that fails earlier with a less nice error message. This is because before --work-tree was always passed to git commands, even in a bare repo, while now it's not.
2012-05-18 20:38:26 +00:00
{- Removes a file, which may or may not exist, and does not have to
- be a regular file.
2012-06-06 17:13:13 +00:00
-
- 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
2020-03-05 17:56:39 +00:00
{- Like createDirectoryIfMissing True, but it will only create
- missing parent directories up to but not including the directory
- in the first parameter.
-
- For example, createDirectoryUnder "/tmp/foo" "/tmp/foo/bar/baz"
- will create /tmp/foo/bar if necessary, but if /tmp/foo does not exist,
- it will throw an exception.
-
- The exception thrown is the same that createDirectory throws if the
- parent directory does not exist.
-
- If the second FilePath is not under the first
- FilePath (or the same as it), it will fail with an exception
- even if the second FilePath's parent directory already exists.
-
- Either or both of the FilePaths can be relative, or absolute.
- They will be normalized as necessary.
-
- Note that, the second FilePath, if relative, is relative to the current
- working directory, not to the first FilePath.
-}
createDirectoryUnder :: FilePath -> FilePath -> IO ()
createDirectoryUnder topdir dir0 = do
p <- relPathDirToFile topdir dir0
let dirs = splitDirectories p
-- Catch cases where the dir is not beneath the topdir.
-- If the relative path between them starts with "..",
-- it's not. And on Windows, if they are on different drives,
-- the path will not be relative.
if headMaybe dirs == Just ".." || isAbsolute p
then ioError $ customerror userErrorType
("createDirectoryFrom: not located in " ++ topdir)
-- If dir0 is the same as the topdir, don't try to create
-- it, but make sure it does exist.
else if null dirs
then unlessM (doesDirectoryExist topdir) $
ioError $ customerror doesNotExistErrorType
"createDirectoryFrom: does not exist"
else createdirs $
map (topdir </>) (reverse (scanl1 (</>) dirs))
where
customerror t s = mkIOError t s Nothing (Just dir0)
createdirs [] = pure ()
createdirs (dir:[]) = createdir dir ioError
createdirs (dir:dirs) = createdir dir $ \_ -> do
createdirs dirs
createdir dir ioError
-- This is the same method used by createDirectoryIfMissing,
-- in particular the handling of errors that occur when the
-- directory already exists. See its source for explanation
-- of several subtleties.
createdir dir notexisthandler = tryIOError (createDirectory dir) >>= \case
Right () -> pure ()
Left e
| isDoesNotExistError e -> notexisthandler e
| isAlreadyExistsError e || isPermissionError e -> do
unlessM (doesDirectoryExist dir) $
ioError e
| otherwise -> ioError e