summaryrefslogtreecommitdiff
path: root/Command
diff options
context:
space:
mode:
authorGravatar Joey Hess <joeyh@joeyh.name>2016-12-16 16:32:29 -0400
committerGravatar Joey Hess <joeyh@joeyh.name>2016-12-16 16:38:06 -0400
commit6aa7e136b5d246228723f4c9996bda11f66c4445 (patch)
tree145310079adb607fae058a0a1dd42c7f155d26e1 /Command
parent353b59a000dd0e4941b3c36a7fd02d23f3cf44a1 (diff)
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.
Diffstat (limited to 'Command')
-rw-r--r--Command/P2P.hs45
1 files changed, 8 insertions, 37 deletions
diff --git a/Command/P2P.hs b/Command/P2P.hs
index d59d774c4..323906f36 100644
--- a/Command/P2P.hs
+++ b/Command/P2P.hs
@@ -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