The former can be useful to make remotes that don't get fully synced with local changes, which comes up in a lot of situations. The latter was mostly added for symmetry, but could be useful (though less likely to be). Implementing `remote.<name>.annex-pull` was a bit tricky, as there's no one place where git-annex pulls/fetches from remotes. I audited all instances of "fetch" and "pull". A few cases were left not checking this config: * Git.Repair can try to pull missing refs from a remote, and if the local repo is corrupted, that seems a reasonable thing to do even though the config would normally prevent it. * Assistant.WebApp.Gpg and Remote.Gcrypt and Remote.Git do fetches as part of the setup process of a remote. The config would probably not be set then, and having the setup fail seems worse than honoring it if it is already set. I have not prevented all the code that does a "merge" from merging branches from remotes with remote.<name>.annex-pull=false. That could perhaps be done, but it would need a way to map from branch name to remote name, and the way refspecs work makes that hard to get really correct. So if the user fetches manually, the git-annex branch will get merged, for example. Anther way of looking at/justifying this is that the setting is called "annex-pull", not "annex-merge". This commit was supported by the NSF-funded DataLad project.
		
			
				
	
	
		
			71 lines
		
	
	
	
		
			2 KiB
			
		
	
	
	
		
			Haskell
		
	
	
	
	
	
			
		
		
	
	
			71 lines
		
	
	
	
		
			2 KiB
			
		
	
	
	
		
			Haskell
		
	
	
	
	
	
{- git-remote-daemon utilities
 | 
						|
 -
 | 
						|
 - Copyright 2014-2016 Joey Hess <id@joeyh.name>
 | 
						|
 -
 | 
						|
 - Licensed under the GNU GPL version 3 or higher.
 | 
						|
 -}
 | 
						|
 | 
						|
module RemoteDaemon.Common
 | 
						|
	( liftAnnex
 | 
						|
	, inLocalRepo
 | 
						|
	, checkShouldFetch
 | 
						|
	, ConnectionStatus(..)
 | 
						|
	, robustConnection
 | 
						|
	) where
 | 
						|
 | 
						|
import qualified Annex
 | 
						|
import Annex.Common
 | 
						|
import RemoteDaemon.Types
 | 
						|
import qualified Git
 | 
						|
import Annex.CatFile
 | 
						|
import Utility.ThreadScheduler
 | 
						|
 | 
						|
import Control.Concurrent
 | 
						|
 | 
						|
-- Runs an Annex action. Long-running actions should be avoided,
 | 
						|
-- since only one liftAnnex can be running at a time, across all
 | 
						|
-- transports.
 | 
						|
liftAnnex :: TransportHandle -> Annex a -> IO a
 | 
						|
liftAnnex (TransportHandle _ annexstate) a = do
 | 
						|
	st <- takeMVar annexstate
 | 
						|
	(r, st') <- Annex.run st a
 | 
						|
	putMVar annexstate st'
 | 
						|
	return r
 | 
						|
 | 
						|
inLocalRepo :: TransportHandle -> (Git.Repo -> IO a) -> IO a
 | 
						|
inLocalRepo (TransportHandle (LocalRepo g) _) a = a g
 | 
						|
 | 
						|
-- Check if some shas should be fetched from the remote,
 | 
						|
-- and presumably later merged.
 | 
						|
checkShouldFetch :: RemoteGitConfig -> TransportHandle -> [Git.Sha] -> IO Bool
 | 
						|
checkShouldFetch gc transporthandle shas
 | 
						|
	| remoteAnnexPull gc = checkNewShas transporthandle shas
 | 
						|
	| otherwise = return False
 | 
						|
 | 
						|
-- Check if any of the shas are actally new in the local git repo,
 | 
						|
-- to avoid unnecessary fetching.
 | 
						|
checkNewShas :: TransportHandle -> [Git.Sha] -> IO Bool
 | 
						|
checkNewShas transporthandle = check
 | 
						|
  where
 | 
						|
	check [] = return True
 | 
						|
	check (r:rs) = maybe (check rs) (const $ return False)
 | 
						|
		=<< liftAnnex transporthandle (catObjectDetails r)
 | 
						|
 | 
						|
data ConnectionStatus = ConnectionStopping | ConnectionClosed
 | 
						|
 | 
						|
{- Make connection robust, retrying on error, with exponential backoff. -}
 | 
						|
robustConnection :: Int -> IO ConnectionStatus -> IO ()
 | 
						|
robustConnection backoff a = 
 | 
						|
	caught =<< a `catchNonAsync` (const $ return ConnectionClosed)
 | 
						|
  where
 | 
						|
	caught ConnectionStopping = return ()
 | 
						|
	caught ConnectionClosed = do
 | 
						|
		threadDelaySeconds (Seconds backoff)
 | 
						|
		robustConnection increasedbackoff a
 | 
						|
 | 
						|
	increasedbackoff
 | 
						|
		| b2 > maxbackoff = maxbackoff
 | 
						|
		| otherwise = b2
 | 
						|
	  where
 | 
						|
		b2 = backoff * 2
 | 
						|
		maxbackoff = 3600 -- one hour
 |