aboutsummaryrefslogtreecommitdiff
path: root/P2P
diff options
context:
space:
mode:
authorGravatar Joey Hess <joeyh@joeyh.name>2016-12-16 18:26:07 -0400
committerGravatar Joey Hess <joeyh@joeyh.name>2016-12-16 18:26:07 -0400
commit82bb3565a3b4ae4442d006b06c1bd487cba783a8 (patch)
tree6d7681bed722e263a67770852930bdd1754e07b5 /P2P
parent097c82b17ed0f3c96d1ca1617f42c39650dc9ab2 (diff)
Revert "p2p --link now defaults to setting up a bi-directional link"
This reverts commit 6aa7e136b5d246228723f4c9996bda11f66c4445. On second thought, this was an overcomplication of what should be the lowest-level primitive. Let's build bi-directional links at the pairing level with eg magic wormhole.
Diffstat (limited to 'P2P')
-rw-r--r--P2P/Address.hs5
-rw-r--r--P2P/Annex.hs63
-rw-r--r--P2P/Protocol.hs16
3 files changed, 1 insertions, 83 deletions
diff --git a/P2P/Address.hs b/P2P/Address.hs
index 919739327..1b1f66059 100644
--- a/P2P/Address.hs
+++ b/P2P/Address.hs
@@ -14,7 +14,6 @@ import Git.Types
import Creds
import Utility.AuthToken
import Utility.Tor
-import qualified Utility.SimpleProtocol as Proto
import qualified Data.Text as T
@@ -47,10 +46,6 @@ 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:"
diff --git a/P2P/Annex.hs b/P2P/Annex.hs
index 56f94d2bb..9971762f5 100644
--- a/P2P/Annex.hs
+++ b/P2P/Annex.hs
@@ -11,8 +11,6 @@ module P2P.Annex
( RunMode(..)
, P2PConnection(..)
, runFullProto
- , unusedPeerRemoteName
- , linkAddress
) where
import Annex.Common
@@ -21,16 +19,9 @@ 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
@@ -129,17 +120,6 @@ 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.
@@ -172,46 +152,3 @@ 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
diff --git a/P2P/Protocol.hs b/P2P/Protocol.hs
index c383fa966..135409e26 100644
--- a/P2P/Protocol.hs
+++ b/P2P/Protocol.hs
@@ -14,7 +14,6 @@ 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
@@ -50,7 +49,6 @@ 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,9 +69,8 @@ data Message
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_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"]
@@ -95,7 +92,6 @@ 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
@@ -240,8 +236,6 @@ 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
@@ -261,11 +255,6 @@ 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)
@@ -365,9 +354,6 @@ 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