add gitAnnexChildProcess and use instead of incorrect use of runsGitAnnexChildProcess

Fixes reversion in 8.20200617 that made annex.pidlock being enabled result
in some commands stalling, particularly those needing to autoinit.

Renamed runsGitAnnexChildProcess to make clearer where it should be
used.

Arguably, it would be better to have a way to make any process git-annex
runs have the env var set. But then it would need to take the pid lock
when running any and all processes, and that would be a problem when
git-annex runs two processes concurrently. So, I'm left doing it ad-hoc
in places where git-annex really does run a child process, directly
or indirectly via a particular git command.
This commit is contained in:
Joey Hess 2020-08-25 14:57:25 -04:00
parent 6b0532e532
commit 7bdb0cdc0d
No known key found for this signature in database
GPG key ID: DB12DB0FF05F8F38
9 changed files with 97 additions and 33 deletions

View file

@ -1,4 +1,4 @@
{- Temporarily changing the files git uses. {- Temporarily changing how git-annex runs git commands.
- -
- Copyright 2014-2020 Joey Hess <id@joeyh.name> - Copyright 2014-2020 Joey Hess <id@joeyh.name>
- -
@ -135,7 +135,8 @@ withAltRepo modrepo unmodrepo a = do
} }
either E.throw return v either E.throw return v
{- Wrap around actions that may run a git-annex child process. {- Wrap around actions that may run a git-annex child process via a git
- command.
- -
- When pid locking is in use, this tries to take the pid lock, and if - When pid locking is in use, this tries to take the pid lock, and if
- successful, holds it while running the child process. The action - successful, holds it while running the child process. The action
@ -147,10 +148,13 @@ withAltRepo modrepo unmodrepo a = do
- the child. The child is assumed to not do any locking that conflicts - the child. The child is assumed to not do any locking that conflicts
- with the parent, but if it did happen to do that, it would be noticed - with the parent, but if it did happen to do that, it would be noticed
- when git-annex is used without pid locking. - when git-annex is used without pid locking.
-
- When git-annex runs its child process directly, gitAnnexChildProcess is
- used instead of this.
-} -}
runsGitAnnexChildProcess :: Annex a -> Annex a runsGitAnnexChildProcessViaGit :: Annex a -> Annex a
#ifndef mingw32_HOST_OS #ifndef mingw32_HOST_OS
runsGitAnnexChildProcess a = pidLockFile >>= \case runsGitAnnexChildProcessViaGit a = pidLockFile >>= \case
Nothing -> a Nothing -> a
Just pidlock -> bracket (setup pidlock) cleanup (go pidlock) Just pidlock -> bracket (setup pidlock) cleanup (go pidlock)
where where
@ -163,7 +167,7 @@ runsGitAnnexChildProcess a = pidLockFile >>= \case
go pidlock (Just _h) = do go pidlock (Just _h) = do
v <- liftIO $ PidF.pidLockEnv pidlock v <- liftIO $ PidF.pidLockEnv pidlock
let addenv g = do let addenv g = do
g' <- liftIO $ addGitEnv g v "1" g' <- liftIO $ addGitEnv g v PidF.pidLockEnvValue
return (g', ()) return (g', ())
let rmenv oldg g let rmenv oldg g
| any (\(k, _) -> k == v) (fromMaybe [] (Git.gitEnv oldg)) = g | any (\(k, _) -> k == v) (fromMaybe [] (Git.gitEnv oldg)) = g
@ -174,12 +178,12 @@ runsGitAnnexChildProcess a = pidLockFile >>= \case
in g { Git.gitEnv = e' } in g { Git.gitEnv = e' }
withAltRepo addenv rmenv (const a) withAltRepo addenv rmenv (const a)
#else #else
runsGitAnnexChildProcess a = a runsGitAnnexChildProcessViaGit a = a
#endif #endif
runsGitAnnexChildProcess' :: Git.Repo -> (Git.Repo -> IO a) -> Annex a runsGitAnnexChildProcessViaGit' :: Git.Repo -> (Git.Repo -> IO a) -> Annex a
#ifndef mingw32_HOST_OS #ifndef mingw32_HOST_OS
runsGitAnnexChildProcess' r a = pidLockFile >>= \case runsGitAnnexChildProcessViaGit' r a = pidLockFile >>= \case
Nothing -> liftIO $ a r Nothing -> liftIO $ a r
Just pidlock -> liftIO $ bracket (setup pidlock) cleanup (go pidlock) Just pidlock -> liftIO $ bracket (setup pidlock) cleanup (go pidlock)
where where
@ -191,8 +195,8 @@ runsGitAnnexChildProcess' r a = pidLockFile >>= \case
go _ Nothing = a r go _ Nothing = a r
go pidlock (Just _h) = do go pidlock (Just _h) = do
v <- PidF.pidLockEnv pidlock v <- PidF.pidLockEnv pidlock
r' <- addGitEnv r v "1" r' <- addGitEnv r v PidF.pidLockEnvValue
a r' a r'
#else #else
runsGitAnnexChildProcess' r a = liftIO $ a r runsGitAnnexChildProcessViaGit' r a = liftIO $ a r
#endif #endif

View file

@ -37,7 +37,6 @@ import Annex.UUID
import Annex.WorkTree import Annex.WorkTree
import Annex.Fixup import Annex.Fixup
import Annex.Path import Annex.Path
import Annex.GitOverlay
import Config import Config
import Config.Files import Config.Files
import Config.Smudge import Config.Smudge
@ -327,18 +326,18 @@ fixupUnusualReposAfterInit = do
- The enabling is done in a child process to avoid it using stdio. - The enabling is done in a child process to avoid it using stdio.
-} -}
autoEnableSpecialRemotes :: Annex () autoEnableSpecialRemotes :: Annex ()
autoEnableSpecialRemotes = runsGitAnnexChildProcess $ do autoEnableSpecialRemotes = do
rp <- fromRawFilePath <$> fromRepo Git.repoPath rp <- fromRawFilePath <$> fromRepo Git.repoPath
cmd <- liftIO programPath withNullHandle $ \nullh -> gitAnnexChildProcess
liftIO $ withNullHandle $ \nullh -> do [ "init"
let p = (proc cmd , "--autoenable"
[ "init" ]
, "--autoenable" (\p -> p
])
{ std_out = UseHandle nullh { std_out = UseHandle nullh
, std_err = UseHandle nullh , std_err = UseHandle nullh
, std_in = UseHandle nullh , std_in = UseHandle nullh
, cwd = Just rp , cwd = Just rp
} }
withCreateProcess p $ \_ _ _ pid -> void $ waitForProcess pid )
(\_ _ _ pid -> void $ waitForProcess pid)
remotesChanged remotesChanged

View file

@ -218,7 +218,7 @@ restagePointerFile (Restage True) f orig = withTSDelta $ \tsd ->
[ Param "-c" [ Param "-c"
, Param $ "core.safecrlf=" ++ boolConfig False , Param $ "core.safecrlf=" ++ boolConfig False
] } ] }
runsGitAnnexChildProcess' r'' $ \r''' -> runsGitAnnexChildProcessViaGit' r'' $ \r''' ->
liftIO $ Git.UpdateIndex.refreshIndex r''' $ \feed -> liftIO $ Git.UpdateIndex.refreshIndex r''' $ \feed ->
forM_ l $ \(f', checkunmodified) -> forM_ l $ \(f', checkunmodified) ->
whenM checkunmodified $ whenM checkunmodified $

View file

@ -1,15 +1,23 @@
{- git-annex program path {- git-annex program path
- -
- Copyright 2013 Joey Hess <id@joeyh.name> - Copyright 2013-2020 Joey Hess <id@joeyh.name>
- -
- Licensed under the GNU AGPL version 3 or higher. - Licensed under the GNU AGPL version 3 or higher.
-} -}
{-# LANGUAGE CPP #-}
module Annex.Path where module Annex.Path where
import Common import Annex.Common
import Config.Files import Config.Files
import Utility.Env import Utility.Env
#ifndef mingw32_HOST_OS
import qualified Utility.LockFile.PidLock as PidF
import qualified Utility.LockPool.PidLock as PidP
import Utility.LockPool (dropLock)
import Config
#endif
import System.Environment (getExecutablePath) import System.Environment (getExecutablePath)
@ -45,3 +53,44 @@ cannotFindProgram :: IO a
cannotFindProgram = do cannotFindProgram = do
f <- programFile f <- programFile
giveup $ "cannot find git-annex program in PATH or in " ++ f giveup $ "cannot find git-annex program in PATH or in " ++ f
{- Runs a git-annex child process.
-
- Like runsGitAnnexChildProcessViaGit, when pid locking is in use,
- this takes the pid lock, while running it, and sets an env var
- that prevents the child process trying to take the pid lock,
- to avoid it deadlocking.
-}
gitAnnexChildProcess
:: [String]
-> (CreateProcess -> CreateProcess)
-> (Maybe Handle -> Maybe Handle -> Maybe Handle -> ProcessHandle -> IO a)
-> Annex a
gitAnnexChildProcess ps f a = do
cmd <- liftIO programPath
let p = f (proc cmd ps)
let gonopidlock = withCreateProcess p a
#ifndef mingw32_HOST_OS
pidLockFile >>= liftIO . \case
Nothing -> gonopidlock
Just pidlock -> bracket
(setup pidlock)
cleanup
(go gonopidlock p pidlock)
where
setup pidlock = PidP.tryLock pidlock
cleanup (Just h) = dropLock h
cleanup Nothing = return ()
go gonopidlock _ _ Nothing = gonopidlock
go _ p pidlock (Just _h) = do
v <- PidF.pidLockEnv pidlock
baseenv <- case env p of
Nothing -> getEnvironment
Just baseenv -> pure baseenv
let p' = p { env = Just ((v, PidF.pidLockEnvValue) : baseenv) }
withCreateProcess p' a
#else
gonopidlock
#endif

View file

@ -9,6 +9,9 @@ git-annex (8.20200815) UNRELEASED; urgency=medium
* stack.yaml: Updated to lts-16.10. * stack.yaml: Updated to lts-16.10.
* Fix reversion in 7.20190322 that made addurl --file not be honored * Fix reversion in 7.20190322 that made addurl --file not be honored
when youtube-dl was used to download media. when youtube-dl was used to download media.
* Fix reversion in 8.20200617 that made annex.pidlock being enabled
result in some commands stalling, particularly those needing to
autoinit.
-- Joey Hess <id@joeyh.name> Fri, 14 Aug 2020 14:57:45 -0400 -- Joey Hess <id@joeyh.name> Fri, 14 Aug 2020 14:57:45 -0400

View file

@ -65,7 +65,6 @@ import Annex.UpdateInstead
import Annex.Export import Annex.Export
import Annex.TaggedPush import Annex.TaggedPush
import Annex.CurrentBranch import Annex.CurrentBranch
import Annex.GitOverlay
import qualified Database.Export as Export import qualified Database.Export as Export
import Utility.Bloom import Utility.Bloom
import Utility.OptParse import Utility.OptParse
@ -515,10 +514,12 @@ pushRemote o remote (Just branch, _) = do
postpushupdate repo = case Git.repoWorkTree repo of postpushupdate repo = case Git.repoWorkTree repo of
Nothing -> return True Nothing -> return True
Just wt -> ifM needemulation Just wt -> ifM needemulation
( runsGitAnnexChildProcess $ liftIO $ do ( gitAnnexChildProcess ["post-receive"]
p <- programPath (\cp -> cp { cwd = Just (fromRawFilePath wt) })
boolSystem' p [Param "post-receive"] (\_ _ _ pid -> waitForProcess pid >>= return . \case
(\cp -> cp { cwd = Just (fromRawFilePath wt) }) ExitSuccess -> True
_ -> False
)
, return True , return True
) )
where where

View file

@ -15,7 +15,6 @@ import qualified Git
import Config import Config
import Annex.Path import Annex.Path
import Annex.Version import Annex.Version
import Annex.GitOverlay
import Types.RepoVersion import Types.RepoVersion
#ifndef mingw32_HOST_OS #ifndef mingw32_HOST_OS
import qualified Upgrade.V0 import qualified Upgrade.V0
@ -104,13 +103,16 @@ upgrade automatic destversion = do
-- upgrading a git repo other than the current repo. -- upgrading a git repo other than the current repo.
upgraderemote = do upgraderemote = do
rp <- fromRawFilePath <$> fromRepo Git.repoPath rp <- fromRawFilePath <$> fromRepo Git.repoPath
cmd <- liftIO programPath gitAnnexChildProcess
runsGitAnnexChildProcess $ liftIO $ boolSystem' cmd [ "upgrade"
[ Param "upgrade" , "--quiet"
, Param "--quiet" , "--autoonly"
, Param "--autoonly"
] ]
(\p -> p { cwd = Just rp }) (\p -> p { cwd = Just rp })
(\_ _ _ pid -> waitForProcess pid >>= return . \case
ExitSuccess -> True
_ -> False
)
upgradingRemote :: Annex Bool upgradingRemote :: Annex Bool
upgradingRemote = isJust <$> fromRepo Git.remoteName upgradingRemote = isJust <$> fromRepo Git.remoteName

View file

@ -15,6 +15,7 @@ module Utility.LockFile.PidLock (
checkLocked, checkLocked,
checkSaneLock, checkSaneLock,
pidLockEnv, pidLockEnv,
pidLockEnvValue,
) where ) where
import Utility.PartialPrelude import Utility.PartialPrelude
@ -293,3 +294,6 @@ pidLockEnv :: FilePath -> IO String
pidLockEnv lockfile = do pidLockEnv lockfile = do
abslockfile <- absPath lockfile abslockfile <- absPath lockfile
return $ "PIDLOCK_" ++ filter legalInEnvVar abslockfile return $ "PIDLOCK_" ++ filter legalInEnvVar abslockfile
pidLockEnvValue :: String
pidLockEnvValue = "1"

View file

@ -74,3 +74,5 @@ done.
[[!meta author=yoh]] [[!meta author=yoh]]
[[!tag projects/datalad]] [[!tag projects/datalad]]
> [[fixed|done]] --[[Joey]]