Merge branch 'wip'

This commit is contained in:
Joey Hess 2019-05-07 13:07:45 -04:00
commit aaeb85361c
No known key found for this signature in database
GPG key ID: DB12DB0FF05F8F38
8 changed files with 65 additions and 35 deletions

View file

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

View file

@ -31,6 +31,7 @@ module Annex.Locations (
gitAnnexTmpOtherDir,
gitAnnexTmpOtherLock,
gitAnnexTmpOtherDirOld,
gitAnnexTmpWatcherDir,
gitAnnexTmpObjectDir,
gitAnnexTmpObjectLocation,
gitAnnexTmpWorkDir,
@ -264,10 +265,14 @@ gitAnnexTmpOtherDir r = addTrailingPathSeparator $ gitAnnexDir r </> "othertmp"
gitAnnexTmpOtherLock :: Git.Repo -> FilePath
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 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. -}
gitAnnexTmpObjectLocation :: Key -> Git.Repo -> FilePath
gitAnnexTmpObjectLocation key r = gitAnnexTmpObjectDir r </> keyFile key

View file

@ -1,6 +1,6 @@
{- 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.
-}
@ -29,7 +29,7 @@ import Config
import Annex.Content
import Annex.Ingest
import Annex.Link
import Annex.Tmp
import Annex.Perms
import Annex.CatFile
import Annex.InodeSentinal
import Annex.Version
@ -56,8 +56,14 @@ commitThread = namedThread "Committer" $ do
maybe delayaddDefault (return . Just . Seconds)
=<< annexDelayAdd <$> Annex.getGitConfig
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
readychanges <- handleAdds havelsof delayadd $
readychanges <- handleAdds lockdowndir havelsof delayadd $
simplifyChanges changes
if shouldCommit False time (length readychanges) readychanges
then do
@ -265,21 +271,21 @@ delayaddDefault = return Nothing
- Any pending adds that are not ready yet are put back into the ChangeChan,
- where they will be retried later.
-}
handleAdds :: Bool -> Maybe Seconds -> [Change] -> Assistant [Change]
handleAdds havelsof delayadd cs = returnWhen (null incomplete) $ do
handleAdds :: FilePath -> Bool -> Maybe Seconds -> [Change] -> Assistant [Change]
handleAdds lockdowndir havelsof delayadd cs = returnWhen (null incomplete) $ do
let (pending, inprocess) = partition isPendingAddChange incomplete
direct <- liftAnnex isDirect
unlocked <- liftAnnex versionSupportsUnlockedPointers
let lockingfiles = not (unlocked || direct)
let lockdownconfig = LockDownConfig
{ lockingFile = lockingfiles
, hardlinkFileTmp = True
, hardlinkFileTmpDir = Just lockdowndir
}
(pending', cleanup) <- if unlocked || direct
then return (pending, noop)
else findnew pending
(postponed, toadd) <- partitionEithers
<$> safeToAdd lockdownconfig havelsof delayadd pending' inprocess
<$> safeToAdd lockdowndir lockdownconfig havelsof delayadd pending' inprocess
cleanup
unless (null postponed) $
@ -294,7 +300,7 @@ handleAdds havelsof delayadd cs = returnWhen (null incomplete) $ do
if DirWatcher.eventsCoalesce || null added || unlocked || direct
then return $ added ++ otherchanges
else do
r <- handleAdds havelsof delayadd =<< getChanges
r <- handleAdds lockdowndir havelsof delayadd =<< getChanges
return $ r ++ added ++ otherchanges
where
(incomplete, otherchanges) = partition (\c -> isPendingAddChange c || isInProcessAddChange c) cs
@ -341,7 +347,7 @@ handleAdds havelsof delayadd cs = returnWhen (null incomplete) $ do
delta <- liftAnnex getTSDelta
let cfg = LockDownConfig
{ lockingFile = False
, hardlinkFileTmp = True
, hardlinkFileTmpDir = Just lockdowndir
}
if M.null m
then forM toadd (add cfg)
@ -429,9 +435,9 @@ handleAdds havelsof delayadd cs = returnWhen (null incomplete) $ do
-
- Check by running lsof on the repository.
-}
safeToAdd :: LockDownConfig -> Bool -> Maybe Seconds -> [Change] -> [Change] -> Assistant [Either Change Change]
safeToAdd _ _ _ [] [] = return []
safeToAdd lockdownconfig havelsof delayadd pending inprocess = do
safeToAdd :: FilePath -> LockDownConfig -> Bool -> Maybe Seconds -> [Change] -> [Change] -> Assistant [Either Change Change]
safeToAdd _ _ _ _ [] [] = return []
safeToAdd lockdowndir lockdownconfig havelsof delayadd pending inprocess = do
maybe noop (liftIO . threadDelaySeconds) delayadd
liftAnnex $ do
lockeddown <- forM pending $ lockDown lockdownconfig . changeFile
@ -478,7 +484,7 @@ safeToAdd lockdownconfig havelsof delayadd pending inprocess = do
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.
-
- 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
let segments = segmentXargsUnordered $ map keyFilename keysources
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

View file

@ -1,3 +1,10 @@
git-annex (7.20190508) UNRELEASED; urgency=medium
* 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
git-annex (7.20190507) upstream; urgency=medium
* Fix reversion in last release that caused wrong tree to be written

View file

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

View file

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

View file

@ -132,7 +132,7 @@ clean file = do
cfg = LockDownConfig
{ lockingFile = False
, hardlinkFileTmp = False
, hardlinkFileTmpDir = Nothing
}
-- 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.
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
cleanup stale othertmp files was only added a couple months back.