summaryrefslogtreecommitdiff
path: root/Command
diff options
context:
space:
mode:
authorGravatar Joey Hess <joey@kitenet.net>2011-12-30 21:17:36 -0400
committerGravatar Joey Hess <joey@kitenet.net>2011-12-30 21:17:36 -0400
commite7d3e546c298add0a39ec1a979d9b1574b9b9b76 (patch)
tree92f2f0ffa32a57d57e317847fb63cae37d0bd591 /Command
parentdd8451f0f8092450049472793c325bcaa35f0fb7 (diff)
sync --fast: Selects some of the remotes with the lowest annex.cost and syncs those, in addition to any specified at the command line.
Diffstat (limited to 'Command')
-rw-r--r--Command/Sync.hs23
1 files changed, 19 insertions, 4 deletions
diff --git a/Command/Sync.hs b/Command/Sync.hs
index a3450278c..81b77e5cc 100644
--- a/Command/Sync.hs
+++ b/Command/Sync.hs
@@ -13,14 +13,17 @@ module Command.Sync where
import Common.Annex
import Command
import qualified Remote
+import qualified Annex
import qualified Annex.Branch
import qualified Git.Command
import qualified Git.Branch
import qualified Git.Config
import qualified Git.Ref
import qualified Git
+import qualified Types.Remote
import qualified Data.ByteString.Lazy.Char8 as L
+import qualified Data.Map as M
def :: [Command]
def = [command "sync" (paramOptional (paramRepeating paramRemote))
@@ -28,9 +31,9 @@ def = [command "sync" (paramOptional (paramRepeating paramRemote))
-- syncing involves several operations, any of which can independantly fail
seek :: CommandSeek
-seek args = do
+seek rs = do
!branch <- currentBranch
- remotes <- syncRemotes args
+ remotes <- syncRemotes rs
return $ concat $
[ [ commit ]
, [ mergeLocal branch ]
@@ -44,11 +47,23 @@ syncBranch :: Git.Ref -> Git.Ref
syncBranch = Git.Ref.under "refs/heads/synced/"
syncRemotes :: [String] -> Annex [Remote.Remote Annex]
-syncRemotes [] = filterM hasurl =<< Remote.remoteList
+syncRemotes rs = do
+ fast <- Annex.getState Annex.fast
+ if fast
+ then nub <$> pickfast
+ else wanted
where
+ wanted
+ | null rs = filterM hasurl =<< Remote.remoteList
+ | otherwise = listed
+ listed = mapM Remote.byName rs
hasurl r = not . null <$> geturl r
geturl r = fromRepo $ Git.Config.get ("remote." ++ Remote.name r ++ ".url") ""
-syncRemotes rs = mapM Remote.byName rs
+ pickfast = (++) <$> listed <*> (fastest <$> Remote.remoteList)
+ fastest = fromMaybe [] . headMaybe .
+ map snd . sort . M.toList . costmap
+ costmap = M.fromListWith (++) . map costpair
+ costpair r = (Types.Remote.cost r, [r])
commit :: CommandStart
commit = do