git-annex/Command/Unlock.hs
Joey Hess 16d7432a2f
prevent deadlock when reconcileStaged runs restagePointerFiles
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
2025-09-22 14:56:50 -04:00

72 lines
2 KiB
Haskell

{- git-annex command
-
- Copyright 2010-2022 Joey Hess <id@joeyh.name>
-
- Licensed under the GNU AGPL version 3 or higher.
-}
module Command.Unlock where
import Command
import Annex.Content
import Annex.Perms
import Annex.Link
import Annex.ReplaceFile
import Annex.InodeSentinal
import Utility.InodeCache
import Git.FilePath
import qualified Database.Keys
import qualified Utility.RawFilePath as R
import System.PosixCompat.Files (fileMode)
cmd :: Command
cmd = mkcmd "unlock" "unlock files for modification"
editcmd :: Command
editcmd = mkcmd "edit" "same as unlock"
mkcmd :: String -> String -> Command
mkcmd n d = withAnnexOptions [jsonOptions, annexedMatchingOptions] $
command n SectionCommon d paramPaths (withParams seek)
seek :: CmdParams -> CommandSeek
seek ps = withFilesInGitAnnex ww seeker =<< workTreeItems ww ps
where
ww = WarnUnmatchLsFiles "unlock"
seeker = AnnexedFileSeeker
{ startAction = const start
, checkContentPresent = Nothing
, usesLocationLog = False
}
start :: SeekInput -> OsPath -> Key -> CommandStart
start si file key = ifM (isJust <$> isAnnexLink file)
( starting "unlock" ai si $ perform file key
, stop
)
where
ai = mkActionItem (key, AssociatedFile (Just file))
perform :: OsPath -> Key -> CommandPerform
perform dest key = do
destmode <- liftIO $ catchMaybeIO $ fileMode <$> R.getFileStatus (fromOsPath dest)
destic <- replaceWorkTreeFile dest $ \tmp -> do
ifM (inAnnex key)
( do
r <- linkFromAnnex' key tmp destmode
case r of
LinkAnnexOk -> return ()
LinkAnnexNoop -> return ()
LinkAnnexFailed -> giveup "unlock failed"
, liftIO $ writePointerFile tmp key destmode
)
withTSDelta (liftIO . genInodeCache tmp)
next $ cleanup dest destic key destmode
cleanup :: OsPath -> Maybe InodeCache -> Key -> Maybe FileMode -> CommandCleanup
cleanup dest destic key destmode = do
stagePointerFile dest destmode =<< hashPointerFile key
maybe noop (restagePointerFile QueueRestage dest) destic
Database.Keys.addAssociatedFile key =<< inRepo (toTopFilePath dest)
return True