2011-04-28 00:06:07 +00:00
|
|
|
|
{- A remote that is only accessible by rsync.
|
|
|
|
|
-
|
|
|
|
|
- Copyright 2011 Joey Hess <joey@kitenet.net>
|
|
|
|
|
-
|
|
|
|
|
- Licensed under the GNU GPL version 3 or higher.
|
|
|
|
|
-}
|
|
|
|
|
|
2013-05-10 21:29:59 +00:00
|
|
|
|
{-# LANGUAGE CPP #-}
|
|
|
|
|
|
2013-09-08 18:54:28 +00:00
|
|
|
|
module Remote.Rsync (
|
|
|
|
|
remote,
|
|
|
|
|
storeEncrypted,
|
|
|
|
|
retrieveEncrypted,
|
|
|
|
|
remove,
|
|
|
|
|
checkPresent,
|
|
|
|
|
withRsyncScratchDir,
|
|
|
|
|
genRsyncOpts,
|
|
|
|
|
RsyncOpts
|
|
|
|
|
) where
|
2011-04-28 00:06:07 +00:00
|
|
|
|
|
2012-06-20 17:13:40 +00:00
|
|
|
|
import qualified Data.ByteString.Lazy as L
|
2011-04-28 00:06:07 +00:00
|
|
|
|
import qualified Data.Map as M
|
2013-08-02 16:27:32 +00:00
|
|
|
|
#ifndef mingw32_HOST_OS
|
2012-07-18 19:30:26 +00:00
|
|
|
|
import System.Posix.Process (getProcessID)
|
2013-05-11 20:03:00 +00:00
|
|
|
|
#else
|
2013-12-11 04:15:10 +00:00
|
|
|
|
import System.Win32.Process.Current (getCurrentProcessId)
|
2013-05-10 21:29:59 +00:00
|
|
|
|
#endif
|
2011-10-04 02:24:57 +00:00
|
|
|
|
|
2011-10-05 20:02:51 +00:00
|
|
|
|
import Common.Annex
|
2011-06-02 01:56:04 +00:00
|
|
|
|
import Types.Remote
|
2011-06-30 17:16:57 +00:00
|
|
|
|
import qualified Git
|
2011-04-28 00:06:07 +00:00
|
|
|
|
import Config
|
2013-03-13 20:16:01 +00:00
|
|
|
|
import Config.Cost
|
2011-10-04 04:40:47 +00:00
|
|
|
|
import Annex.Content
|
2013-09-07 22:38:00 +00:00
|
|
|
|
import Annex.UUID
|
2013-04-13 22:10:49 +00:00
|
|
|
|
import Annex.Ssh
|
2011-08-17 00:49:54 +00:00
|
|
|
|
import Remote.Helper.Special
|
|
|
|
|
import Remote.Helper.Encryptable
|
2011-04-28 00:06:07 +00:00
|
|
|
|
import Crypto
|
2012-09-19 18:28:32 +00:00
|
|
|
|
import Utility.Rsync
|
2013-02-15 17:33:36 +00:00
|
|
|
|
import Utility.CopyFile
|
2013-03-28 21:03:04 +00:00
|
|
|
|
import Utility.Metered
|
2012-06-06 00:25:32 +00:00
|
|
|
|
import Annex.Perms
|
2011-04-28 00:06:07 +00:00
|
|
|
|
|
|
|
|
|
type RsyncUrl = String
|
|
|
|
|
|
2012-05-02 17:08:31 +00:00
|
|
|
|
data RsyncOpts = RsyncOpts
|
|
|
|
|
{ rsyncUrl :: RsyncUrl
|
|
|
|
|
, rsyncOptions :: [CommandParam]
|
|
|
|
|
, rsyncShellEscape :: Bool
|
2011-04-28 00:06:07 +00:00
|
|
|
|
}
|
|
|
|
|
|
2011-12-31 08:11:39 +00:00
|
|
|
|
remote :: RemoteType
|
2011-04-28 00:06:07 +00:00
|
|
|
|
remote = RemoteType {
|
|
|
|
|
typename = "rsync",
|
|
|
|
|
enumerate = findSpecialRemotes "rsyncurl",
|
|
|
|
|
generate = gen,
|
|
|
|
|
setup = rsyncSetup
|
|
|
|
|
}
|
|
|
|
|
|
2013-09-12 19:54:35 +00:00
|
|
|
|
gen :: Git.Repo -> UUID -> RemoteConfig -> RemoteGitConfig -> Annex (Maybe Remote)
|
2013-01-01 17:52:47 +00:00
|
|
|
|
gen r u c gc = do
|
|
|
|
|
cst <- remoteCost gc expensiveRemoteCost
|
2013-09-08 18:54:28 +00:00
|
|
|
|
(transport, url) <- rsyncTransport gc $
|
|
|
|
|
fromMaybe (error "missing rsyncurl") $ remoteAnnexRsyncUrl gc
|
|
|
|
|
let o = genRsyncOpts c gc transport url
|
|
|
|
|
let islocal = rsyncUrlIsPath $ rsyncUrl o
|
2013-09-12 19:54:35 +00:00
|
|
|
|
return $ Just $ encryptableRemote c
|
2013-09-01 18:12:00 +00:00
|
|
|
|
(storeEncrypted o $ getGpgEncParams (c,gc))
|
2011-04-28 00:06:07 +00:00
|
|
|
|
(retrieveEncrypted o)
|
2012-07-22 17:48:50 +00:00
|
|
|
|
Remote
|
|
|
|
|
{ uuid = u
|
|
|
|
|
, cost = cst
|
|
|
|
|
, name = Git.repoDescribe r
|
2012-12-13 04:45:27 +00:00
|
|
|
|
, storeKey = store o
|
2012-07-22 17:48:50 +00:00
|
|
|
|
, retrieveKeyFile = retrieve o
|
|
|
|
|
, retrieveKeyFileCheap = retrieveCheap o
|
|
|
|
|
, removeKey = remove o
|
|
|
|
|
, hasKey = checkPresent r o
|
|
|
|
|
, hasKeyCheap = False
|
|
|
|
|
, whereisKey = Nothing
|
2013-10-11 20:03:18 +00:00
|
|
|
|
, remoteFsck = Nothing
|
2013-10-27 19:38:59 +00:00
|
|
|
|
, repairRepo = Nothing
|
2013-11-02 20:37:28 +00:00
|
|
|
|
, config = c
|
2012-07-22 17:48:50 +00:00
|
|
|
|
, repo = r
|
2013-01-01 17:52:47 +00:00
|
|
|
|
, gitconfig = gc
|
2013-03-15 23:16:13 +00:00
|
|
|
|
, localpath = if islocal
|
2012-07-22 17:48:50 +00:00
|
|
|
|
then Just $ rsyncUrl o
|
|
|
|
|
else Nothing
|
2012-08-26 19:39:02 +00:00
|
|
|
|
, readonly = False
|
2013-09-26 03:19:01 +00:00
|
|
|
|
, globallyAvailable = not islocal
|
2012-07-22 17:48:50 +00:00
|
|
|
|
, remotetype = remote
|
|
|
|
|
}
|
2013-09-08 18:54:28 +00:00
|
|
|
|
|
|
|
|
|
genRsyncOpts :: RemoteConfig -> RemoteGitConfig -> [CommandParam] -> RsyncUrl -> RsyncOpts
|
|
|
|
|
genRsyncOpts c gc transport url = RsyncOpts url (transport ++ opts) escape
|
2012-11-11 04:51:07 +00:00
|
|
|
|
where
|
2013-01-01 17:52:47 +00:00
|
|
|
|
opts = map Param $ filter safe $ remoteAnnexRsyncOptions gc
|
|
|
|
|
escape = M.lookup "shellescape" c /= Just "no"
|
|
|
|
|
safe opt
|
2012-11-11 04:51:07 +00:00
|
|
|
|
-- Don't allow user to pass --delete to rsync;
|
|
|
|
|
-- that could cause it to delete other keys
|
|
|
|
|
-- in the same hash bucket as a key it sends.
|
2013-01-01 17:52:47 +00:00
|
|
|
|
| opt == "--delete" = False
|
|
|
|
|
| opt == "--delete-excluded" = False
|
2012-11-11 04:51:07 +00:00
|
|
|
|
| otherwise = True
|
2013-09-08 18:54:28 +00:00
|
|
|
|
|
|
|
|
|
rsyncTransport :: RemoteGitConfig -> RsyncUrl -> Annex ([CommandParam], RsyncUrl)
|
|
|
|
|
rsyncTransport gc rawurl
|
|
|
|
|
| rsyncUrlIsShell rawurl =
|
|
|
|
|
(\rsh -> return (rsyncShell rsh, resturl)) =<<
|
|
|
|
|
case fromNull ["ssh"] (remoteAnnexRsyncTransport gc) of
|
|
|
|
|
"ssh":sshopts -> do
|
|
|
|
|
let (port, sshopts') = sshReadPort sshopts
|
|
|
|
|
host = takeWhile (/=':') resturl
|
|
|
|
|
-- Connection caching
|
|
|
|
|
(Param "ssh":) <$> sshCachingOptions
|
|
|
|
|
(host, port)
|
|
|
|
|
(map Param $ loginopt ++ sshopts')
|
|
|
|
|
"rsh":rshopts -> return $ map Param $ "rsh" :
|
|
|
|
|
loginopt ++ rshopts
|
|
|
|
|
rsh -> error $ "Unknown Rsync transport: "
|
|
|
|
|
++ unwords rsh
|
|
|
|
|
| otherwise = return ([], rawurl)
|
|
|
|
|
where
|
2013-04-13 22:10:49 +00:00
|
|
|
|
(login,resturl) = case separate (=='@') rawurl of
|
2013-09-08 18:54:28 +00:00
|
|
|
|
(h, "") -> (Nothing, h)
|
|
|
|
|
(l, h) -> (Just l, h)
|
2013-04-13 22:10:49 +00:00
|
|
|
|
loginopt = maybe [] (\l -> ["-l",l]) login
|
2013-09-08 18:54:28 +00:00
|
|
|
|
fromNull as xs = if null xs then as else xs
|
2011-04-28 00:30:43 +00:00
|
|
|
|
|
2013-09-07 22:38:00 +00:00
|
|
|
|
rsyncSetup :: Maybe UUID -> RemoteConfig -> Annex (RemoteConfig, UUID)
|
|
|
|
|
rsyncSetup mu c = do
|
|
|
|
|
u <- maybe (liftIO genUUID) return mu
|
2011-04-28 00:06:07 +00:00
|
|
|
|
-- verify configuration is sane
|
2011-07-15 16:47:14 +00:00
|
|
|
|
let url = fromMaybe (error "Specify rsyncurl=") $
|
2011-05-15 06:49:43 +00:00
|
|
|
|
M.lookup "rsyncurl" c
|
2011-04-28 00:06:07 +00:00
|
|
|
|
c' <- encryptionSetup c
|
|
|
|
|
|
|
|
|
|
-- The rsyncurl is stored in git config, not only in this remote's
|
|
|
|
|
-- persistant state, so it can vary between hosts.
|
|
|
|
|
gitConfigSpecialRemote u c' "rsyncurl" url
|
2013-09-07 22:38:00 +00:00
|
|
|
|
return (c', u)
|
2011-04-28 00:06:07 +00:00
|
|
|
|
|
2011-11-18 16:53:48 +00:00
|
|
|
|
rsyncEscape :: RsyncOpts -> String -> String
|
|
|
|
|
rsyncEscape o s
|
2012-05-02 17:08:31 +00:00
|
|
|
|
| rsyncShellEscape o && rsyncUrlIsShell (rsyncUrl o) = shellEscape s
|
2011-11-18 16:53:48 +00:00
|
|
|
|
| otherwise = s
|
|
|
|
|
|
2011-12-02 19:50:27 +00:00
|
|
|
|
rsyncUrls :: RsyncOpts -> Key -> [String]
|
|
|
|
|
rsyncUrls o k = map use annexHashes
|
2012-11-11 04:51:07 +00:00
|
|
|
|
where
|
|
|
|
|
use h = rsyncUrl o </> h k </> rsyncEscape o (f </> f)
|
|
|
|
|
f = keyFile k
|
2011-04-28 00:06:07 +00:00
|
|
|
|
|
2012-09-21 18:50:14 +00:00
|
|
|
|
store :: RsyncOpts -> Key -> AssociatedFile -> MeterUpdate -> Annex Bool
|
2013-02-15 17:42:41 +00:00
|
|
|
|
store o k _f p = sendAnnex k (void $ remove o k) $ rsyncSend o p k False
|
2011-04-28 00:06:07 +00:00
|
|
|
|
|
2013-09-01 18:12:00 +00:00
|
|
|
|
storeEncrypted :: RsyncOpts -> [CommandParam] -> (Cipher, Key) -> Key -> MeterUpdate -> Annex Bool
|
2013-03-11 01:33:13 +00:00
|
|
|
|
storeEncrypted o gpgOpts (cipher, enck) k p = withTmp enck $ \tmp ->
|
2013-01-09 22:42:29 +00:00
|
|
|
|
sendAnnex k (void $ remove o enck) $ \src -> do
|
2013-03-11 01:33:13 +00:00
|
|
|
|
liftIO $ encrypt gpgOpts cipher (feedFile src) $
|
2013-01-06 18:29:01 +00:00
|
|
|
|
readBytes $ L.writeFile tmp
|
2013-02-15 17:42:41 +00:00
|
|
|
|
rsyncSend o p enck True tmp
|
2011-04-28 00:06:07 +00:00
|
|
|
|
|
2013-04-11 21:15:45 +00:00
|
|
|
|
retrieve :: RsyncOpts -> Key -> AssociatedFile -> FilePath -> MeterUpdate -> Annex Bool
|
|
|
|
|
retrieve o k _ f p = rsyncRetrieve o k f (Just p)
|
2012-01-20 17:23:11 +00:00
|
|
|
|
|
|
|
|
|
retrieveCheap :: RsyncOpts -> Key -> FilePath -> Annex Bool
|
2013-04-11 21:15:45 +00:00
|
|
|
|
retrieveCheap o k f = ifM (preseedTmp k f) ( rsyncRetrieve o k f Nothing , return False )
|
2011-04-28 00:06:07 +00:00
|
|
|
|
|
2013-04-11 21:15:45 +00:00
|
|
|
|
retrieveEncrypted :: RsyncOpts -> (Cipher, Key) -> Key -> FilePath -> MeterUpdate -> Annex Bool
|
|
|
|
|
retrieveEncrypted o (cipher, enck) _ f p = withTmp enck $ \tmp ->
|
|
|
|
|
ifM (rsyncRetrieve o enck tmp (Just p))
|
2012-03-16 00:39:25 +00:00
|
|
|
|
( liftIO $ catchBoolIO $ do
|
2012-11-18 19:27:44 +00:00
|
|
|
|
decrypt cipher (feedFile tmp) $
|
|
|
|
|
readBytes $ L.writeFile f
|
2011-04-28 00:06:07 +00:00
|
|
|
|
return True
|
2012-03-16 00:39:25 +00:00
|
|
|
|
, return False
|
|
|
|
|
)
|
2011-04-28 00:06:07 +00:00
|
|
|
|
|
|
|
|
|
remove :: RsyncOpts -> Key -> Annex Bool
|
2013-05-09 17:49:47 +00:00
|
|
|
|
remove o k = do
|
|
|
|
|
ps <- sendParams
|
|
|
|
|
withRsyncScratchDir $ \tmp -> liftIO $ do
|
|
|
|
|
{- Send an empty directory to rysnc to make it delete. -}
|
|
|
|
|
let dummy = tmp </> keyFile k
|
|
|
|
|
createDirectoryIfMissing True dummy
|
|
|
|
|
rsync $ rsyncOptions o ++ ps ++
|
|
|
|
|
map (\s -> Param $ "--include=" ++ s) includes ++
|
|
|
|
|
[ Param "--exclude=*" -- exclude everything else
|
|
|
|
|
, Params "--quiet --delete --recursive"
|
|
|
|
|
, partialParams
|
|
|
|
|
, Param $ addTrailingPathSeparator dummy
|
|
|
|
|
, Param $ rsyncUrl o
|
|
|
|
|
]
|
2012-11-11 04:51:07 +00:00
|
|
|
|
where
|
|
|
|
|
{- Specify include rules to match the directories where the
|
|
|
|
|
- content could be. Note that the parent directories have
|
|
|
|
|
- to also be explicitly included, due to how rsync
|
|
|
|
|
- traverses directories. -}
|
|
|
|
|
includes = concatMap use annexHashes
|
|
|
|
|
use h = let dir = h k in
|
|
|
|
|
[ parentDir dir
|
|
|
|
|
, dir
|
|
|
|
|
-- match content directory and anything in it
|
|
|
|
|
, dir </> keyFile k </> "***"
|
|
|
|
|
]
|
2011-04-28 00:06:07 +00:00
|
|
|
|
|
2011-11-09 22:33:15 +00:00
|
|
|
|
checkPresent :: Git.Repo -> RsyncOpts -> Key -> Annex (Either String Bool)
|
2011-04-28 00:06:07 +00:00
|
|
|
|
checkPresent r o k = do
|
2011-07-19 18:07:23 +00:00
|
|
|
|
showAction $ "checking " ++ Git.repoDescribe r
|
2011-12-02 19:50:27 +00:00
|
|
|
|
-- note: Does not currently differentiate between rsync failing
|
2011-04-28 00:06:07 +00:00
|
|
|
|
-- to connect, and the file not being present.
|
2011-12-02 19:50:27 +00:00
|
|
|
|
Right <$> check
|
2012-11-11 04:51:07 +00:00
|
|
|
|
where
|
2012-12-13 04:45:27 +00:00
|
|
|
|
check = untilTrue (rsyncUrls o k) $ \u ->
|
2012-11-11 04:51:07 +00:00
|
|
|
|
liftIO $ catchBoolIO $ do
|
|
|
|
|
withQuietOutput createProcessSuccess $
|
|
|
|
|
proc "rsync" $ toCommand $
|
|
|
|
|
rsyncOptions o ++ [Param u]
|
|
|
|
|
return True
|
2011-04-28 00:06:07 +00:00
|
|
|
|
|
|
|
|
|
{- Rsync params to enable resumes of sending files safely,
|
|
|
|
|
- ensure that files are only moved into place once complete
|
|
|
|
|
-}
|
|
|
|
|
partialParams :: CommandParam
|
2012-07-10 18:40:31 +00:00
|
|
|
|
partialParams = Params "--partial --partial-dir=.rsync-partial"
|
2011-04-28 00:06:07 +00:00
|
|
|
|
|
2013-05-09 17:49:47 +00:00
|
|
|
|
{- When sending files from crippled filesystems, the permissions can be all
|
|
|
|
|
- messed up, and it's better to use the default permissions on the
|
|
|
|
|
- destination. -}
|
|
|
|
|
sendParams :: Annex [CommandParam]
|
|
|
|
|
sendParams = ifM crippledFileSystem
|
|
|
|
|
( return [rsyncUseDestinationPermissions]
|
|
|
|
|
, return []
|
|
|
|
|
)
|
|
|
|
|
|
2011-04-28 00:06:07 +00:00
|
|
|
|
{- Runs an action in an empty scratch directory that can be used to build
|
|
|
|
|
- up trees for rsync. -}
|
2013-09-24 21:25:47 +00:00
|
|
|
|
withRsyncScratchDir :: (FilePath -> Annex a) -> Annex a
|
2011-04-28 00:06:07 +00:00
|
|
|
|
withRsyncScratchDir a = do
|
2013-08-02 16:27:32 +00:00
|
|
|
|
#ifndef mingw32_HOST_OS
|
2013-05-11 20:03:00 +00:00
|
|
|
|
v <- liftIO getProcessID
|
|
|
|
|
#else
|
2013-12-11 04:15:10 +00:00
|
|
|
|
v <- liftIO getCurrentProcessId
|
2013-05-11 20:03:00 +00:00
|
|
|
|
#endif
|
2011-11-08 19:34:10 +00:00
|
|
|
|
t <- fromRepo gitAnnexTmpDir
|
2012-06-06 00:25:32 +00:00
|
|
|
|
createAnnexDirectory t
|
2013-05-11 20:03:00 +00:00
|
|
|
|
let tmp = t </> "rsynctmp" </> show v
|
2011-04-28 00:06:07 +00:00
|
|
|
|
nuke tmp
|
2011-07-15 16:47:14 +00:00
|
|
|
|
liftIO $ createDirectoryIfMissing True tmp
|
2012-01-03 04:29:27 +00:00
|
|
|
|
nuke tmp `after` a tmp
|
2012-11-11 04:51:07 +00:00
|
|
|
|
where
|
|
|
|
|
nuke d = liftIO $ whenM (doesDirectoryExist d) $
|
|
|
|
|
removeDirectoryRecursive d
|
2011-04-28 00:06:07 +00:00
|
|
|
|
|
2013-04-11 21:15:45 +00:00
|
|
|
|
rsyncRetrieve :: RsyncOpts -> Key -> FilePath -> Maybe MeterUpdate -> Annex Bool
|
|
|
|
|
rsyncRetrieve o k dest callback =
|
2013-12-02 16:53:39 +00:00
|
|
|
|
showResumable $ untilTrue (rsyncUrls o k) $ \u -> rsyncRemote o callback
|
2013-04-11 21:15:45 +00:00
|
|
|
|
-- use inplace when retrieving to support resuming
|
|
|
|
|
[ Param "--inplace"
|
|
|
|
|
, Param u
|
2013-05-14 17:24:15 +00:00
|
|
|
|
, File dest
|
2013-04-11 21:15:45 +00:00
|
|
|
|
]
|
|
|
|
|
|
2013-12-02 16:53:39 +00:00
|
|
|
|
showResumable :: Annex Bool -> Annex Bool
|
|
|
|
|
showResumable a = ifM a
|
|
|
|
|
( return True
|
|
|
|
|
, do
|
|
|
|
|
showLongNote "rsync failed -- run git annex again to resume file transfer"
|
|
|
|
|
return False
|
|
|
|
|
)
|
|
|
|
|
|
2013-09-26 03:19:01 +00:00
|
|
|
|
rsyncRemote :: RsyncOpts -> Maybe MeterUpdate -> [CommandParam] -> Annex Bool
|
2012-09-20 17:50:21 +00:00
|
|
|
|
rsyncRemote o callback params = do
|
2011-07-19 18:07:23 +00:00
|
|
|
|
showOutput -- make way for progress bar
|
2013-12-02 16:53:39 +00:00
|
|
|
|
liftIO $ (maybe rsync rsyncProgress callback) ps
|
2012-11-11 04:51:07 +00:00
|
|
|
|
where
|
|
|
|
|
defaultParams = [Params "--progress"]
|
|
|
|
|
ps = rsyncOptions o ++ defaultParams ++ params
|
2011-04-28 00:06:07 +00:00
|
|
|
|
|
|
|
|
|
{- To send a single key is slightly tricky; need to build up a temporary
|
2012-12-13 04:45:27 +00:00
|
|
|
|
- directory structure to pass to rsync so it can create the hash
|
2013-02-15 17:33:36 +00:00
|
|
|
|
- directories.
|
|
|
|
|
-
|
|
|
|
|
- This would not be necessary if the hash directory structure used locally
|
|
|
|
|
- was always the same as that used on the rsync remote. So if that's ever
|
2013-06-10 17:10:30 +00:00
|
|
|
|
- unified, this gets nicer.
|
2013-02-15 17:33:36 +00:00
|
|
|
|
- (When we have the right hash directory structure, we can just
|
|
|
|
|
- pass --include=X --include=X/Y --include=X/Y/file --exclude=*)
|
|
|
|
|
-}
|
2013-02-15 17:42:41 +00:00
|
|
|
|
rsyncSend :: RsyncOpts -> MeterUpdate -> Key -> Bool -> FilePath -> Annex Bool
|
|
|
|
|
rsyncSend o callback k canrename src = withRsyncScratchDir $ \tmp -> do
|
2011-12-15 22:11:42 +00:00
|
|
|
|
let dest = tmp </> Prelude.head (keyPaths k)
|
2011-07-15 16:47:14 +00:00
|
|
|
|
liftIO $ createDirectoryIfMissing True $ parentDir dest
|
2013-06-10 17:10:30 +00:00
|
|
|
|
ok <- liftIO $ if canrename
|
2013-02-15 17:48:25 +00:00
|
|
|
|
then do
|
2013-06-10 17:10:30 +00:00
|
|
|
|
renameFile src dest
|
2013-02-15 17:48:25 +00:00
|
|
|
|
return True
|
2013-06-10 17:10:30 +00:00
|
|
|
|
else createLinkOrCopy src dest
|
2013-05-09 17:49:47 +00:00
|
|
|
|
ps <- sendParams
|
2013-02-15 17:33:36 +00:00
|
|
|
|
if ok
|
2013-12-02 16:53:39 +00:00
|
|
|
|
then showResumable $ rsyncRemote o (Just callback) $ ps ++
|
2013-02-15 17:33:36 +00:00
|
|
|
|
[ Param "--recursive"
|
|
|
|
|
, partialParams
|
|
|
|
|
-- tmp/ to send contents of tmp dir
|
2013-05-14 17:24:15 +00:00
|
|
|
|
, File $ addTrailingPathSeparator tmp
|
2013-02-15 17:33:36 +00:00
|
|
|
|
, Param $ rsyncUrl o
|
|
|
|
|
]
|
|
|
|
|
else return False
|