hooked up XMPP git push send/receive (but not yet control flow)

This commit is contained in:
Joey Hess 2012-11-08 14:02:37 -04:00
parent 17fd1bd919
commit 0238e4ba07
5 changed files with 95 additions and 49 deletions

View file

@ -52,7 +52,7 @@ xmppClient urlrenderer d = do
Just c -> retry (runclient c) =<< getCurrentTime Just c -> retry (runclient c) =<< getCurrentTime
where where
liftAssistant = runAssistant d liftAssistant = runAssistant d
xAssistant = liftIO . liftAssistant inAssistant = liftIO . liftAssistant
{- When the client exits, it's restarted; {- When the client exits, it's restarted;
- if it keeps failing, back off to wait 5 minutes before - if it keeps failing, back off to wait 5 minutes before
@ -73,30 +73,35 @@ xmppClient urlrenderer d = do
selfjid <- bindJID jid selfjid <- bindJID jid
putStanza gitAnnexSignature putStanza gitAnnexSignature
xAssistant $ debug ["connected", show selfjid] inAssistant $ debug ["connected", show selfjid]
{- The buddy list starts empty each time {- The buddy list starts empty each time
- the client connects, so that stale info - the client connects, so that stale info
- is not retained. -} - is not retained. -}
void $ xAssistant $ void $ inAssistant $
updateBuddyList (const noBuddies) <<~ buddyList updateBuddyList (const noBuddies) <<~ buddyList
xmppThread $ receivenotifications selfjid xmppThread $ receivenotifications selfjid
forever $ do forever $ do
a <- xAssistant $ relayNetMessage selfjid a <- inAssistant $ relayNetMessage selfjid
a a
receivenotifications selfjid = forever $ do receivenotifications selfjid = forever $ do
l <- decodeStanza selfjid <$> getStanza l <- decodeStanza selfjid <$> getStanza
xAssistant $ debug ["received:", show l] inAssistant $ debug ["received:", show l]
mapM_ (handle selfjid) l mapM_ (handle selfjid) l
handle _ (PresenceMessage p) = void $ xAssistant $ handle _ (PresenceMessage p) = void $ inAssistant $
updateBuddyList (updateBuddies p) <<~ buddyList updateBuddyList (updateBuddies p) <<~ buddyList
handle _ (GotNetMessage QueryPresence) = putStanza gitAnnexSignature handle _ (GotNetMessage QueryPresence) = putStanza gitAnnexSignature
handle _ (GotNetMessage (NotifyPush us)) = void $ xAssistant $ handle _ (GotNetMessage (NotifyPush us)) = void $ inAssistant $
pull us pull us
handle selfjid (GotNetMessage (PairingNotification stage t u)) = handle selfjid (GotNetMessage (PairingNotification stage c u)) =
maybe noop (xAssistant . pairMsgReceived urlrenderer stage u selfjid) (parseJID t) maybe noop (inAssistant . pairMsgReceived urlrenderer stage u selfjid) (parseJID c)
handle selfjid (GotNetMessage (PushRequest c)) = error "TODO"
handle selfjid (GotNetMessage (StartingPush c)) = error "TODO"
handle selfjid (GotNetMessage (ReceivePackOutput c b)) = error "TODO"
handle selfjid (GotNetMessage (SendPackOutput c b)) = error "TODO"
handle selfjid (GotNetMessage (ReceivePackDone c code)) = error "TODO"
handle _ (Ignorable _) = noop handle _ (Ignorable _) = noop
handle _ (Unknown _) = noop handle _ (Unknown _) = noop
handle _ (ProtocolError _) = noop handle _ (ProtocolError _) = noop
@ -117,7 +122,7 @@ decodeStanza selfjid s@(ReceivedPresence p)
| presenceFrom p == Just selfjid = [Ignorable s] | presenceFrom p == Just selfjid = [Ignorable s]
| otherwise = maybe [PresenceMessage p] decode (getGitAnnexAttrValue p) | otherwise = maybe [PresenceMessage p] decode (getGitAnnexAttrValue p)
where where
decode (attr, v) decode (attr, v, _tag)
| attr == pushAttr = impliedp $ GotNetMessage $ NotifyPush $ | attr == pushAttr = impliedp $ GotNetMessage $ NotifyPush $
decodePushNotification v decodePushNotification v
| attr == queryAttr = impliedp $ GotNetMessage QueryPresence | attr == queryAttr = impliedp $ GotNetMessage QueryPresence
@ -131,10 +136,15 @@ decodeStanza selfjid s@(ReceivedMessage m)
| messageType m == MessageError = [ProtocolError s] | messageType m == MessageError = [ProtocolError s]
| otherwise = maybe [Unknown s] decode (getGitAnnexAttrValue m) | otherwise = maybe [Unknown s] decode (getGitAnnexAttrValue m)
where where
decode (attr, v) decode (attr, v, tag)
| attr == pairAttr = | attr == pairAttr = use $ decodePairingNotification v
[maybe (Unknown s) GotNetMessage (decodePairingNotification v m)] | attr == pushRequestAttr = use decodePushRequest
| attr == startingPushAttr = use decodeStartingPush
| attr == receivePackAttr = use $ decodeReceivePackOutput tag
| attr == sendPackAttr = use $ decodeSendPackOutput tag
| attr == receivePackDoneAttr = use $ decodeReceivePackDone v
| otherwise = [Unknown s] | otherwise = [Unknown s]
use v = [maybe (Unknown s) GotNetMessage (v m)]
decodeStanza _ s = [Unknown s] 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. -}
@ -142,15 +152,23 @@ relayNetMessage :: JID -> Assistant (XMPP ())
relayNetMessage selfjid = convert =<< waitNetMessage relayNetMessage selfjid = convert =<< waitNetMessage
where where
convert (NotifyPush us) = return $ putStanza $ pushNotification us convert (NotifyPush us) = return $ putStanza $ pushNotification us
convert QueryPresence = return $ putStanza $ presenceQuery convert QueryPresence = return $ putStanza presenceQuery
convert (PairingNotification stage t u) = case parseJID t of convert (PairingNotification stage c u) = withclient c $ \tojid -> do
Nothing -> return $ noop
Just tojid
| tojid == selfjid -> return $ noop
| otherwise -> do
changeBuddyPairing tojid True changeBuddyPairing tojid True
return $ putStanza $ return $ putStanza $ pairingNotification stage u tojid selfjid
pairingNotification stage u tojid selfjid convert (PushRequest c) = sendclient c pushRequest
convert (StartingPush c) = sendclient c startingPush
convert (ReceivePackOutput c b) = sendclient c $ receivePackOutput b
convert (SendPackOutput c b) = sendclient c $ sendPackOutput b
convert (ReceivePackDone c code) = sendclient c $ receivePackDone code
sendclient c construct = withclient c $ \tojid ->
return $ putStanza $ construct tojid selfjid
withclient c a = case parseJID c of
Nothing -> return noop
Just tojid
| tojid == selfjid -> return noop
| otherwise -> a tojid
{- Runs a XMPP action in a separate thread, using a session to allow it {- Runs a XMPP action in a separate thread, using a session to allow it
- to access the same XMPP client. -} - to access the same XMPP client. -}

View file

@ -22,20 +22,23 @@ data NetMessage
-- requests other clients to inform us of their presence -- requests other clients to inform us of their presence
| QueryPresence | QueryPresence
-- notification about a stage in the pairing process, -- notification about a stage in the pairing process,
-- involving a client identified by the Text, and a UUID. -- involving a client, and a UUID.
| PairingNotification PairStage Text UUID | PairingNotification PairStage ClientID UUID
-- request that a git push be sent over the out of band network -- request that a git push be sent over the out of band network
| PushRequest | PushRequest ClientID
-- indicates that a PushRequest has been seen and a push is starting -- indicates that a push is starting
| StartingPush | StartingPush ClientID
-- a chunk of output of git receive-pack -- a chunk of output of git receive-pack
| ReceivePackOutput ByteString | ReceivePackOutput ClientID ByteString
-- a chuck of output of git send-pack -- a chuck of output of git send-pack
| SendPackOutput ByteString | SendPackOutput ClientID ByteString
-- sent when git receive-pack exits, with its exit code -- sent when git receive-pack exits, with its exit code
| ReceivePackDone ExitCode | ReceivePackDone ClientID ExitCode
deriving (Show) deriving (Show)
{- Something used to identify a specific client to send the message to. -}
type ClientID = Text
data NetMessagerControl = NetMessagerControl data NetMessagerControl = NetMessagerControl
{ netMessages :: TChan (NetMessage) { netMessages :: TChan (NetMessage)
, netMessagerRestart :: MSampleVar () , netMessagerRestart :: MSampleVar ()

View file

@ -55,14 +55,16 @@ instance GitAnnexTaggable Presence where
insertGitAnnexTag p elt = p { presencePayloads = extendedAway : elt : presencePayloads p } insertGitAnnexTag p elt = p { presencePayloads = extendedAway : elt : presencePayloads p }
extractGitAnnexTag = headMaybe . filter isGitAnnexTag . presencePayloads extractGitAnnexTag = headMaybe . filter isGitAnnexTag . presencePayloads
{- Gets the attr and its value value from a git-annex tag. {- Gets the attr and its value value from a git-annex tag, as well as the
- tag.
- -
- Each git-annex tag has a single attribute. -} - Each git-annex tag has a single attribute. -}
getGitAnnexAttrValue :: GitAnnexTaggable a => a -> Maybe (Name, Text) getGitAnnexAttrValue :: GitAnnexTaggable a => a -> Maybe (Name, Text, Element)
getGitAnnexAttrValue a = case extractGitAnnexTag a of getGitAnnexAttrValue a = case extractGitAnnexTag a of
Just (tag@(Element _ [(attr, _)] _)) -> (,) Just (tag@(Element _ [(attr, _)] _)) -> (,,)
<$> pure attr <$> pure attr
<*> attributeText attr tag <*> attributeText attr tag
<*> pure tag
_ -> Nothing _ -> Nothing
{- A presence with a git-annex tag in it. -} {- A presence with a git-annex tag in it. -}
@ -120,17 +122,20 @@ encodePairingNotification pairstage u = T.unwords $ map T.pack
] ]
decodePairingNotification :: Text -> Message -> Maybe NetMessage decodePairingNotification :: Text -> Message -> Maybe NetMessage
decodePairingNotification t msg = parse $ words $ T.unpack t decodePairingNotification t m = parse $ words $ T.unpack t
where where
parse [stage, u] = PairingNotification parse [stage, u] = PairingNotification
<$> readish stage <$> readish stage
<*> (formatJID <$> messageFrom msg) <*> (formatJID <$> messageFrom m)
<*> pure (toUUID u) <*> pure (toUUID u)
parse _ = Nothing parse _ = Nothing
pushRequest :: JID -> JID -> Message pushRequest :: JID -> JID -> Message
pushRequest = gitAnnexMessage $ gitAnnexTag pushRequestAttr T.empty pushRequest = gitAnnexMessage $ gitAnnexTag pushRequestAttr T.empty
decodePushRequest :: Message -> Maybe NetMessage
decodePushRequest m = PushRequest <$> (formatJID <$> messageFrom m)
pushRequestAttr :: Name pushRequestAttr :: Name
pushRequestAttr = "pushrequest" pushRequestAttr = "pushrequest"
@ -140,6 +145,9 @@ startingPush = gitAnnexMessage $ gitAnnexTag startingPushAttr T.empty
startingPushAttr :: Name startingPushAttr :: Name
startingPushAttr = "startingpush" startingPushAttr = "startingpush"
decodeStartingPush :: Message -> Maybe NetMessage
decodeStartingPush m = StartingPush <$> (formatJID <$> messageFrom m)
receivePackOutput :: ByteString -> JID -> JID -> Message receivePackOutput :: ByteString -> JID -> JID -> Message
receivePackOutput = gitAnnexMessage . receivePackOutput = gitAnnexMessage .
gitAnnexTagContent receivePackAttr T.empty . encodeTagContent gitAnnexTagContent receivePackAttr T.empty . encodeTagContent
@ -147,6 +155,11 @@ receivePackOutput = gitAnnexMessage .
receivePackAttr :: Name receivePackAttr :: Name
receivePackAttr = "rp" receivePackAttr = "rp"
decodeReceivePackOutput :: Element -> Message -> Maybe NetMessage
decodeReceivePackOutput t m = ReceivePackOutput
<$> (formatJID <$> messageFrom m)
<*> decodeTagContent t
sendPackOutput :: ByteString -> JID -> JID -> Message sendPackOutput :: ByteString -> JID -> JID -> Message
sendPackOutput = gitAnnexMessage . sendPackOutput = gitAnnexMessage .
gitAnnexTagContent sendPackAttr T.empty . encodeTagContent gitAnnexTagContent sendPackAttr T.empty . encodeTagContent
@ -154,15 +167,21 @@ sendPackOutput = gitAnnexMessage .
sendPackAttr :: Name sendPackAttr :: Name
sendPackAttr = "sp" sendPackAttr = "sp"
decodeSendPackOutput :: Element -> Message -> Maybe NetMessage
decodeSendPackOutput t m = SendPackOutput
<$> (formatJID <$> messageFrom m)
<*> decodeTagContent t
receivePackDone :: ExitCode -> JID -> JID -> Message receivePackDone :: ExitCode -> JID -> JID -> Message
receivePackDone = gitAnnexMessage . gitAnnexTag receivePackAttr . T.pack . show . toi receivePackDone = gitAnnexMessage . gitAnnexTag receivePackAttr . T.pack . show . toi
where where
toi (ExitSuccess) = 0 toi (ExitSuccess) = 0
toi (ExitFailure i) = i toi (ExitFailure i) = i
decodeReceivePackDone :: Text -> ExitCode decodeReceivePackDone :: Text -> Message -> Maybe NetMessage
decodeReceivePackDone t = fromMaybe (ExitFailure 1) $ decodeReceivePackDone t m = ReceivePackDone
fromi <$> readish (T.unpack t) <$> (formatJID <$> messageFrom m)
<*> (fromi <$> readish (T.unpack t))
where where
fromi 0 = ExitSuccess fromi 0 = ExitSuccess
fromi i = ExitFailure i fromi i = ExitFailure i

View file

@ -8,6 +8,8 @@
module Assistant.XMPP.Git where module Assistant.XMPP.Git where
import Assistant.Common import Assistant.Common
import Assistant.NetMessager
import Assistant.Types.NetMessager
import Assistant.XMPP import Assistant.XMPP
import Assistant.XMPP.Buddies import Assistant.XMPP.Buddies
import Assistant.DaemonStatus import Assistant.DaemonStatus
@ -77,7 +79,10 @@ makeXMPPGitRemote buddyname jid u = do
- We listen at the other end of the pipe and relay to and from XMPP. - We listen at the other end of the pipe and relay to and from XMPP.
-} -}
xmppPush :: Remote -> [Ref] -> Assistant Bool xmppPush :: Remote -> [Ref] -> Assistant Bool
xmppPush remote refs = do xmppPush remote refs = error "TODO"
xmppPush' :: ClientID -> Remote -> [Ref] -> Assistant Bool
xmppPush' cid remote refs = do
program <- liftIO readProgramFile program <- liftIO readProgramFile
(Fd inf, writepush) <- liftIO createPipe (Fd inf, writepush) <- liftIO createPipe
@ -115,7 +120,7 @@ xmppPush remote refs = do
b <- liftIO $ B.hGetSome inh 1024 b <- liftIO $ B.hGetSome inh 1024
when (B.null b) $ when (B.null b) $
liftIO $ killThread =<< myThreadId liftIO $ killThread =<< myThreadId
-- TODO relay b to xmpp sendNetMessage $ SendPackOutput cid b
error "TODO" error "TODO"
fromxmpp outh = forever $ do fromxmpp outh = forever $ do
-- TODO get b from xmpp -- TODO get b from xmpp
@ -168,12 +173,13 @@ xmppGitRelay = do
| otherwise -> ExitFailure n | otherwise -> ExitFailure n
Nothing -> ExitFailure 1 Nothing -> ExitFailure 1
{- Relays git receive-pack to and from XMPP, and propigates its exit status. -} {- Relays git receive-pack stdin and stdout via XMPP, as well as propigating
xmppReceivePack :: Assistant Bool - its exit status to XMPP. -}
xmppReceivePack = do xmppReceivePack :: ClientID -> Assistant Bool
xmppReceivePack cid = do
feeder <- asIO1 toxmpp feeder <- asIO1 toxmpp
reader <- asIO1 fromxmpp reader <- asIO1 fromxmpp
controller <- asIO1 controlxmpp sendexitcode <- asIO1 $ sendNetMessage . ReceivePackDone cid
repodir <- liftAnnex $ fromRepo repoPath repodir <- liftAnnex $ fromRepo repoPath
let p = (proc "git" ["receive-pack", repodir]) let p = (proc "git" ["receive-pack", repodir])
{ std_in = CreatePipe { std_in = CreatePipe
@ -185,7 +191,7 @@ xmppReceivePack = do
feedertid <- forkIO $ feeder outh feedertid <- forkIO $ feeder outh
void $ reader inh void $ reader inh
code <- waitForProcess pid code <- waitForProcess pid
void $ controller code void $ sendexitcode code
killThread feedertid killThread feedertid
return $ code == ExitSuccess return $ code == ExitSuccess
where where
@ -194,7 +200,6 @@ xmppReceivePack = do
if B.null b if B.null b
then return () -- EOF then return () -- EOF
else do else do
error "TODO feed b to xmpp" sendNetMessage $ ReceivePackOutput cid b
toxmpp outh toxmpp outh
fromxmpp _inh = error "TODO feed xmpp to inh" fromxmpp _inh = error "TODO feed xmpp to inh"
controlxmpp _code = error "TODO propigate exit code"

View file

@ -58,11 +58,11 @@ For pairing, a chat message is sent, containing:
To request that a peer push to us, a chat message can be sent: To request that a peer push to us, a chat message can be sent:
<git-annex xmlns='git-annex' pushrequest="" /> <git-annex xmlns='git-annex' pushrequest="uuid" />
When a peer is ready to send a git push, it sends: When a peer is ready to send a git push, it sends:
<git-annex xmlns='git-annex' startingpush="" /> <git-annex xmlns='git-annex' startingpush="uuid" />
The receiver runs `git receive-pack`, and sends back its output in The receiver runs `git receive-pack`, and sends back its output in
one or more chat messages: one or more chat messages:
@ -71,7 +71,8 @@ one or more chat messages:
007b27ca394d26a05d9b6beefa1b07da456caa2157d7 refs/heads/git-annex report-status delete-refs side-band-64k quiet ofs-delta 007b27ca394d26a05d9b6beefa1b07da456caa2157d7 refs/heads/git-annex report-status delete-refs side-band-64k quiet ofs-delta
</git-annex> </git-annex>
The sender replies with the data from `git push`: The sender replies with the data from `git push` (which does not need
to actually be started until this point):
<git-annex xmlns='git-annex' sp=""> <git-annex xmlns='git-annex' sp="">
data data