
Fix hang that could occur when using git-annex adjust on a branch with a
number of files greater than annex.queuesize. Or potentially other
commands.
When reconcileStaged is running, the database is being opened. But
restagePointerFiles closes the database, and later writes to it. So it will
deadlock if called by reconcileStaged.
The deadlock occurred when the git queue happened to be full, causing
adding a call to restagePointerFiles to it to flush the queue and
restagePointerFiles to run at the wrong time.
Fixed by making reconcileStaged, when it populates or depopulates a pointer
file, arrange for restagePointerFiles to be run as a cleanup action, rather
than from the git queue.
But, what if restagePointerFiles is already in the git queue before
reconcileStaged is run? If it adds anything else to the git queue, causing
the queue to flush, it would still deadlock. To avoid this hypothetical
situation, added a Annex.inreconcilestaged, and made restagePointerFiles
check it and not do anything.
Note that, I did consider the simpler approach of only running
restagePointerFiles as a cleanup action, rather than from the git queue.
But see commit 6a3bd283b8
for why it was made
to use the queue in the first place. I wanted to avoid tying this bug fix
to a behavior change.
Sponsored-by: mycroft
88 lines
2.5 KiB
Haskell
88 lines
2.5 KiB
Haskell
{- git-annex command
|
|
-
|
|
- Copyright 2010-2024 Joey Hess <id@joeyh.name>
|
|
-
|
|
- Licensed under the GNU AGPL version 3 or higher.
|
|
-}
|
|
|
|
{-# LANGUAGE CPP #-}
|
|
|
|
module Command.PreCommit where
|
|
|
|
import Command
|
|
import qualified Command.Fix
|
|
import qualified Command.Smudge
|
|
import Annex.Hook
|
|
import Annex.Link
|
|
import Annex.View
|
|
import Annex.View.ViewedFile
|
|
import Logs.View
|
|
import Logs.MetaData
|
|
import Types.View
|
|
import Types.MetaData
|
|
import qualified Annex
|
|
import qualified Annex.Branch
|
|
|
|
import qualified Data.Set as S
|
|
import qualified Data.Text as T
|
|
|
|
cmd :: Command
|
|
cmd = noCommit $ command "pre-commit" SectionPlumbing
|
|
"run by git pre-commit hook"
|
|
paramPaths
|
|
(withParams seek)
|
|
|
|
seek :: CmdParams -> CommandSeek
|
|
seek ps = do
|
|
let ww = WarnUnmatchWorkTreeItems "pre-commit"
|
|
l <- workTreeItems ww ps
|
|
-- fix symlinks to files being committed
|
|
flip (withFilesToBeCommitted ww) l $ \(si, f) -> commandAction $
|
|
maybe stop (Command.Fix.start Command.Fix.FixSymlinks si f)
|
|
=<< isAnnexLink f
|
|
-- after a merge conflict or git cherry-pick or stash, pointer
|
|
-- files in the worktree won't be populated, so populate them here
|
|
Command.Smudge.updateSmudged NoRestage
|
|
|
|
runAnnexHook preCommitAnnexHook annexPreCommitCommand
|
|
|
|
-- committing changes to a view updates metadata
|
|
currentView >>= \case
|
|
Nothing -> noop
|
|
Just (v, _madj) -> do
|
|
withViewChanges
|
|
(addViewMetaData v)
|
|
(removeViewMetaData v)
|
|
-- Manually commit in this case, because
|
|
-- noCommit prevents automatic commit.
|
|
whenM (annexAlwaysCommit <$> Annex.getGitConfig) $
|
|
Annex.Branch.commit =<< Annex.Branch.commitMessage
|
|
|
|
addViewMetaData :: View -> ViewedFile -> Key -> CommandStart
|
|
addViewMetaData v f k = starting "metadata" ai si $
|
|
next $ changeMetaData k $ fromView v f
|
|
where
|
|
ai = mkActionItem (k, f)
|
|
si = SeekInput []
|
|
|
|
removeViewMetaData :: View -> ViewedFile -> Key -> CommandStart
|
|
removeViewMetaData v f k = starting "metadata" ai si $
|
|
next $ changeMetaData k $ unsetMetaData $ fromView v f
|
|
where
|
|
ai = mkActionItem (k, f)
|
|
si = SeekInput []
|
|
|
|
changeMetaData :: Key -> MetaData -> CommandCleanup
|
|
changeMetaData k metadata = do
|
|
showMetaDataChange metadata
|
|
addMetaData k metadata
|
|
return True
|
|
|
|
showMetaDataChange :: MetaData -> Annex ()
|
|
showMetaDataChange = showLongNote . UnquotedString . unlines . concatMap showmeta . fromMetaData
|
|
where
|
|
showmeta (f, vs) = map (showmetavalue f) $ S.toList vs
|
|
showmetavalue f v = T.unpack (fromMetaField f) <> showset v <> "=" <> decodeBS (fromMetaValue v)
|
|
showset v
|
|
| isSet v = "+"
|
|
| otherwise = "-"
|