summaryrefslogtreecommitdiff
diff options
context:
space:
mode:
authorGravatar Joey Hess <joey@kitenet.net>2011-12-30 15:02:37 -0400
committerGravatar Joey Hess <joey@kitenet.net>2011-12-30 15:02:37 -0400
commitdc83d721c274829e37dd25f64d04415f50e0031e (patch)
tree79855fa08e53910dc759d71126f6d934e13dd5ba
parent5287d1dc3f293b6eb7f6759fe9f25be1ad85fbae (diff)
parentb6e7b40be4721595bafd3b1ea9c439cead07b7ff (diff)
Merge remote-tracking branch 'nomeata/master' into sync
-rw-r--r--Command/Sync.hs126
-rw-r--r--doc/git-annex.mdwn13
2 files changed, 101 insertions, 38 deletions
diff --git a/Command/Sync.hs b/Command/Sync.hs
index 36c4eeef0..cc8818889 100644
--- a/Command/Sync.hs
+++ b/Command/Sync.hs
@@ -1,3 +1,4 @@
+{-# LANGUAGE BangPatterns #-}
{- git-annex command
-
- Copyright 2011 Joey Hess <joey@kitenet.net>
@@ -9,20 +10,49 @@ module Command.Sync where
import Common.Annex
import Command
+import qualified Remote
import qualified Annex.Branch
import qualified Git.Command
import qualified Git.Config
import qualified Git.Ref
import qualified Git
+import qualified Command.Merge
import qualified Data.ByteString.Lazy.Char8 as L
def :: [Command]
-def = [command "sync" paramPaths seek "synchronize local repository with remote"]
+def = [command "sync" (paramOptional (paramRepeating paramRemote))
+ [seek] "synchronize local repository with remote repositories"]
-- syncing involves several operations, any of which can independantly fail
-seek :: [CommandSeek]
-seek = map withNothing [commit, pull, push]
+seek :: CommandSeek
+seek args = do
+ !branch <- currentBranch
+ remotes <- if null args
+ then defaultSyncRemotes branch
+ else mapM Remote.byName args
+ showStart "syncing" $ "branch " ++ Git.Ref.describe branch ++ " with remote repositories " ++ intercalate "," (map Remote.name remotes)
+ showOutput
+ return $
+ [ commit
+ , mergeLocal branch
+ ] ++
+ [ fetch remote | remote <- remotes ] ++
+ [ mergeRemote remote branch | remote <- remotes ] ++
+ [ Command.Merge.start ] ++
+ [ pushLocal branch ] ++
+ [ pushRemote remote branch | remote <- remotes ]
+
+defaultSyncRemotes :: Git.Ref -> Annex [Remote.Remote Annex]
+defaultSyncRemotes branch = mapM Remote.byName =<< process . L.unpack <$> inRepo showref
+ where
+ syncbranch = Git.Ref $ "refs/heads/synced/" ++ Git.Ref.describe branch
+ showref = Git.Command.pipeRead
+ [Param "show-ref", Param (Git.Ref.describe syncbranch)]
+ process = map getRemoteName . filter isRemote . map getBranchName . lines
+ isRemote r = "refs/remotes/" `isPrefixOf` r
+ getBranchName = snd . separate (== ' ')
+ getRemoteName = fst . separate (== '/') . snd . separate (== '/') . snd . separate (== '/')
commit :: CommandStart
commit = do
@@ -31,44 +61,72 @@ commit = do
showOutput
-- Commit will fail when the tree is clean, so ignore failure.
_ <- inRepo $ Git.Command.runBool "commit"
- [Param "-a", Param "-m", Param "sync"]
+ [Param "-a", Param "-m", Param "git-annex automatic sync"]
return True
-pull :: CommandStart
-pull = do
- remote <- defaultRemote
- showStart "pull" remote
+mergeLocal :: Git.Ref -> CommandStart
+mergeLocal branch =
+ mergeFromIfExists $ Git.Ref $ "refs/heads/synced/" ++ Git.Ref.describe branch
+
+pushLocal :: Git.Ref -> CommandStart
+pushLocal branch = do
+ let syncBranch = Git.Ref $ "refs/heads/synced/" ++ Git.Ref.describe branch
+ ex <- inRepo $ Git.Ref.exists syncBranch
+ if ex then do
+ showStart "updateing" $
+ Git.Ref.describe syncBranch ++
+ " to the state of " ++ Git.Ref.describe branch ++ "..."
+ next $ next $
+ inRepo $ Git.Command.runBool "branch" [Param "-f", Param (Git.Ref.describe syncBranch)]
+ else
+ return Nothing
+
+mergeFromIfExists :: Git.Ref -> CommandStart
+mergeFromIfExists fromBranch = do
+ ex <- inRepo $ Git.Ref.exists fromBranch
+ if ex then do
+ showStart "merging" $ Git.Ref.describe fromBranch ++ "..."
+ next $ next $
+ inRepo $ Git.Command.runBool "merge" [Param (show fromBranch)]
+ else do
+ showNote $ Git.Ref.describe fromBranch ++ " does not exist, not merging."
+ showOutput
+ return Nothing
+
+
+fetch :: Remote.Remote Annex -> CommandStart
+fetch remote = do
+ showStart "fetching from" (Remote.name remote)
next $ next $ do
showOutput
checkRemote remote
- inRepo $ Git.Command.runBool "pull" [Param remote]
+ inRepo $ Git.Command.runBool "fetch" [Param (Remote.name remote)]
-push :: CommandStart
-push = do
- remote <- defaultRemote
- showStart "push" remote
- next $ next $ do
- Annex.Branch.update
- showOutput
- inRepo $ Git.Command.runBool "push" [Param remote, matchingbranches]
- where
- -- git push may be configured to not push matching
- -- branches; this should ensure it always does.
- matchingbranches = Param ":"
-
--- the remote defaults to origin when not configured
-defaultRemote :: Annex String
-defaultRemote = do
- branch <- currentBranch
- fromRepo $ Git.Config.get ("branch." ++ branch ++ ".remote") "origin"
-
-currentBranch :: Annex String
-currentBranch = Git.Ref.describe . Git.Ref . firstLine . L.unpack <$>
+mergeRemote :: Remote.Remote Annex -> Git.Ref -> CommandStart
+mergeRemote remote branch =
+ mergeFromIfExists $ Git.Ref $ "refs/remotes/" ++ Remote.name remote ++ "/synced/" ++ Git.Ref.describe branch
+
+pushRemote :: Remote.Remote Annex -> Git.Ref -> CommandStart
+pushRemote remote branch = do
+ showStart "pushing to" (Remote.name remote)
+ let syncbranch = Git.Ref $ "refs/heads/synced/" ++ Git.Ref.describe branch
+ let syncbranchRemote = Git.Ref $ "refs/remotes/" ++ Remote.name remote ++ "/" ++ Git.Ref.describe syncbranch
+ let refspec = Git.Ref.describe branch ++ ":" ++ Git.Ref.describe syncbranch
+ ex <- inRepo $ Git.Ref.exists syncbranchRemote
+ next $ next $ do
+ showOutput
+ inRepo $ Git.Command.runBool "push" $
+ [ Param (Remote.name remote)
+ , Param (Git.Ref.describe Annex.Branch.name) ] ++
+ [ Param refspec | ex ]
+
+currentBranch :: Annex Git.Ref
+currentBranch = Git.Ref . firstLine . L.unpack <$>
inRepo (Git.Command.pipeRead [Param "symbolic-ref", Param "HEAD"])
-checkRemote :: String -> Annex ()
+checkRemote :: Remote.Remote Annex -> Annex ()
checkRemote remote = do
remoteurl <- fromRepo $
- Git.Config.get ("remote." ++ remote ++ ".url") ""
- when (null remoteurl) $ do
- error $ "No url is configured for the remote: " ++ remote
+ Git.Config.get ("remote." ++ Remote.name remote ++ ".url") ""
+ when (null remoteurl) $
+ error $ "No url is configured for the remote: " ++ Remote.name remote
diff --git a/doc/git-annex.mdwn b/doc/git-annex.mdwn
index 8096005ce..320453f18 100644
--- a/doc/git-annex.mdwn
+++ b/doc/git-annex.mdwn
@@ -122,13 +122,18 @@ subdirectories).
* sync
- Use this command when you want to synchronize the local repository
- with its default remote (typically "origin"). The sync process involves
- first committing all local changes, then pulling and merging any changes
- from the remote, and finally pushing the repository's state to the remote.
+ Use this command when you want to synchronize the local repository with
+ one or more other repositories. The sync process involves first committing
+ all local changes, then fetching and merging the `synced/master` and the
+ `git-annex` branch from the remote repositories and finally pushing the
+ changes back to these remote branches.
You can use standard git commands to do each of those steps by hand,
or if you don't want to worry about the details, you can use sync.
+ By default, `git annex sync` will sync all remote repositories that have a
+ `synced/master` branch. If you want to include/exclude a repository from
+ this list, just create or delete this branch.
+
Note that sync does not transfer any file contents from or to the remote.
* addurl [url ...]