separate data type for push stages

This improves type safety.
This commit is contained in:
Joey Hess 2012-11-10 12:18:00 -04:00
parent dedd2a407e
commit 81953c2131
6 changed files with 76 additions and 76 deletions

View file

@ -74,17 +74,19 @@ queueNetPushMessage m = do
running <- readTMVar (netMessagerPushRunning nm) running <- readTMVar (netMessagerPushRunning nm)
case running of case running of
NoPushRunning -> return False NoPushRunning -> return False
SendPushRunning cid -> go nm cid SendPushRunning runningcid -> do
ReceivePushRunning cid -> go nm cid go nm m runningcid
return True
ReceivePushRunning runningcid -> do
go nm m runningcid
return True
where where
go nm cid go nm (Pushing cid stage) runningcid
| getClientID m == Just cid = do | cid == runningcid = writeTChan (netMessagesPush nm) m
writeTChan (netMessagesPush nm) m | isPushInitiation stage = defer nm
return True | otherwise = noop
| otherwise = do go _ _ _ = noop
when (isPushInitiationMessage m) $
defer nm
return True
defer nm = do defer nm = do
s <- takeTMVar (netMessagesDeferredPush nm) s <- takeTMVar (netMessagesDeferredPush nm)
putTMVar (netMessagesDeferredPush nm) $ S.insert m s putTMVar (netMessagesDeferredPush nm) $ S.insert m s

View file

@ -98,9 +98,10 @@ pushToRemotes now notifypushes remotes = do
<*> inRepo Git.Branch.current <*> inRepo Git.Branch.current
<*> getUUID <*> getUUID
let (xmppremotes, normalremotes) = partition isXMPPRemote remotes let (xmppremotes, normalremotes) = partition isXMPPRemote remotes
r <- go True branch g u normalremotes ret <- go True branch g u normalremotes
mapM_ (sendNetMessage . CanPush . getXMPPClientID) xmppremotes forM_ xmppremotes $ \r ->
return r sendNetMessage $ Pushing (getXMPPClientID r) CanPush
return ret
where where
go _ Nothing _ _ _ = return True -- no branch, so nothing to do go _ Nothing _ _ _ = return True -- no branch, so nothing to do
go shouldretry (Just branch) g u rs = do go shouldretry (Just branch) g u rs = do

View file

@ -96,11 +96,11 @@ xmppClient urlrenderer d = do
handle _ (GotNetMessage (NotifyPush us)) = void $ inAssistant $ pull us handle _ (GotNetMessage (NotifyPush us)) = void $ inAssistant $ pull us
handle selfjid (GotNetMessage (PairingNotification stage c u)) = handle selfjid (GotNetMessage (PairingNotification stage c u)) =
maybe noop (inAssistant . pairMsgReceived urlrenderer stage u selfjid) (parseJID c) maybe noop (inAssistant . pairMsgReceived urlrenderer stage u selfjid) (parseJID c)
handle _ (GotNetMessage pushmsg) handle _ (GotNetMessage m@(Pushing _ pushstage))
| isPushInitiationMessage pushmsg = inAssistant $ | isPushInitiation pushstage = inAssistant $
unlessM (queueNetPushMessage pushmsg) $ unlessM (queueNetPushMessage m) $
void $ forkIO <~> handlePushMessage pushmsg void $ forkIO <~> handlePushMessage m
| otherwise = void $ inAssistant $ queueNetPushMessage pushmsg | otherwise = void $ inAssistant $ queueNetPushMessage m
handle _ (Ignorable _) = noop handle _ (Ignorable _) = noop
handle _ (Unknown _) = noop handle _ (Unknown _) = noop
handle _ (ProtocolError _) = noop handle _ (ProtocolError _) = noop
@ -158,12 +158,12 @@ relayNetMessage selfjid = convert =<< waitNetMessage
convert (PairingNotification stage c u) = withclient c $ \tojid -> do convert (PairingNotification stage c u) = withclient c $ \tojid -> do
changeBuddyPairing tojid True changeBuddyPairing tojid True
return $ putStanza $ pairingNotification stage u tojid selfjid return $ putStanza $ pairingNotification stage u tojid selfjid
convert (CanPush c) = sendclient c canPush convert (Pushing c CanPush) = sendclient c canPush
convert (PushRequest c) = sendclient c pushRequest convert (Pushing c PushRequest) = sendclient c pushRequest
convert (StartingPush c) = sendclient c startingPush convert (Pushing c StartingPush) = sendclient c startingPush
convert (ReceivePackOutput c b) = sendclient c $ receivePackOutput b convert (Pushing c (ReceivePackOutput b)) = sendclient c $ receivePackOutput b
convert (SendPackOutput c b) = sendclient c $ sendPackOutput b convert (Pushing c (SendPackOutput b)) = sendclient c $ sendPackOutput b
convert (ReceivePackDone c code) = sendclient c $ receivePackDone code convert (Pushing c (ReceivePackDone code)) = sendclient c $ receivePackDone code
sendclient c construct = withclient c $ \tojid -> sendclient c construct = withclient c $ \tojid ->
return $ putStanza $ construct tojid selfjid return $ putStanza $ construct tojid selfjid

View file

@ -25,39 +25,36 @@ data NetMessage
-- notification about a stage in the pairing process, -- notification about a stage in the pairing process,
-- involving a client, and a UUID. -- involving a client, and a UUID.
| PairingNotification PairStage ClientID UUID | PairingNotification PairStage ClientID UUID
-- indicates that we have data to push over the out of band network -- used for git push over the network messager
| CanPush ClientID | Pushing ClientID PushStage
-- request that a git push be sent over the out of band network
| PushRequest ClientID
-- indicates that a push is starting
| StartingPush ClientID
-- a chunk of output of git receive-pack
| ReceivePackOutput ClientID ByteString
-- a chuck of output of git send-pack
| SendPackOutput ClientID ByteString
-- sent when git receive-pack exits, with its exit code
| ReceivePackDone ClientID ExitCode
deriving (Show, Eq, Ord) deriving (Show, Eq, Ord)
{- Something used to identify the client, or clients to send the message to. -} {- Something used to identify the client, or clients to send the message to. -}
type ClientID = Text type ClientID = Text
getClientID :: NetMessage -> Maybe ClientID data PushStage
getClientID (NotifyPush _) = Nothing -- indicates that we have data to push over the out of band network
getClientID QueryPresence = Nothing = CanPush
getClientID (PairingNotification _ cid _) = Just cid -- request that a git push be sent over the out of band network
getClientID (CanPush cid) = Just cid | PushRequest
getClientID (PushRequest cid) = Just cid -- indicates that a push is starting
getClientID (StartingPush cid) = Just cid | StartingPush
getClientID (ReceivePackOutput cid _) = Just cid -- a chunk of output of git receive-pack
getClientID (SendPackOutput cid _) = Just cid | ReceivePackOutput ByteString
getClientID (ReceivePackDone cid _) = Just cid -- a chuck of output of git send-pack
| SendPackOutput ByteString
-- sent when git receive-pack exits, with its exit code
| ReceivePackDone ExitCode
deriving (Show, Eq, Ord)
isPushInitiationMessage :: NetMessage -> Bool data PushRunning = NoPushRunning | SendPushRunning ClientID | ReceivePushRunning ClientID
isPushInitiationMessage (CanPush _) = True deriving (Eq)
isPushInitiationMessage (PushRequest _) = True
isPushInitiationMessage (StartingPush _) = True isPushInitiation :: PushStage -> Bool
isPushInitiationMessage _ = False isPushInitiation CanPush = True
isPushInitiation PushRequest = True
isPushInitiation StartingPush = True
isPushInitiation _ = False
data NetMessager = NetMessager data NetMessager = NetMessager
-- outgoing messages -- outgoing messages
@ -72,9 +69,6 @@ data NetMessager = NetMessager
, netMessagerRestart :: MSampleVar () , netMessagerRestart :: MSampleVar ()
} }
data PushRunning = NoPushRunning | SendPushRunning ClientID | ReceivePushRunning ClientID
deriving (Eq)
newNetMessager :: IO NetMessager newNetMessager :: IO NetMessager
newNetMessager = NetMessager newNetMessager = NetMessager
<$> atomically newTChan <$> atomically newTChan

View file

@ -137,7 +137,7 @@ canPush :: JID -> JID -> Message
canPush = gitAnnexMessage $ gitAnnexTag canPushAttr T.empty canPush = gitAnnexMessage $ gitAnnexTag canPushAttr T.empty
decodeCanPush :: Message -> GitAnnexTagInfo -> Maybe NetMessage decodeCanPush :: Message -> GitAnnexTagInfo -> Maybe NetMessage
decodeCanPush m _ = CanPush <$> (formatJID <$> messageFrom m) decodeCanPush m _ = Pushing <$> (formatJID <$> messageFrom m) <*> pure CanPush
canPushAttr :: Name canPushAttr :: Name
canPushAttr = "canpush" canPushAttr = "canpush"
@ -146,7 +146,7 @@ pushRequest :: JID -> JID -> Message
pushRequest = gitAnnexMessage $ gitAnnexTag pushRequestAttr T.empty pushRequest = gitAnnexMessage $ gitAnnexTag pushRequestAttr T.empty
decodePushRequest :: Message -> GitAnnexTagInfo -> Maybe NetMessage decodePushRequest :: Message -> GitAnnexTagInfo -> Maybe NetMessage
decodePushRequest m _ = PushRequest <$> (formatJID <$> messageFrom m) decodePushRequest m _ = Pushing <$> (formatJID <$> messageFrom m) <*> pure PushRequest
pushRequestAttr :: Name pushRequestAttr :: Name
pushRequestAttr = "pushrequest" pushRequestAttr = "pushrequest"
@ -158,7 +158,7 @@ startingPushAttr :: Name
startingPushAttr = "startingpush" startingPushAttr = "startingpush"
decodeStartingPush :: Message -> GitAnnexTagInfo -> Maybe NetMessage decodeStartingPush :: Message -> GitAnnexTagInfo -> Maybe NetMessage
decodeStartingPush m _ = StartingPush <$> (formatJID <$> messageFrom m) decodeStartingPush m _ = Pushing <$> (formatJID <$> messageFrom m) <*> pure StartingPush
receivePackOutput :: ByteString -> JID -> JID -> Message receivePackOutput :: ByteString -> JID -> JID -> Message
receivePackOutput = gitAnnexMessage . receivePackOutput = gitAnnexMessage .
@ -168,9 +168,9 @@ receivePackAttr :: Name
receivePackAttr = "rp" receivePackAttr = "rp"
decodeReceivePackOutput :: Message -> GitAnnexTagInfo -> Maybe NetMessage decodeReceivePackOutput :: Message -> GitAnnexTagInfo -> Maybe NetMessage
decodeReceivePackOutput m i = ReceivePackOutput decodeReceivePackOutput m i = Pushing
<$> (formatJID <$> messageFrom m) <$> (formatJID <$> messageFrom m)
<*> decodeTagContent (tagElement i) <*> (ReceivePackOutput <$> decodeTagContent (tagElement i))
sendPackOutput :: ByteString -> JID -> JID -> Message sendPackOutput :: ByteString -> JID -> JID -> Message
sendPackOutput = gitAnnexMessage . sendPackOutput = gitAnnexMessage .
@ -180,9 +180,9 @@ sendPackAttr :: Name
sendPackAttr = "sp" sendPackAttr = "sp"
decodeSendPackOutput :: Message -> GitAnnexTagInfo -> Maybe NetMessage decodeSendPackOutput :: Message -> GitAnnexTagInfo -> Maybe NetMessage
decodeSendPackOutput m i = SendPackOutput decodeSendPackOutput m i = Pushing
<$> (formatJID <$> messageFrom m) <$> (formatJID <$> messageFrom m)
<*> decodeTagContent (tagElement i) <*> (SendPackOutput <$> decodeTagContent (tagElement i))
receivePackDone :: ExitCode -> JID -> JID -> Message receivePackDone :: ExitCode -> JID -> JID -> Message
receivePackDone = gitAnnexMessage . gitAnnexTag receivePackDoneAttr . T.pack . show . toi receivePackDone = gitAnnexMessage . gitAnnexTag receivePackDoneAttr . T.pack . show . toi
@ -191,9 +191,9 @@ receivePackDone = gitAnnexMessage . gitAnnexTag receivePackDoneAttr . T.pack . s
toi (ExitFailure i) = i toi (ExitFailure i) = i
decodeReceivePackDone :: Message -> GitAnnexTagInfo -> Maybe NetMessage decodeReceivePackDone :: Message -> GitAnnexTagInfo -> Maybe NetMessage
decodeReceivePackDone m i = ReceivePackDone decodeReceivePackDone m i = Pushing
<$> (formatJID <$> messageFrom m) <$> (formatJID <$> messageFrom m)
<*> (convert <$> readish (T.unpack $ tagValue i)) <*> (ReceivePackDone . convert <$> readish (T.unpack $ tagValue i))
where where
convert 0 = ExitSuccess convert 0 = ExitSuccess
convert n = ExitFailure n convert n = ExitFailure n

View file

@ -74,7 +74,7 @@ makeXMPPGitRemote buddyname jid u = do
-} -}
xmppPush :: ClientID -> Remote -> [Ref] -> Assistant Bool xmppPush :: ClientID -> Remote -> [Ref] -> Assistant Bool
xmppPush cid remote refs = runPush (SendPushRunning cid) handleDeferred $ do xmppPush cid remote refs = runPush (SendPushRunning cid) handleDeferred $ do
sendNetMessage $ StartingPush cid sendNetMessage $ Pushing cid StartingPush
(Fd inf, writepush) <- liftIO createPipe (Fd inf, writepush) <- liftIO createPipe
(readpush, Fd outf) <- liftIO createPipe (readpush, Fd outf) <- liftIO createPipe
@ -118,12 +118,14 @@ xmppPush cid remote refs = runPush (SendPushRunning cid) handleDeferred $ do
b <- liftIO $ B.hGetSome inh chunkSize b <- liftIO $ B.hGetSome inh chunkSize
if B.null b if B.null b
then liftIO $ killThread =<< myThreadId then liftIO $ killThread =<< myThreadId
else sendNetMessage $ SendPackOutput cid b else sendNetMessage $ Pushing cid $ SendPackOutput b
fromxmpp outh controlh = forever $ do fromxmpp outh controlh = forever $ do
m <- waitNetPushMessage m <- waitNetPushMessage
case m of case m of
(ReceivePackOutput _ b) -> liftIO $ writeChunk outh b (Pushing _ (ReceivePackOutput b)) ->
(ReceivePackDone _ exitcode) -> liftIO $ do liftIO $ writeChunk outh b
(Pushing _ (ReceivePackDone exitcode)) ->
liftIO $ do
hPrint controlh exitcode hPrint controlh exitcode
hFlush controlh hFlush controlh
_ -> noop _ -> noop
@ -197,7 +199,7 @@ xmppReceivePack cid = runPush (ReceivePushRunning cid) handleDeferred $ do
readertid <- forkIO <~> relayfromxmpp inh readertid <- forkIO <~> relayfromxmpp inh
relaytoxmpp outh relaytoxmpp outh
code <- liftIO $ waitForProcess pid code <- liftIO $ waitForProcess pid
void $ sendNetMessage $ ReceivePackDone cid code void $ sendNetMessage $ Pushing cid $ ReceivePackDone code
liftIO $ do liftIO $ do
killThread readertid killThread readertid
hClose inh hClose inh
@ -208,12 +210,13 @@ xmppReceivePack cid = runPush (ReceivePushRunning cid) handleDeferred $ do
b <- liftIO $ B.hGetSome outh chunkSize b <- liftIO $ B.hGetSome outh chunkSize
-- empty is EOF, so exit -- empty is EOF, so exit
unless (B.null b) $ do unless (B.null b) $ do
sendNetMessage $ ReceivePackOutput cid b sendNetMessage $ Pushing cid $ ReceivePackOutput b
relaytoxmpp outh relaytoxmpp outh
relayfromxmpp inh = forever $ do relayfromxmpp inh = forever $ do
m <- waitNetPushMessage m <- waitNetPushMessage
case m of case m of
(SendPackOutput _ b) -> liftIO $ writeChunk inh b (Pushing _ (SendPackOutput b)) ->
liftIO $ writeChunk inh b
_ -> noop _ -> noop
xmppRemotes :: ClientID -> Assistant [Remote] xmppRemotes :: ClientID -> Assistant [Remote]
@ -230,15 +233,15 @@ whenXMPPRemote :: ClientID -> Assistant () -> Assistant ()
whenXMPPRemote cid = unlessM (null <$> xmppRemotes cid) whenXMPPRemote cid = unlessM (null <$> xmppRemotes cid)
handlePushMessage :: NetMessage -> Assistant () handlePushMessage :: NetMessage -> Assistant ()
handlePushMessage (CanPush cid) = whenXMPPRemote cid $ handlePushMessage (Pushing cid CanPush) = whenXMPPRemote cid $
sendNetMessage $ PushRequest cid sendNetMessage $ Pushing cid PushRequest
handlePushMessage (PushRequest cid) = do handlePushMessage (Pushing cid PushRequest) = do
rs <- xmppRemotes cid rs <- xmppRemotes cid
current <- liftAnnex $ inRepo Git.Branch.current current <- liftAnnex $ inRepo Git.Branch.current
--let refs = catMaybes [current, Just Annex.Branch.fullname] -- TODO --let refs = catMaybes [current, Just Annex.Branch.fullname] -- TODO
let refs = [Ref "master:refs/remotes/xmpp/newmaster"] let refs = [Ref "master:refs/remotes/xmpp/newmaster"]
forM_ rs $ \r -> xmppPush cid r refs forM_ rs $ \r -> xmppPush cid r refs
handlePushMessage (StartingPush cid) = whenXMPPRemote cid $ handlePushMessage (Pushing cid StartingPush) = whenXMPPRemote cid $
void $ xmppReceivePack cid void $ xmppReceivePack cid
handlePushMessage _ = noop handlePushMessage _ = noop