finished XMPP pairing!

This includes keeping track of which buddies we're pairing with, to know
which PairAck are legitimate.
This commit is contained in:
Joey Hess 2012-11-05 17:43:17 -04:00
parent da65c5c1d1
commit da6fb44446
10 changed files with 142 additions and 50 deletions

View file

@ -18,6 +18,7 @@ module Annex.UUID (
prepUUID, prepUUID,
genUUID, genUUID,
removeRepoUUID, removeRepoUUID,
storeUUID,
) where ) where
import Common.Annex import Common.Annex

View file

@ -317,7 +317,7 @@ pairRequestReceivedAlert who button = Alert
pairRequestAcknowledgedAlert :: String -> Maybe AlertButton -> Alert pairRequestAcknowledgedAlert :: String -> Maybe AlertButton -> Alert
pairRequestAcknowledgedAlert who button = baseActivityAlert pairRequestAcknowledgedAlert who button = baseActivityAlert
{ alertData = ["Pair request with", UnTensed (T.pack who), Tensed "in progress" "complete"] { alertData = ["Pairing with", UnTensed (T.pack who), Tensed "in progress" "complete"]
, alertPriority = High , alertPriority = High
, alertCombiner = Just $ dataCombiner $ \_old new -> new , alertCombiner = Just $ dataCombiner $ \_old new -> new
, alertButton = button , alertButton = button

View file

@ -26,10 +26,10 @@ setupAuthorizedKeys msg repodir = do
where where
pubkey = remoteSshPubKey $ pairMsgData msg pubkey = remoteSshPubKey $ pairMsgData msg
{- When pairing is complete, this is used to set up the remote for the host {- When local pairing is complete, this is used to set up the remote for
- we paired with. -} - the host we paired with. -}
finishedPairing :: PairMsg -> SshKeyPair -> Assistant () finishedLocalPairing :: PairMsg -> SshKeyPair -> Assistant ()
finishedPairing msg keypair = do finishedLocalPairing msg keypair = do
sshdata <- liftIO $ setupSshKeyPair keypair =<< pairMsgToSshData msg sshdata <- liftIO $ setupSshKeyPair keypair =<< pairMsgToSshData msg
{- Ensure that we know the ssh host key for the host we paired with. {- Ensure that we know the ssh host key for the host we paired with.
- If we don't, ssh over to get it. -} - If we don't, ssh over to get it. -}

View file

@ -123,7 +123,7 @@ pairAckReceived True (Just pip) msg cache = do
stopSending pip stopSending pip
repodir <- repoPath <$> liftAnnex gitRepo repodir <- repoPath <$> liftAnnex gitRepo
liftIO $ setupAuthorizedKeys msg repodir liftIO $ setupAuthorizedKeys msg repodir
finishedPairing msg (inProgressSshKeyPair pip) finishedLocalPairing msg (inProgressSshKeyPair pip)
startSending pip PairDone $ multicastPairMsg startSending pip PairDone $ multicastPairMsg
(Just 1) (inProgressSecret pip) (inProgressPairData pip) (Just 1) (inProgressSecret pip) (inProgressPairData pip)
return $ pip : take 10 cache return $ pip : take 10 cache
@ -153,4 +153,4 @@ pairDoneReceived False _ _ = noop -- not verified
pairDoneReceived True Nothing _ = noop -- not in progress pairDoneReceived True Nothing _ = noop -- not in progress
pairDoneReceived True (Just pip) msg = do pairDoneReceived True (Just pip) msg = do
stopSending pip stopSending pip
finishedPairing msg (inProgressSshKeyPair pip) finishedLocalPairing msg (inProgressSshKeyPair pip)

View file

@ -22,11 +22,14 @@ import Assistant.WebApp
import Assistant.WebApp.Types import Assistant.WebApp.Types
import Assistant.Alert import Assistant.Alert
import Assistant.Pairing import Assistant.Pairing
import Assistant.XMPP.Git
import Annex.UUID
import Network.Protocol.XMPP import Network.Protocol.XMPP
import Control.Concurrent import Control.Concurrent
import qualified Data.Text as T import qualified Data.Text as T
import qualified Data.Set as S import qualified Data.Set as S
import qualified Data.Map as M
import qualified Git.Branch import qualified Git.Branch
import Data.Time.Clock import Data.Time.Clock
@ -36,17 +39,17 @@ xmppClientThread urlrenderer = NamedThread "XMPPClient" $ do
- can be run from within the XMPP monad using liftIO. Ugly. -} - can be run from within the XMPP monad using liftIO. Ugly. -}
iodebug <- asIO1 debug iodebug <- asIO1 debug
iopull <- asIO1 pull iopull <- asIO1 pull
iopairReqReceived <- asIO2 $ pairReqReceived urlrenderer iopairMsgReceived <- asIO2 $ pairMsgReceived urlrenderer
ioupdatebuddies <- asIO1 $ \p -> ioupdatebuddies <- asIO1 $ \p ->
updateBuddyList (updateBuddies p) <<~ buddyList updateBuddyList (updateBuddies p) <<~ buddyList
ioemptybuddies <- asIO $ ioemptybuddies <- asIO $
updateBuddyList (const noBuddies) <<~ buddyList updateBuddyList (const noBuddies) <<~ buddyList
iorelay <- asIO1 relayNetMessage iorelay <- asIO1 relayNetMessage
ioclientthread <- asIO $ ioclientthread <- asIO $
go iorelay iodebug iopull ioupdatebuddies ioemptybuddies iopairReqReceived go iorelay iodebug iopull ioupdatebuddies ioemptybuddies iopairMsgReceived
restartableClient ioclientthread restartableClient ioclientthread
where where
go iorelay iodebug iopull ioupdatebuddies ioemptybuddies iopairReqReceived = do go iorelay iodebug iopull ioupdatebuddies ioemptybuddies iopairMsgReceived = do
v <- liftAnnex getXMPPCreds v <- liftAnnex getXMPPCreds
case v of case v of
Nothing -> noop Nothing -> noop
@ -85,23 +88,19 @@ xmppClientThread urlrenderer = NamedThread "XMPPClient" $ do
receivenotifications selfjid = forever $ do receivenotifications selfjid = forever $ do
l <- decodeStanza selfjid <$> getStanza l <- decodeStanza selfjid <$> getStanza
debug' ["received:", show l] debug' ["received:", show l]
mapM_ handle l mapM_ (handle selfjid) l
handle (PresenceMessage p) = handle _ (PresenceMessage p) =
void $ liftIO $ ioupdatebuddies p void $ liftIO $ ioupdatebuddies p
handle (GotNetMessage QueryPresence) = handle _ (GotNetMessage QueryPresence) =
putStanza gitAnnexSignature putStanza gitAnnexSignature
handle (GotNetMessage (NotifyPush us)) = handle _ (GotNetMessage (NotifyPush us)) =
void $ liftIO $ iopull us void $ liftIO $ iopull us
handle (GotNetMessage (PairingNotification stage t u)) = handle selfjid (GotNetMessage (PairingNotification stage t u)) =
maybe noop (handlePairing stage u) (parseJID t) maybe noop (\jid -> liftIO $ iopairMsgReceived (stage, u) (selfjid, jid)) (parseJID t)
handle (Ignorable _) = noop handle _ (Ignorable _) = noop
handle (Unknown _) = noop handle _ (Unknown _) = noop
handle (ProtocolError _) = noop handle _ (ProtocolError _) = noop
handlePairing PairReq u jid = liftIO $ iopairReqReceived u jid
handlePairing PairAck _ _ = error "TODO"
handlePairing PairDone _ _ = error "TODO"
data XMPPEvent data XMPPEvent
= GotNetMessage NetMessage = GotNetMessage NetMessage
@ -139,16 +138,18 @@ decodeStanza _ s = [Unknown s]
{- Waits for a NetMessager message to be sent, and relays it to XMPP. -} {- Waits for a NetMessager message to be sent, and relays it to XMPP. -}
relayNetMessage :: JID -> Assistant (XMPP ()) relayNetMessage :: JID -> Assistant (XMPP ())
relayNetMessage selfjid = convert <$> waitNetMessage relayNetMessage selfjid = convert =<< waitNetMessage
where where
convert (NotifyPush us) = putStanza $ pushNotification us convert (NotifyPush us) = return $ putStanza $ pushNotification us
convert QueryPresence = putStanza $ presenceQuery convert QueryPresence = return $ putStanza $ presenceQuery
convert (PairingNotification stage t u) = case parseJID t of convert (PairingNotification stage t u) = case parseJID t of
Nothing -> noop Nothing -> return $ noop
Just tojid Just tojid
| tojid == selfjid -> noop | tojid == selfjid -> return $ noop
| otherwise -> putStanza $ | otherwise -> do
pairingNotification stage u tojid selfjid changeBuddyPairing tojid True
return $ putStanza $
pairingNotification stage u tojid selfjid
{- Runs the client, handing restart events. -} {- Runs the client, handing restart events. -}
restartableClient :: IO () -> Assistant () restartableClient :: IO () -> Assistant ()
@ -193,17 +194,44 @@ pull us = do
unlessM (all id . fst <$> manualPull branch [r]) $ unlessM (all id . fst <$> manualPull branch [r]) $
pullone rs branch pullone rs branch
{- Show an alert when a PairReq is seen, unless the PairReq came from pairMsgReceived :: UrlRenderer -> (PairStage, UUID) -> (JID, JID) -> Assistant ()
- another client using our JID. In that case, just start pairing. -} pairMsgReceived urlrenderer (PairReq, theiruuid) (selfjid, theirjid)
pairReqReceived :: UrlRenderer -> UUID -> JID -> Assistant () -- PairReq from another client using our JID is automatically accepted.
pairReqReceived urlrenderer u jid = do | baseJID selfjid == baseJID theirjid = do
-- TODO: check same JID selfuuid <- liftAnnex getUUID
let route = FinishXMPPPairR (PairKey u $ formatJID jid) sendNetMessage $
url <- liftIO $ renderUrl urlrenderer route [] PairingNotification PairAck (formatJID theirjid) selfuuid
close <- asIO1 removeAlert finishXMPPPairing theirjid theiruuid
void $ addAlert $ pairRequestReceivedAlert (T.unpack $ buddyName jid) -- Show an alert to let the user decide if they want to pair.
AlertButton | otherwise = do
{ buttonUrl = url let route = FinishXMPPPairR (PairKey theiruuid $ formatJID theirjid)
, buttonLabel = T.pack "Respond" url <- liftIO $ renderUrl urlrenderer route []
, buttonAction = Just close close <- asIO1 removeAlert
} void $ addAlert $ pairRequestReceivedAlert (T.unpack $ buddyName theirjid)
AlertButton
{ buttonUrl = url
, buttonLabel = T.pack "Respond"
, buttonAction = Just close
}
pairMsgReceived _ (PairAck, theiruuid) (_selfjid, theirjid) =
{- PairAck must come from one of the buddies we are pairing with;
- don't pair with just anyone. -}
whenM (isBuddyPairing theirjid) $ do
changeBuddyPairing theirjid False
selfuuid <- liftAnnex getUUID
sendNetMessage $
PairingNotification PairDone (formatJID theirjid) selfuuid
finishXMPPPairing theirjid theiruuid
pairMsgReceived _ (PairDone, _theiruuid) (_selfjid, theirjid) =
changeBuddyPairing theirjid False
isBuddyPairing :: JID -> Assistant Bool
isBuddyPairing jid = maybe False buddyPairing <$>
getBuddy (genBuddyKey jid) <<~ buddyList
changeBuddyPairing :: JID -> Bool -> Assistant ()
changeBuddyPairing jid ispairing =
updateBuddyList (M.adjust set key) <<~ buddyList
where
key = genBuddyKey jid
set b = b { buddyPairing = ispairing }

View file

@ -32,6 +32,7 @@ data Buddy = Buddy
{ buddyPresent :: S.Set Client { buddyPresent :: S.Set Client
, buddyAway :: S.Set Client , buddyAway :: S.Set Client
, buddyAssistants :: S.Set Client , buddyAssistants :: S.Set Client
, buddyPairing :: Bool
} }
#else #else
data Buddy = Buddy data Buddy = Buddy

View file

@ -32,6 +32,7 @@ import Annex.UUID
import Assistant.XMPP import Assistant.XMPP
import Assistant.XMPP.Client import Assistant.XMPP.Client
import Assistant.XMPP.Buddies import Assistant.XMPP.Buddies
import Assistant.XMPP.Git
import Network.Protocol.XMPP import Network.Protocol.XMPP
import Assistant.Types.NetMessager import Assistant.Types.NetMessager
import Assistant.NetMessager import Assistant.NetMessager
@ -139,9 +140,15 @@ getFinishLocalPairR _ = noLocalPairing
getFinishXMPPPairR :: PairKey -> Handler RepHtml getFinishXMPPPairR :: PairKey -> Handler RepHtml
#ifdef WITH_XMPP #ifdef WITH_XMPP
getFinishXMPPPairR (PairKey u t) = case parseJID t of getFinishXMPPPairR (PairKey theiruuid t) = case parseJID t of
Nothing -> error "bad JID" Nothing -> error "bad JID"
Just jid -> error "TODO" Just theirjid -> do
liftAssistant $ do
selfuuid <- liftAnnex getUUID
sendNetMessage $
PairingNotification PairAck (formatJID theirjid) selfuuid
finishXMPPPairing theirjid theiruuid
redirect RepositoriesR
#else #else
getFinishXMPPPairR _ _ = noXMPPPairing getFinishXMPPPairR _ _ = noXMPPPairing
#endif #endif

View file

@ -17,8 +17,8 @@ import qualified Data.Set as S
import Data.Text (Text) import Data.Text (Text)
import qualified Data.Text as T import qualified Data.Text as T
genKey :: JID -> BuddyKey genBuddyKey :: JID -> BuddyKey
genKey j = BuddyKey $ formatJID $ baseJID j genBuddyKey j = BuddyKey $ formatJID $ baseJID j
buddyName :: JID -> Text buddyName :: JID -> Text
buddyName j = maybe (T.pack "") strNode (jidNode j) buddyName j = maybe (T.pack "") strNode (jidNode j)
@ -28,7 +28,7 @@ buddyName j = maybe (T.pack "") strNode (jidNode j)
- If the buddy has no clients at all anymore, returns Nothing. -} - If the buddy has no clients at all anymore, returns Nothing. -}
buddySummary :: Buddy -> Maybe (Text, Bool, Bool, BuddyKey) buddySummary :: Buddy -> Maybe (Text, Bool, Bool, BuddyKey)
buddySummary b = case clients of buddySummary b = case clients of
((Client j):_) -> Just (buddyName j, away, canpair, genKey j) ((Client j):_) -> Just (buddyName j, away, canpair, genBuddyKey j)
[] -> Nothing [] -> Nothing
where where
away = S.null (buddyPresent b) && S.null (buddyAssistants b) away = S.null (buddyPresent b) && S.null (buddyAssistants b)
@ -39,7 +39,7 @@ buddySummary b = case clients of
updateBuddies :: Presence -> Buddies -> Buddies updateBuddies :: Presence -> Buddies -> Buddies
updateBuddies p@(Presence { presenceFrom = Just jid }) = M.alter update key updateBuddies p@(Presence { presenceFrom = Just jid }) = M.alter update key
where where
key = genKey jid key = genBuddyKey jid
update (Just b) = Just $ applyPresence p b update (Just b) = Just $ applyPresence p b
update Nothing = newBuddy p update Nothing = newBuddy p
updateBuddies _ = id updateBuddies _ = id
@ -56,6 +56,7 @@ newBuddy p
{ buddyPresent = S.empty { buddyPresent = S.empty
, buddyAway = S.empty , buddyAway = S.empty
, buddyAssistants = S.empty , buddyAssistants = S.empty
, buddyPairing = False
} }
applyPresence :: Presence -> Buddy -> Buddy applyPresence :: Presence -> Buddy -> Buddy

49
Assistant/XMPP/Git.hs Normal file
View file

@ -0,0 +1,49 @@
{- git over XMPP
-
- Copyright 2012 Joey Hess <joey@kitenet.net>
-
- Licensed under the GNU GPL version 3 or higher.
-}
module Assistant.XMPP.Git where
import Assistant.Common
import Assistant.XMPP
import Assistant.XMPP.Buddies
import Assistant.DaemonStatus
import Assistant.Alert
import Assistant.MakeRemote
import Assistant.Sync
import Annex.UUID
import Config
import qualified Types.Remote as Remote
import Network.Protocol.XMPP
import qualified Data.Text as T
finishXMPPPairing :: JID -> UUID -> Assistant ()
finishXMPPPairing jid u = void $ alertWhile alert $
makeXMPPGitRemote buddy (baseJID jid) u
where
buddy = T.unpack $ buddyName jid
alert = pairRequestAcknowledgedAlert buddy Nothing
{- A git remote for an XMPP user? This is represented as a git remote
- that has no location set. The user's XMPP address is stored in the
- xmppaddress setting.
-
- The UUID of their remote is also stored as usual.
-}
makeXMPPGitRemote :: String -> JID -> UUID -> Assistant Bool
makeXMPPGitRemote buddyname jid u = do
remote <- liftAnnex $ addRemote $ makeGitRemote buddyname "" -- no location
liftAnnex $ do
let r = Remote.repo remote
storeUUID (remoteConfig r "uuid") u
setConfig (remoteConfig r "xmppaddress") xmppaddress
syncNewRemote remote
return True
where
xmppaddress = T.unpack $ formatJID $ baseJID jid

View file

@ -881,6 +881,11 @@ Here are all the supported configuration settings.
Used to identify Amazon S3 special remotes. Used to identify Amazon S3 special remotes.
Normally this is automaticaly set up by `git annex initremote`. Normally this is automaticaly set up by `git annex initremote`.
* `remote.<name>.annex-xmppaddress`
Used to identify the XMPP address of a Jabber buddy.
Normally this is set up by the git-annex assistant when pairing over XMPP.
# CONFIGURATION VIA .gitattributes # CONFIGURATION VIA .gitattributes
The key-value backend used when adding a new file to the annex can be The key-value backend used when adding a new file to the annex can be