convert createAnnexDirectory to use createDirectoryUnder
It will create foo/.git/annex/, but not foo/.git/ and not foo/. This will avoid it creating an empty path to a repo when a drive is yanked out and the mount point goes away, for example.
This commit is contained in:
parent
5b022eea87
commit
ebbc5004fa
2 changed files with 30 additions and 25 deletions
|
@ -1,6 +1,6 @@
|
||||||
{- git-annex file permissions
|
{- git-annex file permissions
|
||||||
-
|
-
|
||||||
- Copyright 2012 Joey Hess <id@joeyh.name>
|
- Copyright 2012-2020 Joey Hess <id@joeyh.name>
|
||||||
-
|
-
|
||||||
- Licensed under the GNU AGPL version 3 or higher.
|
- Licensed under the GNU AGPL version 3 or higher.
|
||||||
-}
|
-}
|
||||||
|
@ -65,21 +65,16 @@ annexFileMode = withShared $ return . go
|
||||||
go _ = stdFileMode
|
go _ = stdFileMode
|
||||||
sharedmode = combineModes groupSharedModes
|
sharedmode = combineModes groupSharedModes
|
||||||
|
|
||||||
{- Creates a directory inside the gitAnnexDir, including any parent
|
{- Creates a directory inside the gitAnnexDir, creating any parent
|
||||||
- directories. Makes directories with appropriate permissions. -}
|
- directories up to and including the gitAnnexDir.
|
||||||
|
- Makes directories with appropriate permissions. -}
|
||||||
createAnnexDirectory :: FilePath -> Annex ()
|
createAnnexDirectory :: FilePath -> Annex ()
|
||||||
createAnnexDirectory dir = walk dir [] =<< top
|
createAnnexDirectory dir = do
|
||||||
|
top <- parentDir . fromRawFilePath <$> fromRepo gitAnnexDir
|
||||||
|
createDirectoryUnder' top dir createdir
|
||||||
where
|
where
|
||||||
top = parentDir . fromRawFilePath <$> fromRepo gitAnnexDir
|
createdir p = do
|
||||||
walk d below stop
|
liftIO $ createDirectory p
|
||||||
| d `equalFilePath` stop = done
|
|
||||||
| otherwise = ifM (liftIO $ doesDirectoryExist d)
|
|
||||||
( done
|
|
||||||
, walk (parentDir d) (d:below) stop
|
|
||||||
)
|
|
||||||
where
|
|
||||||
done = forM_ below $ \p -> do
|
|
||||||
liftIO $ createDirectoryIfMissing True p
|
|
||||||
setAnnexDirPerm p
|
setAnnexDirPerm p
|
||||||
|
|
||||||
{- Normally, blocks writing to an annexed file, and modifies file
|
{- Normally, blocks writing to an annexed file, and modifies file
|
||||||
|
|
|
@ -19,6 +19,7 @@ import Control.Monad
|
||||||
import System.FilePath
|
import System.FilePath
|
||||||
import System.PosixCompat.Files
|
import System.PosixCompat.Files
|
||||||
import Control.Applicative
|
import Control.Applicative
|
||||||
|
import Control.Monad.IO.Class
|
||||||
import System.IO.Unsafe (unsafeInterleaveIO)
|
import System.IO.Unsafe (unsafeInterleaveIO)
|
||||||
import System.IO.Error
|
import System.IO.Error
|
||||||
import Data.Maybe
|
import Data.Maybe
|
||||||
|
@ -181,20 +182,29 @@ nukeFile file = void $ tryWhenExists go
|
||||||
- working directory, not to the first FilePath.
|
- working directory, not to the first FilePath.
|
||||||
-}
|
-}
|
||||||
createDirectoryUnder :: FilePath -> FilePath -> IO ()
|
createDirectoryUnder :: FilePath -> FilePath -> IO ()
|
||||||
createDirectoryUnder topdir dir0 = do
|
createDirectoryUnder topdir dir =
|
||||||
p <- relPathDirToFile topdir dir0
|
createDirectoryUnder' topdir dir createDirectory
|
||||||
|
|
||||||
|
createDirectoryUnder'
|
||||||
|
:: (MonadIO m, MonadCatch m)
|
||||||
|
=> FilePath
|
||||||
|
-> FilePath
|
||||||
|
-> (FilePath -> m ())
|
||||||
|
-> m ()
|
||||||
|
createDirectoryUnder' topdir dir0 mkdir = do
|
||||||
|
p <- liftIO $ relPathDirToFile topdir dir0
|
||||||
let dirs = splitDirectories p
|
let dirs = splitDirectories p
|
||||||
-- Catch cases where the dir is not beneath the topdir.
|
-- Catch cases where the dir is not beneath the topdir.
|
||||||
-- If the relative path between them starts with "..",
|
-- If the relative path between them starts with "..",
|
||||||
-- it's not. And on Windows, if they are on different drives,
|
-- it's not. And on Windows, if they are on different drives,
|
||||||
-- the path will not be relative.
|
-- the path will not be relative.
|
||||||
if headMaybe dirs == Just ".." || isAbsolute p
|
if headMaybe dirs == Just ".." || isAbsolute p
|
||||||
then ioError $ customerror userErrorType
|
then liftIO $ ioError $ customerror userErrorType
|
||||||
("createDirectoryFrom: not located in " ++ topdir)
|
("createDirectoryFrom: not located in " ++ topdir)
|
||||||
-- If dir0 is the same as the topdir, don't try to create
|
-- If dir0 is the same as the topdir, don't try to create
|
||||||
-- it, but make sure it does exist.
|
-- it, but make sure it does exist.
|
||||||
else if null dirs
|
else if null dirs
|
||||||
then unlessM (doesDirectoryExist topdir) $
|
then liftIO $ unlessM (doesDirectoryExist topdir) $
|
||||||
ioError $ customerror doesNotExistErrorType
|
ioError $ customerror doesNotExistErrorType
|
||||||
"createDirectoryFrom: does not exist"
|
"createDirectoryFrom: does not exist"
|
||||||
else createdirs $
|
else createdirs $
|
||||||
|
@ -203,20 +213,20 @@ createDirectoryUnder topdir dir0 = do
|
||||||
customerror t s = mkIOError t s Nothing (Just dir0)
|
customerror t s = mkIOError t s Nothing (Just dir0)
|
||||||
|
|
||||||
createdirs [] = pure ()
|
createdirs [] = pure ()
|
||||||
createdirs (dir:[]) = createdir dir ioError
|
createdirs (dir:[]) = createdir dir (liftIO . ioError)
|
||||||
createdirs (dir:dirs) = createdir dir $ \_ -> do
|
createdirs (dir:dirs) = createdir dir $ \_ -> do
|
||||||
createdirs dirs
|
createdirs dirs
|
||||||
createdir dir ioError
|
createdir dir (liftIO . ioError)
|
||||||
|
|
||||||
-- This is the same method used by createDirectoryIfMissing,
|
-- This is the same method used by createDirectoryIfMissing,
|
||||||
-- in particular the handling of errors that occur when the
|
-- in particular the handling of errors that occur when the
|
||||||
-- directory already exists. See its source for explanation
|
-- directory already exists. See its source for explanation
|
||||||
-- of several subtleties.
|
-- of several subtleties.
|
||||||
createdir dir notexisthandler = tryIOError (createDirectory dir) >>= \case
|
createdir dir notexisthandler = tryIO (mkdir dir) >>= \case
|
||||||
Right () -> pure ()
|
Right () -> pure ()
|
||||||
Left e
|
Left e
|
||||||
| isDoesNotExistError e -> notexisthandler e
|
| isDoesNotExistError e -> notexisthandler e
|
||||||
| isAlreadyExistsError e || isPermissionError e -> do
|
| isAlreadyExistsError e || isPermissionError e ->
|
||||||
unlessM (doesDirectoryExist dir) $
|
liftIO $ unlessM (doesDirectoryExist dir) $
|
||||||
ioError e
|
ioError e
|
||||||
| otherwise -> ioError e
|
| otherwise -> liftIO $ ioError e
|
||||||
|
|
Loading…
Add table
Add a link
Reference in a new issue