Ssh password prompting improved when using -J
When ssh connection caching is enabled (and when GIT_ANNEX_USE_GIT_SSH is not set), only one ssh password prompt will be made per host, and only one ssh password prompt will be made at a time. This also fixes a race in prepSocket's stale ssh connection stopping when run with -J. It was possible for one thread to start a cached ssh connection, and another thread to immediately stop it, resulting in excess connections being made. This commit was supported by the NSF-funded DataLad project.
This commit is contained in:
parent
782c30b8a4
commit
6992fe133b
8 changed files with 104 additions and 36 deletions
6
Annex.hs
6
Annex.hs
|
@ -124,6 +124,7 @@ data AnnexState = AnnexState
|
||||||
, groupmap :: Maybe GroupMap
|
, groupmap :: Maybe GroupMap
|
||||||
, ciphers :: M.Map StorableCipher Cipher
|
, ciphers :: M.Map StorableCipher Cipher
|
||||||
, lockcache :: LockCache
|
, lockcache :: LockCache
|
||||||
|
, sshstalecleaned :: MVar ()
|
||||||
, flags :: M.Map String Bool
|
, flags :: M.Map String Bool
|
||||||
, fields :: M.Map String String
|
, fields :: M.Map String String
|
||||||
, cleanup :: M.Map CleanupAction (Annex ())
|
, cleanup :: M.Map CleanupAction (Annex ())
|
||||||
|
@ -145,6 +146,8 @@ data AnnexState = AnnexState
|
||||||
newState :: GitConfig -> Git.Repo -> IO AnnexState
|
newState :: GitConfig -> Git.Repo -> IO AnnexState
|
||||||
newState c r = do
|
newState c r = do
|
||||||
emptyactiveremotes <- newMVar M.empty
|
emptyactiveremotes <- newMVar M.empty
|
||||||
|
o <- newMessageState
|
||||||
|
sc <- newMVar ()
|
||||||
return $ AnnexState
|
return $ AnnexState
|
||||||
{ repo = r
|
{ repo = r
|
||||||
, repoadjustment = return
|
, repoadjustment = return
|
||||||
|
@ -152,7 +155,7 @@ newState c r = do
|
||||||
, backend = Nothing
|
, backend = Nothing
|
||||||
, remotes = []
|
, remotes = []
|
||||||
, remoteannexstate = M.empty
|
, remoteannexstate = M.empty
|
||||||
, output = def
|
, output = o
|
||||||
, concurrency = NonConcurrent
|
, concurrency = NonConcurrent
|
||||||
, force = False
|
, force = False
|
||||||
, fast = False
|
, fast = False
|
||||||
|
@ -175,6 +178,7 @@ newState c r = do
|
||||||
, groupmap = Nothing
|
, groupmap = Nothing
|
||||||
, ciphers = M.empty
|
, ciphers = M.empty
|
||||||
, lockcache = M.empty
|
, lockcache = M.empty
|
||||||
|
, sshstalecleaned = sc
|
||||||
, flags = M.empty
|
, flags = M.empty
|
||||||
, fields = M.empty
|
, fields = M.empty
|
||||||
, cleanup = M.empty
|
, cleanup = M.empty
|
||||||
|
|
|
@ -11,6 +11,7 @@ module Annex.LockFile (
|
||||||
lockFileCached,
|
lockFileCached,
|
||||||
unlockFile,
|
unlockFile,
|
||||||
getLockCache,
|
getLockCache,
|
||||||
|
fromLockCache,
|
||||||
withExclusiveLock,
|
withExclusiveLock,
|
||||||
tryExclusiveLock,
|
tryExclusiveLock,
|
||||||
) where
|
) where
|
||||||
|
|
87
Annex/Ssh.hs
87
Annex/Ssh.hs
|
@ -23,10 +23,6 @@ module Annex.Ssh (
|
||||||
runSshAskPass
|
runSshAskPass
|
||||||
) where
|
) where
|
||||||
|
|
||||||
import qualified Data.Map as M
|
|
||||||
import Data.Hash.MD5
|
|
||||||
import System.Exit
|
|
||||||
|
|
||||||
import Annex.Common
|
import Annex.Common
|
||||||
import Annex.LockFile
|
import Annex.LockFile
|
||||||
import qualified Build.SysConfig as SysConfig
|
import qualified Build.SysConfig as SysConfig
|
||||||
|
@ -38,6 +34,7 @@ import Annex.Path
|
||||||
import Utility.Env
|
import Utility.Env
|
||||||
import Utility.FileSystemEncoding
|
import Utility.FileSystemEncoding
|
||||||
import Types.CleanupActions
|
import Types.CleanupActions
|
||||||
|
import Types.Messages
|
||||||
import Git.Env
|
import Git.Env
|
||||||
import Git.Ssh
|
import Git.Ssh
|
||||||
#ifndef mingw32_HOST_OS
|
#ifndef mingw32_HOST_OS
|
||||||
|
@ -45,6 +42,9 @@ import Annex.Perms
|
||||||
import Annex.LockPool
|
import Annex.LockPool
|
||||||
#endif
|
#endif
|
||||||
|
|
||||||
|
import Data.Hash.MD5
|
||||||
|
import Control.Concurrent
|
||||||
|
|
||||||
{- Some ssh commands are fed stdin on a pipe and so should be allowed to
|
{- Some ssh commands are fed stdin on a pipe and so should be allowed to
|
||||||
- consume it. But ssh commands that are not piped stdin should generally
|
- consume it. But ssh commands that are not piped stdin should generally
|
||||||
- not be allowed to consume the process's stdin. -}
|
- not be allowed to consume the process's stdin. -}
|
||||||
|
@ -71,16 +71,18 @@ sshCommand cs (host, port) gc remotecmd = ifM (liftIO safe_GIT_SSH)
|
||||||
sshOptions :: ConsumeStdin -> (String, Maybe Integer) -> RemoteGitConfig -> [CommandParam] -> Annex [CommandParam]
|
sshOptions :: ConsumeStdin -> (String, Maybe Integer) -> RemoteGitConfig -> [CommandParam] -> Annex [CommandParam]
|
||||||
sshOptions cs (host, port) gc opts = go =<< sshCachingInfo (host, port)
|
sshOptions cs (host, port) gc opts = go =<< sshCachingInfo (host, port)
|
||||||
where
|
where
|
||||||
go (Nothing, params) = ret params
|
go (Nothing, params) = return $ mkparams cs params
|
||||||
go (Just socketfile, params) = do
|
go (Just socketfile, params) = do
|
||||||
prepSocket socketfile
|
prepSocket socketfile gc
|
||||||
ret params
|
(Param host : mkparams NoConsumeStdin params)
|
||||||
ret ps = return $ concat
|
|
||||||
|
return $ mkparams cs params
|
||||||
|
mkparams cs' ps = concat
|
||||||
[ ps
|
[ ps
|
||||||
, map Param (remoteAnnexSshOptions gc)
|
, map Param (remoteAnnexSshOptions gc)
|
||||||
, opts
|
, opts
|
||||||
, portParams port
|
, portParams port
|
||||||
, consumeStdinParams cs
|
, consumeStdinParams cs'
|
||||||
, [Param "-T"]
|
, [Param "-T"]
|
||||||
]
|
]
|
||||||
|
|
||||||
|
@ -158,21 +160,52 @@ portParams :: Maybe Integer -> [CommandParam]
|
||||||
portParams Nothing = []
|
portParams Nothing = []
|
||||||
portParams (Just port) = [Param "-p", Param $ show port]
|
portParams (Just port) = [Param "-p", Param $ show port]
|
||||||
|
|
||||||
{- Prepare to use a socket file for ssh connection caching.
|
{- Prepare to use a socket file for ssh connection caching.
|
||||||
- Locks a lock file to prevent other git-annex processes from
|
-
|
||||||
- stopping the ssh multiplexer on this socket. -}
|
- When concurrency is enabled, this blocks until a ssh connection
|
||||||
prepSocket :: FilePath -> Annex ()
|
- has been made to the host. So, any password prompting by ssh will
|
||||||
prepSocket socketfile = do
|
- happen in this call, and only one ssh process will prompt at a time.
|
||||||
-- If the lock pool is empty, this is the first ssh of this
|
-
|
||||||
-- run. There could be stale ssh connections hanging around
|
- Locks the socket lock file to prevent other git-annex processes from
|
||||||
|
- stopping the ssh multiplexer on this socket.
|
||||||
|
-}
|
||||||
|
prepSocket :: FilePath -> RemoteGitConfig -> [CommandParam] -> Annex ()
|
||||||
|
prepSocket socketfile gc sshparams = do
|
||||||
|
-- There could be stale ssh connections hanging around
|
||||||
-- from a previous git-annex run that was interrupted.
|
-- from a previous git-annex run that was interrupted.
|
||||||
whenM (not . any isLock . M.keys <$> getLockCache)
|
-- This must run only once, before we have made any ssh connection.
|
||||||
|
whenM (isJust <$> (liftIO . tryTakeMVar =<< Annex.getState Annex.sshstalecleaned)) $
|
||||||
sshCleanup
|
sshCleanup
|
||||||
-- Cleanup at end of this run.
|
-- Cleanup at shutdown.
|
||||||
Annex.addCleanup SshCachingCleanup sshCleanup
|
Annex.addCleanup SshCachingCleanup sshCleanup
|
||||||
|
|
||||||
liftIO $ createDirectoryIfMissing True $ parentDir socketfile
|
liftIO $ createDirectoryIfMissing True $ parentDir socketfile
|
||||||
lockFileCached $ socket2lock socketfile
|
let socketlock = socket2lock socketfile
|
||||||
|
|
||||||
|
prompt $ \s -> when (concurrentOutputEnabled s) $
|
||||||
|
-- If the LockCache already has the socketlock in it,
|
||||||
|
-- the connection has already been started. Otherwise,
|
||||||
|
-- get the connection started now.
|
||||||
|
whenM (isNothing <$> fromLockCache socketlock) $
|
||||||
|
void $ liftIO $ boolSystem "ssh" $
|
||||||
|
sshparams ++ startSshConnection gc
|
||||||
|
|
||||||
|
lockFileCached socketlock
|
||||||
|
|
||||||
|
-- Parameters to get ssh connected to the remote host,
|
||||||
|
-- by asking it to run a no-op command.
|
||||||
|
--
|
||||||
|
-- Could simply run "true", but the remote host may only
|
||||||
|
-- allow git-annex-shell to run. So, run git-annex-shell inannex
|
||||||
|
-- with the path to the remote repository and no other parameters,
|
||||||
|
-- which is a no-op supported by all versions of git-annex-shell.
|
||||||
|
startSshConnection :: RemoteGitConfig -> [CommandParam]
|
||||||
|
startSshConnection gc =
|
||||||
|
[ Param "git-annex-shell"
|
||||||
|
, Param "inannex"
|
||||||
|
, File $ Git.repoPath $ gitConfigRepo $
|
||||||
|
remoteGitConfig gc
|
||||||
|
]
|
||||||
|
|
||||||
{- Find ssh socket files.
|
{- Find ssh socket files.
|
||||||
-
|
-
|
||||||
|
@ -324,12 +357,20 @@ sshOptionsTo remote gc localr
|
||||||
Just host -> ifM (liftIO $ safe_GIT_SSH <&&> gitSshEnvSet)
|
Just host -> ifM (liftIO $ safe_GIT_SSH <&&> gitSshEnvSet)
|
||||||
( unchanged
|
( unchanged
|
||||||
, do
|
, do
|
||||||
(msockfile, _) <- sshCachingInfo (host, Git.Url.port remote)
|
let port = Git.Url.port remote
|
||||||
|
(msockfile, cacheparams) <- sshCachingInfo (host, port)
|
||||||
case msockfile of
|
case msockfile of
|
||||||
Nothing -> use []
|
Nothing -> use []
|
||||||
Just sockfile -> do
|
Just sockfile -> do
|
||||||
prepSocket sockfile
|
prepSocket sockfile gc $
|
||||||
use (sshConnectionCachingParams sockfile)
|
Param host : concat
|
||||||
|
[ cacheparams
|
||||||
|
, map Param (remoteAnnexSshOptions gc)
|
||||||
|
, portParams port
|
||||||
|
, consumeStdinParams NoConsumeStdin
|
||||||
|
, [Param "-T"]
|
||||||
|
]
|
||||||
|
use cacheparams
|
||||||
)
|
)
|
||||||
where
|
where
|
||||||
unchanged = return localr
|
unchanged = return localr
|
||||||
|
|
|
@ -1,3 +1,12 @@
|
||||||
|
git-annex (6.20170511) UNRELEASED; urgency=medium
|
||||||
|
|
||||||
|
* Ssh password prompting improved when using -J for concurrency.
|
||||||
|
When ssh connection caching is enabled (and when GIT_ANNEX_USE_GIT_SSH
|
||||||
|
is not set), only one ssh password prompt will be made per host, and
|
||||||
|
only one ssh password prompt will be made at a time.
|
||||||
|
|
||||||
|
-- Joey Hess <id@joeyh.name> Thu, 11 May 2017 15:16:23 -0400
|
||||||
|
|
||||||
git-annex (6.20170510) unstable; urgency=medium
|
git-annex (6.20170510) unstable; urgency=medium
|
||||||
|
|
||||||
* When a http remote does not expose an annex.uuid config, only warn
|
* When a http remote does not expose an annex.uuid config, only warn
|
||||||
|
|
16
Messages.hs
16
Messages.hs
|
@ -1,6 +1,6 @@
|
||||||
{- git-annex output messages
|
{- git-annex output messages
|
||||||
-
|
-
|
||||||
- Copyright 2010-2016 Joey Hess <id@joeyh.name>
|
- Copyright 2010-2017 Joey Hess <id@joeyh.name>
|
||||||
-
|
-
|
||||||
- Licensed under the GNU GPL version 3 or higher.
|
- Licensed under the GNU GPL version 3 or higher.
|
||||||
-}
|
-}
|
||||||
|
@ -41,12 +41,14 @@ module Messages (
|
||||||
outputMessage,
|
outputMessage,
|
||||||
implicitMessage,
|
implicitMessage,
|
||||||
withMessageState,
|
withMessageState,
|
||||||
|
prompt,
|
||||||
) where
|
) where
|
||||||
|
|
||||||
import System.Log.Logger
|
import System.Log.Logger
|
||||||
import System.Log.Formatter
|
import System.Log.Formatter
|
||||||
import System.Log.Handler (setFormatter)
|
import System.Log.Handler (setFormatter)
|
||||||
import System.Log.Handler.Simple
|
import System.Log.Handler.Simple
|
||||||
|
import Control.Concurrent
|
||||||
|
|
||||||
import Common
|
import Common
|
||||||
import Types
|
import Types
|
||||||
|
@ -219,3 +221,15 @@ commandProgressDisabled = withMessageState $ \s -> return $
|
||||||
- output. -}
|
- output. -}
|
||||||
implicitMessage :: Annex () -> Annex ()
|
implicitMessage :: Annex () -> Annex ()
|
||||||
implicitMessage = whenM (implicitMessages <$> Annex.getState Annex.output)
|
implicitMessage = whenM (implicitMessages <$> Annex.getState Annex.output)
|
||||||
|
|
||||||
|
{- Prevents any concurrent console access while running an action, so
|
||||||
|
- that the action is the only thing using the console, and can eg prompt
|
||||||
|
- the user.
|
||||||
|
-}
|
||||||
|
prompt :: (MessageState -> Annex a) -> Annex a
|
||||||
|
prompt a = withMessageState $ \s ->
|
||||||
|
if concurrentOutputEnabled s
|
||||||
|
then
|
||||||
|
let l = promptLock s
|
||||||
|
in bracketIO (takeMVar l) (putMVar l) (const (a s))
|
||||||
|
else a s
|
||||||
|
|
|
@ -13,7 +13,6 @@ import Types.Messages
|
||||||
import Messages.Concurrent
|
import Messages.Concurrent
|
||||||
import Messages.JSON
|
import Messages.JSON
|
||||||
|
|
||||||
|
|
||||||
withMessageState :: (MessageState -> Annex a) -> Annex a
|
withMessageState :: (MessageState -> Annex a) -> Annex a
|
||||||
withMessageState a = Annex.getState Annex.output >>= a
|
withMessageState a = Annex.getState Annex.output >>= a
|
||||||
|
|
||||||
|
|
|
@ -1,6 +1,6 @@
|
||||||
{- git-annex Messages data types
|
{- git-annex Messages data types
|
||||||
-
|
-
|
||||||
- Copyright 2012 Joey Hess <id@joeyh.name>
|
- Copyright 2012-2017 Joey Hess <id@joeyh.name>
|
||||||
-
|
-
|
||||||
- Licensed under the GNU GPL version 3 or higher.
|
- Licensed under the GNU GPL version 3 or higher.
|
||||||
-}
|
-}
|
||||||
|
@ -9,9 +9,9 @@
|
||||||
|
|
||||||
module Types.Messages where
|
module Types.Messages where
|
||||||
|
|
||||||
import Data.Default
|
|
||||||
import qualified Data.Aeson as Aeson
|
import qualified Data.Aeson as Aeson
|
||||||
|
|
||||||
|
import Control.Concurrent
|
||||||
#ifdef WITH_CONCURRENTOUTPUT
|
#ifdef WITH_CONCURRENTOUTPUT
|
||||||
import System.Console.Regions (ConsoleRegion)
|
import System.Console.Regions (ConsoleRegion)
|
||||||
#endif
|
#endif
|
||||||
|
@ -32,11 +32,13 @@ data MessageState = MessageState
|
||||||
, consoleRegionErrFlag :: Bool
|
, consoleRegionErrFlag :: Bool
|
||||||
#endif
|
#endif
|
||||||
, jsonBuffer :: Maybe Aeson.Object
|
, jsonBuffer :: Maybe Aeson.Object
|
||||||
|
, promptLock :: MVar () -- left full when not prompting
|
||||||
}
|
}
|
||||||
|
|
||||||
instance Default MessageState
|
newMessageState :: IO MessageState
|
||||||
where
|
newMessageState = do
|
||||||
def = MessageState
|
promptlock <- newMVar ()
|
||||||
|
return $ MessageState
|
||||||
{ outputType = NormalOutput
|
{ outputType = NormalOutput
|
||||||
, concurrentOutputEnabled = False
|
, concurrentOutputEnabled = False
|
||||||
, sideActionBlock = NoBlock
|
, sideActionBlock = NoBlock
|
||||||
|
@ -46,4 +48,5 @@ instance Default MessageState
|
||||||
, consoleRegionErrFlag = False
|
, consoleRegionErrFlag = False
|
||||||
#endif
|
#endif
|
||||||
, jsonBuffer = Nothing
|
, jsonBuffer = Nothing
|
||||||
|
, promptLock = promptlock
|
||||||
}
|
}
|
||||||
|
|
|
@ -37,9 +37,6 @@ non-concurrent uses the current, faster path.
|
||||||
prepSocket takes a shared
|
prepSocket takes a shared
|
||||||
file level lock of the socket's lock file, which is used to tell when
|
file level lock of the socket's lock file, which is used to tell when
|
||||||
another git-annex process is using the connection multiplexer.
|
another git-annex process is using the connection multiplexer.
|
||||||
So, an optimisation would be for prepSocket to try to take a non-blocking
|
So, an optimisation would be for prepSocket to check if it's already
|
||||||
exclusive file-level lock. If it fails, it knows some process has
|
taken that shared lock, and then it does not need to start the multiplexer.
|
||||||
already taken the shared lock, and so the multiplexer is started and no
|
|
||||||
password prompting needs to be done. So it does not need to try to start
|
|
||||||
the multiplexer in this case.
|
|
||||||
"""]]
|
"""]]
|
||||||
|
|
Loading…
Reference in a new issue