aboutsummaryrefslogtreecommitdiff
diff options
context:
space:
mode:
-rw-r--r--Command/P2PStdIO.hs20
-rw-r--r--P2P/IO.hs5
-rw-r--r--P2P/Protocol.hs4
-rw-r--r--Remote/Git.hs57
-rw-r--r--Remote/Helper/P2P.hs67
-rw-r--r--Remote/Helper/Ssh.hs98
-rw-r--r--Remote/P2P.hs72
-rw-r--r--Utility/Process.hs6
-rw-r--r--doc/devblog/day_488__groundwork_for_using_p2pstdio.mdwn30
-rw-r--r--doc/git-annex-shell.mdwn5
-rw-r--r--doc/git-annex.mdwn2
-rw-r--r--doc/todo/accellerate_ssh_remotes_with_git-annex-shell_mass_protocol.mdwn4
-rw-r--r--git-annex.cabal1
13 files changed, 286 insertions, 85 deletions
diff --git a/Command/P2PStdIO.hs b/Command/P2PStdIO.hs
index f6e4ae0f0..cb7e54f28 100644
--- a/Command/P2PStdIO.hs
+++ b/Command/P2PStdIO.hs
@@ -11,34 +11,30 @@ import Command
import P2P.IO
import P2P.Annex
import qualified P2P.Protocol as P2P
-import Git.Types
import qualified Annex
import Annex.UUID
import qualified CmdLine.GitAnnexShell.Checks as Checks
-import qualified CmdLine.GitAnnexShell.Fields as Fields
-import Utility.AuthToken
-import Utility.Tmp.Dir
cmd :: Command
cmd = noMessages $ command "p2pstdio" SectionPlumbing
"communicate in P2P protocol over stdio"
- paramNothing (withParams seek)
+ paramUUID (withParams seek)
seek :: CmdParams -> CommandSeek
-seek = withNothing start
+seek [u] = commandAction $ start $ toUUID u
+seek _ = giveup "missing UUID parameter"
-start :: CommandStart
-start = do
+start :: UUID -> CommandStart
+start theiruuid = do
servermode <- liftIO $
Checks.checkEnvSet Checks.readOnlyEnv >>= return . \case
True -> P2P.ServeReadOnly
False -> P2P.ServeReadWrite
- theiruuid <- Fields.getField Fields.remoteUUID >>= \case
- Nothing -> giveup "missing remoteuuid field"
- Just u -> return (toUUID u)
myuuid <- getUUID
conn <- stdioP2PConnection <$> Annex.gitRepo
- let server = P2P.serveAuthed servermode myuuid
+ let server = do
+ P2P.net $ P2P.sendMessage (P2P.AUTH_SUCCESS myuuid)
+ P2P.serveAuthed servermode myuuid
runFullProto (Serving theiruuid Nothing) conn server >>= \case
Right () -> next $ next $ return True
Left e -> giveup e
diff --git a/P2P/IO.hs b/P2P/IO.hs
index 6cdc5b7d5..8b532c7f4 100644
--- a/P2P/IO.hs
+++ b/P2P/IO.hs
@@ -10,6 +10,7 @@
module P2P.IO
( RunProto
, P2PConnection(..)
+ , ClosableConnection(..)
, stdioP2PConnection
, connectPeer
, closeConnection
@@ -51,6 +52,10 @@ data P2PConnection = P2PConnection
, connOhdl :: Handle
}
+data ClosableConnection conn
+ = OpenConnection conn
+ | ClosedConnection
+
-- P2PConnection using stdio.
stdioP2PConnection :: Git.Repo -> P2PConnection
stdioP2PConnection g = P2PConnection
diff --git a/P2P/Protocol.hs b/P2P/Protocol.hs
index c750ae6ff..4acbaadef 100644
--- a/P2P/Protocol.hs
+++ b/P2P/Protocol.hs
@@ -250,6 +250,10 @@ $(makeFree ''LocalF)
auth :: UUID -> AuthToken -> Proto (Maybe UUID)
auth myuuid t = do
net $ sendMessage (AUTH myuuid t)
+ postAuth
+
+postAuth :: Proto (Maybe UUID)
+postAuth = do
r <- net receiveMessage
case r of
AUTH_SUCCESS theiruuid -> return $ Just theiruuid
diff --git a/Remote/Git.hs b/Remote/Git.hs
index caa677464..0edd04117 100644
--- a/Remote/Git.hs
+++ b/Remote/Git.hs
@@ -54,6 +54,10 @@ import Remote.Helper.Export
import qualified Remote.Helper.Ssh as Ssh
import qualified Remote.GCrypt
import qualified Remote.P2P
+import qualified Remote.Helper.P2P as P2PHelper
+import qualified P2P.Protocol as P2P
+import qualified P2P.Annex as P2P
+import qualified P2P.IO as P2P
import P2P.Address
import Annex.Path
import Creds
@@ -147,11 +151,12 @@ gen r u c gc
| otherwise = case repoP2PAddress r of
Nothing -> do
duc <- mkDeferredUUIDCheck r u gc
- go duc <$> remoteCost gc defcst
+ connpool <- Ssh.mkP2PSshConnectionPool
+ go duc connpool <$> remoteCost gc defcst
Just addr -> Remote.P2P.chainGen addr r u c gc
where
defcst = if repoCheap r then cheapRemoteCost else expensiveRemoteCost
- go duc cst = Just new
+ go duc connpool cst = Just new
where
new = Remote
{ uuid = u
@@ -160,7 +165,7 @@ gen r u c gc
, storeKey = copyToRemote new duc
, retrieveKeyFile = copyFromRemote new
, retrieveKeyFileCheap = copyFromRemoteCheap new
- , removeKey = dropKey new duc
+ , removeKey = dropKey new duc connpool
, lockContent = Just (lockKey new duc)
, checkPresent = inAnnex new duc
, checkPresentCheap = repoCheap r
@@ -365,8 +370,8 @@ keyUrls r key = map tourl locs'
remoteconfig = gitconfig r
cfg = remoteGitConfig remoteconfig
-dropKey :: Remote -> DeferredUUIDCheck -> Key -> Annex Bool
-dropKey r duc key
+dropKey :: Remote -> DeferredUUIDCheck -> Ssh.P2PSshConnectionPool -> Key -> Annex Bool
+dropKey r duc connpool key
| not $ Git.repoIsUrl (repo r) = ifM duc
( guardUsable (repo r) (return False) $
commitOnCleanup r $ onLocalFast r $ do
@@ -380,7 +385,9 @@ dropKey r duc key
, return False
)
| Git.repoIsHttp (repo r) = giveup "dropping from http remote not supported"
- | otherwise = commitOnCleanup r $ Ssh.dropKey (repo r) key
+ | otherwise = commitOnCleanup r $ do
+ let fallback = Ssh.dropKey (repo r) key
+ P2PHelper.remove (runProto r connpool fallback) key
lockKey :: Remote -> DeferredUUIDCheck -> Key -> (VerifiedCopy -> Annex r) -> Annex r
lockKey r duc key callback
@@ -729,10 +736,11 @@ mkCopier remotewanthardlink rsyncparams = do
, return copier
)
-{- Normally the UUID is checked at startup, but annex-checkuuid config
- - can prevent that. To avoid getting confused, a deferred
- - check is done just before the repository is used. This returns False
- - when the repository UUID is not as expected. -}
+{- Normally the UUID of a local repository is checked at startup,
+ - but annex-checkuuid config can prevent that. To avoid getting
+ - confused, a deferred check is done just before the repository
+ - is used.
+ - This returns False when the repository UUID is not as expected. -}
type DeferredUUIDCheck = Annex Bool
mkDeferredUUIDCheck :: Git.Repo -> UUID -> RemoteGitConfig -> Annex DeferredUUIDCheck
@@ -751,3 +759,32 @@ mkDeferredUUIDCheck r u gc
return ok
, liftIO $ readMVar v
)
+
+-- Runs a P2P Proto action on a remote when it supports that,
+-- otherwise the fallback action.
+runProto :: Remote -> Ssh.P2PSshConnectionPool -> Annex a -> P2P.Proto a -> Annex (Maybe a)
+runProto r connpool fallback proto = Just <$>
+ (Ssh.getP2PSshConnection r connpool >>= maybe fallback go)
+ where
+ go c = do
+ (c', v) <- runProtoConn proto c
+ case v of
+ Just res -> do
+ liftIO $ Ssh.storeP2PSshConnection connpool c'
+ return res
+ -- Running the proto failed, either due to a protocol
+ -- error or a network error, so discard the
+ -- connection, and run the fallback.
+ Nothing -> fallback
+
+runProtoConn :: P2P.Proto a -> Ssh.P2PSshConnection -> Annex (Ssh.P2PSshConnection, Maybe a)
+runProtoConn _ P2P.ClosedConnection = return (P2P.ClosedConnection, Nothing)
+runProtoConn a conn@(P2P.OpenConnection (c, _pid)) =
+ P2P.runFullProto P2P.Client c a >>= \case
+ Right r -> return (conn, Just r)
+ -- When runFullProto fails, the connection is no longer
+ -- usable, so close it.
+ Left e -> do
+ warning $ "Lost connection (" ++ e ++ ")"
+ conn' <- liftIO $ Ssh.closeP2PSshConnection conn
+ return (conn', Nothing)
diff --git a/Remote/Helper/P2P.hs b/Remote/Helper/P2P.hs
new file mode 100644
index 000000000..272489755
--- /dev/null
+++ b/Remote/Helper/P2P.hs
@@ -0,0 +1,67 @@
+{- Helpers for remotes using the git-annex P2P protocol.
+ -
+ - Copyright 2016-2018 Joey Hess <id@joeyh.name>
+ -
+ - Licensed under the GNU GPL version 3 or higher.
+ -}
+
+{-# LANGUAGE RankNTypes #-}
+
+module Remote.Helper.P2P where
+
+import Annex.Common
+import qualified P2P.Protocol as P2P
+import P2P.IO
+import Types.Remote
+import Annex.Content
+import Config.Cost
+import Messages.Progress
+import Utility.Metered
+import Types.NumCopies
+
+import Control.Concurrent
+
+-- Runs a Proto action using a connection it sets up.
+type ProtoRunner a = P2P.Proto a -> Annex (Maybe a)
+
+-- Runs a Proto action using a ClosableConnection.
+type ProtoConnRunner c = forall a. P2P.Proto a -> ClosableConnection c -> Annex (ClosableConnection c, Maybe a)
+
+-- Runs an Annex action with a connection from the pool, adding it back to
+-- the pool when done.
+type WithConn a c = (ClosableConnection c -> Annex (ClosableConnection c, a)) -> Annex a
+
+store :: ProtoRunner Bool -> Key -> AssociatedFile -> MeterUpdate -> Annex Bool
+store runner k af p = do
+ let getsrcfile = fmap fst <$> prepSendAnnex k
+ metered (Just p) k getsrcfile $ \p' ->
+ fromMaybe False
+ <$> runner (P2P.put k af p')
+
+retrieve :: ProtoRunner Bool -> Key -> AssociatedFile -> FilePath -> MeterUpdate -> Annex (Bool, Verification)
+retrieve runner k af dest p = unVerified $
+ metered (Just p) k (return Nothing) $ \p' -> fromMaybe False
+ <$> runner (P2P.get dest k af p')
+
+remove :: ProtoRunner Bool -> Key -> Annex Bool
+remove runner k = fromMaybe False <$> runner (P2P.remove k)
+
+checkpresent :: ProtoRunner Bool -> Key -> Annex Bool
+checkpresent runner k = maybe unavail return =<< runner (P2P.checkPresent k)
+ where
+ unavail = giveup "can't connect to remote"
+
+lock :: WithConn a c -> ProtoConnRunner c -> UUID -> Key -> (VerifiedCopy -> Annex a) -> Annex a
+lock withconn connrunner u k callback = withconn $ \conn -> do
+ connv <- liftIO $ newMVar conn
+ let runproto d p = do
+ c <- liftIO $ takeMVar connv
+ (c', mr) <- connrunner p c
+ liftIO $ putMVar connv c'
+ return (fromMaybe d mr)
+ r <- P2P.lockContentWhile runproto k go
+ conn' <- liftIO $ takeMVar connv
+ return (conn', r)
+ where
+ go False = giveup "can't lock content"
+ go True = withVerifiedCopy LockedCopy u (return True) callback
diff --git a/Remote/Helper/Ssh.hs b/Remote/Helper/Ssh.hs
index a4d91ab92..84a1ee8cc 100644
--- a/Remote/Helper/Ssh.hs
+++ b/Remote/Helper/Ssh.hs
@@ -1,6 +1,6 @@
{- git-annex remote access with ssh and git-annex-shell
-
- - Copyright 2011-2013 Joey Hess <id@joeyh.name>
+ - Copyright 2011-2018 Joey Hess <id@joeyh.name>
-
- Licensed under the GNU GPL version 3 or higher.
-}
@@ -23,6 +23,10 @@ import Utility.SshHost
import Types.Remote
import Types.Transfer
import Config
+import qualified P2P.Protocol as P2P
+import qualified P2P.IO as P2P
+
+import Control.Concurrent.STM
toRepo :: ConsumeStdin -> Git.Repo -> RemoteGitConfig -> SshCommand -> Annex (FilePath, [CommandParam])
toRepo cs r gc remotecmd = do
@@ -91,9 +95,9 @@ onRemote cs r (with, errorval) command params fields = do
inAnnex :: Git.Repo -> Key -> Annex Bool
inAnnex r k = do
showChecking r
- onRemote NoConsumeStdin r (check, cantCheck r) "inannex" [Param $ key2file k] []
+ onRemote NoConsumeStdin r (runcheck, cantCheck r) "inannex" [Param $ key2file k] []
where
- check c p = dispatch =<< safeSystem c p
+ runcheck c p = dispatch =<< safeSystem c p
dispatch ExitSuccess = return True
dispatch (ExitFailure 1) = return False
dispatch _ = cantCheck r
@@ -179,3 +183,91 @@ rsyncParams r direction = do
-- successfully locked.
contentLockedMarker :: String
contentLockedMarker = "OK"
+
+-- A connection over ssh to git-annex shell speaking the P2P protocol.
+type P2PSshConnection = P2P.ClosableConnection (P2P.P2PConnection, ProcessHandle)
+
+closeP2PSshConnection :: P2PSshConnection -> IO P2PSshConnection
+closeP2PSshConnection P2P.ClosedConnection = return P2P.ClosedConnection
+closeP2PSshConnection (P2P.OpenConnection (conn, pid)) = do
+ P2P.closeConnection conn
+ void $ waitForProcess pid
+ return P2P.ClosedConnection
+
+-- Pool of connections over ssh to git-annex-shell p2pstdio.
+type P2PSshConnectionPool = TVar (Maybe P2PSshConnectionPoolState)
+
+data P2PSshConnectionPoolState
+ = P2PSshConnections [P2PSshConnection]
+ -- Remotes using an old version of git-annex-shell don't support P2P
+ | P2PSshUnsupported
+
+mkP2PSshConnectionPool :: Annex P2PSshConnectionPool
+mkP2PSshConnectionPool = liftIO $ newTVarIO Nothing
+
+-- Takes a connection from the pool, if any are available, otherwise
+-- tries to open a new one.
+getP2PSshConnection :: Remote -> P2PSshConnectionPool -> Annex (Maybe P2PSshConnection)
+getP2PSshConnection r connpool = getexistingconn >>= \case
+ Nothing -> return Nothing
+ Just Nothing -> openP2PSshConnection r connpool
+ Just (Just c) -> return (Just c)
+ where
+ getexistingconn = liftIO $ atomically $ readTVar connpool >>= \case
+ Just P2PSshUnsupported -> return Nothing
+ Just (P2PSshConnections (c:cs)) -> do
+ writeTVar connpool (Just (P2PSshConnections cs))
+ return (Just (Just c))
+ Just (P2PSshConnections []) -> return (Just Nothing)
+ Nothing -> return (Just Nothing)
+
+-- Add a connection to the pool, unless it's closed.
+storeP2PSshConnection :: P2PSshConnectionPool -> P2PSshConnection -> IO ()
+storeP2PSshConnection _ P2P.ClosedConnection = return ()
+storeP2PSshConnection connpool conn = atomically $ modifyTVar' connpool $ \case
+ Just (P2PSshConnections cs) -> Just (P2PSshConnections (conn:cs))
+ _ -> Just (P2PSshConnections [conn])
+
+-- Try to open a P2PSshConnection.
+-- The new connection is not added to the pool, so it's available
+-- for the caller to use.
+-- If the remote does not support the P2P protocol, that's remembered in
+-- the connection pool.
+openP2PSshConnection :: Remote -> P2PSshConnectionPool -> Annex (Maybe P2PSshConnection)
+openP2PSshConnection r connpool = do
+ u <- getUUID
+ let ps = [Param (fromUUID u)]
+ git_annex_shell ConsumeStdin (repo r) "p2pstdio" ps [] >>= \case
+ Nothing -> do
+ liftIO $ rememberunsupported
+ return Nothing
+ Just (cmd, params) -> start cmd params
+ where
+ start cmd params = liftIO $ withNullHandle $ \nullh -> do
+ -- stderr is discarded because old versions of git-annex
+ -- shell always error
+ (Just from, Just to, Nothing, pid) <- createProcess $
+ (proc cmd (toCommand params))
+ { std_in = CreatePipe
+ , std_out = CreatePipe
+ , std_err = UseHandle nullh
+ }
+ let conn = P2P.P2PConnection
+ { P2P.connRepo = repo r
+ , P2P.connCheckAuth = const False
+ , P2P.connIhdl = to
+ , P2P.connOhdl = from
+ }
+ let c = P2P.OpenConnection (conn, pid)
+ -- When the connection is successful, the remote
+ -- will send an AUTH_SUCCESS with its uuid.
+ tryNonAsync (P2P.runNetProto conn $ P2P.postAuth) >>= \case
+ Right (Right (Just theiruuid)) | theiruuid == uuid r ->
+ return $ Just c
+ _ -> do
+ void $ closeP2PSshConnection c
+ rememberunsupported
+ return Nothing
+ rememberunsupported = atomically $
+ modifyTVar' connpool $
+ maybe (Just P2PSshUnsupported) Just
diff --git a/Remote/P2P.hs b/Remote/P2P.hs
index 83ce258de..95c7f6ede 100644
--- a/Remote/P2P.hs
+++ b/Remote/P2P.hs
@@ -1,6 +1,6 @@
{- git remotes using the git-annex P2P protocol
-
- - Copyright 2016 Joey Hess <id@joeyh.name>
+ - Copyright 2016-2018 Joey Hess <id@joeyh.name>
-
- Licensed under the GNU GPL version 3 or higher.
-}
@@ -21,17 +21,13 @@ import Types.Remote
import Types.GitConfig
import qualified Git
import Annex.UUID
-import Annex.Content
import Config
import Config.Cost
import Remote.Helper.Git
import Remote.Helper.Export
-import Messages.Progress
-import Utility.Metered
+import Remote.Helper.P2P
import Utility.AuthToken
-import Types.NumCopies
-import Control.Concurrent
import Control.Concurrent.STM
remote :: RemoteType
@@ -49,16 +45,18 @@ chainGen :: P2PAddress -> Git.Repo -> UUID -> RemoteConfig -> RemoteGitConfig ->
chainGen addr r u c gc = do
connpool <- mkConnectionPool
cst <- remoteCost gc veryExpensiveRemoteCost
+ let protorunner = runProto u addr connpool
+ let withconn = withConnection u addr connpool
let this = Remote
{ uuid = u
, cost = cst
, name = Git.repoDescribe r
- , storeKey = store u addr connpool
- , retrieveKeyFile = retrieve u addr connpool
+ , storeKey = store protorunner
+ , retrieveKeyFile = retrieve protorunner
, retrieveKeyFileCheap = \_ _ _ -> return False
- , removeKey = remove u addr connpool
- , lockContent = Just (lock u addr connpool)
- , checkPresent = checkpresent u addr connpool
+ , removeKey = remove protorunner
+ , lockContent = Just $ lock withconn runProtoConn u
+ , checkPresent = checkpresent protorunner
, checkPresentCheap = False
, exportActions = exportUnsupported
, whereisKey = Nothing
@@ -78,48 +76,8 @@ chainGen addr r u c gc = do
}
return (Just this)
-store :: UUID -> P2PAddress -> ConnectionPool -> Key -> AssociatedFile -> MeterUpdate -> Annex Bool
-store u addr connpool k af p = do
- let getsrcfile = fmap fst <$> prepSendAnnex k
- metered (Just p) k getsrcfile $ \p' ->
- fromMaybe False
- <$> runProto u addr connpool (P2P.put k af p')
-
-retrieve :: UUID -> P2PAddress -> ConnectionPool -> Key -> AssociatedFile -> FilePath -> MeterUpdate -> Annex (Bool, Verification)
-retrieve u addr connpool k af dest p = unVerified $
- metered (Just p) k (return Nothing) $ \p' -> fromMaybe False
- <$> runProto u addr connpool (P2P.get dest k af p')
-
-remove :: UUID -> P2PAddress -> ConnectionPool -> Key -> Annex Bool
-remove u addr connpool k = fromMaybe False
- <$> runProto u addr connpool (P2P.remove k)
-
-checkpresent :: UUID -> P2PAddress -> ConnectionPool -> Key -> Annex Bool
-checkpresent u addr connpool k = maybe unavail return
- =<< runProto u addr connpool (P2P.checkPresent k)
- where
- unavail = giveup "can't connect to peer"
-
-lock :: UUID -> P2PAddress -> ConnectionPool -> Key -> (VerifiedCopy -> Annex r) -> Annex r
-lock u addr connpool k callback =
- withConnection u addr connpool $ \conn -> do
- connv <- liftIO $ newMVar conn
- let runproto d p = do
- c <- liftIO $ takeMVar connv
- (c', mr) <- runProto' p c
- liftIO $ putMVar connv c'
- return (fromMaybe d mr)
- r <- P2P.lockContentWhile runproto k go
- conn' <- liftIO $ takeMVar connv
- return (conn', r)
- where
- go False = giveup "can't lock content"
- go True = withVerifiedCopy LockedCopy u (return True) callback
-
--- | A connection to the peer.
-data Connection
- = OpenConnection P2PConnection
- | ClosedConnection
+-- | A connection to the peer, which can be closed.
+type Connection = ClosableConnection P2PConnection
type ConnectionPool = TVar [Connection]
@@ -128,11 +86,11 @@ mkConnectionPool = liftIO $ newTVarIO []
-- Runs the Proto action.
runProto :: UUID -> P2PAddress -> ConnectionPool -> P2P.Proto a -> Annex (Maybe a)
-runProto u addr connpool a = withConnection u addr connpool (runProto' a)
+runProto u addr connpool a = withConnection u addr connpool (runProtoConn a)
-runProto' :: P2P.Proto a -> Connection -> Annex (Connection, Maybe a)
-runProto' _ ClosedConnection = return (ClosedConnection, Nothing)
-runProto' a (OpenConnection conn) = do
+runProtoConn :: P2P.Proto a -> Connection -> Annex (Connection, Maybe a)
+runProtoConn _ ClosedConnection = return (ClosedConnection, Nothing)
+runProtoConn a (OpenConnection conn) = do
v <- runFullProto Client conn a
-- When runFullProto fails, the connection is no longer usable,
-- so close it.
diff --git a/Utility/Process.hs b/Utility/Process.hs
index ff454f799..1807a1335 100644
--- a/Utility/Process.hs
+++ b/Utility/Process.hs
@@ -27,6 +27,7 @@ module Utility.Process (
withHandle,
withIOHandles,
withOEHandles,
+ withNullHandle,
withQuietOutput,
feedWithQuietOutput,
createProcess,
@@ -213,13 +214,16 @@ withOEHandles creator p a = creator p' $ a . oeHandles
, std_err = CreatePipe
}
+withNullHandle :: (Handle -> IO a) -> IO a
+withNullHandle = withFile devNull WriteMode
+
-- | Forces the CreateProcessRunner to run quietly;
-- both stdout and stderr are discarded.
withQuietOutput
:: CreateProcessRunner
-> CreateProcess
-> IO ()
-withQuietOutput creator p = withFile devNull WriteMode $ \nullh -> do
+withQuietOutput creator p = withNullHandle $ \nullh -> do
let p' = p
{ std_out = UseHandle nullh
, std_err = UseHandle nullh
diff --git a/doc/devblog/day_488__groundwork_for_using_p2pstdio.mdwn b/doc/devblog/day_488__groundwork_for_using_p2pstdio.mdwn
new file mode 100644
index 000000000..e09da769a
--- /dev/null
+++ b/doc/devblog/day_488__groundwork_for_using_p2pstdio.mdwn
@@ -0,0 +1,30 @@
+Spent most of the day laying groundwork for using git-annex-shell p2pstdio.
+Implemented pools of ssh connections to it, and added uuid verification.
+Then generalized code from the p2p remote so it can be reused in the git
+remote. The types got super hairy in there, but the code reuse level is
+excellent.
+
+Finally it was time to convert the first ssh remote method
+to use the P2P protocol. I chose key removal, since benchmarking it doesn't
+involve the size of annexed objects.
+
+Here's the P2P protocol in action over ssh:
+
+ [2018-03-08 17:02:47.688627136] chat: ssh ["localhost","-S",".git/annex/ssh/localhost","-o","ControlMaster=auto","-o","ControlPersist=yes","-T","git-annex-shell 'p2pstdio' '/~/tmp/bench/a' '--debug' 'da72c285-2615-4a67-828f-eaae4f42fc3d' --uuid db017fac-eb8f-42d9-9d09-2780b193cef1"]
+ [2018-03-08 17:02:47.901897195] P2P < AUTH-SUCCESS db017fac-eb8f-42d9-9d09-2780b193cef1
+ [2018-03-08 17:02:47.902025504] P2P > REMOVE SHA256E-s4--97b912eb4a61df5f806ca6239dde3e1a4f51ad20aced1642cbb83dc510a5fa6b
+ [2018-03-08 17:02:47.910074003] P2P < SUCCESS
+ [2018-03-08 17:02:47.914181701] P2P > REMOVE SHA256E-s4--6af2f5b785a8930f0bd3edc833e18fa191167ab0535ef359b19a1982a6984e96
+ [2018-03-08 17:02:47.918699806] P2P < SUCCESS
+
+For a benchmark, I set up a repository with 1000 annexed files,
+and cloned it from localhost, then ran `git annex drop --from origin`.
+
+before: 41 seconds
+after: 10 seconds
+
+400% speedup for dropping is pretty great.. And when there's more latency
+than loopback has, the improvement should be more pronounced.
+Will test it this evening over my satellite internet. :)
+
+Today's work was sponsored by Trenton Cronholm on [Patreon](https://patreon.com/joeyh/).
diff --git a/doc/git-annex-shell.mdwn b/doc/git-annex-shell.mdwn
index cf72e091b..fc536e44b 100644
--- a/doc/git-annex-shell.mdwn
+++ b/doc/git-annex-shell.mdwn
@@ -90,12 +90,15 @@ first "/~/" or "/~user/" is expanded to the specified home directory.
Sets up a repository as a gcrypt repository.
-* p2pstdio directory
+* p2pstdio directory uuid
This causes git-annex-shell to communicate using the git-annex p2p
protocol over stdio. When supported by git-annex-shell, this allows
multiple actions to be run over a single connection, improving speed.
+ The uuid is the one belonging to the repository that will be
+ communicating with git-annex-shell.
+
# OPTIONS
Most options are the same as in git-annex. The ones specific
diff --git a/doc/git-annex.mdwn b/doc/git-annex.mdwn
index db8cfca61..7f89bdbf4 100644
--- a/doc/git-annex.mdwn
+++ b/doc/git-annex.mdwn
@@ -1244,7 +1244,7 @@ Here are all the supported configuration settings.
git-annex caches UUIDs of remote repositories here.
-- `remote.<name>.annex-checkuuid`
+* `remote.<name>.annex-checkuuid`
This only affects remotes that have their url pointing to a directory on
the same system. git-annex normally checks the uuid of such
diff --git a/doc/todo/accellerate_ssh_remotes_with_git-annex-shell_mass_protocol.mdwn b/doc/todo/accellerate_ssh_remotes_with_git-annex-shell_mass_protocol.mdwn
index ff4b8c59d..a592e17a9 100644
--- a/doc/todo/accellerate_ssh_remotes_with_git-annex-shell_mass_protocol.mdwn
+++ b/doc/todo/accellerate_ssh_remotes_with_git-annex-shell_mass_protocol.mdwn
@@ -40,3 +40,7 @@ Implementation todos:
git-annex-shell recvkey has a speed optimisation, when it's told the file
being sent is locked, it can avoid an expensive verification.
* Maybe similar for transfers in the other direction?
+* What happens when the assistant is running and some connections are open
+ and it moves between networks?
+* If it's unable to ssh to a host to run p2pstdio, it will fall back to the
+ old method. What if the host is down, does this double the timeout?
diff --git a/git-annex.cabal b/git-annex.cabal
index 6a8aa490a..f577c583a 100644
--- a/git-annex.cabal
+++ b/git-annex.cabal
@@ -931,6 +931,7 @@ Executable git-annex
Remote.Helper.Hooks
Remote.Helper.Http
Remote.Helper.Messages
+ Remote.Helper.P2P
Remote.Helper.ReadOnly
Remote.Helper.Special
Remote.Helper.Ssh