summaryrefslogtreecommitdiff
diff options
context:
space:
mode:
authorGravatar Joey Hess <joey@kitenet.net>2012-10-14 14:47:01 -0400
committerGravatar Joey Hess <joey@kitenet.net>2012-10-14 14:50:03 -0400
commit83c8c3104583d6fea4c44751b39191b1f4af443f (patch)
tree670ee370decd2e9e4fca38f4f66077e77c92dce5
parentec23c75632cf1b8e4e3d5049a2c0a7623a9ae958 (diff)
better variable name
-rw-r--r--Assistant/DaemonStatus.hs23
-rw-r--r--Assistant/Sync.hs2
-rw-r--r--Assistant/Threads/MountWatcher.hs2
-rw-r--r--Assistant/Threads/Pusher.hs2
-rw-r--r--Assistant/Threads/TransferScanner.hs6
-rw-r--r--Assistant/Threads/TransferWatcher.hs2
-rw-r--r--Assistant/TransferQueue.hs4
7 files changed, 20 insertions, 21 deletions
diff --git a/Assistant/DaemonStatus.hs b/Assistant/DaemonStatus.hs
index 8146f977e..60b560b90 100644
--- a/Assistant/DaemonStatus.hs
+++ b/Assistant/DaemonStatus.hs
@@ -41,8 +41,8 @@ data DaemonStatus = DaemonStatus
-- Messages to display to the user.
, alertMap :: AlertMap
, lastAlertId :: AlertId
- -- Ordered list of remotes to talk to.
- , knownRemotes :: [Remote]
+ -- Ordered list of remotes to sync with.
+ , syncRemotes :: [Remote]
-- Pairing request that is in progress.
, pairingInProgress :: Maybe PairingInProgress
-- Broadcasts notifications about all changes to the DaemonStatus
@@ -89,21 +89,20 @@ modifyDaemonStatus dstatus a = do
return b
{- Syncable remotes ordered by cost. -}
-calcKnownRemotes :: Annex [Remote]
-calcKnownRemotes = do
+calcSyncRemotes :: Annex [Remote]
+calcSyncRemotes = do
rs <- filterM (repoSyncable . Remote.repo) =<<
concat . Remote.byCost <$> Remote.enabledRemoteList
alive <- snd <$> trustPartition DeadTrusted (map Remote.uuid rs)
let good r = Remote.uuid r `elem` alive
return $ filter good rs
-{- Updates the cached ordered list of remotes from the list in Annex
- - state. -}
-updateKnownRemotes :: DaemonStatusHandle -> Annex ()
-updateKnownRemotes dstatus = do
- remotes <- calcKnownRemotes
+{- Updates the sycRemotes list from the list of all remotes in Annex state. -}
+updateSyncRemotes :: DaemonStatusHandle -> Annex ()
+updateSyncRemotes dstatus = do
+ remotes <- calcSyncRemotes
liftIO $ modifyDaemonStatus_ dstatus $
- \s -> s { knownRemotes = remotes }
+ \s -> s { syncRemotes = remotes }
{- 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. -}
@@ -113,12 +112,12 @@ startDaemonStatus = do
status <- liftIO $
flip catchDefaultIO (readDaemonStatusFile file) =<< newDaemonStatus
transfers <- M.fromList <$> getTransfers
- remotes <- calcKnownRemotes
+ remotes <- calcSyncRemotes
liftIO $ atomically $ newTMVar status
{ scanComplete = False
, sanityCheckRunning = False
, currentTransfers = transfers
- , knownRemotes = remotes
+ , syncRemotes = remotes
}
{- Don't just dump out the structure, because it will change over time,
diff --git a/Assistant/Sync.hs b/Assistant/Sync.hs
index 59aa6205c..6c167e2ea 100644
--- a/Assistant/Sync.hs
+++ b/Assistant/Sync.hs
@@ -156,5 +156,5 @@ manualPull st currentbranch remotes = do
{- Start syncing a newly added remote, using a background thread. -}
syncNewRemote :: ThreadState -> DaemonStatusHandle -> ScanRemoteMap -> Remote -> IO ()
syncNewRemote st dstatus scanremotes remote = do
- runThreadState st $ updateKnownRemotes dstatus
+ runThreadState st $ updateSyncRemotes dstatus
void $ forkIO $ reconnectRemotes "SyncRemote" st dstatus scanremotes [remote]
diff --git a/Assistant/Threads/MountWatcher.hs b/Assistant/Threads/MountWatcher.hs
index 79fcce08c..462f5843c 100644
--- a/Assistant/Threads/MountWatcher.hs
+++ b/Assistant/Threads/MountWatcher.hs
@@ -174,7 +174,7 @@ remotesUnder st dstatus dir = runThreadState st $ do
let (waschanged, rs') = unzip pairs
when (any id waschanged) $ do
Annex.changeState $ \s -> s { Annex.remotes = rs' }
- updateKnownRemotes dstatus
+ updateSyncRemotes dstatus
return $ map snd $ filter fst pairs
where
checkremote repotop r = case Remote.localpath r of
diff --git a/Assistant/Threads/Pusher.hs b/Assistant/Threads/Pusher.hs
index dee563d74..4f3a2dd09 100644
--- a/Assistant/Threads/Pusher.hs
+++ b/Assistant/Threads/Pusher.hs
@@ -52,7 +52,7 @@ pushThread st dstatus commitchan pushmap = thread $ runEvery (Seconds 2) $ do
now <- getCurrentTime
if shouldPush now commits
then do
- remotes <- filter pushable . knownRemotes
+ remotes <- filter pushable . syncRemotes
<$> getDaemonStatus dstatus
unless (null remotes) $
void $ alertWhile dstatus (pushAlert remotes) $
diff --git a/Assistant/Threads/TransferScanner.hs b/Assistant/Threads/TransferScanner.hs
index 8f44f24d1..bc5837529 100644
--- a/Assistant/Threads/TransferScanner.hs
+++ b/Assistant/Threads/TransferScanner.hs
@@ -61,7 +61,7 @@ transferScannerThread st dstatus scanremotes transferqueue = thread $ do
- lost.
-}
startupScan = addScanRemotes scanremotes True
- =<< knownRemotes <$> getDaemonStatus dstatus
+ =<< syncRemotes <$> getDaemonStatus dstatus
{- This is a cheap scan for failed transfers involving a remote. -}
failedTransferScan :: ThreadState -> DaemonStatusHandle -> TransferQueue -> Remote -> IO ()
@@ -117,8 +117,8 @@ expensiveScan st dstatus transferqueue rs = unless onlyweb $ do
{- Queue transfers from any known remote. The known
- remotes may have changed since this scan began. -}
let use a = do
- knownrs <- liftIO $ knownRemotes <$> getDaemonStatus dstatus
- return $ catMaybes $ map (a key locs) knownrs
+ syncrs <- liftIO $ syncRemotes <$> getDaemonStatus dstatus
+ return $ catMaybes $ map (a key locs) syncrs
ifM (inAnnex key)
( filterM (wantSend (Just f) . Remote.uuid . fst)
=<< use (check Upload False)
diff --git a/Assistant/Threads/TransferWatcher.hs b/Assistant/Threads/TransferWatcher.hs
index 16d247860..95a594d5d 100644
--- a/Assistant/Threads/TransferWatcher.hs
+++ b/Assistant/Threads/TransferWatcher.hs
@@ -67,7 +67,7 @@ onAdd st dstatus _ file _ = case parseTransferFile file of
[ "transfer starting:"
, show t
]
- r <- headMaybe . filter (sameuuid t) . knownRemotes
+ r <- headMaybe . filter (sameuuid t) . syncRemotes
<$> getDaemonStatus dstatus
updateTransferInfo dstatus t info
{ transferRemote = r }
diff --git a/Assistant/TransferQueue.hs b/Assistant/TransferQueue.hs
index 9b081d32e..766d2b44a 100644
--- a/Assistant/TransferQueue.hs
+++ b/Assistant/TransferQueue.hs
@@ -71,7 +71,7 @@ queueTransfersMatching matching schedule q dstatus k f direction
where
go = do
rs <- sufficientremotes
- =<< knownRemotes <$> liftIO (getDaemonStatus dstatus)
+ =<< syncRemotes <$> liftIO (getDaemonStatus dstatus)
let matchingrs = filter (matching . Remote.uuid) rs
if null matchingrs
then defer
@@ -104,7 +104,7 @@ queueTransfersMatching matching schedule q dstatus k f direction
- any others in the list to try again later. -}
queueDeferredDownloads :: Schedule -> TransferQueue -> DaemonStatusHandle -> Annex ()
queueDeferredDownloads schedule q dstatus = do
- rs <- knownRemotes <$> liftIO (getDaemonStatus dstatus)
+ rs <- syncRemotes <$> liftIO (getDaemonStatus dstatus)
l <- liftIO $ atomically $ swapTVar (deferreddownloads q) []
left <- filterM (queue rs) l
unless (null left) $