tag xmpp pushes with jid
This fixes the issue mentioned in the last commit. Turns out just collecting UUID of clients behind a XMPP remote is insufficient (although I should probably still do it for other reasons), because a single remote repo might be connected via both XMPP and local pairing. So a way is needed to know when a push was received from any client using a given XMPP remote over XMPP, as opposed to via ssh.
This commit is contained in:
parent
c23ea9e311
commit
cbb6e1fae4
7 changed files with 76 additions and 49 deletions
|
@ -1,4 +1,4 @@
|
||||||
{- git-annex uuid-tagged pushes
|
{- git-annex tagged pushes
|
||||||
-
|
-
|
||||||
- Copyright 2012 Joey Hess <joey@kitenet.net>
|
- Copyright 2012 Joey Hess <joey@kitenet.net>
|
||||||
-
|
-
|
||||||
|
@ -13,9 +13,11 @@ import qualified Annex.Branch
|
||||||
import qualified Git
|
import qualified Git
|
||||||
import qualified Git.Ref
|
import qualified Git.Ref
|
||||||
import qualified Git.Command
|
import qualified Git.Command
|
||||||
|
import Utility.Base64
|
||||||
|
|
||||||
{- Converts a git branch into a branch that is tagged with a UUID, typically
|
{- Converts a git branch into a branch that is tagged with a UUID, typically
|
||||||
- the UUID of the repo that will be pushing it.
|
- the UUID of the repo that will be pushing it, and possibly with other
|
||||||
|
- information.
|
||||||
-
|
-
|
||||||
- Pushing to branches on the remote that have out uuid in them is ugly,
|
- Pushing to branches on the remote that have out uuid in them is ugly,
|
||||||
- but it reserves those branches for pushing by us, and so our pushes will
|
- but it reserves those branches for pushing by us, and so our pushes will
|
||||||
|
@ -23,25 +25,33 @@ import qualified Git.Command
|
||||||
-
|
-
|
||||||
- To avoid cluttering up the branch display, the branch is put under
|
- To avoid cluttering up the branch display, the branch is put under
|
||||||
- refs/synced/, rather than the usual refs/remotes/
|
- refs/synced/, rather than the usual refs/remotes/
|
||||||
|
-
|
||||||
|
- Both UUIDs and Base64 encoded data are always legal to be used in git
|
||||||
|
- refs, per git-check-ref-format.
|
||||||
-}
|
-}
|
||||||
toTaggedBranch :: UUID -> Git.Branch -> Git.Branch
|
toTaggedBranch :: UUID -> Maybe String -> Git.Branch -> Git.Branch
|
||||||
toTaggedBranch u b = Git.Ref $ concat
|
toTaggedBranch u info b = Git.Ref $ join "/" $ catMaybes
|
||||||
[ s
|
[ Just "refs/synced"
|
||||||
, ":"
|
, Just $ fromUUID u
|
||||||
, "refs/synced/" ++ fromUUID u ++ "/" ++ s
|
, toB64 <$> info
|
||||||
|
, Just $ show $ Git.Ref.base b
|
||||||
]
|
]
|
||||||
where
|
|
||||||
s = show $ Git.Ref.base b
|
|
||||||
|
|
||||||
branchTaggedBy :: Git.Branch -> Maybe UUID
|
fromTaggedBranch :: Git.Branch -> Maybe (UUID, Maybe String)
|
||||||
branchTaggedBy b = case split "/" $ show b of
|
fromTaggedBranch b = case split "/" $ show b of
|
||||||
("refs":"synced":u:_base) -> Just $ toUUID u
|
("refs":"synced":u:info:_base) ->
|
||||||
|
Just (toUUID u, fromB64Maybe info)
|
||||||
|
("refs":"synced":u:_base) ->
|
||||||
|
Just (toUUID u, Nothing)
|
||||||
_ -> Nothing
|
_ -> Nothing
|
||||||
|
where
|
||||||
|
|
||||||
taggedPush :: UUID -> Git.Ref -> Remote -> Git.Repo -> IO Bool
|
taggedPush :: UUID -> Maybe String -> Git.Ref -> Remote -> Git.Repo -> IO Bool
|
||||||
taggedPush u branch remote = Git.Command.runBool
|
taggedPush u info branch remote = Git.Command.runBool
|
||||||
[ Param "push"
|
[ Param "push"
|
||||||
, Param $ Remote.name remote
|
, Param $ Remote.name remote
|
||||||
, Param $ show $ toTaggedBranch u Annex.Branch.name
|
, Param $ refspec Annex.Branch.name
|
||||||
, Param $ show $ toTaggedBranch u branch
|
, Param $ refspec branch
|
||||||
]
|
]
|
||||||
|
where
|
||||||
|
refspec b = show b ++ ":" ++ show (toTaggedBranch u info b)
|
||||||
|
|
|
@ -48,11 +48,9 @@ reconnectRemotes _ [] = noop
|
||||||
reconnectRemotes notifypushes rs = void $ do
|
reconnectRemotes notifypushes rs = void $ do
|
||||||
modifyDaemonStatus_ $ \s -> s
|
modifyDaemonStatus_ $ \s -> s
|
||||||
{ desynced = S.union (S.fromList $ map Remote.uuid xmppremotes) (desynced s) }
|
{ desynced = S.union (S.fromList $ map Remote.uuid xmppremotes) (desynced s) }
|
||||||
alertWhile (syncAlert normalremotes) $ do
|
if null normalremotes
|
||||||
(ok, diverged) <- sync
|
then go
|
||||||
=<< liftAnnex (inRepo Git.Branch.current)
|
else alertWhile (syncAlert normalremotes) go
|
||||||
addScanRemotes diverged rs
|
|
||||||
return ok
|
|
||||||
where
|
where
|
||||||
gitremotes = filter (notspecialremote . Remote.repo) rs
|
gitremotes = filter (notspecialremote . Remote.repo) rs
|
||||||
(xmppremotes, normalremotes) = partition isXMPPRemote gitremotes
|
(xmppremotes, normalremotes) = partition isXMPPRemote gitremotes
|
||||||
|
@ -69,6 +67,11 @@ reconnectRemotes notifypushes rs = void $ do
|
||||||
sync Nothing = do
|
sync Nothing = do
|
||||||
diverged <- snd <$> manualPull Nothing gitremotes
|
diverged <- snd <$> manualPull Nothing gitremotes
|
||||||
return (True, diverged)
|
return (True, diverged)
|
||||||
|
go = do
|
||||||
|
(ok, diverged) <- sync
|
||||||
|
=<< liftAnnex (inRepo Git.Branch.current)
|
||||||
|
addScanRemotes diverged rs
|
||||||
|
return ok
|
||||||
|
|
||||||
{- Updates the local sync branch, then pushes it to all remotes, in
|
{- Updates the local sync branch, then pushes it to all remotes, in
|
||||||
- parallel, along with the git-annex branch. This is the same
|
- parallel, along with the git-annex branch. This is the same
|
||||||
|
@ -137,7 +140,7 @@ pushToRemotes now notifypushes remotes = do
|
||||||
fallback branch g u rs = do
|
fallback branch g u rs = do
|
||||||
debug ["fallback pushing to", show rs]
|
debug ["fallback pushing to", show rs]
|
||||||
(succeeded, failed) <- liftIO $
|
(succeeded, failed) <- liftIO $
|
||||||
inParallel (\r -> taggedPush u branch r g) rs
|
inParallel (\r -> taggedPush u Nothing branch r g) rs
|
||||||
updatemap succeeded failed
|
updatemap succeeded failed
|
||||||
when (notifypushes && (not $ null succeeded)) $
|
when (notifypushes && (not $ null succeeded)) $
|
||||||
sendNetMessage $ NotifyPush $
|
sendNetMessage $ NotifyPush $
|
||||||
|
|
|
@ -22,6 +22,7 @@ import Annex.TaggedPush
|
||||||
import Remote (remoteFromUUID)
|
import Remote (remoteFromUUID)
|
||||||
|
|
||||||
import qualified Data.Set as S
|
import qualified Data.Set as S
|
||||||
|
import qualified Data.Text as T
|
||||||
|
|
||||||
{- This thread watches for changes to .git/refs/, and handles incoming
|
{- This thread watches for changes to .git/refs/, and handles incoming
|
||||||
- pushes. -}
|
- pushes. -}
|
||||||
|
@ -89,21 +90,21 @@ onAdd file
|
||||||
void $ liftAnnex $ Command.Sync.mergeFrom changedbranch
|
void $ liftAnnex $ Command.Sync.mergeFrom changedbranch
|
||||||
mergecurrent _ = noop
|
mergecurrent _ = noop
|
||||||
|
|
||||||
handleDesynced = case branchTaggedBy changedbranch of
|
handleDesynced = case fromTaggedBranch changedbranch of
|
||||||
Nothing -> return False
|
Nothing -> return False
|
||||||
Just u -> do
|
Just (u, info) -> do
|
||||||
s <- desynced <$> getDaemonStatus
|
mr <- liftAnnex $ remoteFromUUID u
|
||||||
if S.member u s
|
case mr of
|
||||||
then do
|
Nothing -> return False
|
||||||
modifyDaemonStatus_ $ \st -> st
|
Just r -> do
|
||||||
{ desynced = S.delete u s }
|
s <- desynced <$> getDaemonStatus
|
||||||
mr <- liftAnnex $ remoteFromUUID u
|
if S.member u s || Just (T.unpack $ getXMPPClientID r) == info
|
||||||
case mr of
|
then do
|
||||||
Just r -> do
|
modifyDaemonStatus_ $ \st -> st
|
||||||
|
{ desynced = S.delete u s }
|
||||||
addScanRemotes True [r]
|
addScanRemotes True [r]
|
||||||
return True
|
return True
|
||||||
Nothing -> return False
|
else return False
|
||||||
else return False
|
|
||||||
|
|
||||||
equivBranches :: Git.Ref -> Git.Ref -> Bool
|
equivBranches :: Git.Ref -> Git.Ref -> Bool
|
||||||
equivBranches x y = base x == base y
|
equivBranches x y = base x == base y
|
||||||
|
|
|
@ -38,18 +38,20 @@ xmppClientThread urlrenderer = namedThread "XMPPClient" $
|
||||||
restartableClient . xmppClient urlrenderer =<< getAssistant id
|
restartableClient . xmppClient urlrenderer =<< getAssistant id
|
||||||
|
|
||||||
{- Runs the client, handing restart events. -}
|
{- Runs the client, handing restart events. -}
|
||||||
restartableClient :: IO () -> Assistant ()
|
restartableClient :: (XMPPCreds -> IO ()) -> Assistant ()
|
||||||
restartableClient a = forever $ do
|
restartableClient a = forever $ go =<< liftAnnex getXMPPCreds
|
||||||
tid <- liftIO $ forkIO a
|
where
|
||||||
waitNetMessagerRestart
|
go Nothing = waitNetMessagerRestart
|
||||||
liftIO $ killThread tid
|
go (Just creds) = do
|
||||||
|
modifyDaemonStatus_ $ \s -> s
|
||||||
|
{ xmppClientID = Just $ xmppJID creds }
|
||||||
|
tid <- liftIO $ forkIO $ a creds
|
||||||
|
waitNetMessagerRestart
|
||||||
|
liftIO $ killThread tid
|
||||||
|
|
||||||
xmppClient :: UrlRenderer -> AssistantData -> IO ()
|
xmppClient :: UrlRenderer -> AssistantData -> XMPPCreds -> IO ()
|
||||||
xmppClient urlrenderer d = do
|
xmppClient urlrenderer d creds =
|
||||||
v <- liftAssistant $ liftAnnex getXMPPCreds
|
retry (runclient creds) =<< getCurrentTime
|
||||||
case v of
|
|
||||||
Nothing -> noop -- will be restarted once creds get configured
|
|
||||||
Just c -> retry (runclient c) =<< getCurrentTime
|
|
||||||
where
|
where
|
||||||
liftAssistant = runAssistant d
|
liftAssistant = runAssistant d
|
||||||
inAssistant = liftIO . liftAssistant
|
inAssistant = liftIO . liftAssistant
|
||||||
|
|
|
@ -15,6 +15,7 @@ import Assistant.Pairing
|
||||||
import Utility.NotificationBroadcaster
|
import Utility.NotificationBroadcaster
|
||||||
import Logs.Transfer
|
import Logs.Transfer
|
||||||
import Assistant.Types.ThreadName
|
import Assistant.Types.ThreadName
|
||||||
|
import Assistant.Types.NetMessager
|
||||||
|
|
||||||
import Control.Concurrent.STM
|
import Control.Concurrent.STM
|
||||||
import Control.Concurrent.Async
|
import Control.Concurrent.Async
|
||||||
|
@ -57,6 +58,8 @@ data DaemonStatus = DaemonStatus
|
||||||
, alertNotifier :: NotificationBroadcaster
|
, alertNotifier :: NotificationBroadcaster
|
||||||
-- Broadcasts notifications when the syncRemotes change
|
-- Broadcasts notifications when the syncRemotes change
|
||||||
, syncRemotesNotifier :: NotificationBroadcaster
|
, syncRemotesNotifier :: NotificationBroadcaster
|
||||||
|
-- When the XMPP client is in use, this will contain its JI.
|
||||||
|
, xmppClientID :: Maybe ClientID
|
||||||
}
|
}
|
||||||
|
|
||||||
type TransferMap = M.Map Transfer TransferInfo
|
type TransferMap = M.Map Transfer TransferInfo
|
||||||
|
@ -83,3 +86,4 @@ newDaemonStatus = DaemonStatus
|
||||||
<*> newNotificationBroadcaster
|
<*> newNotificationBroadcaster
|
||||||
<*> newNotificationBroadcaster
|
<*> newNotificationBroadcaster
|
||||||
<*> newNotificationBroadcaster
|
<*> newNotificationBroadcaster
|
||||||
|
<*> pure Nothing
|
||||||
|
|
|
@ -264,7 +264,8 @@ handlePushInitiation (Pushing cid PushRequest) =
|
||||||
<*> getUUID
|
<*> getUUID
|
||||||
liftIO $ Command.Sync.updateBranch (Command.Sync.syncBranch branch) g
|
liftIO $ Command.Sync.updateBranch (Command.Sync.syncBranch branch) g
|
||||||
debug ["pushing to", show rs]
|
debug ["pushing to", show rs]
|
||||||
forM_ rs $ \r -> xmppPush cid $ taggedPush u branch r
|
selfjid <- ((T.unpack <$>) . xmppClientID) <$> getDaemonStatus
|
||||||
|
forM_ rs $ \r -> xmppPush cid $ taggedPush u selfjid branch r
|
||||||
handlePushInitiation (Pushing cid StartingPush) =
|
handlePushInitiation (Pushing cid StartingPush) =
|
||||||
whenXMPPRemote cid $
|
whenXMPPRemote cid $
|
||||||
void $ xmppReceivePack cid
|
void $ xmppReceivePack cid
|
||||||
|
|
|
@ -5,14 +5,20 @@
|
||||||
- Licensed under the GNU GPL version 3 or higher.
|
- Licensed under the GNU GPL version 3 or higher.
|
||||||
-}
|
-}
|
||||||
|
|
||||||
module Utility.Base64 (toB64, fromB64) where
|
module Utility.Base64 (toB64, fromB64Maybe, fromB64) where
|
||||||
|
|
||||||
import Codec.Binary.Base64
|
import Codec.Binary.Base64
|
||||||
import Data.Bits.Utils
|
import Data.Bits.Utils
|
||||||
|
import Control.Applicative
|
||||||
|
import Data.Maybe
|
||||||
|
|
||||||
toB64 :: String -> String
|
toB64 :: String -> String
|
||||||
toB64 = encode . s2w8
|
toB64 = encode . s2w8
|
||||||
|
|
||||||
|
fromB64Maybe :: String -> Maybe String
|
||||||
|
fromB64Maybe s = w82s <$> decode s
|
||||||
|
|
||||||
fromB64 :: String -> String
|
fromB64 :: String -> String
|
||||||
fromB64 s = maybe bad w82s $ decode s
|
fromB64 = fromMaybe bad . fromB64Maybe
|
||||||
where bad = error "bad base64 encoded data"
|
where
|
||||||
|
bad = error "bad base64 encoded data"
|
||||||
|
|
Loading…
Reference in a new issue