addistant: honor annex.delayadd for non-large files
assistant: When adding non-large files to git, honor annex.delayadd configuration. Also, don't add non-large files to git when they are still being written to. This came for free, since the changes to non-large files get queued up with the ones to large files, and run through the lsof check. Sponsored-by: Luke Shumaker on Patreon
This commit is contained in:
parent
2018cb4a97
commit
8885bd3c5b
5 changed files with 54 additions and 46 deletions
|
@ -1,6 +1,6 @@
|
||||||
{- git-annex assistant commit thread
|
{- git-annex assistant commit thread
|
||||||
-
|
-
|
||||||
- Copyright 2012, 2019 Joey Hess <id@joeyh.name>
|
- Copyright 2012-2021 Joey Hess <id@joeyh.name>
|
||||||
-
|
-
|
||||||
- Licensed under the GNU AGPL version 3 or higher.
|
- Licensed under the GNU AGPL version 3 or higher.
|
||||||
-}
|
-}
|
||||||
|
@ -33,6 +33,7 @@ import Annex.Perms
|
||||||
import Annex.CatFile
|
import Annex.CatFile
|
||||||
import Annex.InodeSentinal
|
import Annex.InodeSentinal
|
||||||
import Annex.CurrentBranch
|
import Annex.CurrentBranch
|
||||||
|
import Annex.FileMatcher
|
||||||
import qualified Annex
|
import qualified Annex
|
||||||
import Utility.InodeCache
|
import Utility.InodeCache
|
||||||
import qualified Database.Keys
|
import qualified Database.Keys
|
||||||
|
@ -52,6 +53,7 @@ commitThread = namedThread "Committer" $ do
|
||||||
havelsof <- liftIO $ inSearchPath "lsof"
|
havelsof <- liftIO $ inSearchPath "lsof"
|
||||||
delayadd <- liftAnnex $
|
delayadd <- liftAnnex $
|
||||||
fmap Seconds . annexDelayAdd <$> Annex.getGitConfig
|
fmap Seconds . annexDelayAdd <$> Annex.getGitConfig
|
||||||
|
largefilematcher <- liftAnnex largeFilesMatcher
|
||||||
msg <- liftAnnex Command.Sync.commitMsg
|
msg <- liftAnnex Command.Sync.commitMsg
|
||||||
lockdowndir <- liftAnnex $ fromRepo gitAnnexTmpWatcherDir
|
lockdowndir <- liftAnnex $ fromRepo gitAnnexTmpWatcherDir
|
||||||
liftAnnex $ do
|
liftAnnex $ do
|
||||||
|
@ -61,7 +63,7 @@ commitThread = namedThread "Committer" $ do
|
||||||
(fromRawFilePath lockdowndir)
|
(fromRawFilePath lockdowndir)
|
||||||
void $ createAnnexDirectory lockdowndir
|
void $ createAnnexDirectory lockdowndir
|
||||||
waitChangeTime $ \(changes, time) -> do
|
waitChangeTime $ \(changes, time) -> do
|
||||||
readychanges <- handleAdds (fromRawFilePath lockdowndir) havelsof delayadd $
|
readychanges <- handleAdds (fromRawFilePath lockdowndir) havelsof largefilematcher delayadd $
|
||||||
simplifyChanges changes
|
simplifyChanges changes
|
||||||
if shouldCommit False time (length readychanges) readychanges
|
if shouldCommit False time (length readychanges) readychanges
|
||||||
then do
|
then do
|
||||||
|
@ -239,7 +241,7 @@ commitStaged msg = do
|
||||||
return ok
|
return ok
|
||||||
|
|
||||||
{- If there are PendingAddChanges, or InProcessAddChanges, the files
|
{- If there are PendingAddChanges, or InProcessAddChanges, the files
|
||||||
- have not yet actually been added to the annex, and that has to be done
|
- have not yet actually been added, and that has to be done
|
||||||
- now, before committing.
|
- now, before committing.
|
||||||
-
|
-
|
||||||
- Deferring the adds to this point causes batches to be bundled together,
|
- Deferring the adds to this point causes batches to be bundled together,
|
||||||
|
@ -257,8 +259,8 @@ commitStaged msg = do
|
||||||
- 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 :: FilePath -> Bool -> Maybe Seconds -> [Change] -> Assistant [Change]
|
handleAdds :: FilePath -> Bool -> GetFileMatcher -> Maybe Seconds -> [Change] -> Assistant [Change]
|
||||||
handleAdds lockdowndir havelsof delayadd cs = returnWhen (null incomplete) $ do
|
handleAdds lockdowndir havelsof largefilematcher delayadd cs = returnWhen (null incomplete) $ do
|
||||||
let (pending, inprocess) = partition isPendingAddChange incomplete
|
let (pending, inprocess) = partition isPendingAddChange incomplete
|
||||||
let lockdownconfig = LockDownConfig
|
let lockdownconfig = LockDownConfig
|
||||||
{ lockingFile = False
|
{ lockingFile = False
|
||||||
|
@ -271,9 +273,12 @@ handleAdds lockdowndir havelsof delayadd cs = returnWhen (null incomplete) $ do
|
||||||
refillChanges postponed
|
refillChanges postponed
|
||||||
|
|
||||||
returnWhen (null toadd) $ do
|
returnWhen (null toadd) $ do
|
||||||
added <- addaction toadd $
|
(toaddannexed, toaddsmall) <- partitionEithers
|
||||||
catMaybes <$> addunlocked toadd
|
<$> mapM checksmall toadd
|
||||||
return $ added ++ otherchanges
|
addsmall toaddsmall
|
||||||
|
addedannexed <- addaction toadd $
|
||||||
|
catMaybes <$> addannexed toaddannexed
|
||||||
|
return $ addedannexed ++ toaddsmall ++ otherchanges
|
||||||
where
|
where
|
||||||
(incomplete, otherchanges) = partition (\c -> isPendingAddChange c || isInProcessAddChange c) cs
|
(incomplete, otherchanges) = partition (\c -> isPendingAddChange c || isInProcessAddChange c) cs
|
||||||
|
|
||||||
|
@ -281,25 +286,24 @@ handleAdds lockdowndir havelsof delayadd cs = returnWhen (null incomplete) $ do
|
||||||
| c = return otherchanges
|
| c = return otherchanges
|
||||||
| otherwise = a
|
| otherwise = a
|
||||||
|
|
||||||
add :: LockDownConfig -> Change -> Assistant (Maybe Change)
|
checksmall change =
|
||||||
add lockdownconfig change@(InProcessAddChange { lockedDown = ld }) =
|
ifM (liftAnnex $ checkFileMatcher largefilematcher (toRawFilePath (changeFile change)))
|
||||||
catchDefaultIO Nothing <~> doadd
|
( return (Left change)
|
||||||
where
|
, return (Right change)
|
||||||
ks = keySource ld
|
)
|
||||||
doadd = sanitycheck ks $ do
|
|
||||||
(mkey, _mcache) <- liftAnnex $ do
|
addsmall [] = noop
|
||||||
showStart "add" (keyFilename ks) (SeekInput [])
|
addsmall toadd = liftAnnex $ Annex.Queue.addCommand [] "add"
|
||||||
ingest nullMeterUpdate (Just $ LockedDown lockdownconfig ks) Nothing
|
[ Param "--force", Param "--"] (map changeFile toadd)
|
||||||
maybe (failedingest change) (done change $ fromRawFilePath $ keyFilename ks) mkey
|
|
||||||
add _ _ = return Nothing
|
|
||||||
|
|
||||||
{- Avoid overhead of re-injesting a renamed unlocked file, by
|
{- Avoid overhead of re-injesting a renamed unlocked file, by
|
||||||
- examining the other Changes to see if a removed file has the
|
- examining the other Changes to see if a removed file has the
|
||||||
- same InodeCache as the new file. If so, we can just update
|
- same InodeCache as the new file. If so, we can just update
|
||||||
- bookkeeping, and stage the file in git.
|
- bookkeeping, and stage the file in git.
|
||||||
-}
|
-}
|
||||||
addunlocked :: [Change] -> Assistant [Maybe Change]
|
addannexed :: [Change] -> Assistant [Maybe Change]
|
||||||
addunlocked toadd = do
|
addannexed [] = return []
|
||||||
|
addannexed toadd = do
|
||||||
ct <- liftAnnex compareInodeCachesWith
|
ct <- liftAnnex compareInodeCachesWith
|
||||||
m <- liftAnnex $ removedKeysMap ct cs
|
m <- liftAnnex $ removedKeysMap ct cs
|
||||||
delta <- liftAnnex getTSDelta
|
delta <- liftAnnex getTSDelta
|
||||||
|
@ -308,16 +312,28 @@ handleAdds lockdowndir havelsof delayadd cs = returnWhen (null incomplete) $ do
|
||||||
, hardlinkFileTmpDir = Just (toRawFilePath lockdowndir)
|
, hardlinkFileTmpDir = Just (toRawFilePath lockdowndir)
|
||||||
}
|
}
|
||||||
if M.null m
|
if M.null m
|
||||||
then forM toadd (add cfg)
|
then forM toadd (addannexed' cfg)
|
||||||
else forM toadd $ \c -> do
|
else forM toadd $ \c -> do
|
||||||
mcache <- liftIO $ genInodeCache (toRawFilePath (changeFile c)) delta
|
mcache <- liftIO $ genInodeCache (toRawFilePath (changeFile c)) delta
|
||||||
case mcache of
|
case mcache of
|
||||||
Nothing -> add cfg c
|
Nothing -> addannexed' cfg c
|
||||||
Just cache ->
|
Just cache ->
|
||||||
case M.lookup (inodeCacheToKey ct cache) m of
|
case M.lookup (inodeCacheToKey ct cache) m of
|
||||||
Nothing -> add cfg c
|
Nothing -> addannexed' cfg c
|
||||||
Just k -> fastadd c k
|
Just k -> fastadd c k
|
||||||
|
|
||||||
|
addannexed' :: LockDownConfig -> Change -> Assistant (Maybe Change)
|
||||||
|
addannexed' lockdownconfig change@(InProcessAddChange { lockedDown = ld }) =
|
||||||
|
catchDefaultIO Nothing <~> doadd
|
||||||
|
where
|
||||||
|
ks = keySource ld
|
||||||
|
doadd = sanitycheck ks $ do
|
||||||
|
(mkey, _mcache) <- liftAnnex $ do
|
||||||
|
showStart "add" (keyFilename ks) (SeekInput [])
|
||||||
|
ingest nullMeterUpdate (Just $ LockedDown lockdownconfig ks) Nothing
|
||||||
|
maybe (failedingest change) (done change $ fromRawFilePath $ keyFilename ks) mkey
|
||||||
|
addannexed' _ _ = return Nothing
|
||||||
|
|
||||||
fastadd :: Change -> Key -> Assistant (Maybe Change)
|
fastadd :: Change -> Key -> Assistant (Maybe Change)
|
||||||
fastadd change key = do
|
fastadd change key = do
|
||||||
let source = keySource $ lockedDown change
|
let source = keySource $ lockedDown change
|
||||||
|
|
|
@ -34,7 +34,6 @@ import Annex.WorkTree
|
||||||
import Annex.CatFile
|
import Annex.CatFile
|
||||||
import Annex.CheckIgnore
|
import Annex.CheckIgnore
|
||||||
import Annex.Link
|
import Annex.Link
|
||||||
import Annex.FileMatcher
|
|
||||||
import Annex.Content
|
import Annex.Content
|
||||||
import Annex.ReplaceFile
|
import Annex.ReplaceFile
|
||||||
import Annex.InodeSentinal
|
import Annex.InodeSentinal
|
||||||
|
@ -89,9 +88,8 @@ watchThread = namedThread "Watcher" $
|
||||||
runWatcher :: Assistant ()
|
runWatcher :: Assistant ()
|
||||||
runWatcher = do
|
runWatcher = do
|
||||||
startup <- asIO1 startupScan
|
startup <- asIO1 startupScan
|
||||||
matcher <- liftAnnex largeFilesMatcher
|
|
||||||
symlinkssupported <- liftAnnex $ coreSymlinks <$> Annex.getGitConfig
|
symlinkssupported <- liftAnnex $ coreSymlinks <$> Annex.getGitConfig
|
||||||
addhook <- hook $ onAddUnlocked symlinkssupported matcher
|
addhook <- hook $ onAddUnlocked symlinkssupported
|
||||||
delhook <- hook onDel
|
delhook <- hook onDel
|
||||||
addsymlinkhook <- hook onAddSymlink
|
addsymlinkhook <- hook onAddSymlink
|
||||||
deldirhook <- hook onDelDir
|
deldirhook <- hook onDelDir
|
||||||
|
@ -193,24 +191,14 @@ runHandler handler file filestatus = void $ do
|
||||||
| "./" `isPrefixOf` file = drop 2 f
|
| "./" `isPrefixOf` file = drop 2 f
|
||||||
| otherwise = f
|
| otherwise = f
|
||||||
|
|
||||||
{- Small files are added to git as-is, while large ones go into the annex. -}
|
|
||||||
add :: GetFileMatcher -> FilePath -> Assistant (Maybe Change)
|
|
||||||
add largefilematcher file = ifM (liftAnnex $ checkFileMatcher largefilematcher (toRawFilePath file))
|
|
||||||
( pendingAddChange file
|
|
||||||
, do
|
|
||||||
liftAnnex $ Annex.Queue.addCommand [] "add"
|
|
||||||
[Param "--force", Param "--"] [file]
|
|
||||||
madeChange file AddFileChange
|
|
||||||
)
|
|
||||||
|
|
||||||
shouldRestage :: DaemonStatus -> Bool
|
shouldRestage :: DaemonStatus -> Bool
|
||||||
shouldRestage ds = scanComplete ds || forceRestage ds
|
shouldRestage ds = scanComplete ds || forceRestage ds
|
||||||
|
|
||||||
onAddUnlocked :: Bool -> GetFileMatcher -> Handler
|
onAddUnlocked :: Bool -> Handler
|
||||||
onAddUnlocked symlinkssupported matcher f fs = do
|
onAddUnlocked symlinkssupported f fs = do
|
||||||
mk <- liftIO $ isPointerFile $ toRawFilePath f
|
mk <- liftIO $ isPointerFile $ toRawFilePath f
|
||||||
case mk of
|
case mk of
|
||||||
Nothing -> onAddUnlocked' contentchanged addassociatedfile addlink samefilestatus symlinkssupported matcher f fs
|
Nothing -> onAddUnlocked' contentchanged addassociatedfile addlink samefilestatus symlinkssupported f fs
|
||||||
Just k -> addlink f k
|
Just k -> addlink f k
|
||||||
where
|
where
|
||||||
addassociatedfile key file =
|
addassociatedfile key file =
|
||||||
|
@ -240,9 +228,8 @@ onAddUnlocked'
|
||||||
-> (FilePath -> Key -> Assistant (Maybe Change))
|
-> (FilePath -> Key -> Assistant (Maybe Change))
|
||||||
-> (Key -> FilePath -> FileStatus -> Annex Bool)
|
-> (Key -> FilePath -> FileStatus -> Annex Bool)
|
||||||
-> Bool
|
-> Bool
|
||||||
-> GetFileMatcher
|
|
||||||
-> Handler
|
-> Handler
|
||||||
onAddUnlocked' contentchanged addassociatedfile addlink samefilestatus symlinkssupported matcher file fs = do
|
onAddUnlocked' contentchanged addassociatedfile addlink samefilestatus symlinkssupported file fs = do
|
||||||
v <- liftAnnex $ catKeyFile (toRawFilePath file)
|
v <- liftAnnex $ catKeyFile (toRawFilePath file)
|
||||||
case (v, fs) of
|
case (v, fs) of
|
||||||
(Just key, Just filestatus) ->
|
(Just key, Just filestatus) ->
|
||||||
|
@ -259,12 +246,12 @@ onAddUnlocked' contentchanged addassociatedfile addlink samefilestatus symlinkss
|
||||||
, guardSymlinkStandin (Just key) $ do
|
, guardSymlinkStandin (Just key) $ do
|
||||||
debug ["changed", file]
|
debug ["changed", file]
|
||||||
liftAnnex $ contentchanged key file
|
liftAnnex $ contentchanged key file
|
||||||
add matcher file
|
pendingAddChange file
|
||||||
)
|
)
|
||||||
_ -> unlessIgnored file $
|
_ -> unlessIgnored file $
|
||||||
guardSymlinkStandin Nothing $ do
|
guardSymlinkStandin Nothing $ do
|
||||||
debug ["add", file]
|
debug ["add", file]
|
||||||
add matcher file
|
pendingAddChange file
|
||||||
where
|
where
|
||||||
{- On a filesystem without symlinks, we'll get changes for regular
|
{- On a filesystem without symlinks, we'll get changes for regular
|
||||||
- files that git uses to stand-in for symlinks. Detect when
|
- files that git uses to stand-in for symlinks. Detect when
|
||||||
|
|
|
@ -8,6 +8,9 @@ git-annex (8.20210631) UNRELEASED; urgency=medium
|
||||||
* init: Fix misbehavior when core.sharedRepository = group that
|
* init: Fix misbehavior when core.sharedRepository = group that
|
||||||
caused it to enter an adjusted branch and set annex.crippledfilesystem
|
caused it to enter an adjusted branch and set annex.crippledfilesystem
|
||||||
(Reversion in version 8.20210630)
|
(Reversion in version 8.20210630)
|
||||||
|
* assistant: When adding non-large files to git, honor annex.delayadd
|
||||||
|
configuration. Also, don't add non-large files to git when they
|
||||||
|
are still being written to.
|
||||||
|
|
||||||
-- Joey Hess <id@joeyh.name> Wed, 30 Jun 2021 17:55:10 -0400
|
-- Joey Hess <id@joeyh.name> Wed, 30 Jun 2021 17:55:10 -0400
|
||||||
|
|
||||||
|
|
|
@ -42,3 +42,5 @@ local repository version: 8
|
||||||
"""]]
|
"""]]
|
||||||
|
|
||||||
### Have you had any luck using git-annex before? (Sometimes we get tired of reading bug reports all day and a lil' positive end note does wonders)
|
### Have you had any luck using git-annex before? (Sometimes we get tired of reading bug reports all day and a lil' positive end note does wonders)
|
||||||
|
|
||||||
|
> [[fixed|done]] --[[Joey]]
|
||||||
|
|
|
@ -1765,8 +1765,8 @@ Remotes are configured using these settings in `.git/config`.
|
||||||
to close it.
|
to close it.
|
||||||
|
|
||||||
Note that this only delays adding files created while the daemon is
|
Note that this only delays adding files created while the daemon is
|
||||||
running. Changes made when it is not running will be added the next time
|
running. Changes made when it is not running will be added immediately
|
||||||
it is started up.
|
the next time it is started up.
|
||||||
|
|
||||||
* `annex.expireunused`
|
* `annex.expireunused`
|
||||||
|
|
||||||
|
|
Loading…
Add table
Add a link
Reference in a new issue