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.
|
|
|
|
|
-}
|
|
|
|
|
|
|
|
|
|
module Remote.Rsync (remote) where
|
|
|
|
|
|
|
|
|
|
import qualified Data.ByteString.Lazy.Char8 as L
|
|
|
|
|
import qualified Data.Map as M
|
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
|
2011-10-04 04:40:47 +00:00
|
|
|
|
import Annex.Content
|
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
|
2011-07-06 00:24:10 +00:00
|
|
|
|
import Utility.RsyncFile
|
2011-04-28 00:06:07 +00:00
|
|
|
|
|
|
|
|
|
type RsyncUrl = String
|
|
|
|
|
|
|
|
|
|
data RsyncOpts = RsyncOpts {
|
|
|
|
|
rsyncUrl :: RsyncUrl,
|
|
|
|
|
rsyncOptions :: [CommandParam]
|
|
|
|
|
}
|
|
|
|
|
|
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
|
|
|
|
|
}
|
|
|
|
|
|
2011-12-31 08:11:39 +00:00
|
|
|
|
gen :: Git.Repo -> UUID -> Maybe RemoteConfig -> Annex Remote
|
2011-04-28 00:06:07 +00:00
|
|
|
|
gen r u c = do
|
2011-04-28 00:30:43 +00:00
|
|
|
|
o <- genRsyncOpts r
|
2011-04-28 00:06:07 +00:00
|
|
|
|
cst <- remoteCost r expensiveRemoteCost
|
|
|
|
|
return $ encryptableRemote c
|
|
|
|
|
(storeEncrypted o)
|
|
|
|
|
(retrieveEncrypted o)
|
|
|
|
|
Remote {
|
|
|
|
|
uuid = u,
|
|
|
|
|
cost = cst,
|
|
|
|
|
name = Git.repoDescribe r,
|
|
|
|
|
storeKey = store o,
|
|
|
|
|
retrieveKeyFile = retrieve o,
|
2012-01-20 17:23:11 +00:00
|
|
|
|
retrieveKeyFileCheap = retrieveCheap o,
|
2011-04-28 00:06:07 +00:00
|
|
|
|
removeKey = remove o,
|
|
|
|
|
hasKey = checkPresent r o,
|
2011-04-28 18:39:51 +00:00
|
|
|
|
hasKeyCheap = False,
|
2011-09-19 00:11:39 +00:00
|
|
|
|
config = Nothing,
|
2011-12-31 07:27:37 +00:00
|
|
|
|
repo = r,
|
|
|
|
|
remotetype = remote
|
2011-04-28 00:06:07 +00:00
|
|
|
|
}
|
|
|
|
|
|
2011-04-28 00:30:43 +00:00
|
|
|
|
genRsyncOpts :: Git.Repo -> Annex RsyncOpts
|
|
|
|
|
genRsyncOpts r = do
|
|
|
|
|
url <- getConfig r "rsyncurl" (error "missing rsyncurl")
|
|
|
|
|
opts <- getConfig r "rsync-options" ""
|
|
|
|
|
return $ RsyncOpts url $ map Param $ filter safe $ words opts
|
|
|
|
|
where
|
|
|
|
|
safe o
|
|
|
|
|
-- 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.
|
|
|
|
|
| o == "--delete" = False
|
|
|
|
|
| o == "--delete-excluded" = False
|
|
|
|
|
| otherwise = True
|
|
|
|
|
|
2011-04-28 00:06:07 +00:00
|
|
|
|
rsyncSetup :: UUID -> RemoteConfig -> Annex RemoteConfig
|
|
|
|
|
rsyncSetup u c = do
|
|
|
|
|
-- 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
|
|
|
|
|
return c'
|
|
|
|
|
|
2011-11-18 16:53:48 +00:00
|
|
|
|
rsyncEscape :: RsyncOpts -> String -> String
|
|
|
|
|
rsyncEscape o s
|
|
|
|
|
| rsyncUrlIsShell (rsyncUrl o) = shellEscape s
|
|
|
|
|
| otherwise = s
|
|
|
|
|
|
2011-12-02 19:50:27 +00:00
|
|
|
|
rsyncUrls :: RsyncOpts -> Key -> [String]
|
|
|
|
|
rsyncUrls o k = map use annexHashes
|
|
|
|
|
where
|
|
|
|
|
use h = rsyncUrl o </> h k </> rsyncEscape o (f </> f)
|
2011-04-28 00:06:07 +00:00
|
|
|
|
f = keyFile k
|
|
|
|
|
|
|
|
|
|
store :: RsyncOpts -> Key -> Annex Bool
|
2011-11-29 02:43:51 +00:00
|
|
|
|
store o k = rsyncSend o k =<< inRepo (gitAnnexLocation k)
|
2011-04-28 00:06:07 +00:00
|
|
|
|
|
|
|
|
|
storeEncrypted :: RsyncOpts -> (Cipher, Key) -> Key -> Annex Bool
|
|
|
|
|
storeEncrypted o (cipher, enck) k = withTmp enck $ \tmp -> do
|
2011-11-29 02:43:51 +00:00
|
|
|
|
src <- inRepo $ gitAnnexLocation k
|
2011-11-08 19:34:10 +00:00
|
|
|
|
liftIO $ withEncryptedContent cipher (L.readFile src) $ L.writeFile tmp
|
2011-04-28 00:06:07 +00:00
|
|
|
|
rsyncSend o enck tmp
|
|
|
|
|
|
2012-01-20 17:23:11 +00:00
|
|
|
|
retrieve :: RsyncOpts -> Key -> FilePath -> Annex Bool
|
|
|
|
|
retrieve o k f = untilTrue (rsyncUrls o k) $ \u -> rsyncRemote o
|
|
|
|
|
-- use inplace when retrieving to support resuming
|
|
|
|
|
[ Param "--inplace"
|
|
|
|
|
, Param u
|
|
|
|
|
, Param f
|
|
|
|
|
]
|
|
|
|
|
|
|
|
|
|
retrieveCheap :: RsyncOpts -> Key -> FilePath -> Annex Bool
|
|
|
|
|
retrieveCheap o k f = do
|
|
|
|
|
ok <- preseedTmp k f
|
|
|
|
|
if ok
|
|
|
|
|
then retrieve o k f
|
|
|
|
|
else return False
|
2011-04-28 00:06:07 +00:00
|
|
|
|
|
|
|
|
|
retrieveEncrypted :: RsyncOpts -> (Cipher, Key) -> FilePath -> Annex Bool
|
|
|
|
|
retrieveEncrypted o (cipher, enck) f = withTmp enck $ \tmp -> do
|
2012-01-20 17:23:11 +00:00
|
|
|
|
res <- retrieve o enck tmp
|
2011-04-28 00:06:07 +00:00
|
|
|
|
if res
|
2011-11-11 00:24:24 +00:00
|
|
|
|
then liftIO $ catchBoolIO $ do
|
2011-04-28 00:06:07 +00:00
|
|
|
|
withDecryptedContent cipher (L.readFile tmp) $ L.writeFile f
|
|
|
|
|
return True
|
|
|
|
|
else return res
|
|
|
|
|
|
|
|
|
|
remove :: RsyncOpts -> Key -> Annex Bool
|
2011-12-21 20:56:48 +00:00
|
|
|
|
remove o k = 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 ++
|
|
|
|
|
map (\s -> Param $ "--include=" ++ s) includes ++
|
|
|
|
|
[ Param "--exclude=*" -- exclude everything else
|
|
|
|
|
, Params "--quiet --delete --recursive"
|
|
|
|
|
, partialParams
|
|
|
|
|
, Param $ addTrailingPathSeparator dummy
|
|
|
|
|
, Param $ rsyncUrl o
|
|
|
|
|
]
|
|
|
|
|
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-12-02 20:10:52 +00:00
|
|
|
|
]
|
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
|
2011-04-28 00:06:07 +00:00
|
|
|
|
where
|
2011-12-02 20:10:52 +00:00
|
|
|
|
check = untilTrue (rsyncUrls o k) $ \u ->
|
2011-12-02 19:50:27 +00:00
|
|
|
|
liftIO $ boolSystem "sh" [Param "-c", Param (cmd u)]
|
|
|
|
|
cmd u = "rsync --quiet " ++ shellEscape u ++ " 2>/dev/null"
|
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
|
|
|
|
|
partialParams = Params "--no-inplace --partial --partial-dir=.rsync-partial"
|
|
|
|
|
|
|
|
|
|
{- Runs an action in an empty scratch directory that can be used to build
|
|
|
|
|
- up trees for rsync. -}
|
|
|
|
|
withRsyncScratchDir :: (FilePath -> Annex Bool) -> Annex Bool
|
|
|
|
|
withRsyncScratchDir a = do
|
2011-07-15 16:47:14 +00:00
|
|
|
|
pid <- liftIO getProcessID
|
2011-11-08 19:34:10 +00:00
|
|
|
|
t <- fromRepo gitAnnexTmpDir
|
|
|
|
|
let tmp = t </> "rsynctmp" </> show pid
|
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
|
2011-04-28 00:06:07 +00:00
|
|
|
|
where
|
2012-01-24 19:28:13 +00:00
|
|
|
|
nuke d = liftIO $ whenM (doesDirectoryExist d) $
|
|
|
|
|
removeDirectoryRecursive d
|
2011-04-28 00:06:07 +00:00
|
|
|
|
|
|
|
|
|
rsyncRemote :: RsyncOpts -> [CommandParam] -> Annex Bool
|
|
|
|
|
rsyncRemote o params = do
|
2011-07-19 18:07:23 +00:00
|
|
|
|
showOutput -- make way for progress bar
|
2011-04-28 00:06:07 +00:00
|
|
|
|
res <- liftIO $ rsync $ rsyncOptions o ++ defaultParams ++ params
|
|
|
|
|
if res
|
|
|
|
|
then return res
|
|
|
|
|
else do
|
|
|
|
|
showLongNote "rsync failed -- run git annex again to resume file transfer"
|
|
|
|
|
return res
|
|
|
|
|
where
|
|
|
|
|
defaultParams = [Params "--progress"]
|
|
|
|
|
|
|
|
|
|
{- To send a single key is slightly tricky; need to build up a temporary
|
|
|
|
|
directory structure to pass to rsync so it can create the hash
|
|
|
|
|
directories. -}
|
|
|
|
|
rsyncSend :: RsyncOpts -> Key -> FilePath -> Annex Bool
|
|
|
|
|
rsyncSend o k 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
|
2011-04-28 00:06:07 +00:00
|
|
|
|
liftIO $ createLink src dest
|
2011-07-15 16:47:14 +00:00
|
|
|
|
rsyncRemote o
|
2011-04-28 00:06:07 +00:00
|
|
|
|
[ Param "--recursive"
|
|
|
|
|
, partialParams
|
|
|
|
|
-- tmp/ to send contents of tmp dir
|
|
|
|
|
, Param $ addTrailingPathSeparator tmp
|
|
|
|
|
, Param $ rsyncUrl o
|
|
|
|
|
]
|