Renaming is not supported; it might be possible to use --fuzzy to get rsync to notice the file is being renamed, but that is a bit ..fuzzy. On the other hand, interrupted transfers of an exported file are resumed, since rsync is great at that. Had to adjust the exporttree docs, which said interrupted transfers would restart. Note that remove no longer makes the empty directory dummy, instead sending the top-level empty directory. This works just as well and I noticed the dummy was unncessary when refactoring it into removeGeneric. Verified that behavior of remove is not changed, and git annex testremote does pass. This commit was sponsored by Brock Spratlen on Patreon.
		
			
				
	
	
		
			51 lines
		
	
	
	
		
			1.1 KiB
			
		
	
	
	
		
			Haskell
		
	
	
	
	
	
			
		
		
	
	
			51 lines
		
	
	
	
		
			1.1 KiB
			
		
	
	
	
		
			Haskell
		
	
	
	
	
	
{- Rsync urls.
 | 
						|
 -
 | 
						|
 - Copyright 2014-2018 Joey Hess <id@joeyh.name>
 | 
						|
 -
 | 
						|
 - Licensed under the GNU GPL version 3 or higher.
 | 
						|
 -}
 | 
						|
 | 
						|
{-# LANGUAGE CPP #-}
 | 
						|
 | 
						|
module Remote.Rsync.RsyncUrl where
 | 
						|
 | 
						|
import Types
 | 
						|
import Annex.Locations
 | 
						|
import Utility.Rsync
 | 
						|
import Utility.SafeCommand
 | 
						|
 | 
						|
import Data.Default
 | 
						|
import System.FilePath.Posix
 | 
						|
#ifdef mingw32_HOST_OS
 | 
						|
import Utility.Split
 | 
						|
#endif
 | 
						|
import Annex.DirHashes
 | 
						|
 | 
						|
type RsyncUrl = String
 | 
						|
 | 
						|
data RsyncOpts = RsyncOpts
 | 
						|
	{ rsyncUrl :: RsyncUrl
 | 
						|
	, rsyncOptions :: [CommandParam]
 | 
						|
	, rsyncUploadOptions :: [CommandParam]
 | 
						|
	, rsyncDownloadOptions :: [CommandParam]
 | 
						|
	, rsyncShellEscape :: Bool
 | 
						|
}
 | 
						|
 | 
						|
rsyncEscape :: RsyncOpts -> RsyncUrl -> RsyncUrl
 | 
						|
rsyncEscape o u
 | 
						|
	| rsyncShellEscape o && rsyncUrlIsShell (rsyncUrl o) = shellEscape u
 | 
						|
	| otherwise = u
 | 
						|
 | 
						|
mkRsyncUrl :: RsyncOpts -> FilePath -> RsyncUrl
 | 
						|
mkRsyncUrl o f = rsyncUrl o </> rsyncEscape o f
 | 
						|
 | 
						|
rsyncUrls :: RsyncOpts -> Key -> [RsyncUrl]
 | 
						|
rsyncUrls o k = map use dirHashes
 | 
						|
  where
 | 
						|
	use h = rsyncUrl o </> hash h </> rsyncEscape o (f </> f)
 | 
						|
	f = keyFile k
 | 
						|
#ifndef mingw32_HOST_OS
 | 
						|
	hash h = h def k
 | 
						|
#else
 | 
						|
	hash h = replace "\\" "/" (h def k)
 | 
						|
#endif
 |