summaryrefslogtreecommitdiff
diff options
context:
space:
mode:
authorGravatar Joey Hess <joey@kitenet.net>2012-11-11 16:23:16 -0400
committerGravatar Joey Hess <joey@kitenet.net>2012-11-11 16:23:16 -0400
commit6068fd160ffeb930368a4c4c2a8818ace71f29ab (patch)
tree3f5a183e9594854a55f17cfdca740516943084c6
parent0d21e323e0d095232e347859adaaf2cc2cd71592 (diff)
don't try to transfer data to/from XMPP remotes
Partition syncRemotes into ones needing git sync (ie, non-special remotes), and ones needing data sync (ie, non-XMPP remotes).
-rw-r--r--Assistant/DaemonStatus.hs32
-rw-r--r--Assistant/Drop.hs2
-rw-r--r--Assistant/NetMessager.hs9
-rw-r--r--Assistant/Threads/Pusher.hs9
-rw-r--r--Assistant/Threads/TransferScanner.hs4
-rw-r--r--Assistant/Threads/XMPPClient.hs2
-rw-r--r--Assistant/TransferQueue.hs4
-rw-r--r--Assistant/Types/DaemonStatus.hs8
-rw-r--r--Assistant/XMPP/Git.hs2
9 files changed, 39 insertions, 33 deletions
diff --git a/Assistant/DaemonStatus.hs b/Assistant/DaemonStatus.hs
index a93f4105a..8a4a7a16d 100644
--- a/Assistant/DaemonStatus.hs
+++ b/Assistant/DaemonStatus.hs
@@ -10,11 +10,13 @@ module Assistant.DaemonStatus where
import Assistant.Common
import Assistant.Alert
import Utility.TempFile
+import Assistant.Types.NetMessager
import Utility.NotificationBroadcaster
import Logs.Transfer
import Logs.Trust
import qualified Remote
import qualified Types.Remote as Remote
+import qualified Git
import Config
import Control.Concurrent.STM
@@ -23,6 +25,7 @@ import Data.Time.Clock.POSIX
import Data.Time
import System.Locale
import qualified Data.Map as M
+import qualified Data.Text as T
getDaemonStatus :: Assistant DaemonStatus
getDaemonStatus = (atomically . readTMVar) <<~ daemonStatusHandle
@@ -41,20 +44,23 @@ modifyDaemonStatus a = do
sendNotification $ changeNotifier s
return b
-{- Syncable remotes ordered by cost. -}
-calcSyncRemotes :: Annex [Remote]
+{- Returns a function that updates the lists of syncable remotes. -}
+calcSyncRemotes :: Annex (DaemonStatus -> DaemonStatus)
calcSyncRemotes = do
rs <- filterM (repoSyncable . Remote.repo) =<<
concat . Remote.byCost <$> Remote.enabledRemoteList
alive <- trustExclude DeadTrusted (map Remote.uuid rs)
let good r = Remote.uuid r `elem` alive
- return $ filter good rs
+ let syncable = filter good rs
+ return $ \dstatus -> dstatus
+ { syncRemotes = syncable
+ , syncGitRemotes = filter (not . Remote.specialRemote) syncable
+ , syncDataRemotes = filter (not . isXMPPRemote) syncable
+ }
{- Updates the sycRemotes list from the list of all remotes in Annex state. -}
updateSyncRemotes :: Assistant ()
-updateSyncRemotes = do
- remotes <- liftAnnex calcSyncRemotes
- modifyDaemonStatus_ $ \s -> s { syncRemotes = remotes }
+updateSyncRemotes = modifyDaemonStatus_ =<< liftAnnex calcSyncRemotes
{- Load any previous daemon status file, and store it in a MVar for this
- process to use as its DaemonStatus. Also gets current transfer status. -}
@@ -64,12 +70,11 @@ startDaemonStatus = do
status <- liftIO $
flip catchDefaultIO (readDaemonStatusFile file) =<< newDaemonStatus
transfers <- M.fromList <$> getTransfers
- remotes <- calcSyncRemotes
- liftIO $ atomically $ newTMVar status
+ addsync <- calcSyncRemotes
+ liftIO $ atomically $ newTMVar $ addsync $ status
{ scanComplete = False
, sanityCheckRunning = False
, currentTransfers = transfers
- , syncRemotes = remotes
}
{- Don't just dump out the structure, because it will change over time,
@@ -221,3 +226,12 @@ alertDuring :: Alert -> Assistant a -> Assistant a
alertDuring alert a = do
i <- addAlert $ alert { alertClass = Activity }
removeAlert i `after` a
+
+{- Remotes using the XMPP transport have urls like xmpp::user@host -}
+isXMPPRemote :: Remote -> Bool
+isXMPPRemote remote = Git.repoIsUrl r && "xmpp::" `isPrefixOf` Git.repoLocation r
+ where
+ r = Remote.repo remote
+
+getXMPPClientID :: Remote -> ClientID
+getXMPPClientID r = T.pack $ drop (length "xmpp::") (Git.repoLocation (Remote.repo r))
diff --git a/Assistant/Drop.hs b/Assistant/Drop.hs
index d28a05a53..66e738a6f 100644
--- a/Assistant/Drop.hs
+++ b/Assistant/Drop.hs
@@ -23,7 +23,7 @@ import Config
handleDrops :: Bool -> Key -> AssociatedFile -> Assistant ()
handleDrops _ _ Nothing = noop
handleDrops fromhere key f = do
- syncrs <- syncRemotes <$> getDaemonStatus
+ syncrs <- syncDataRemotes <$> getDaemonStatus
liftAnnex $ do
locs <- loggedLocations key
handleDrops' locs syncrs fromhere key f
diff --git a/Assistant/NetMessager.hs b/Assistant/NetMessager.hs
index e3ef89b04..d9450ad27 100644
--- a/Assistant/NetMessager.hs
+++ b/Assistant/NetMessager.hs
@@ -95,12 +95,3 @@ queueNetPushMessage _ = return False
waitNetPushMessage :: PushSide -> Assistant (NetMessage)
waitNetPushMessage side = (atomically . readTChan)
<<~ (getSide side . netMessagesPush . netMessager)
-
-{- Remotes using the XMPP transport have urls like xmpp::user@host -}
-isXMPPRemote :: Remote -> Bool
-isXMPPRemote remote = Git.repoIsUrl r && "xmpp::" `isPrefixOf` Git.repoLocation r
- where
- r = Remote.repo remote
-
-getXMPPClientID :: Remote -> ClientID
-getXMPPClientID r = T.pack $ drop (length "xmpp::") (Git.repoLocation (Remote.repo r))
diff --git a/Assistant/Threads/Pusher.hs b/Assistant/Threads/Pusher.hs
index 69974a21c..035a454a1 100644
--- a/Assistant/Threads/Pusher.hs
+++ b/Assistant/Threads/Pusher.hs
@@ -15,7 +15,6 @@ import Assistant.Alert
import Assistant.DaemonStatus
import Assistant.Sync
import Utility.ThreadScheduler
-import qualified Remote
import qualified Types.Remote as Remote
import Data.Time.Clock
@@ -46,7 +45,8 @@ pushThread = NamedThread "Pusher" $ runEvery (Seconds 2) <~> do
-- Now see if now's a good time to push.
if shouldPush commits
then do
- remotes <- filter pushable . syncRemotes <$> getDaemonStatus
+ remotes <- filter (not . Remote.readonly)
+ . syncGitRemotes <$> getDaemonStatus
unless (null remotes) $
void $ alertWhile (pushAlert remotes) $ do
now <- liftIO $ getCurrentTime
@@ -54,11 +54,6 @@ pushThread = NamedThread "Pusher" $ runEvery (Seconds 2) <~> do
else do
debug ["delaying push of", show (length commits), "commits"]
refillCommits commits
- where
- pushable r
- | Remote.specialRemote r = False
- | Remote.readonly r = False
- | otherwise = True
{- Decide if now is a good time to push to remotes.
-
diff --git a/Assistant/Threads/TransferScanner.hs b/Assistant/Threads/TransferScanner.hs
index 3b3c3f304..918a266c7 100644
--- a/Assistant/Threads/TransferScanner.hs
+++ b/Assistant/Threads/TransferScanner.hs
@@ -57,7 +57,7 @@ transferScannerThread = NamedThread "TransferScanner" $ do
- and then the system (or us) crashed, and that info was
- lost.
-}
- startupScan = addScanRemotes True =<< syncRemotes <$> getDaemonStatus
+ startupScan = addScanRemotes True =<< syncDataRemotes <$> getDaemonStatus
{- This is a cheap scan for failed transfers involving a remote. -}
failedTransferScan :: Remote -> Assistant ()
@@ -114,7 +114,7 @@ expensiveScan rs = unless onlyweb $ do
findtransfers f (key, _) = do
{- The syncable remotes may have changed since this
- scan began. -}
- syncrs <- syncRemotes <$> getDaemonStatus
+ syncrs <- syncDataRemotes <$> getDaemonStatus
liftAnnex $ do
locs <- loggedLocations key
present <- inAnnex key
diff --git a/Assistant/Threads/XMPPClient.hs b/Assistant/Threads/XMPPClient.hs
index 8df9ff04e..641e6da66 100644
--- a/Assistant/Threads/XMPPClient.hs
+++ b/Assistant/Threads/XMPPClient.hs
@@ -190,7 +190,7 @@ xmppThread a = do
pull :: [UUID] -> Assistant ()
pull [] = noop
pull us = do
- rs <- filter matching . syncRemotes <$> getDaemonStatus
+ rs <- filter matching . syncGitRemotes <$> getDaemonStatus
debug $ "push notification for" : map (fromUUID . Remote.uuid ) rs
pullone rs =<< liftAnnex (inRepo Git.Branch.current)
where
diff --git a/Assistant/TransferQueue.hs b/Assistant/TransferQueue.hs
index 8e403cc43..4d46b0920 100644
--- a/Assistant/TransferQueue.hs
+++ b/Assistant/TransferQueue.hs
@@ -57,7 +57,7 @@ queueTransfersMatching matching schedule k f direction
where
go = do
rs <- liftAnnex . sufficientremotes
- =<< syncRemotes <$> getDaemonStatus
+ =<< syncDataRemotes <$> getDaemonStatus
let matchingrs = filter (matching . Remote.uuid) rs
if null matchingrs
then defer
@@ -94,7 +94,7 @@ queueDeferredDownloads :: Schedule -> Assistant ()
queueDeferredDownloads schedule = do
q <- getAssistant transferQueue
l <- liftIO $ atomically $ swapTVar (deferreddownloads q) []
- rs <- syncRemotes <$> getDaemonStatus
+ rs <- syncDataRemotes <$> getDaemonStatus
left <- filterM (queue rs) l
unless (null left) $
liftIO $ atomically $ modifyTVar' (deferreddownloads q) $
diff --git a/Assistant/Types/DaemonStatus.hs b/Assistant/Types/DaemonStatus.hs
index ca4122d55..df0928d6e 100644
--- a/Assistant/Types/DaemonStatus.hs
+++ b/Assistant/Types/DaemonStatus.hs
@@ -33,8 +33,12 @@ data DaemonStatus = DaemonStatus
-- Messages to display to the user.
, alertMap :: AlertMap
, lastAlertId :: AlertId
- -- Ordered list of remotes to sync with.
+ -- Ordered list of all remotes that can be synced with
, syncRemotes :: [Remote]
+ -- Ordered list of remotes to sync git with
+ , syncGitRemotes :: [Remote]
+ -- Ordered list of remotes to sync data with
+ , syncDataRemotes :: [Remote]
-- Pairing request that is in progress.
, pairingInProgress :: Maybe PairingInProgress
-- Broadcasts notifications about all changes to the DaemonStatus
@@ -60,6 +64,8 @@ newDaemonStatus = DaemonStatus
<*> pure M.empty
<*> pure firstAlertId
<*> pure []
+ <*> pure []
+ <*> pure []
<*> pure Nothing
<*> newNotificationBroadcaster
<*> newNotificationBroadcaster
diff --git a/Assistant/XMPP/Git.hs b/Assistant/XMPP/Git.hs
index 2d72df531..da143eae4 100644
--- a/Assistant/XMPP/Git.hs
+++ b/Assistant/XMPP/Git.hs
@@ -238,7 +238,7 @@ xmppRemotes cid = case baseJID <$> parseJID cid of
Nothing -> return []
Just jid -> do
let loc = gitXMPPLocation jid
- filter (matching loc . Remote.repo) . syncRemotes
+ filter (matching loc . Remote.repo) . syncGitRemotes
<$> getDaemonStatus
where
matching loc r = repoIsUrl r && repoLocation r == loc