avoid ingest lockdown file escaping the withOtherTmp call

Fixes bug that caused git-annex to fail to add a file when another
git-annex process cleaned up the temp directory it was using.

Solution is just to push withOtherTmp out to a higher level, so that
the whole ingest process can be completed inside it.

But in the assistant, that was not practical to do, since withOtherTmp runs
in the Annex monad and the assistant does not. Worked around by introducing
a separate temp directory that only the assistant uses for lockdown.
Since only one assistant can run at a time, it's easy to clean up that
directory of old cruft at startup.
This commit is contained in:
Joey Hess 2019-05-07 13:04:39 -04:00
parent 2a41712ef1
commit 2d33122215
No known key found for this signature in database
GPG key ID: DB12DB0FF05F8F38
8 changed files with 60 additions and 35 deletions

View file

@ -30,7 +30,6 @@ import Backend
import Annex.Content import Annex.Content
import Annex.Content.Direct import Annex.Content.Direct
import Annex.Perms import Annex.Perms
import Annex.Tmp
import Annex.Link import Annex.Link
import Annex.MetaData import Annex.MetaData
import Annex.CurrentBranch import Annex.CurrentBranch
@ -58,8 +57,10 @@ data LockedDown = LockedDown
deriving (Show) deriving (Show)
data LockDownConfig = LockDownConfig data LockDownConfig = LockDownConfig
{ lockingFile :: Bool -- ^ write bit removed during lock down { lockingFile :: Bool
, hardlinkFileTmp :: Bool -- ^ hard link to temp directory -- ^ write bit removed during lock down
, hardlinkFileTmpDir :: Maybe FilePath
-- ^ hard link to temp directory
} }
deriving (Show) deriving (Show)
@ -83,27 +84,35 @@ lockDown cfg file = either
=<< lockDown' cfg file =<< lockDown' cfg file
lockDown' :: LockDownConfig -> FilePath -> Annex (Either IOException LockedDown) lockDown' :: LockDownConfig -> FilePath -> Annex (Either IOException LockedDown)
lockDown' cfg file = ifM (pure (not (hardlinkFileTmp cfg)) <||> crippledFileSystem) lockDown' cfg file = tryIO $ ifM crippledFileSystem
( withTSDelta $ liftIO . tryIO . nohardlink ( nohardlink
, tryIO $ withOtherTmp $ \tmp -> do , case hardlinkFileTmpDir cfg of
when (lockingFile cfg) $ Nothing -> nohardlink
freezeContent file Just tmpdir -> withhardlink tmpdir
withTSDelta $ \delta -> liftIO $ do
(tmpfile, h) <- openTempFile tmp $
relatedTemplate $ "ingest-" ++ takeFileName file
hClose h
nukeFile tmpfile
withhardlink delta tmpfile `catchIO` const (nohardlink delta)
) )
where where
nohardlink delta = do nohardlink = withTSDelta $ liftIO . nohardlink'
nohardlink' delta = do
cache <- genInodeCache file delta cache <- genInodeCache file delta
return $ LockedDown cfg $ KeySource return $ LockedDown cfg $ KeySource
{ keyFilename = file { keyFilename = file
, contentLocation = file , contentLocation = file
, inodeCache = cache , inodeCache = cache
} }
withhardlink delta tmpfile = do
withhardlink tmpdir = do
when (lockingFile cfg) $
freezeContent file
withTSDelta $ \delta -> liftIO $ do
(tmpfile, h) <- openTempFile tmpdir $
relatedTemplate $ "ingest-" ++ takeFileName file
hClose h
nukeFile tmpfile
withhardlink' delta tmpfile
`catchIO` const (nohardlink' delta)
withhardlink' delta tmpfile = do
createLink file tmpfile createLink file tmpfile
cache <- genInodeCache tmpfile delta cache <- genInodeCache tmpfile delta
return $ LockedDown cfg $ KeySource return $ LockedDown cfg $ KeySource

View file

@ -31,6 +31,7 @@ module Annex.Locations (
gitAnnexTmpOtherDir, gitAnnexTmpOtherDir,
gitAnnexTmpOtherLock, gitAnnexTmpOtherLock,
gitAnnexTmpOtherDirOld, gitAnnexTmpOtherDirOld,
gitAnnexTmpWatcherDir,
gitAnnexTmpObjectDir, gitAnnexTmpObjectDir,
gitAnnexTmpObjectLocation, gitAnnexTmpObjectLocation,
gitAnnexTmpWorkDir, gitAnnexTmpWorkDir,
@ -264,10 +265,14 @@ gitAnnexTmpOtherDir r = addTrailingPathSeparator $ gitAnnexDir r </> "othertmp"
gitAnnexTmpOtherLock :: Git.Repo -> FilePath gitAnnexTmpOtherLock :: Git.Repo -> FilePath
gitAnnexTmpOtherLock r = gitAnnexDir r </> "othertmp.lck" gitAnnexTmpOtherLock r = gitAnnexDir r </> "othertmp.lck"
{- Directory used by old versions of git-annex. -} {- Tmp directory used by old versions of git-annex. -}
gitAnnexTmpOtherDirOld :: Git.Repo -> FilePath gitAnnexTmpOtherDirOld :: Git.Repo -> FilePath
gitAnnexTmpOtherDirOld r = addTrailingPathSeparator $ gitAnnexDir r </> "misctmp" gitAnnexTmpOtherDirOld r = addTrailingPathSeparator $ gitAnnexDir r </> "misctmp"
{- .git/annex/watchtmp/ is used by the watcher and assistant -}
gitAnnexTmpWatcherDir :: Git.Repo -> FilePath
gitAnnexTmpWatcherDir r = addTrailingPathSeparator $ gitAnnexDir r </> "watchtmp"
{- The temp file to use for a given key's content. -} {- The temp file to use for a given key's content. -}
gitAnnexTmpObjectLocation :: Key -> Git.Repo -> FilePath gitAnnexTmpObjectLocation :: Key -> Git.Repo -> FilePath
gitAnnexTmpObjectLocation key r = gitAnnexTmpObjectDir r </> keyFile key gitAnnexTmpObjectLocation key r = gitAnnexTmpObjectDir r </> keyFile key

View file

@ -1,6 +1,6 @@
{- git-annex assistant commit thread {- git-annex assistant commit thread
- -
- Copyright 2012 Joey Hess <id@joeyh.name> - Copyright 2012, 2019 Joey Hess <id@joeyh.name>
- -
- Licensed under the GNU AGPL version 3 or higher. - Licensed under the GNU AGPL version 3 or higher.
-} -}
@ -29,7 +29,7 @@ import Config
import Annex.Content import Annex.Content
import Annex.Ingest import Annex.Ingest
import Annex.Link import Annex.Link
import Annex.Tmp import Annex.Perms
import Annex.CatFile import Annex.CatFile
import Annex.InodeSentinal import Annex.InodeSentinal
import Annex.Version import Annex.Version
@ -56,8 +56,14 @@ commitThread = namedThread "Committer" $ do
maybe delayaddDefault (return . Just . Seconds) maybe delayaddDefault (return . Just . Seconds)
=<< annexDelayAdd <$> Annex.getGitConfig =<< annexDelayAdd <$> Annex.getGitConfig
msg <- liftAnnex Command.Sync.commitMsg msg <- liftAnnex Command.Sync.commitMsg
lockdowndir <- liftAnnex $ fromRepo gitAnnexTmpWatcherDir
liftAnnex $ do
-- Clean up anything left behind by a previous process
-- on unclean shutdown.
void $ liftIO $ tryIO $ removeDirectoryRecursive lockdowndir
void $ createAnnexDirectory lockdowndir
waitChangeTime $ \(changes, time) -> do waitChangeTime $ \(changes, time) -> do
readychanges <- handleAdds havelsof delayadd $ readychanges <- handleAdds lockdowndir havelsof delayadd $
simplifyChanges changes simplifyChanges changes
if shouldCommit False time (length readychanges) readychanges if shouldCommit False time (length readychanges) readychanges
then do then do
@ -265,21 +271,21 @@ delayaddDefault = return Nothing
- Any pending adds that are not ready yet are put back into the ChangeChan, - Any pending adds that are not ready yet are put back into the ChangeChan,
- where they will be retried later. - where they will be retried later.
-} -}
handleAdds :: Bool -> Maybe Seconds -> [Change] -> Assistant [Change] handleAdds :: FilePath -> Bool -> Maybe Seconds -> [Change] -> Assistant [Change]
handleAdds havelsof delayadd cs = returnWhen (null incomplete) $ do handleAdds lockdowndir havelsof delayadd cs = returnWhen (null incomplete) $ do
let (pending, inprocess) = partition isPendingAddChange incomplete let (pending, inprocess) = partition isPendingAddChange incomplete
direct <- liftAnnex isDirect direct <- liftAnnex isDirect
unlocked <- liftAnnex versionSupportsUnlockedPointers unlocked <- liftAnnex versionSupportsUnlockedPointers
let lockingfiles = not (unlocked || direct) let lockingfiles = not (unlocked || direct)
let lockdownconfig = LockDownConfig let lockdownconfig = LockDownConfig
{ lockingFile = lockingfiles { lockingFile = lockingfiles
, hardlinkFileTmp = True , hardlinkFileTmpDir = Just lockdowndir
} }
(pending', cleanup) <- if unlocked || direct (pending', cleanup) <- if unlocked || direct
then return (pending, noop) then return (pending, noop)
else findnew pending else findnew pending
(postponed, toadd) <- partitionEithers (postponed, toadd) <- partitionEithers
<$> safeToAdd lockdownconfig havelsof delayadd pending' inprocess <$> safeToAdd lockdowndir lockdownconfig havelsof delayadd pending' inprocess
cleanup cleanup
unless (null postponed) $ unless (null postponed) $
@ -294,7 +300,7 @@ handleAdds havelsof delayadd cs = returnWhen (null incomplete) $ do
if DirWatcher.eventsCoalesce || null added || unlocked || direct if DirWatcher.eventsCoalesce || null added || unlocked || direct
then return $ added ++ otherchanges then return $ added ++ otherchanges
else do else do
r <- handleAdds havelsof delayadd =<< getChanges r <- handleAdds lockdowndir havelsof delayadd =<< getChanges
return $ r ++ added ++ otherchanges return $ r ++ added ++ otherchanges
where where
(incomplete, otherchanges) = partition (\c -> isPendingAddChange c || isInProcessAddChange c) cs (incomplete, otherchanges) = partition (\c -> isPendingAddChange c || isInProcessAddChange c) cs
@ -341,7 +347,7 @@ handleAdds havelsof delayadd cs = returnWhen (null incomplete) $ do
delta <- liftAnnex getTSDelta delta <- liftAnnex getTSDelta
let cfg = LockDownConfig let cfg = LockDownConfig
{ lockingFile = False { lockingFile = False
, hardlinkFileTmp = True , hardlinkFileTmpDir = Just lockdowndir
} }
if M.null m if M.null m
then forM toadd (add cfg) then forM toadd (add cfg)
@ -429,9 +435,9 @@ handleAdds havelsof delayadd cs = returnWhen (null incomplete) $ do
- -
- Check by running lsof on the repository. - Check by running lsof on the repository.
-} -}
safeToAdd :: LockDownConfig -> Bool -> Maybe Seconds -> [Change] -> [Change] -> Assistant [Either Change Change] safeToAdd :: FilePath -> LockDownConfig -> Bool -> Maybe Seconds -> [Change] -> [Change] -> Assistant [Either Change Change]
safeToAdd _ _ _ [] [] = return [] safeToAdd _ _ _ _ [] [] = return []
safeToAdd lockdownconfig havelsof delayadd pending inprocess = do safeToAdd lockdowndir lockdownconfig havelsof delayadd pending inprocess = do
maybe noop (liftIO . threadDelaySeconds) delayadd maybe noop (liftIO . threadDelaySeconds) delayadd
liftAnnex $ do liftAnnex $ do
lockeddown <- forM pending $ lockDown lockdownconfig . changeFile lockeddown <- forM pending $ lockDown lockdownconfig . changeFile
@ -478,7 +484,7 @@ safeToAdd lockdownconfig havelsof delayadd pending inprocess = do
allRight = return . map Right allRight = return . map Right
{- Normally the KeySources are locked down inside the temp directory, {- Normally the KeySources are locked down inside the lockdowndir,
- so can just lsof that, which is quite efficient. - so can just lsof that, which is quite efficient.
- -
- In crippled filesystem mode, there is no lock down, so must run lsof - In crippled filesystem mode, there is no lock down, so must run lsof
@ -488,7 +494,7 @@ safeToAdd lockdownconfig havelsof delayadd pending inprocess = do
( liftIO $ do ( liftIO $ do
let segments = segmentXargsUnordered $ map keyFilename keysources let segments = segmentXargsUnordered $ map keyFilename keysources
concat <$> forM segments (\fs -> Lsof.query $ "--" : fs) concat <$> forM segments (\fs -> Lsof.query $ "--" : fs)
, withOtherTmp $ liftIO . Lsof.queryDir , liftIO $ Lsof.queryDir lockdowndir
) )
{- After a Change is committed, queue any necessary transfers or drops {- After a Change is committed, queue any necessary transfers or drops

View file

@ -4,6 +4,8 @@ git-annex (7.20190504) UNRELEASED; urgency=medium
to remote tracking branch after an export of a subtree. to remote tracking branch after an export of a subtree.
* Improved locking when multiple git-annex processes are writing to * Improved locking when multiple git-annex processes are writing to
the .git/index file the .git/index file
* Fixed bug that caused git-annex to fail to add a file when another
git-annex process cleaned up the temp directory it was using.
-- Joey Hess <id@joeyh.name> Mon, 06 May 2019 13:52:02 -0400 -- Joey Hess <id@joeyh.name> Mon, 06 May 2019 13:52:02 -0400

View file

@ -19,6 +19,7 @@ import Config
import Annex.FileMatcher import Annex.FileMatcher
import Annex.Link import Annex.Link
import Annex.Version import Annex.Version
import Annex.Tmp
import Git.FilePath import Git.FilePath
cmd :: Command cmd :: Command
@ -137,11 +138,11 @@ start file = do
next $ next $ addFile file next $ next $ addFile file
perform :: FilePath -> CommandPerform perform :: FilePath -> CommandPerform
perform file = do perform file = withOtherTmp $ \tmpdir -> do
lockingfile <- not <$> addUnlocked lockingfile <- not <$> addUnlocked
let cfg = LockDownConfig let cfg = LockDownConfig
{ lockingFile = lockingfile { lockingFile = lockingfile
, hardlinkFileTmp = True , hardlinkFileTmpDir = Just tmpdir
} }
lockDown cfg file >>= ingestAdd >>= finish lockDown cfg file >>= ingestAdd >>= finish
where where

View file

@ -214,7 +214,7 @@ startLocal largematcher mode (srcfile, destfile) =
-- has to be done to clean up from it. -- has to be done to clean up from it.
let cfg = LockDownConfig let cfg = LockDownConfig
{ lockingFile = lockingfile { lockingFile = lockingfile
, hardlinkFileTmp = False , hardlinkFileTmpDir = Nothing
} }
v <- lockDown cfg srcfile v <- lockDown cfg srcfile
case v of case v of

View file

@ -132,7 +132,7 @@ clean file = do
cfg = LockDownConfig cfg = LockDownConfig
{ lockingFile = False { lockingFile = False
, hardlinkFileTmp = False , hardlinkFileTmpDir = Nothing
} }
-- git diff can run the clean filter on files outside the -- git diff can run the clean filter on files outside the

View file

@ -14,6 +14,8 @@ temp filepath. So, it's escaped the locking that `withOtherTmp` does, and
another process can clean up the temp files at the wrong point in time. another process can clean up the temp files at the wrong point in time.
This will need some significant code reworking to fix. This will need some significant code reworking to fix.
> [[fixed|done]] --[[Joey]]
This is a fairly new problem because the code to have other processes This is a fairly new problem because the code to have other processes
cleanup stale othertmp files was only added a couple months back. cleanup stale othertmp files was only added a couple months back.