git-annex/Command/Sync.hs

170 lines
4.9 KiB
Haskell
Raw Normal View History

{- git-annex command
-
- Copyright 2011 Joey Hess <joey@kitenet.net>
2011-12-30 20:24:30 +00:00
- Copyright 2011 Joachim Breitner <mail@joachim-breitner.de>
-
- Licensed under the GNU GPL version 3 or higher.
-}
2011-12-30 20:24:30 +00:00
{-# LANGUAGE BangPatterns #-}
module Command.Sync where
import Common.Annex
import Command
import qualified Remote
import qualified Annex
import qualified Annex.Branch
2011-12-14 19:56:11 +00:00
import qualified Git.Command
import qualified Git.Branch
import qualified Git.Ref
import qualified Git
import qualified Types.Remote
import qualified Remote.Git
import qualified Data.Map as M
def :: [Command]
def = [command "sync" (paramOptional (paramRepeating paramRemote))
2011-12-31 06:18:16 +00:00
[seek] "synchronize local repository with remotes"]
2011-12-31 06:18:16 +00:00
-- syncing involves several operations, any of which can independently fail
seek :: CommandSeek
seek rs = do
2012-01-02 15:57:02 +00:00
!branch <- fromMaybe nobranch <$> inRepo Git.Branch.current
remotes <- syncRemotes rs
2012-02-16 04:41:30 +00:00
return $ concat
2011-12-30 21:54:09 +00:00
[ [ commit ]
, [ mergeLocal branch ]
, [ pullRemote remote branch | remote <- remotes ]
2011-12-30 21:54:09 +00:00
, [ mergeAnnex ]
, [ pushLocal branch ]
, [ pushRemote remote branch | remote <- remotes ]
2011-12-30 21:54:09 +00:00
]
2011-12-31 07:38:58 +00:00
where
nobranch = error "no branch is checked out"
2011-12-30 20:24:30 +00:00
syncBranch :: Git.Ref -> Git.Ref
syncBranch = Git.Ref.under "refs/heads/synced/"
2011-12-31 08:11:39 +00:00
remoteBranch :: Remote -> Git.Ref -> Git.Ref
2011-12-31 07:01:18 +00:00
remoteBranch remote = Git.Ref.under $ "refs/remotes/" ++ Remote.name remote
2011-12-31 08:11:39 +00:00
syncRemotes :: [String] -> Annex [Remote]
syncRemotes rs = ifM (Annex.getState Annex.fast) ( nub <$> pickfast , wanted )
where
pickfast = (++) <$> listed <*> (good =<< fastest <$> available)
wanted
| null rs = good =<< concat . byspeed <$> available
| otherwise = listed
listed = catMaybes <$> mapM (Remote.byName . Just) rs
available = filter nonspecial <$> Remote.enabledRemoteList
good = filterM $ Remote.Git.repoAvail . Types.Remote.repo
nonspecial r = Types.Remote.remotetype r == Remote.Git.remote
fastest = fromMaybe [] . headMaybe . byspeed
byspeed = map snd . sort . M.toList . costmap
costmap = M.fromListWith (++) . map costpair
costpair r = (Types.Remote.cost r, [r])
2011-12-10 16:21:22 +00:00
commit :: CommandStart
commit = do
showStart "commit" ""
next $ next $ do
showOutput
Annex.Branch.commit "update"
2011-12-10 16:21:22 +00:00
-- Commit will fail when the tree is clean, so ignore failure.
2011-12-14 19:56:11 +00:00
_ <- inRepo $ Git.Command.runBool "commit"
[Param "-a", Param "-m", Param "git-annex automatic sync"]
2011-12-10 16:21:22 +00:00
return True
mergeLocal :: Git.Ref -> CommandStart
mergeLocal branch = go =<< needmerge
where
syncbranch = syncBranch branch
needmerge = do
2011-12-30 22:52:24 +00:00
unlessM (inRepo $ Git.Ref.exists syncbranch) $
updateBranch syncbranch
inRepo $ Git.Branch.changed branch syncbranch
go False = stop
go True = do
2011-12-30 22:52:24 +00:00
showStart "merge" $ Git.Ref.describe syncbranch
next $ next $ mergeFrom syncbranch
pushLocal :: Git.Ref -> CommandStart
pushLocal branch = do
updateBranch $ syncBranch branch
stop
2011-12-30 22:52:24 +00:00
updateBranch :: Git.Ref -> Annex ()
updateBranch syncbranch =
unlessM go $ error $ "failed to update " ++ show syncbranch
where
go = inRepo $ Git.Command.runBool "branch"
2011-12-30 21:38:38 +00:00
[ Param "-f"
, Param $ show $ Git.Ref.base syncbranch
]
2011-12-31 08:11:39 +00:00
pullRemote :: Remote -> Git.Ref -> CommandStart
pullRemote remote branch = do
showStart "pull" (Remote.name remote)
2011-12-30 21:38:38 +00:00
next $ do
showOutput
stopUnless fetch $
next $ mergeRemote remote branch
where
fetch = inRepo $ Git.Command.runBool "fetch"
[Param $ Remote.name remote]
{- The remote probably has both a master and a synced/master branch.
- Which to merge from? Well, the master has whatever latest changes
- were committed, while the synced/master may have changes that some
- other remote synced to this remote. So, merge them both. -}
2011-12-31 08:11:39 +00:00
mergeRemote :: Remote -> Git.Ref -> CommandCleanup
mergeRemote remote branch = all id <$> (mapM merge =<< tomerge)
where
2011-12-31 07:01:18 +00:00
merge = mergeFrom . remoteBranch remote
tomerge = filterM (changed remote) [branch, syncBranch branch]
2011-12-31 08:11:39 +00:00
pushRemote :: Remote -> Git.Ref -> CommandStart
pushRemote remote branch = go =<< needpush
where
2011-12-31 07:01:18 +00:00
needpush = anyM (newer remote) [syncbranch, Annex.Branch.name]
go False = stop
go True = do
showStart "push" (Remote.name remote)
next $ next $ do
showOutput
2012-02-16 04:41:30 +00:00
inRepo $ Git.Command.runBool "push"
[ Param (Remote.name remote)
2012-02-16 04:41:30 +00:00
, Param (show Annex.Branch.name)
, Param refspec
]
refspec = show (Git.Ref.base branch) ++ ":" ++ show (Git.Ref.base syncbranch)
syncbranch = syncBranch branch
mergeAnnex :: CommandStart
2011-12-30 21:38:38 +00:00
mergeAnnex = do
Annex.Branch.forceUpdate
2011-12-30 21:38:38 +00:00
stop
2011-12-31 06:18:16 +00:00
mergeFrom :: Git.Ref -> CommandCleanup
mergeFrom branch = do
showOutput
inRepo $ Git.Command.runBool "merge" [Param $ show branch]
2011-12-31 07:01:18 +00:00
2011-12-31 08:11:39 +00:00
changed :: Remote -> Git.Ref -> Annex Bool
2011-12-31 07:01:18 +00:00
changed remote b = do
let r = remoteBranch remote b
ifM (inRepo $ Git.Ref.exists r)
( inRepo $ Git.Branch.changed b r
, return False
)
2011-12-31 07:01:18 +00:00
2011-12-31 08:11:39 +00:00
newer :: Remote -> Git.Ref -> Annex Bool
2011-12-31 07:01:18 +00:00
newer remote b = do
let r = remoteBranch remote b
ifM (inRepo $ Git.Ref.exists r)
( inRepo $ Git.Branch.changed r b
, return True
)