misctmp cleanup
* Switch to using .git/annex/othertmp for tmp files other than partial downloads, and make stale files left in that directory when git-annex is interrupted be cleaned up promptly by subsequent git-annex processes. * The .git/annex/misctmp directory is no longer used and git-annex will delete anything lingering in there after it's 1 week old. Also, in Annex.Ingest, made the filename it uses in the tmp dir be prefixed with "ingest-" to avoid potentially using a filename used by some other code.
This commit is contained in:
parent
6de8ce8bb1
commit
d5f2463702
22 changed files with 222 additions and 156 deletions
|
@ -55,7 +55,7 @@ import Annex.CatFile
|
||||||
import Annex.Link
|
import Annex.Link
|
||||||
import Annex.AutoMerge
|
import Annex.AutoMerge
|
||||||
import Annex.Content
|
import Annex.Content
|
||||||
import Annex.Perms
|
import Annex.Tmp
|
||||||
import Annex.GitOverlay
|
import Annex.GitOverlay
|
||||||
import Utility.Tmp.Dir
|
import Utility.Tmp.Dir
|
||||||
import Utility.CopyFile
|
import Utility.CopyFile
|
||||||
|
@ -356,12 +356,10 @@ mergeToAdjustedBranch tomerge (origbranch, adj) mergeconfig canresolvemerge comm
|
||||||
- (Doing the merge this way also lets it run even though the main
|
- (Doing the merge this way also lets it run even though the main
|
||||||
- index file is currently locked.)
|
- index file is currently locked.)
|
||||||
-}
|
-}
|
||||||
changestomerge (Just updatedorig) = do
|
changestomerge (Just updatedorig) = withOtherTmp $ \othertmpdir -> do
|
||||||
misctmpdir <- fromRepo gitAnnexTmpMiscDir
|
|
||||||
void $ createAnnexDirectory misctmpdir
|
|
||||||
tmpwt <- fromRepo gitAnnexMergeDir
|
tmpwt <- fromRepo gitAnnexMergeDir
|
||||||
git_dir <- fromRepo Git.localGitDir
|
git_dir <- fromRepo Git.localGitDir
|
||||||
withTmpDirIn misctmpdir "git" $ \tmpgit -> withWorkTreeRelated tmpgit $
|
withTmpDirIn othertmpdir "git" $ \tmpgit -> withWorkTreeRelated tmpgit $
|
||||||
withemptydir tmpwt $ withWorkTree tmpwt $ do
|
withemptydir tmpwt $ withWorkTree tmpwt $ do
|
||||||
liftIO $ writeFile (tmpgit </> "HEAD") (fromRef updatedorig)
|
liftIO $ writeFile (tmpgit </> "HEAD") (fromRef updatedorig)
|
||||||
-- Copy in refs and packed-refs, to work
|
-- Copy in refs and packed-refs, to work
|
||||||
|
|
|
@ -41,6 +41,7 @@ import Annex.Common
|
||||||
import Annex.BranchState
|
import Annex.BranchState
|
||||||
import Annex.Journal
|
import Annex.Journal
|
||||||
import Annex.GitOverlay
|
import Annex.GitOverlay
|
||||||
|
import Annex.Tmp
|
||||||
import qualified Git
|
import qualified Git
|
||||||
import qualified Git.Command
|
import qualified Git.Command
|
||||||
import qualified Git.Ref
|
import qualified Git.Ref
|
||||||
|
@ -488,9 +489,7 @@ stageJournal jl = withIndex $ do
|
||||||
mapM_ (removeFile . (dir </>)) stagedfs
|
mapM_ (removeFile . (dir </>)) stagedfs
|
||||||
hClose jlogh
|
hClose jlogh
|
||||||
nukeFile jlogf
|
nukeFile jlogf
|
||||||
openjlog = do
|
openjlog = withOtherTmp $ \tmpdir ->
|
||||||
tmpdir <- fromRepo gitAnnexTmpMiscDir
|
|
||||||
createAnnexDirectory tmpdir
|
|
||||||
liftIO $ openTempFile tmpdir "jlog"
|
liftIO $ openTempFile tmpdir "jlog"
|
||||||
|
|
||||||
{- This is run after the refs have been merged into the index,
|
{- This is run after the refs have been merged into the index,
|
||||||
|
|
|
@ -30,6 +30,7 @@ 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
|
||||||
|
@ -84,14 +85,12 @@ lockDown cfg file = either
|
||||||
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 = ifM (pure (not (hardlinkFileTmp cfg)) <||> crippledFileSystem)
|
||||||
( withTSDelta $ liftIO . tryIO . nohardlink
|
( withTSDelta $ liftIO . tryIO . nohardlink
|
||||||
, tryIO $ do
|
, tryIO $ withOtherTmp $ \tmp -> do
|
||||||
tmp <- fromRepo gitAnnexTmpMiscDir
|
|
||||||
createAnnexDirectory tmp
|
|
||||||
when (lockingFile cfg) $
|
when (lockingFile cfg) $
|
||||||
freezeContent file
|
freezeContent file
|
||||||
withTSDelta $ \delta -> liftIO $ do
|
withTSDelta $ \delta -> liftIO $ do
|
||||||
(tmpfile, h) <- openTempFile tmp $
|
(tmpfile, h) <- openTempFile tmp $
|
||||||
relatedTemplate $ takeFileName file
|
relatedTemplate $ "ingest-" ++ takeFileName file
|
||||||
hClose h
|
hClose h
|
||||||
nukeFile tmpfile
|
nukeFile tmpfile
|
||||||
withhardlink delta tmpfile `catchIO` const (nohardlink delta)
|
withhardlink delta tmpfile `catchIO` const (nohardlink delta)
|
||||||
|
|
|
@ -44,6 +44,7 @@ import Annex.Hook
|
||||||
import Annex.InodeSentinal
|
import Annex.InodeSentinal
|
||||||
import Upgrade
|
import Upgrade
|
||||||
import Annex.Perms
|
import Annex.Perms
|
||||||
|
import Annex.Tmp
|
||||||
import Utility.UserInfo
|
import Utility.UserInfo
|
||||||
#ifndef mingw32_HOST_OS
|
#ifndef mingw32_HOST_OS
|
||||||
import Utility.FileMode
|
import Utility.FileMode
|
||||||
|
@ -163,9 +164,7 @@ isInitialized = maybe Annex.Branch.hasSibling (const $ return True) =<< getVersi
|
||||||
{- A crippled filesystem is one that does not allow making symlinks,
|
{- A crippled filesystem is one that does not allow making symlinks,
|
||||||
- or removing write access from files. -}
|
- or removing write access from files. -}
|
||||||
probeCrippledFileSystem :: Annex Bool
|
probeCrippledFileSystem :: Annex Bool
|
||||||
probeCrippledFileSystem = do
|
probeCrippledFileSystem = withOtherTmp $ \tmp -> do
|
||||||
tmp <- fromRepo gitAnnexTmpMiscDir
|
|
||||||
createAnnexDirectory tmp
|
|
||||||
(r, warnings) <- liftIO $ probeCrippledFileSystem' tmp
|
(r, warnings) <- liftIO $ probeCrippledFileSystem' tmp
|
||||||
mapM_ warning warnings
|
mapM_ warning warnings
|
||||||
return r
|
return r
|
||||||
|
@ -222,9 +221,8 @@ probeLockSupport = do
|
||||||
#ifdef mingw32_HOST_OS
|
#ifdef mingw32_HOST_OS
|
||||||
return True
|
return True
|
||||||
#else
|
#else
|
||||||
tmp <- fromRepo gitAnnexTmpMiscDir
|
withOtherTmp $ \tmp -> do
|
||||||
let f = tmp </> "lockprobe"
|
let f = tmp </> "lockprobe"
|
||||||
createAnnexDirectory tmp
|
|
||||||
mode <- annexFileMode
|
mode <- annexFileMode
|
||||||
liftIO $ do
|
liftIO $ do
|
||||||
nukeFile f
|
nukeFile f
|
||||||
|
@ -240,10 +238,9 @@ probeFifoSupport = do
|
||||||
#ifdef mingw32_HOST_OS
|
#ifdef mingw32_HOST_OS
|
||||||
return False
|
return False
|
||||||
#else
|
#else
|
||||||
tmp <- fromRepo gitAnnexTmpMiscDir
|
withOtherTmp $ \tmp -> do
|
||||||
let f = tmp </> "gaprobe"
|
let f = tmp </> "gaprobe"
|
||||||
let f2 = tmp </> "gaprobe2"
|
let f2 = tmp </> "gaprobe2"
|
||||||
createAnnexDirectory tmp
|
|
||||||
liftIO $ do
|
liftIO $ do
|
||||||
nukeFile f
|
nukeFile f
|
||||||
nukeFile f2
|
nukeFile f2
|
||||||
|
|
|
@ -14,6 +14,7 @@ module Annex.Journal where
|
||||||
import Annex.Common
|
import Annex.Common
|
||||||
import qualified Git
|
import qualified Git
|
||||||
import Annex.Perms
|
import Annex.Perms
|
||||||
|
import Annex.Tmp
|
||||||
import Annex.LockFile
|
import Annex.LockFile
|
||||||
import Utility.Directory.Stream
|
import Utility.Directory.Stream
|
||||||
|
|
||||||
|
@ -44,10 +45,8 @@ instance Journalable Builder where
|
||||||
- content, although possibly not the most current one.
|
- content, although possibly not the most current one.
|
||||||
-}
|
-}
|
||||||
setJournalFile :: Journalable content => JournalLocked -> FilePath -> content -> Annex ()
|
setJournalFile :: Journalable content => JournalLocked -> FilePath -> content -> Annex ()
|
||||||
setJournalFile _jl file content = do
|
setJournalFile _jl file content = withOtherTmp $ \tmp -> do
|
||||||
tmp <- fromRepo gitAnnexTmpMiscDir
|
|
||||||
createAnnexDirectory =<< fromRepo gitAnnexJournalDir
|
createAnnexDirectory =<< fromRepo gitAnnexJournalDir
|
||||||
createAnnexDirectory tmp
|
|
||||||
-- journal file is written atomically
|
-- journal file is written atomically
|
||||||
jfile <- fromRepo $ journalFile file
|
jfile <- fromRepo $ journalFile file
|
||||||
let tmpfile = tmp </> takeFileName jfile
|
let tmpfile = tmp </> takeFileName jfile
|
||||||
|
|
|
@ -28,7 +28,9 @@ module Annex.Locations (
|
||||||
annexLocations,
|
annexLocations,
|
||||||
gitAnnexDir,
|
gitAnnexDir,
|
||||||
gitAnnexObjectDir,
|
gitAnnexObjectDir,
|
||||||
gitAnnexTmpMiscDir,
|
gitAnnexTmpOtherDir,
|
||||||
|
gitAnnexTmpOtherLock,
|
||||||
|
gitAnnexTmpOtherDirOld,
|
||||||
gitAnnexTmpObjectDir,
|
gitAnnexTmpObjectDir,
|
||||||
gitAnnexTmpObjectLocation,
|
gitAnnexTmpObjectLocation,
|
||||||
gitAnnexTmpWorkDir,
|
gitAnnexTmpWorkDir,
|
||||||
|
@ -246,14 +248,22 @@ gitAnnexDir r = addTrailingPathSeparator $ Git.localGitDir r </> annexDir
|
||||||
gitAnnexObjectDir :: Git.Repo -> FilePath
|
gitAnnexObjectDir :: Git.Repo -> FilePath
|
||||||
gitAnnexObjectDir r = addTrailingPathSeparator $ Git.localGitDir r </> objectDir
|
gitAnnexObjectDir r = addTrailingPathSeparator $ Git.localGitDir r </> objectDir
|
||||||
|
|
||||||
{- .git/annex/misctmp/ is used for random temp files -}
|
|
||||||
gitAnnexTmpMiscDir :: Git.Repo -> FilePath
|
|
||||||
gitAnnexTmpMiscDir r = addTrailingPathSeparator $ gitAnnexDir r </> "misctmp"
|
|
||||||
|
|
||||||
{- .git/annex/tmp/ is used for temp files for key's contents -}
|
{- .git/annex/tmp/ is used for temp files for key's contents -}
|
||||||
gitAnnexTmpObjectDir :: Git.Repo -> FilePath
|
gitAnnexTmpObjectDir :: Git.Repo -> FilePath
|
||||||
gitAnnexTmpObjectDir r = addTrailingPathSeparator $ gitAnnexDir r </> "tmp"
|
gitAnnexTmpObjectDir r = addTrailingPathSeparator $ gitAnnexDir r </> "tmp"
|
||||||
|
|
||||||
|
{- .git/annex/othertmp/ is used for other temp files -}
|
||||||
|
gitAnnexTmpOtherDir :: Git.Repo -> FilePath
|
||||||
|
gitAnnexTmpOtherDir r = addTrailingPathSeparator $ gitAnnexDir r </> "othertmp"
|
||||||
|
|
||||||
|
{- Lock file for gitAnnexTmpOtherDir. -}
|
||||||
|
gitAnnexTmpOtherLock :: Git.Repo -> FilePath
|
||||||
|
gitAnnexTmpOtherLock r = gitAnnexDir r </> "othertmp.lck"
|
||||||
|
|
||||||
|
{- Directory used by old versions of git-annex. -}
|
||||||
|
gitAnnexTmpOtherDirOld :: Git.Repo -> FilePath
|
||||||
|
gitAnnexTmpOtherDirOld r = addTrailingPathSeparator $ gitAnnexDir r </> "misctmp"
|
||||||
|
|
||||||
{- 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
|
||||||
|
|
|
@ -1,6 +1,6 @@
|
||||||
{- git-annex lock files.
|
{- git-annex lock files.
|
||||||
-
|
-
|
||||||
- Copyright 2012-2015 Joey Hess <id@joeyh.name>
|
- Copyright 2012-2019 Joey Hess <id@joeyh.name>
|
||||||
-
|
-
|
||||||
- Licensed under the GNU GPL version 3 or higher.
|
- Licensed under the GNU GPL version 3 or higher.
|
||||||
-}
|
-}
|
||||||
|
@ -12,6 +12,7 @@ module Annex.LockFile (
|
||||||
unlockFile,
|
unlockFile,
|
||||||
getLockCache,
|
getLockCache,
|
||||||
fromLockCache,
|
fromLockCache,
|
||||||
|
withSharedLock,
|
||||||
withExclusiveLock,
|
withExclusiveLock,
|
||||||
tryExclusiveLock,
|
tryExclusiveLock,
|
||||||
) where
|
) where
|
||||||
|
@ -58,6 +59,21 @@ changeLockCache a = do
|
||||||
m <- getLockCache
|
m <- getLockCache
|
||||||
changeState $ \s -> s { lockcache = a m }
|
changeState $ \s -> s { lockcache = a m }
|
||||||
|
|
||||||
|
{- Runs an action with a shared lock held. If an exclusive lock is held,
|
||||||
|
- blocks until it becomes free. -}
|
||||||
|
withSharedLock :: (Git.Repo -> FilePath) -> Annex a -> Annex a
|
||||||
|
withSharedLock getlockfile a = debugLocks $ do
|
||||||
|
lockfile <- fromRepo getlockfile
|
||||||
|
createAnnexDirectory $ takeDirectory lockfile
|
||||||
|
mode <- annexFileMode
|
||||||
|
bracket (lock mode lockfile) (liftIO . dropLock) (const a)
|
||||||
|
where
|
||||||
|
#ifndef mingw32_HOST_OS
|
||||||
|
lock mode = noUmask mode . lockShared (Just mode)
|
||||||
|
#else
|
||||||
|
lock _mode = liftIO . waitToLock . lockShared
|
||||||
|
#endif
|
||||||
|
|
||||||
{- Runs an action with an exclusive lock held. If the lock is already
|
{- Runs an action with an exclusive lock held. If the lock is already
|
||||||
- held, blocks until it becomes free. -}
|
- held, blocks until it becomes free. -}
|
||||||
withExclusiveLock :: (Git.Repo -> FilePath) -> Annex a -> Annex a
|
withExclusiveLock :: (Git.Repo -> FilePath) -> Annex a -> Annex a
|
||||||
|
|
|
@ -10,7 +10,7 @@
|
||||||
module Annex.ReplaceFile where
|
module Annex.ReplaceFile where
|
||||||
|
|
||||||
import Annex.Common
|
import Annex.Common
|
||||||
import Annex.Perms
|
import Annex.Tmp
|
||||||
import Utility.Tmp.Dir
|
import Utility.Tmp.Dir
|
||||||
import Utility.Path.Max
|
import Utility.Path.Max
|
||||||
|
|
||||||
|
@ -27,21 +27,19 @@ import Utility.Path.Max
|
||||||
- Throws an IO exception when it was unable to replace the file.
|
- Throws an IO exception when it was unable to replace the file.
|
||||||
-}
|
-}
|
||||||
replaceFile :: FilePath -> (FilePath -> Annex a) -> Annex a
|
replaceFile :: FilePath -> (FilePath -> Annex a) -> Annex a
|
||||||
replaceFile file action = do
|
replaceFile file action = withOtherTmp $ \othertmpdir -> do
|
||||||
misctmpdir <- fromRepo gitAnnexTmpMiscDir
|
|
||||||
void $ createAnnexDirectory misctmpdir
|
|
||||||
#ifndef mingw32_HOST_OS
|
#ifndef mingw32_HOST_OS
|
||||||
-- Use part of the filename as the template for the temp
|
-- Use part of the filename as the template for the temp
|
||||||
-- directory. This does not need to be unique, but it
|
-- directory. This does not need to be unique, but it
|
||||||
-- makes it more clear what this temp directory is for.
|
-- makes it more clear what this temp directory is for.
|
||||||
filemax <- liftIO $ fileNameLengthLimit misctmpdir
|
filemax <- liftIO $ fileNameLengthLimit othertmpdir
|
||||||
let basetmp = take (filemax `div` 2) (takeFileName file)
|
let basetmp = take (filemax `div` 2) (takeFileName file)
|
||||||
#else
|
#else
|
||||||
-- Windows has limits on the whole path length, so keep
|
-- Windows has limits on the whole path length, so keep
|
||||||
-- it short.
|
-- it short.
|
||||||
let basetmp = "t"
|
let basetmp = "t"
|
||||||
#endif
|
#endif
|
||||||
withTmpDirIn misctmpdir basetmp $ \tmpdir -> do
|
withTmpDirIn othertmpdir basetmp $ \tmpdir -> do
|
||||||
let tmpfile = tmpdir </> basetmp
|
let tmpfile = tmpdir </> basetmp
|
||||||
r <- action tmpfile
|
r <- action tmpfile
|
||||||
liftIO $ replaceFileFrom tmpfile file
|
liftIO $ replaceFileFrom tmpfile file
|
||||||
|
|
56
Annex/Tmp.hs
Normal file
56
Annex/Tmp.hs
Normal file
|
@ -0,0 +1,56 @@
|
||||||
|
{- git-annex tmp files
|
||||||
|
-
|
||||||
|
- Copyright 2019 Joey Hess <id@joeyh.name>
|
||||||
|
-
|
||||||
|
- Licensed under the GNU GPL version 3 or higher.
|
||||||
|
-}
|
||||||
|
|
||||||
|
module Annex.Tmp where
|
||||||
|
|
||||||
|
import Common
|
||||||
|
import Annex
|
||||||
|
import Annex.Locations
|
||||||
|
import Annex.LockFile
|
||||||
|
import Annex.Perms
|
||||||
|
import Types.CleanupActions
|
||||||
|
|
||||||
|
import Data.Time.Clock.POSIX
|
||||||
|
|
||||||
|
-- | For creation of tmp files, other than for key's contents.
|
||||||
|
--
|
||||||
|
-- The action should normally clean up whatever files it writes to the temp
|
||||||
|
-- directory that is passed to it. However, once the action is done,
|
||||||
|
-- any files left in that directory may be cleaned up by another process at
|
||||||
|
-- any time.
|
||||||
|
withOtherTmp :: (FilePath -> Annex a) -> Annex a
|
||||||
|
withOtherTmp a = do
|
||||||
|
addCleanup OtherTmpCleanup cleanupOtherTmp
|
||||||
|
tmpdir <- fromRepo gitAnnexTmpOtherDir
|
||||||
|
tmplck <- fromRepo gitAnnexTmpOtherLock
|
||||||
|
void $ createAnnexDirectory tmpdir
|
||||||
|
withSharedLock (const tmplck) (a tmpdir)
|
||||||
|
|
||||||
|
-- | Cleans up any tmp files that were left by a previous
|
||||||
|
-- git-annex process that got interrupted or failed to clean up after
|
||||||
|
-- itself for some other reason.
|
||||||
|
--
|
||||||
|
-- Does not do anything if withOtherTmp is running.
|
||||||
|
cleanupOtherTmp :: Annex ()
|
||||||
|
cleanupOtherTmp = do
|
||||||
|
tmplck <- fromRepo gitAnnexTmpOtherLock
|
||||||
|
void $ tryIO $ tryExclusiveLock (const tmplck) $ do
|
||||||
|
tmpdir <- fromRepo gitAnnexTmpOtherDir
|
||||||
|
void $ liftIO $ tryIO $ removeDirectoryRecursive tmpdir
|
||||||
|
-- This is only to clean up cruft left by old versions of
|
||||||
|
-- git-annex; it can be removed eventually.
|
||||||
|
oldtmp <- fromRepo gitAnnexTmpOtherDirOld
|
||||||
|
liftIO $ mapM_ cleanold =<< dirContentsRecursive oldtmp
|
||||||
|
liftIO $ void $ tryIO $ removeDirectory oldtmp -- when empty
|
||||||
|
where
|
||||||
|
cleanold f = do
|
||||||
|
now <- liftIO getPOSIXTime
|
||||||
|
let oldenough = now - (60 * 60 * 24 * 7)
|
||||||
|
catchMaybeIO (modificationTime <$> getSymbolicLinkStatus f) >>= \case
|
||||||
|
Just mtime | realToFrac mtime <= oldenough ->
|
||||||
|
void $ tryIO $ nukeFile f
|
||||||
|
_ -> return ()
|
|
@ -29,6 +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.CatFile
|
import Annex.CatFile
|
||||||
import Annex.InodeSentinal
|
import Annex.InodeSentinal
|
||||||
import Annex.Version
|
import Annex.Version
|
||||||
|
@ -487,9 +488,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)
|
||||||
, do
|
, withOtherTmp $ liftIO . Lsof.queryDir
|
||||||
tmpdir <- fromRepo gitAnnexTmpMiscDir
|
|
||||||
liftIO $ Lsof.queryDir tmpdir
|
|
||||||
)
|
)
|
||||||
|
|
||||||
{- After a Change is committed, queue any necessary transfers or drops
|
{- After a Change is committed, queue any necessary transfers or drops
|
||||||
|
|
|
@ -40,8 +40,8 @@ import Git.Index
|
||||||
import Assistant.Unused
|
import Assistant.Unused
|
||||||
import Logs.Unused
|
import Logs.Unused
|
||||||
import Types.Transfer
|
import Types.Transfer
|
||||||
import Types.Key
|
|
||||||
import Annex.Path
|
import Annex.Path
|
||||||
|
import Annex.Tmp
|
||||||
import qualified Annex
|
import qualified Annex
|
||||||
#ifdef WITH_WEBAPP
|
#ifdef WITH_WEBAPP
|
||||||
import Assistant.WebApp.Types
|
import Assistant.WebApp.Types
|
||||||
|
@ -53,7 +53,6 @@ import Utility.DiskFree
|
||||||
|
|
||||||
import Data.Time.Clock.POSIX
|
import Data.Time.Clock.POSIX
|
||||||
import qualified Data.Text as T
|
import qualified Data.Text as T
|
||||||
import qualified Data.ByteString as S
|
|
||||||
|
|
||||||
{- This thread runs once at startup, and most other threads wait for it
|
{- This thread runs once at startup, and most other threads wait for it
|
||||||
- to finish. (However, the webapp thread does not, to prevent the UI
|
- to finish. (However, the webapp thread does not, to prevent the UI
|
||||||
|
@ -88,9 +87,7 @@ sanityCheckerStartupThread startupdelay = namedThreadUnchecked "SanityCheckerSta
|
||||||
liftIO $ fixUpSshRemotes
|
liftIO $ fixUpSshRemotes
|
||||||
|
|
||||||
{- Clean up old temp files. -}
|
{- Clean up old temp files. -}
|
||||||
void $ liftAnnex $ tryNonAsync $ do
|
void $ liftAnnex $ tryNonAsync $ cleanupOtherTmp
|
||||||
cleanOldTmpMisc
|
|
||||||
cleanReallyOldTmp
|
|
||||||
|
|
||||||
{- If there's a startup delay, it's done here. -}
|
{- If there's a startup delay, it's done here. -}
|
||||||
liftIO $ maybe noop (threadDelaySeconds . Seconds . fromIntegral . durationSeconds) startupdelay
|
liftIO $ maybe noop (threadDelaySeconds . Seconds . fromIntegral . durationSeconds) startupdelay
|
||||||
|
@ -270,58 +267,6 @@ checkOldUnused urlrenderer = go =<< annexExpireUnused <$> liftAnnex Annex.getGit
|
||||||
debug [show $ renderTense Past msg]
|
debug [show $ renderTense Past msg]
|
||||||
#endif
|
#endif
|
||||||
|
|
||||||
{- Files may be left in misctmp by eg, an interrupted add of files
|
|
||||||
- by the assistant, which hard links files to there as part of lockdown
|
|
||||||
- checks. Delete these files if they're more than a day old.
|
|
||||||
-
|
|
||||||
- Note that this is not safe to run after the Watcher starts up, since it
|
|
||||||
- will create such files, and due to hard linking they may have old
|
|
||||||
- mtimes. So, this should only be called from the
|
|
||||||
- sanityCheckerStartupThread, which runs before the Watcher starts up.
|
|
||||||
-
|
|
||||||
- Also, if a git-annex add is being run at the same time the assistant
|
|
||||||
- starts up, its tmp files could be deleted. However, the watcher will
|
|
||||||
- come along and add everything once it starts up anyway, so at worst
|
|
||||||
- this would make the git-annex add fail unexpectedly.
|
|
||||||
-}
|
|
||||||
cleanOldTmpMisc :: Annex ()
|
|
||||||
cleanOldTmpMisc = do
|
|
||||||
now <- liftIO getPOSIXTime
|
|
||||||
let oldenough = now - (60 * 60 * 24)
|
|
||||||
tmp <- fromRepo gitAnnexTmpMiscDir
|
|
||||||
liftIO $ mapM_ (cleanOld (<= oldenough)) =<< dirContentsRecursive tmp
|
|
||||||
|
|
||||||
{- While .git/annex/tmp is now only used for storing partially transferred
|
|
||||||
- objects, older versions of git-annex used it for misctemp. Clean up any
|
|
||||||
- files that might be left from that, by looking for files whose names
|
|
||||||
- cannot be the key of an annexed object. Only delete files older than
|
|
||||||
- 1 week old.
|
|
||||||
-
|
|
||||||
- Also, some remotes such as rsync may use this temp directory for storing
|
|
||||||
- eg, encrypted objects that are being transferred. So, delete old
|
|
||||||
- objects that use a GPGHMAC backend.
|
|
||||||
-}
|
|
||||||
cleanReallyOldTmp :: Annex ()
|
|
||||||
cleanReallyOldTmp = do
|
|
||||||
now <- liftIO getPOSIXTime
|
|
||||||
let oldenough = now - (60 * 60 * 24 * 7)
|
|
||||||
tmp <- fromRepo gitAnnexTmpObjectDir
|
|
||||||
liftIO $ mapM_ (cleanjunk (<= oldenough)) =<< dirContentsRecursive tmp
|
|
||||||
where
|
|
||||||
cleanjunk check f = case fileKey (takeFileName f) of
|
|
||||||
Nothing -> cleanOld check f
|
|
||||||
Just k
|
|
||||||
| "GPGHMAC" `S.isPrefixOf` formatKeyVariety (keyVariety k) ->
|
|
||||||
cleanOld check f
|
|
||||||
| otherwise -> noop
|
|
||||||
|
|
||||||
cleanOld :: (POSIXTime -> Bool) -> FilePath -> IO ()
|
|
||||||
cleanOld check f = go =<< catchMaybeIO getmtime
|
|
||||||
where
|
|
||||||
getmtime = realToFrac . modificationTime <$> getSymbolicLinkStatus f
|
|
||||||
go (Just mtime) | check mtime = nukeFile f
|
|
||||||
go _ = noop
|
|
||||||
|
|
||||||
checkRepoExists :: Assistant ()
|
checkRepoExists :: Assistant ()
|
||||||
checkRepoExists = do
|
checkRepoExists = do
|
||||||
g <- liftAnnex gitRepo
|
g <- liftAnnex gitRepo
|
||||||
|
|
|
@ -30,6 +30,11 @@ git-annex (7.20181212) UNRELEASED; urgency=medium
|
||||||
* addunused, merge, assistant: Avoid creating work tree files in
|
* addunused, merge, assistant: Avoid creating work tree files in
|
||||||
subdirectories in an edge case where the key contains "/".
|
subdirectories in an edge case where the key contains "/".
|
||||||
* testremote: Support testing readonly remotes with the --test-readonly option.
|
* testremote: Support testing readonly remotes with the --test-readonly option.
|
||||||
|
* Switch to using .git/annex/othertmp for tmp files other than partial
|
||||||
|
downloads, and make stale files left in that directory when git-annex
|
||||||
|
is interrupted be cleaned up promptly by subsequent git-annex processes.
|
||||||
|
* The .git/annex/misctmp directory is no longer used and git-annex will
|
||||||
|
delete anything lingering in there after it's 1 week old.
|
||||||
|
|
||||||
-- Joey Hess <id@joeyh.name> Tue, 18 Dec 2018 12:24:52 -0400
|
-- Joey Hess <id@joeyh.name> Tue, 18 Dec 2018 12:24:52 -0400
|
||||||
|
|
||||||
|
|
|
@ -12,6 +12,7 @@ import Config
|
||||||
import Utility.Tmp.Dir
|
import Utility.Tmp.Dir
|
||||||
import Utility.Env
|
import Utility.Env
|
||||||
import Annex.Direct
|
import Annex.Direct
|
||||||
|
import Annex.Tmp
|
||||||
import qualified Git
|
import qualified Git
|
||||||
import qualified Git.Sha
|
import qualified Git.Sha
|
||||||
import qualified Git.Ref
|
import qualified Git.Ref
|
||||||
|
@ -32,9 +33,7 @@ seek = withWords (commandAction . start)
|
||||||
start :: [String] -> CommandStart
|
start :: [String] -> CommandStart
|
||||||
start [] = giveup "Did not specify command to run."
|
start [] = giveup "Did not specify command to run."
|
||||||
start (c:ps) = liftIO . exitWith =<< ifM isDirect
|
start (c:ps) = liftIO . exitWith =<< ifM isDirect
|
||||||
( do
|
( withOtherTmp $ \tmp -> withTmpDirIn tmp "proxy" go
|
||||||
tmp <- gitAnnexTmpMiscDir <$> gitRepo
|
|
||||||
withTmpDirIn tmp "proxy" go
|
|
||||||
, liftIO $ safeSystem c (map Param ps)
|
, liftIO $ safeSystem c (map Param ps)
|
||||||
)
|
)
|
||||||
where
|
where
|
||||||
|
|
|
@ -24,6 +24,7 @@ import Utility.Metered
|
||||||
import Utility.Tmp
|
import Utility.Tmp
|
||||||
import Backend.URL
|
import Backend.URL
|
||||||
import Annex.Perms
|
import Annex.Perms
|
||||||
|
import Annex.Tmp
|
||||||
import Annex.UUID
|
import Annex.UUID
|
||||||
import qualified Annex.Url as Url
|
import qualified Annex.Url as Url
|
||||||
import Remote.Helper.Export
|
import Remote.Helper.Export
|
||||||
|
@ -165,29 +166,20 @@ torrentUrlNum u
|
||||||
torrentUrlKey :: URLString -> Annex Key
|
torrentUrlKey :: URLString -> Annex Key
|
||||||
torrentUrlKey u = return $ fromUrl (fst $ torrentUrlNum u) Nothing
|
torrentUrlKey u = return $ fromUrl (fst $ torrentUrlNum u) Nothing
|
||||||
|
|
||||||
{- Temporary directory used to download a torrent. -}
|
|
||||||
tmpTorrentDir :: URLString -> Annex FilePath
|
|
||||||
tmpTorrentDir u = do
|
|
||||||
d <- fromRepo gitAnnexTmpMiscDir
|
|
||||||
f <- keyFile <$> torrentUrlKey u
|
|
||||||
return (d </> f)
|
|
||||||
|
|
||||||
{- Temporary filename to use to store the torrent file. -}
|
{- Temporary filename to use to store the torrent file. -}
|
||||||
tmpTorrentFile :: URLString -> Annex FilePath
|
tmpTorrentFile :: URLString -> Annex FilePath
|
||||||
tmpTorrentFile u = fromRepo . gitAnnexTmpObjectLocation =<< torrentUrlKey u
|
tmpTorrentFile u = fromRepo . gitAnnexTmpObjectLocation =<< torrentUrlKey u
|
||||||
|
|
||||||
{- A cleanup action is registered to delete the torrent file and its
|
{- A cleanup action is registered to delete the torrent file
|
||||||
- associated temp directory when git-annex exits.
|
- when git-annex exits.
|
||||||
-
|
-
|
||||||
- This allows multiple actions that use the same torrent file and temp
|
- This allows multiple actions that use the same torrent file
|
||||||
- directory to run in a single git-annex run.
|
- directory to run in a single git-annex run, and only download the
|
||||||
|
- torrent file once.
|
||||||
-}
|
-}
|
||||||
registerTorrentCleanup :: URLString -> Annex ()
|
registerTorrentCleanup :: URLString -> Annex ()
|
||||||
registerTorrentCleanup u = Annex.addCleanup (TorrentCleanup u) $ do
|
registerTorrentCleanup u = Annex.addCleanup (TorrentCleanup u) $
|
||||||
liftIO . nukeFile =<< tmpTorrentFile u
|
liftIO . nukeFile =<< tmpTorrentFile u
|
||||||
d <- tmpTorrentDir u
|
|
||||||
liftIO $ whenM (doesDirectoryExist d) $
|
|
||||||
removeDirectoryRecursive d
|
|
||||||
|
|
||||||
{- Downloads the torrent file. (Not its contents.) -}
|
{- Downloads the torrent file. (Not its contents.) -}
|
||||||
downloadTorrentFile :: URLString -> Annex Bool
|
downloadTorrentFile :: URLString -> Annex Bool
|
||||||
|
@ -199,17 +191,16 @@ downloadTorrentFile u = do
|
||||||
showAction "downloading torrent file"
|
showAction "downloading torrent file"
|
||||||
createAnnexDirectory (parentDir torrent)
|
createAnnexDirectory (parentDir torrent)
|
||||||
if isTorrentMagnetUrl u
|
if isTorrentMagnetUrl u
|
||||||
then do
|
then withOtherTmp $ \othertmp -> do
|
||||||
tmpdir <- tmpTorrentDir u
|
kf <- keyFile <$> torrentUrlKey u
|
||||||
let metadir = tmpdir </> "meta"
|
let metadir = othertmp </> "torrentmeta" </> kf
|
||||||
createAnnexDirectory metadir
|
createAnnexDirectory metadir
|
||||||
showOutput
|
showOutput
|
||||||
ok <- downloadMagnetLink u metadir torrent
|
ok <- downloadMagnetLink u metadir torrent
|
||||||
liftIO $ removeDirectoryRecursive metadir
|
liftIO $ removeDirectoryRecursive metadir
|
||||||
return ok
|
return ok
|
||||||
else do
|
else withOtherTmp $ \othertmp -> do
|
||||||
misctmp <- fromRepo gitAnnexTmpMiscDir
|
withTmpFileIn othertmp "torrent" $ \f h -> do
|
||||||
withTmpFileIn misctmp "torrent" $ \f h -> do
|
|
||||||
liftIO $ hClose h
|
liftIO $ hClose h
|
||||||
ok <- Url.withUrlOptions $
|
ok <- Url.withUrlOptions $
|
||||||
liftIO . Url.download nullMeterUpdate u f
|
liftIO . Url.download nullMeterUpdate u f
|
||||||
|
@ -244,13 +235,22 @@ downloadMagnetLink u metadir dest = ifM download
|
||||||
downloadTorrentContent :: Key -> URLString -> FilePath -> Int -> MeterUpdate -> Annex Bool
|
downloadTorrentContent :: Key -> URLString -> FilePath -> Int -> MeterUpdate -> Annex Bool
|
||||||
downloadTorrentContent k u dest filenum p = do
|
downloadTorrentContent k u dest filenum p = do
|
||||||
torrent <- tmpTorrentFile u
|
torrent <- tmpTorrentFile u
|
||||||
tmpdir <- tmpTorrentDir u
|
withOtherTmp $ \othertmp -> do
|
||||||
createAnnexDirectory tmpdir
|
kf <- keyFile <$> torrentUrlKey u
|
||||||
|
let downloaddir = othertmp </> "torrent" </> kf
|
||||||
|
createAnnexDirectory downloaddir
|
||||||
f <- wantedfile torrent
|
f <- wantedfile torrent
|
||||||
showOutput
|
showOutput
|
||||||
ifM (download torrent tmpdir <&&> liftIO (doesFileExist (tmpdir </> f)))
|
ifM (download torrent downloaddir <&&> liftIO (doesFileExist (downloaddir </> f)))
|
||||||
( do
|
( do
|
||||||
liftIO $ renameFile (tmpdir </> f) dest
|
liftIO $ renameFile (downloaddir </> f) dest
|
||||||
|
-- The downloaddir is not removed here,
|
||||||
|
-- so if aria downloaded parts of other
|
||||||
|
-- files, and this is called again, it will
|
||||||
|
-- resume where it left off.
|
||||||
|
-- withOtherTmp registers a cleanup action
|
||||||
|
-- that will clean up leftover files when
|
||||||
|
-- git-annex terminates.
|
||||||
return True
|
return True
|
||||||
, return False
|
, return False
|
||||||
)
|
)
|
||||||
|
|
|
@ -16,7 +16,7 @@ import Annex.Common
|
||||||
import Utility.FileMode
|
import Utility.FileMode
|
||||||
import Remote.Helper.Special
|
import Remote.Helper.Special
|
||||||
import qualified Remote.Helper.Chunked.Legacy as Legacy
|
import qualified Remote.Helper.Chunked.Legacy as Legacy
|
||||||
import Annex.Perms
|
import Annex.Tmp
|
||||||
import Utility.Metered
|
import Utility.Metered
|
||||||
|
|
||||||
withCheckedFiles :: (FilePath -> IO Bool) -> FilePath -> (FilePath -> Key -> [FilePath]) -> Key -> ([FilePath] -> IO Bool) -> IO Bool
|
withCheckedFiles :: (FilePath -> IO Bool) -> FilePath -> (FilePath -> Key -> [FilePath]) -> Key -> ([FilePath] -> IO Bool) -> IO Bool
|
||||||
|
@ -89,10 +89,8 @@ store chunksize finalizer k b p = storeHelper finalizer k $ \dests ->
|
||||||
- :/ This is legacy code..
|
- :/ This is legacy code..
|
||||||
-}
|
-}
|
||||||
retrieve :: (FilePath -> Key -> [FilePath]) -> FilePath -> Preparer Retriever
|
retrieve :: (FilePath -> Key -> [FilePath]) -> FilePath -> Preparer Retriever
|
||||||
retrieve locations d basek a = do
|
retrieve locations d basek a = withOtherTmp $ \tmpdir -> do
|
||||||
showLongNote "This remote uses the deprecated chunksize setting. So this will be quite slow."
|
showLongNote "This remote uses the deprecated chunksize setting. So this will be quite slow."
|
||||||
tmpdir <- fromRepo $ gitAnnexTmpMiscDir
|
|
||||||
createAnnexDirectory tmpdir
|
|
||||||
let tmp = tmpdir </> keyFile basek ++ ".directorylegacy.tmp"
|
let tmp = tmpdir </> keyFile basek ++ ".directorylegacy.tmp"
|
||||||
a $ Just $ byteRetriever $ \k sink -> do
|
a $ Just $ byteRetriever $ \k sink -> do
|
||||||
liftIO $ void $ withStoredFiles d locations k $ \fs -> do
|
liftIO $ void $ withStoredFiles d locations k $ \fs -> do
|
||||||
|
|
2
Test.hs
2
Test.hs
|
@ -1621,7 +1621,7 @@ test_crypto = do
|
||||||
gpgcmd = Utility.Gpg.mkGpgCmd Nothing
|
gpgcmd = Utility.Gpg.mkGpgCmd Nothing
|
||||||
testscheme scheme = intmpclonerepo $ whenM (Utility.Path.inPath (Utility.Gpg.unGpgCmd gpgcmd)) $ do
|
testscheme scheme = intmpclonerepo $ whenM (Utility.Path.inPath (Utility.Gpg.unGpgCmd gpgcmd)) $ do
|
||||||
gpgtmpdir <- annexeval $ (</> "gpgtest")
|
gpgtmpdir <- annexeval $ (</> "gpgtest")
|
||||||
<$> Annex.fromRepo Annex.Locations.gitAnnexTmpMiscDir
|
<$> Annex.fromRepo Annex.Locations.gitAnnexTmpOtherDir
|
||||||
annexeval $ Annex.Perms.createAnnexDirectory gpgtmpdir
|
annexeval $ Annex.Perms.createAnnexDirectory gpgtmpdir
|
||||||
Utility.Gpg.testTestHarness gpgtmpdir gpgcmd
|
Utility.Gpg.testTestHarness gpgtmpdir gpgcmd
|
||||||
@? "test harness self-test failed"
|
@? "test harness self-test failed"
|
||||||
|
|
|
@ -17,4 +17,5 @@ data CleanupAction
|
||||||
| FsckCleanup
|
| FsckCleanup
|
||||||
| SshCachingCleanup
|
| SshCachingCleanup
|
||||||
| TorrentCleanup URLString
|
| TorrentCleanup URLString
|
||||||
|
| OtherTmpCleanup
|
||||||
deriving (Eq, Ord)
|
deriving (Eq, Ord)
|
||||||
|
|
|
@ -0,0 +1,11 @@
|
||||||
|
[[!comment format=mdwn
|
||||||
|
username="joey"
|
||||||
|
subject="""comment 11"""
|
||||||
|
date="2019-01-17T20:01:51Z"
|
||||||
|
content="""
|
||||||
|
There were actually a few ways git-annex could be interrupted and leave
|
||||||
|
droppings in misctmp.
|
||||||
|
|
||||||
|
This is now dealt with, a subsequent run of git-annex will clean up
|
||||||
|
leftover files from a previous interrupted run.
|
||||||
|
"""]]
|
|
@ -0,0 +1,11 @@
|
||||||
|
[[!comment format=mdwn
|
||||||
|
username="joey"
|
||||||
|
subject="""comment 3"""
|
||||||
|
date="2019-01-17T20:00:57Z"
|
||||||
|
content="""
|
||||||
|
There were actually a few ways git-annex could be interrupted and leave
|
||||||
|
droppings in misctmp.
|
||||||
|
|
||||||
|
This is now dealt with, a subsequent run of git-annex will clean up
|
||||||
|
leftover files from a previous interrupted run.
|
||||||
|
"""]]
|
|
@ -33,12 +33,12 @@ that contain the key.
|
||||||
|
|
||||||
This directory contains partially transferred objects.
|
This directory contains partially transferred objects.
|
||||||
|
|
||||||
### `.git/annex/misctmp/`
|
### `.git/annex/othertmp/`
|
||||||
|
|
||||||
This is a temp directory for miscellaneous other temp files.
|
This is a temp directory for miscellaneous other temp files.
|
||||||
|
|
||||||
While .git/annex/objects and .git/annex/tmp can be put on different
|
While .git/annex/objects and .git/annex/tmp can be put on different
|
||||||
filesystems if desired, .git/annex/misctmp
|
filesystems if desired, .git/annex/othertmp
|
||||||
has to be on the same filesystem as the work tree and git repository.
|
has to be on the same filesystem as the work tree and git repository.
|
||||||
|
|
||||||
### `.git/annex/bad/`
|
### `.git/annex/bad/`
|
||||||
|
|
24
doc/todo/delete_old_misctmp_files.mdwn
Normal file
24
doc/todo/delete_old_misctmp_files.mdwn
Normal file
|
@ -0,0 +1,24 @@
|
||||||
|
Files can be left in .git/annex/misctmp when git-annex is interrupted in
|
||||||
|
the middle of an operation that uses it. Especially with `git annex add`
|
||||||
|
being interrupted can leave a large file hard linked in there, which can
|
||||||
|
become a problem for the user.
|
||||||
|
|
||||||
|
While it would be possible to hook SIGINT and clean up the files, that
|
||||||
|
wouldn't catch every way git-annex could be interrupted; ie power failure.
|
||||||
|
|
||||||
|
The assistant has some code that deletes misctmp files there older than 1
|
||||||
|
day. Perhaps when git-annex uses the misctmp directory it should first
|
||||||
|
perform such a cleanup pass.
|
||||||
|
|
||||||
|
A 1 day timeout is not ideal.. Imagine a git-annex add of a really big file
|
||||||
|
where the checksum takes more than 1 day.
|
||||||
|
|
||||||
|
Let's use a lock file. There can be a single one for the whole misctmp
|
||||||
|
directory. When it's being used, a shared lock is held. Take an exclusive
|
||||||
|
lock before cleaning it.
|
||||||
|
|
||||||
|
Since old versions of git-annex could still be in use and using the misctmp
|
||||||
|
directory, let's rename the directory that new versions of git-annex
|
||||||
|
use to .git/annex/othertmp.
|
||||||
|
|
||||||
|
[[done]] --[[Joey]]
|
|
@ -645,6 +645,7 @@ Executable git-annex
|
||||||
Annex.SpecialRemote
|
Annex.SpecialRemote
|
||||||
Annex.Ssh
|
Annex.Ssh
|
||||||
Annex.TaggedPush
|
Annex.TaggedPush
|
||||||
|
Annex.Tmp
|
||||||
Annex.Transfer
|
Annex.Transfer
|
||||||
Annex.UpdateInstead
|
Annex.UpdateInstead
|
||||||
Annex.UUID
|
Annex.UUID
|
||||||
|
|
Loading…
Add table
Add a link
Reference in a new issue