Merge remote-tracking branch 'nomeata/master' into sync
This commit is contained in:
		
				commit
				
					
						dc83d721c2
					
				
			
		
					 2 changed files with 99 additions and 36 deletions
				
			
		
							
								
								
									
										120
									
								
								Command/Sync.hs
									
										
									
									
									
								
							
							
						
						
									
										120
									
								
								Command/Sync.hs
									
										
									
									
									
								
							| 
						 | 
					@ -1,3 +1,4 @@
 | 
				
			||||||
 | 
					{-# LANGUAGE BangPatterns #-}
 | 
				
			||||||
{- git-annex command
 | 
					{- git-annex command
 | 
				
			||||||
 -
 | 
					 -
 | 
				
			||||||
 - Copyright 2011 Joey Hess <joey@kitenet.net>
 | 
					 - Copyright 2011 Joey Hess <joey@kitenet.net>
 | 
				
			||||||
| 
						 | 
					@ -9,20 +10,49 @@ module Command.Sync where
 | 
				
			||||||
 | 
					
 | 
				
			||||||
import Common.Annex
 | 
					import Common.Annex
 | 
				
			||||||
import Command
 | 
					import Command
 | 
				
			||||||
 | 
					import qualified Remote
 | 
				
			||||||
import qualified Annex.Branch
 | 
					import qualified Annex.Branch
 | 
				
			||||||
import qualified Git.Command
 | 
					import qualified Git.Command
 | 
				
			||||||
import qualified Git.Config
 | 
					import qualified Git.Config
 | 
				
			||||||
import qualified Git.Ref
 | 
					import qualified Git.Ref
 | 
				
			||||||
import qualified Git
 | 
					import qualified Git
 | 
				
			||||||
 | 
					import qualified Command.Merge
 | 
				
			||||||
 | 
					
 | 
				
			||||||
import qualified Data.ByteString.Lazy.Char8 as L
 | 
					import qualified Data.ByteString.Lazy.Char8 as L
 | 
				
			||||||
 | 
					
 | 
				
			||||||
def :: [Command]
 | 
					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
 | 
					-- syncing involves several operations, any of which can independantly fail
 | 
				
			||||||
seek :: [CommandSeek]
 | 
					seek :: CommandSeek
 | 
				
			||||||
seek = map withNothing [commit, pull, push]
 | 
					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 :: CommandStart
 | 
				
			||||||
commit = do
 | 
					commit = do
 | 
				
			||||||
| 
						 | 
					@ -31,44 +61,72 @@ commit = do
 | 
				
			||||||
		showOutput
 | 
							showOutput
 | 
				
			||||||
		-- Commit will fail when the tree is clean, so ignore failure.
 | 
							-- Commit will fail when the tree is clean, so ignore failure.
 | 
				
			||||||
		_ <- inRepo $ Git.Command.runBool "commit"
 | 
							_ <- inRepo $ Git.Command.runBool "commit"
 | 
				
			||||||
			[Param "-a", Param "-m", Param "sync"]
 | 
								[Param "-a", Param "-m", Param "git-annex automatic sync"]
 | 
				
			||||||
		return True
 | 
							return True
 | 
				
			||||||
 | 
					
 | 
				
			||||||
pull :: CommandStart
 | 
					mergeLocal :: Git.Ref -> CommandStart
 | 
				
			||||||
pull = do
 | 
					mergeLocal branch =
 | 
				
			||||||
	remote <- defaultRemote
 | 
					    mergeFromIfExists $ Git.Ref $ "refs/heads/synced/" ++ Git.Ref.describe branch
 | 
				
			||||||
	showStart "pull" remote
 | 
					
 | 
				
			||||||
 | 
					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
 | 
						next $ next $ do
 | 
				
			||||||
		showOutput
 | 
							showOutput
 | 
				
			||||||
		checkRemote remote
 | 
							checkRemote remote
 | 
				
			||||||
		inRepo $ Git.Command.runBool "pull" [Param remote]
 | 
							inRepo $ Git.Command.runBool "fetch" [Param (Remote.name remote)]
 | 
				
			||||||
 | 
					
 | 
				
			||||||
push :: CommandStart
 | 
					mergeRemote :: Remote.Remote Annex -> Git.Ref -> CommandStart
 | 
				
			||||||
push = do
 | 
					mergeRemote remote branch =
 | 
				
			||||||
	remote <- defaultRemote
 | 
					    mergeFromIfExists $ Git.Ref $ "refs/remotes/" ++ Remote.name remote ++ "/synced/" ++ Git.Ref.describe branch
 | 
				
			||||||
	showStart "push" remote
 | 
					
 | 
				
			||||||
 | 
					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
 | 
					    next $ next $ do
 | 
				
			||||||
		Annex.Branch.update
 | 
					 | 
				
			||||||
            showOutput
 | 
					            showOutput
 | 
				
			||||||
		inRepo $ Git.Command.runBool "push" [Param remote, matchingbranches]
 | 
					            inRepo $ Git.Command.runBool "push" $
 | 
				
			||||||
	where
 | 
					                [ Param (Remote.name remote)
 | 
				
			||||||
		-- git push may be configured to not push matching
 | 
					                , Param (Git.Ref.describe Annex.Branch.name) ] ++ 
 | 
				
			||||||
		-- branches; this should ensure it always does.
 | 
					                [ Param refspec | ex ]
 | 
				
			||||||
		matchingbranches = Param ":"
 | 
					 | 
				
			||||||
 | 
					
 | 
				
			||||||
-- the remote defaults to origin when not configured
 | 
					currentBranch :: Annex Git.Ref
 | 
				
			||||||
defaultRemote :: Annex String
 | 
					currentBranch = Git.Ref . firstLine . L.unpack <$>
 | 
				
			||||||
defaultRemote = do
 | 
					 | 
				
			||||||
	branch <- currentBranch
 | 
					 | 
				
			||||||
	fromRepo $ Git.Config.get ("branch." ++ branch ++ ".remote") "origin"
 | 
					 | 
				
			||||||
 | 
					 | 
				
			||||||
currentBranch :: Annex String
 | 
					 | 
				
			||||||
currentBranch = Git.Ref.describe . Git.Ref . firstLine . L.unpack <$>
 | 
					 | 
				
			||||||
	inRepo (Git.Command.pipeRead [Param "symbolic-ref", Param "HEAD"])
 | 
						inRepo (Git.Command.pipeRead [Param "symbolic-ref", Param "HEAD"])
 | 
				
			||||||
 | 
					
 | 
				
			||||||
checkRemote :: String -> Annex ()
 | 
					checkRemote :: Remote.Remote Annex -> Annex ()
 | 
				
			||||||
checkRemote remote = do
 | 
					checkRemote remote = do
 | 
				
			||||||
	remoteurl <- fromRepo $
 | 
						remoteurl <- fromRepo $
 | 
				
			||||||
		Git.Config.get ("remote." ++ remote ++ ".url") ""
 | 
							Git.Config.get ("remote." ++ Remote.name remote ++ ".url") ""
 | 
				
			||||||
	when (null remoteurl) $ do
 | 
						when (null remoteurl) $
 | 
				
			||||||
		error $ "No url is configured for the remote: " ++ remote
 | 
							error $ "No url is configured for the remote: " ++ Remote.name remote
 | 
				
			||||||
| 
						 | 
					
 | 
				
			||||||
| 
						 | 
					@ -122,13 +122,18 @@ subdirectories).
 | 
				
			||||||
 | 
					
 | 
				
			||||||
* sync
 | 
					* sync
 | 
				
			||||||
 | 
					
 | 
				
			||||||
  Use this command when you want to synchronize the local repository
 | 
					  Use this command when you want to synchronize the local repository with
 | 
				
			||||||
  with its default remote (typically "origin"). The sync process involves
 | 
					  one or more other repositories. The sync process involves first committing
 | 
				
			||||||
  first committing all local changes, then pulling and merging any changes
 | 
					  all local changes, then fetching and merging the `synced/master` and the
 | 
				
			||||||
  from the remote, and finally pushing the repository's state to the remote.
 | 
					  `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,
 | 
					  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.
 | 
					  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.
 | 
					  Note that sync does not transfer any file contents from or to the remote.
 | 
				
			||||||
 | 
					
 | 
				
			||||||
* addurl [url ...]
 | 
					* addurl [url ...]
 | 
				
			||||||
| 
						 | 
					
 | 
				
			||||||
		Loading…
	
	Add table
		Add a link
		
	
		Reference in a new issue