p2p --link now defaults to setting up a bi-directional link
Both the local and remote git repositories get remotes added pointing at one-another. Makes pairing twice as easy! Security: The new LINK command in the protocol can be sent repeatedly, but only by a peer who has authenticated with us. So, it's entirely safe to add a link back to that peer, or to some other peer it knows about. Anything we receive over such a link, the peer could send us over the current connection. There is some risk of being flooded with LINKs, and adding too many remotes. To guard against that, there's a hard cap on the number of remotes that can be set up this way. This will only be a problem if setting up large p2p networks that have exceptional interconnectedness. A new, dedicated authtoken is created when sending LINK. This also allows, in theory, using a p2p network like tor, to learn about links on other networks, like telehash. This commit was sponsored by Bruno BEAUFILS on Patreon.
This commit is contained in:
parent
e67a310da1
commit
3037feb1bf
7 changed files with 105 additions and 46 deletions
|
@ -14,6 +14,9 @@ git-annex (6.20161211) UNRELEASED; urgency=medium
|
|||
be processed without requiring it to be in the current encoding.
|
||||
* p2p: --link no longer takes a remote name, instead the --name
|
||||
option can be used.
|
||||
* p2p --link now defaults to setting up a bi-directional link;
|
||||
both the local and remote git repositories get remotes added
|
||||
pointing at one-another.
|
||||
|
||||
-- Joey Hess <id@joeyh.name> Sun, 11 Dec 2016 21:29:51 -0400
|
||||
|
||||
|
|
|
@ -10,15 +10,10 @@ module Command.P2P where
|
|||
import Command
|
||||
import P2P.Address
|
||||
import P2P.Auth
|
||||
import P2P.IO
|
||||
import qualified P2P.Protocol as P2P
|
||||
import P2P.Annex
|
||||
import Utility.AuthToken
|
||||
import Git.Types
|
||||
import qualified Git.Remote
|
||||
import qualified Git.Command
|
||||
import qualified Annex
|
||||
import Annex.UUID
|
||||
import Config
|
||||
|
||||
cmd :: Command
|
||||
cmd = command "p2p" SectionSetup
|
||||
|
@ -55,16 +50,6 @@ seek (LinkRemote, Just name) = commandAction $
|
|||
seek (LinkRemote, Nothing) = commandAction $
|
||||
linkRemote =<< unusedPeerRemoteName
|
||||
|
||||
unusedPeerRemoteName :: Annex RemoteName
|
||||
unusedPeerRemoteName = go (1 :: Integer) =<< usednames
|
||||
where
|
||||
usednames = mapMaybe remoteName . remotes <$> Annex.gitRepo
|
||||
go n names = do
|
||||
let name = "peer" ++ show n
|
||||
if name `elem` names
|
||||
then go (n+1) names
|
||||
else return name
|
||||
|
||||
-- Only addresses are output to stdout, to allow scripting.
|
||||
genAddresses :: [P2PAddress] -> Annex ()
|
||||
genAddresses [] = giveup "No P2P networks are currrently available."
|
||||
|
@ -95,24 +80,10 @@ linkRemote remotename = do
|
|||
Nothing -> do
|
||||
liftIO $ hPutStrLn stderr "Unable to parse that address, please check its format and try again."
|
||||
prompt
|
||||
Just addr -> setup addr
|
||||
setup (P2PAddressAuth addr authtoken) = do
|
||||
g <- Annex.gitRepo
|
||||
conn <- liftIO $ connectPeer g addr
|
||||
`catchNonAsync` connerror
|
||||
u <- getUUID
|
||||
v <- liftIO $ runNetProto conn $ P2P.auth u authtoken
|
||||
case v of
|
||||
Right (Just theiruuid) -> do
|
||||
ok <- inRepo $ Git.Command.runBool
|
||||
[ Param "remote", Param "add"
|
||||
, Param remotename
|
||||
, Param (formatP2PAddress addr)
|
||||
]
|
||||
when ok $ do
|
||||
storeUUIDIn (remoteConfig remotename "uuid") theiruuid
|
||||
storeP2PRemoteAuthToken addr authtoken
|
||||
return ok
|
||||
Right Nothing -> giveup "Unable to authenticate with peer. Please check the address and try again."
|
||||
Left e -> giveup $ "Unable to authenticate with peer: " ++ e
|
||||
connerror e = giveup $ "Unable to connect with peer. Please check that the peer is connected to the network, and try again. (" ++ show e ++ ")"
|
||||
Just addr -> do
|
||||
myaddrs <- loadP2PAddresses
|
||||
authtoken <- liftIO $ genAuthToken 128
|
||||
storeP2PAuthToken authtoken
|
||||
let linkbackto = map (`P2PAddressAuth` authtoken) myaddrs
|
||||
linkAddress addr linkbackto remotename
|
||||
>>= either giveup return
|
||||
|
|
|
@ -14,6 +14,7 @@ import Git.Types
|
|||
import Creds
|
||||
import Utility.AuthToken
|
||||
import Utility.Tor
|
||||
import qualified Utility.SimpleProtocol as Proto
|
||||
|
||||
import qualified Data.Text as T
|
||||
|
||||
|
@ -46,6 +47,10 @@ instance FormatP2PAddress P2PAddress where
|
|||
return (TorAnnex (OnionAddress onionaddr) onionport)
|
||||
| otherwise = Nothing
|
||||
|
||||
instance Proto.Serializable P2PAddressAuth where
|
||||
serialize = formatP2PAddress
|
||||
deserialize = unformatP2PAddress
|
||||
|
||||
torAnnexScheme :: String
|
||||
torAnnexScheme = "tor-annex:"
|
||||
|
||||
|
|
63
P2P/Annex.hs
63
P2P/Annex.hs
|
@ -11,6 +11,8 @@ module P2P.Annex
|
|||
( RunMode(..)
|
||||
, P2PConnection(..)
|
||||
, runFullProto
|
||||
, unusedPeerRemoteName
|
||||
, linkAddress
|
||||
) where
|
||||
|
||||
import Annex.Common
|
||||
|
@ -19,9 +21,16 @@ import Annex.Transfer
|
|||
import Annex.ChangedRefs
|
||||
import P2P.Protocol
|
||||
import P2P.IO
|
||||
import P2P.Address
|
||||
import P2P.Auth
|
||||
import Logs.Location
|
||||
import Types.NumCopies
|
||||
import Utility.Metered
|
||||
import qualified Git.Command
|
||||
import qualified Annex
|
||||
import Annex.UUID
|
||||
import Git.Types (RemoteName, remoteName, remotes)
|
||||
import Config
|
||||
|
||||
import Control.Monad.Free
|
||||
|
||||
|
@ -120,6 +129,17 @@ runLocal runmode runner a = case a of
|
|||
Left e -> return (Left (show e))
|
||||
Right changedrefs -> runner (next changedrefs)
|
||||
_ -> return $ Left "change notification not available"
|
||||
AddLinkToPeer addr next -> do
|
||||
v <- tryNonAsync $ do
|
||||
-- Flood protection; don't let a huge number
|
||||
-- of peer remotes be created.
|
||||
ns <- usedPeerRemoteNames
|
||||
if length ns > 100
|
||||
then return $ Right False
|
||||
else linkAddress addr [] =<< unusedPeerRemoteName
|
||||
case v of
|
||||
Right (Right r) -> runner (next r)
|
||||
_ -> runner (next False)
|
||||
where
|
||||
transfer mk k af ta = case runmode of
|
||||
-- Update transfer logs when serving.
|
||||
|
@ -152,3 +172,46 @@ runLocal runmode runner a = case a of
|
|||
liftIO $ hSeek h AbsoluteSeek o
|
||||
b <- liftIO $ hGetContentsMetered h p'
|
||||
runner (sender b)
|
||||
|
||||
unusedPeerRemoteName :: Annex RemoteName
|
||||
unusedPeerRemoteName = go (1 :: Integer) =<< usedPeerRemoteNames
|
||||
where
|
||||
go n names = do
|
||||
let name = "peer" ++ show n
|
||||
if name `elem` names
|
||||
then go (n+1) names
|
||||
else return name
|
||||
|
||||
usedPeerRemoteNames :: Annex [RemoteName]
|
||||
usedPeerRemoteNames = filter ("peer" `isPrefixOf`)
|
||||
. mapMaybe remoteName . remotes <$> Annex.gitRepo
|
||||
|
||||
linkAddress :: P2PAddressAuth -> [P2PAddressAuth] -> RemoteName -> Annex (Either String Bool)
|
||||
linkAddress (P2PAddressAuth addr authtoken) linkbackto remotename = do
|
||||
g <- Annex.gitRepo
|
||||
cv <- liftIO $ tryNonAsync $ connectPeer g addr
|
||||
case cv of
|
||||
Left e -> return $ Left $ "Unable to connect with peer. Please check that the peer is connected to the network, and try again. (" ++ show e ++ ")"
|
||||
Right conn -> do
|
||||
u <- getUUID
|
||||
v <- liftIO $ runNetProto conn $ do
|
||||
authresp <- P2P.Protocol.auth u authtoken
|
||||
lbok <- forM linkbackto $ P2P.Protocol.link
|
||||
return (authresp, lbok)
|
||||
case v of
|
||||
Right (Just theiruuid, lbok) -> do
|
||||
ok <- inRepo $ Git.Command.runBool
|
||||
[ Param "remote", Param "add"
|
||||
, Param remotename
|
||||
, Param (formatP2PAddress addr)
|
||||
]
|
||||
when ok $ do
|
||||
storeUUIDIn (remoteConfig remotename "uuid") theiruuid
|
||||
storeP2PRemoteAuthToken addr authtoken
|
||||
if not ok
|
||||
then return $ Right False
|
||||
else if or lbok || null linkbackto
|
||||
then return $ Right True
|
||||
else return $ Left "Linked with peer. However, the peer was unable to link back to us, so the link is one-way."
|
||||
Right (Nothing, _) -> return $ Left "Unable to authenticate with peer. Please check the address and try again."
|
||||
Left e -> return $ Left $ "Unable to authenticate with peer: " ++ e
|
||||
|
|
|
@ -14,6 +14,7 @@ module P2P.Protocol where
|
|||
import qualified Utility.SimpleProtocol as Proto
|
||||
import Types.Key
|
||||
import Types.UUID
|
||||
import P2P.Address
|
||||
import Utility.AuthToken
|
||||
import Utility.Applicative
|
||||
import Utility.PartialPrelude
|
||||
|
@ -49,6 +50,7 @@ data Message
|
|||
= AUTH UUID AuthToken -- uuid of the peer that is authenticating
|
||||
| AUTH_SUCCESS UUID -- uuid of the remote peer
|
||||
| AUTH_FAILURE
|
||||
| LINK P2PAddressAuth -- sending an address that the peer may link to
|
||||
| CONNECT Service
|
||||
| CONNECTDONE ExitCode
|
||||
| NOTIFYCHANGE
|
||||
|
@ -71,6 +73,7 @@ instance Proto.Sendable Message where
|
|||
formatMessage (AUTH uuid authtoken) = ["AUTH", Proto.serialize uuid, Proto.serialize authtoken]
|
||||
formatMessage (AUTH_SUCCESS uuid) = ["AUTH-SUCCESS", Proto.serialize uuid]
|
||||
formatMessage AUTH_FAILURE = ["AUTH-FAILURE"]
|
||||
formatMessage (LINK addr) = ["LINK", Proto.serialize addr]
|
||||
formatMessage (CONNECT service) = ["CONNECT", Proto.serialize service]
|
||||
formatMessage (CONNECTDONE exitcode) = ["CONNECTDONE", Proto.serialize exitcode]
|
||||
formatMessage NOTIFYCHANGE = ["NOTIFYCHANGE"]
|
||||
|
@ -92,6 +95,7 @@ instance Proto.Receivable Message where
|
|||
parseCommand "AUTH" = Proto.parse2 AUTH
|
||||
parseCommand "AUTH-SUCCESS" = Proto.parse1 AUTH_SUCCESS
|
||||
parseCommand "AUTH-FAILURE" = Proto.parse0 AUTH_FAILURE
|
||||
parseCommand "LINK" = Proto.parse1 LINK
|
||||
parseCommand "CONNECT" = Proto.parse1 CONNECT
|
||||
parseCommand "CONNECTDONE" = Proto.parse1 CONNECTDONE
|
||||
parseCommand "NOTIFYCHANGE" = Proto.parse0 NOTIFYCHANGE
|
||||
|
@ -236,6 +240,8 @@ data LocalF c
|
|||
-- with False.
|
||||
| WaitRefChange (ChangedRefs -> c)
|
||||
-- ^ Waits for one or more git refs to change and returns them.
|
||||
| AddLinkToPeer P2PAddressAuth (Bool -> c)
|
||||
-- ^ Adds a link to a peer using the provided address.
|
||||
deriving (Functor)
|
||||
|
||||
type Local = Free LocalF
|
||||
|
@ -255,6 +261,11 @@ auth myuuid t = do
|
|||
net $ sendMessage (ERROR "auth failed")
|
||||
return Nothing
|
||||
|
||||
link :: P2PAddressAuth -> Proto Bool
|
||||
link addr = do
|
||||
net $ sendMessage (LINK addr)
|
||||
checkSuccess
|
||||
|
||||
checkPresent :: Key -> Proto Bool
|
||||
checkPresent key = do
|
||||
net $ sendMessage (CHECKPRESENT key)
|
||||
|
@ -354,6 +365,9 @@ serveAuth myuuid = serverLoop handler
|
|||
serveAuthed :: UUID -> Proto ()
|
||||
serveAuthed myuuid = void $ serverLoop handler
|
||||
where
|
||||
handler (LINK addr) = do
|
||||
sendSuccess =<< local (addLinkToPeer addr)
|
||||
return ServerContinue
|
||||
handler (LOCKCONTENT key) = do
|
||||
local $ tryLockContent key $ \locked -> do
|
||||
sendSuccess locked
|
||||
|
|
|
@ -24,13 +24,16 @@ services.
|
|||
|
||||
* `--link`
|
||||
|
||||
Sets up a git remote that is accessed over a P2P network.
|
||||
Sets up a link with a peer over the P2P network.
|
||||
|
||||
This will prompt for an address to be entered; you should paste in the
|
||||
address that was generated by --gen-address in the remote repository.
|
||||
|
||||
Defaults to making the git remote be named "peer1", "peer2",
|
||||
etc. This can be overridden with the `--name` option.
|
||||
A git remote will be created, with a name like "peer1", "peer2"
|
||||
by default (the `--name` option can be used to specify the name).
|
||||
|
||||
The link is bi-directional, so the peer will also have a git
|
||||
remote added to it, linking back to the repository where this is run.
|
||||
|
||||
* `--name`
|
||||
|
||||
|
|
|
@ -56,13 +56,13 @@ peer1 remote:
|
|||
|
||||
git annex sync --content peer1
|
||||
|
||||
You can also generate an address for this new peer, by running `git annex
|
||||
p2p --gen-addresses`, and link other peers to that address using `git annex
|
||||
p2p --link`. It's often useful to link peers up in both directions,
|
||||
so peer1 is a remote of peer2 and peer2 is a remote of peer1.
|
||||
|
||||
Any number of peers can be connected this way, within reason.
|
||||
|
||||
(When the second peer links to it, the first peer also
|
||||
gets a new remote added to it, which points to the second peer.
|
||||
So, on the first peer, you can also sync with the second peer.
|
||||
The name of the that remote will be "peer1", or "peer2", etc.)
|
||||
|
||||
## starting git-annex remotedaemon
|
||||
|
||||
Notice the `git annex remotedaemon` being run in the above examples.
|
||||
|
|
Loading…
Reference in a new issue