2011-03-27 19:56:43 +00:00
|
|
|
{- Standard git remotes.
|
|
|
|
-
|
2012-02-25 22:02:49 +00:00
|
|
|
- Copyright 2011-2012 Joey Hess <joey@kitenet.net>
|
2011-03-27 19:56:43 +00:00
|
|
|
-
|
|
|
|
- Licensed under the GNU GPL version 3 or higher.
|
|
|
|
-}
|
|
|
|
|
2013-05-11 20:03:00 +00:00
|
|
|
{-# LANGUAGE CPP #-}
|
|
|
|
|
2012-07-22 17:48:50 +00:00
|
|
|
module Remote.Git (
|
|
|
|
remote,
|
|
|
|
configRead,
|
|
|
|
repoAvail,
|
|
|
|
) where
|
2011-03-27 19:56:43 +00:00
|
|
|
|
2011-03-29 17:49:54 +00:00
|
|
|
import qualified Data.Map as M
|
2012-03-17 04:22:05 +00:00
|
|
|
import Control.Exception.Extensible
|
2011-03-27 19:56:43 +00:00
|
|
|
|
2011-10-05 20:02:51 +00:00
|
|
|
import Common.Annex
|
2012-09-19 18:28:32 +00:00
|
|
|
import Utility.Rsync
|
2012-01-10 19:29:10 +00:00
|
|
|
import Remote.Helper.Ssh
|
2013-05-14 17:53:29 +00:00
|
|
|
import Annex.Ssh
|
2011-06-02 01:56:04 +00:00
|
|
|
import Types.Remote
|
2013-01-01 17:52:47 +00:00
|
|
|
import Types.GitConfig
|
2011-06-30 17:16:57 +00:00
|
|
|
import qualified Git
|
2011-12-13 19:05:07 +00:00
|
|
|
import qualified Git.Config
|
|
|
|
import qualified Git.Construct
|
2012-10-12 17:45:14 +00:00
|
|
|
import qualified Git.Command
|
2013-09-05 20:02:39 +00:00
|
|
|
import qualified Git.GCrypt
|
2011-03-27 19:56:43 +00:00
|
|
|
import qualified Annex
|
2012-01-28 19:54:42 +00:00
|
|
|
import Logs.Presence
|
2012-07-01 20:59:54 +00:00
|
|
|
import Logs.Transfer
|
2011-10-15 21:47:03 +00:00
|
|
|
import Annex.UUID
|
2012-09-22 03:25:06 +00:00
|
|
|
import Annex.Exception
|
2011-10-04 04:40:47 +00:00
|
|
|
import qualified Annex.Content
|
2011-12-12 21:38:46 +00:00
|
|
|
import qualified Annex.BranchState
|
2012-02-25 22:02:49 +00:00
|
|
|
import qualified Annex.Branch
|
2011-08-20 20:11:42 +00:00
|
|
|
import qualified Utility.Url as Url
|
2013-05-12 23:19:28 +00:00
|
|
|
import Utility.Tmp
|
2011-03-28 01:43:25 +00:00
|
|
|
import Config
|
2013-03-13 20:16:01 +00:00
|
|
|
import Config.Cost
|
2011-08-17 18:36:20 +00:00
|
|
|
import Init
|
2012-02-10 23:17:41 +00:00
|
|
|
import Types.Key
|
2012-07-02 14:57:51 +00:00
|
|
|
import qualified Fields
|
2012-12-12 23:20:38 +00:00
|
|
|
import Logs.Location
|
2013-03-28 21:03:04 +00:00
|
|
|
import Utility.Metered
|
2013-08-04 17:12:18 +00:00
|
|
|
#ifndef mingw32_HOST_OS
|
|
|
|
import Utility.CopyFile
|
|
|
|
#endif
|
2011-03-27 19:56:43 +00:00
|
|
|
|
2012-09-20 17:35:53 +00:00
|
|
|
import Control.Concurrent
|
2012-10-05 21:03:58 +00:00
|
|
|
import Control.Concurrent.MSampleVar
|
2012-09-22 03:25:06 +00:00
|
|
|
import System.Process (std_in, std_err)
|
2012-09-20 17:35:53 +00:00
|
|
|
|
2011-12-31 08:11:39 +00:00
|
|
|
remote :: RemoteType
|
2011-03-29 18:55:59 +00:00
|
|
|
remote = RemoteType {
|
|
|
|
typename = "git",
|
2011-03-29 21:57:20 +00:00
|
|
|
enumerate = list,
|
|
|
|
generate = gen,
|
2011-03-29 18:55:59 +00:00
|
|
|
setup = error "not supported"
|
|
|
|
}
|
2011-03-29 03:51:07 +00:00
|
|
|
|
2011-03-29 21:57:20 +00:00
|
|
|
list :: Annex [Git.Repo]
|
|
|
|
list = do
|
2011-12-14 19:30:14 +00:00
|
|
|
c <- fromRepo Git.config
|
2012-06-26 21:15:17 +00:00
|
|
|
rs <- mapM (tweakurl c) =<< fromRepo Git.remotes
|
2012-07-22 17:48:50 +00:00
|
|
|
mapM configRead rs
|
2012-10-29 01:27:15 +00:00
|
|
|
where
|
|
|
|
annexurl n = "remote." ++ n ++ ".annexurl"
|
|
|
|
tweakurl c r = do
|
|
|
|
let n = fromJust $ Git.remoteName r
|
|
|
|
case M.lookup (annexurl n) c of
|
|
|
|
Nothing -> return r
|
|
|
|
Just url -> inRepo $ \g ->
|
|
|
|
Git.Construct.remoteNamed n $
|
|
|
|
Git.Construct.fromRemoteLocation url g
|
2012-07-22 17:48:50 +00:00
|
|
|
|
|
|
|
{- It's assumed to be cheap to read the config of non-URL remotes, so this is
|
|
|
|
- done each time git-annex is run in a way that uses remotes.
|
|
|
|
-
|
|
|
|
- Conversely, the config of an URL remote is only read when there is no
|
|
|
|
- cached UUID value. -}
|
|
|
|
configRead :: Git.Repo -> Annex Git.Repo
|
|
|
|
configRead r = do
|
2013-01-01 17:52:47 +00:00
|
|
|
g <- fromRepo id
|
|
|
|
let c = extractRemoteGitConfig g (Git.repoDescribe r)
|
2012-07-22 17:48:50 +00:00
|
|
|
u <- getRepoUUID r
|
2013-01-01 17:52:47 +00:00
|
|
|
case (repoCheap r, remoteAnnexIgnore c, u) of
|
|
|
|
(_, True, _) -> return r
|
2012-07-22 17:48:50 +00:00
|
|
|
(True, _, _) -> tryGitConfigRead r
|
|
|
|
(False, _, NoUUID) -> tryGitConfigRead r
|
|
|
|
_ -> return r
|
2011-03-28 01:43:25 +00:00
|
|
|
|
2012-06-26 21:15:17 +00:00
|
|
|
repoCheap :: Git.Repo -> Bool
|
|
|
|
repoCheap = not . Git.repoIsUrl
|
2011-03-30 19:15:46 +00:00
|
|
|
|
2013-01-01 17:52:47 +00:00
|
|
|
gen :: Git.Repo -> UUID -> RemoteConfig -> RemoteGitConfig -> Annex Remote
|
|
|
|
gen r u _ gc = go <$> remoteCost gc defcst
|
2012-10-29 01:27:15 +00:00
|
|
|
where
|
|
|
|
defcst = if repoCheap r then cheapRemoteCost else expensiveRemoteCost
|
2013-01-01 17:52:47 +00:00
|
|
|
go cst = new
|
|
|
|
where
|
|
|
|
new = Remote
|
|
|
|
{ uuid = u
|
|
|
|
, cost = cst
|
|
|
|
, name = Git.repoDescribe r
|
|
|
|
, storeKey = copyToRemote new
|
|
|
|
, retrieveKeyFile = copyFromRemote new
|
|
|
|
, retrieveKeyFileCheap = copyFromRemoteCheap new
|
|
|
|
, removeKey = dropKey new
|
|
|
|
, hasKey = inAnnex r
|
|
|
|
, hasKeyCheap = repoCheap r
|
|
|
|
, whereisKey = Nothing
|
|
|
|
, config = M.empty
|
|
|
|
, localpath = if Git.repoIsLocal r || Git.repoIsLocalUnknown r
|
|
|
|
then Just $ Git.repoPath r
|
|
|
|
else Nothing
|
|
|
|
, repo = r
|
|
|
|
, gitconfig = gc
|
2013-04-04 19:46:33 +00:00
|
|
|
{ remoteGitConfig = Just $ extractGitConfig r }
|
2013-01-01 17:52:47 +00:00
|
|
|
, readonly = Git.repoIsHttp r
|
2013-03-15 23:16:13 +00:00
|
|
|
, globallyAvailable = not $ Git.repoIsLocal r || Git.repoIsLocalUnknown r
|
2013-01-01 17:52:47 +00:00
|
|
|
, remotetype = remote
|
|
|
|
}
|
2011-03-27 19:56:43 +00:00
|
|
|
|
2012-06-27 02:27:30 +00:00
|
|
|
{- Checks relatively inexpensively if a repository is available for use. -}
|
|
|
|
repoAvail :: Git.Repo -> Annex Bool
|
|
|
|
repoAvail r
|
|
|
|
| Git.repoIsHttp r = return True
|
|
|
|
| Git.repoIsUrl r = return True
|
|
|
|
| Git.repoIsLocalUnknown r = return False
|
|
|
|
| otherwise = liftIO $ catchBoolIO $ onLocal r $ return True
|
|
|
|
|
|
|
|
{- Avoids performing an action on a local repository that's not usable.
|
|
|
|
- Does not check that the repository is still available on disk. -}
|
|
|
|
guardUsable :: Git.Repo -> a -> Annex a -> Annex a
|
|
|
|
guardUsable r onerr a
|
|
|
|
| Git.repoIsLocalUnknown r = return onerr
|
|
|
|
| otherwise = a
|
|
|
|
|
2011-03-28 01:43:25 +00:00
|
|
|
{- Tries to read the config for a specified remote, updates state, and
|
|
|
|
- returns the updated repo. -}
|
|
|
|
tryGitConfigRead :: Git.Repo -> Annex Git.Repo
|
2011-03-27 19:56:43 +00:00
|
|
|
tryGitConfigRead r
|
2013-04-24 00:06:02 +00:00
|
|
|
| haveconfig r = return r -- already read
|
2012-10-12 17:45:14 +00:00
|
|
|
| Git.repoIsSsh r = store $ do
|
2013-05-25 05:47:19 +00:00
|
|
|
v <- onRemote r (pipedconfig, Left undefined) "configlist" [] []
|
2013-04-24 00:06:02 +00:00
|
|
|
case v of
|
|
|
|
Right r'
|
|
|
|
| haveconfig r' -> return r'
|
|
|
|
| otherwise -> configlist_failed
|
|
|
|
Left _ -> configlist_failed
|
2012-04-22 05:13:09 +00:00
|
|
|
| Git.repoIsHttp r = do
|
|
|
|
headers <- getHttpHeaders
|
2013-05-25 05:47:19 +00:00
|
|
|
store $ geturlconfig headers
|
2013-09-05 20:02:39 +00:00
|
|
|
| Git.GCrypt.isEncrypted r = do
|
|
|
|
g <- gitRepo
|
|
|
|
case Git.GCrypt.remoteRepoId g r of
|
|
|
|
Nothing -> return r
|
|
|
|
Just v -> store $ liftIO $ setUUID r $
|
|
|
|
genUUIDInNameSpace gCryptNameSpace v
|
2011-03-28 01:43:25 +00:00
|
|
|
| Git.repoIsUrl r = return r
|
2011-12-12 06:24:37 +00:00
|
|
|
| otherwise = store $ safely $ onLocal r $ do
|
|
|
|
ensureInitialized
|
|
|
|
Annex.getState Annex.repo
|
2012-10-29 01:27:15 +00:00
|
|
|
where
|
2013-04-24 00:06:02 +00:00
|
|
|
haveconfig = not . M.null . Git.config
|
|
|
|
|
2012-10-29 01:27:15 +00:00
|
|
|
-- Reading config can fail due to IO error or
|
|
|
|
-- for other reasons; catch all possible exceptions.
|
|
|
|
safely a = either (const $ return r) return
|
|
|
|
=<< liftIO (try a :: IO (Either SomeException Git.Repo))
|
2011-08-17 00:48:11 +00:00
|
|
|
|
2013-05-25 05:47:19 +00:00
|
|
|
pipedconfig cmd params = try run :: IO (Either SomeException Git.Repo)
|
|
|
|
where
|
|
|
|
run = withHandle StdoutHandle createProcessSuccess p $ \h -> do
|
2013-03-05 03:27:18 +00:00
|
|
|
fileEncoding h
|
|
|
|
val <- hGetContentsStrict h
|
|
|
|
r' <- Git.Config.store val r
|
|
|
|
when (getUncachedUUID r' == NoUUID && not (null val)) $ do
|
|
|
|
warningIO $ "Failed to get annex.uuid configuration of repository " ++ Git.repoDescribe r
|
|
|
|
warningIO $ "Instead, got: " ++ show val
|
|
|
|
warningIO $ "This is unexpected; please check the network transport!"
|
|
|
|
return r'
|
2012-10-29 01:27:15 +00:00
|
|
|
p = proc cmd $ toCommand params
|
2011-08-17 00:48:11 +00:00
|
|
|
|
2012-10-29 01:27:15 +00:00
|
|
|
geturlconfig headers = do
|
2013-05-25 05:47:19 +00:00
|
|
|
v <- liftIO $ withTmpFile "git-annex.tmp" $ \tmpfile h -> do
|
2012-10-29 01:27:15 +00:00
|
|
|
hClose h
|
2013-05-25 05:47:19 +00:00
|
|
|
ifM (Url.downloadQuiet (Git.repoLocation r ++ "/config") headers [] tmpfile)
|
|
|
|
( pipedconfig "git" [Param "config", Param "--null", Param "--list", Param "--file", File tmpfile]
|
|
|
|
, return $ Left undefined
|
|
|
|
)
|
|
|
|
case v of
|
|
|
|
Left _ -> do
|
|
|
|
set_ignore "not usable by git-annex"
|
|
|
|
return r
|
|
|
|
Right r' -> return r'
|
2011-08-17 00:48:11 +00:00
|
|
|
|
2012-10-29 01:27:15 +00:00
|
|
|
store = observe $ \r' -> do
|
|
|
|
g <- gitRepo
|
|
|
|
let l = Git.remotes g
|
|
|
|
let g' = g { Git.remotes = exchange l r' }
|
|
|
|
Annex.changeState $ \s -> s { Annex.repo = g' }
|
2011-08-17 00:48:11 +00:00
|
|
|
|
2012-10-29 01:27:15 +00:00
|
|
|
exchange [] _ = []
|
|
|
|
exchange (old:ls) new
|
|
|
|
| Git.remoteName old == Git.remoteName new =
|
|
|
|
new : exchange ls new
|
|
|
|
| otherwise =
|
|
|
|
old : exchange ls new
|
2011-03-27 19:56:43 +00:00
|
|
|
|
2013-04-24 00:06:02 +00:00
|
|
|
{- Is this remote just not available, or does
|
|
|
|
- it not have git-annex-shell?
|
|
|
|
- Find out by trying to fetch from the remote. -}
|
|
|
|
configlist_failed = case Git.remoteName r of
|
|
|
|
Nothing -> return r
|
|
|
|
Just n -> do
|
2013-05-25 05:47:19 +00:00
|
|
|
whenM (inRepo $ Git.Command.runBool [Param "fetch", Param "--quiet", Param n]) $
|
|
|
|
set_ignore $ "does not have git-annex installed"
|
2013-04-24 00:06:02 +00:00
|
|
|
return r
|
2013-05-25 05:47:19 +00:00
|
|
|
|
|
|
|
set_ignore msg = case Git.remoteName r of
|
|
|
|
Nothing -> noop
|
|
|
|
Just n -> do
|
|
|
|
let k = "remote." ++ n ++ ".annex-ignore"
|
|
|
|
warning $ "Remote " ++ n ++ " " ++ msg ++ "; setting " ++ k
|
|
|
|
inRepo $ Git.Command.run [Param "config", Param k, Param "true"]
|
2013-04-24 00:06:02 +00:00
|
|
|
|
2011-03-27 19:56:43 +00:00
|
|
|
{- Checks if a given remote has the content for a key inAnnex.
|
2011-11-09 22:33:15 +00:00
|
|
|
- If the remote cannot be accessed, or if it cannot determine
|
|
|
|
- whether it has the content, returns a Left error message.
|
2011-03-27 19:56:43 +00:00
|
|
|
-}
|
2011-11-09 22:33:15 +00:00
|
|
|
inAnnex :: Git.Repo -> Key -> Annex (Either String Bool)
|
2011-08-17 01:04:23 +00:00
|
|
|
inAnnex r key
|
2012-04-22 05:13:09 +00:00
|
|
|
| Git.repoIsHttp r = checkhttp =<< getHttpHeaders
|
2011-08-17 01:04:23 +00:00
|
|
|
| Git.repoIsUrl r = checkremote
|
2011-11-09 22:33:15 +00:00
|
|
|
| otherwise = checklocal
|
2012-10-29 01:27:15 +00:00
|
|
|
where
|
2013-07-18 18:11:56 +00:00
|
|
|
checkhttp headers = do
|
|
|
|
showchecking
|
|
|
|
liftIO $ ifM (anyM (\u -> Url.check u headers (keySize key)) (keyUrls r key))
|
|
|
|
( return $ Right True
|
|
|
|
, return $ Left "not found"
|
|
|
|
)
|
2012-10-29 01:27:15 +00:00
|
|
|
checkremote = do
|
2013-07-18 18:11:56 +00:00
|
|
|
showchecking
|
2012-10-29 01:27:15 +00:00
|
|
|
onRemote r (check, unknown) "inannex" [Param (key2file key)] []
|
|
|
|
where
|
|
|
|
check c p = dispatch <$> safeSystem c p
|
|
|
|
dispatch ExitSuccess = Right True
|
|
|
|
dispatch (ExitFailure 1) = Right False
|
|
|
|
dispatch _ = unknown
|
|
|
|
checklocal = guardUsable r unknown $ dispatch <$> check
|
|
|
|
where
|
|
|
|
check = liftIO $ catchMsgIO $ onLocal r $
|
|
|
|
Annex.Content.inAnnexSafe key
|
|
|
|
dispatch (Left e) = Left e
|
|
|
|
dispatch (Right (Just b)) = Right b
|
|
|
|
dispatch (Right Nothing) = unknown
|
|
|
|
unknown = Left $ "unable to check " ++ Git.repoDescribe r
|
2013-07-18 18:11:56 +00:00
|
|
|
showchecking = showAction $ "checking " ++ Git.repoDescribe r
|
2011-08-17 01:04:23 +00:00
|
|
|
|
2011-08-17 18:36:20 +00:00
|
|
|
{- Runs an action on a local repository inexpensively, by making an annex
|
|
|
|
- monad using that repository. -}
|
|
|
|
onLocal :: Git.Repo -> Annex a -> IO a
|
|
|
|
onLocal r a = do
|
2012-05-18 22:20:53 +00:00
|
|
|
s <- Annex.new r
|
|
|
|
Annex.eval s $ do
|
2011-10-27 18:04:18 +00:00
|
|
|
-- No need to update the branch; its data is not used
|
|
|
|
-- for anything onLocal is used to do.
|
2011-12-12 21:38:46 +00:00
|
|
|
Annex.BranchState.disableUpdate
|
2012-10-04 22:57:53 +00:00
|
|
|
a
|
2011-08-17 18:36:20 +00:00
|
|
|
|
2011-11-29 02:43:51 +00:00
|
|
|
keyUrls :: Git.Repo -> Key -> [String]
|
2013-07-07 17:35:06 +00:00
|
|
|
keyUrls r key = map tourl locs
|
2012-10-29 01:27:15 +00:00
|
|
|
where
|
|
|
|
tourl l = Git.repoLocation r ++ "/" ++ l
|
2013-08-02 16:27:32 +00:00
|
|
|
#ifndef mingw32_HOST_OS
|
2013-07-07 17:35:06 +00:00
|
|
|
locs = annexLocations key
|
|
|
|
#else
|
2013-07-09 20:25:15 +00:00
|
|
|
locs = map (replace "\\" "/") (annexLocations key)
|
2013-07-07 17:35:06 +00:00
|
|
|
#endif
|
2011-08-17 01:04:23 +00:00
|
|
|
|
2013-01-01 17:52:47 +00:00
|
|
|
dropKey :: Remote -> Key -> Annex Bool
|
2011-08-17 01:20:14 +00:00
|
|
|
dropKey r key
|
2013-01-01 17:52:47 +00:00
|
|
|
| not $ Git.repoIsUrl (repo r) =
|
|
|
|
guardUsable (repo r) False $ commitOnCleanup r $ liftIO $ onLocal (repo r) $ do
|
2012-06-27 02:27:30 +00:00
|
|
|
ensureInitialized
|
|
|
|
whenM (Annex.Content.inAnnex key) $ do
|
|
|
|
Annex.Content.lockContent key $
|
|
|
|
Annex.Content.removeAnnex key
|
2012-12-12 23:20:38 +00:00
|
|
|
logStatus key InfoMissing
|
2012-06-27 02:27:30 +00:00
|
|
|
Annex.Content.saveState True
|
|
|
|
return True
|
2013-01-01 17:52:47 +00:00
|
|
|
| Git.repoIsHttp (repo r) = error "dropping from http repo not supported"
|
|
|
|
| otherwise = commitOnCleanup r $ onRemote (repo r) (boolSystem, False) "dropkey"
|
2011-03-27 21:24:20 +00:00
|
|
|
[ Params "--quiet --force"
|
2012-08-08 20:06:01 +00:00
|
|
|
, Param $ key2file key
|
2011-03-27 21:24:20 +00:00
|
|
|
]
|
2012-07-02 14:57:51 +00:00
|
|
|
[]
|
2011-03-27 19:56:43 +00:00
|
|
|
|
|
|
|
{- Tries to copy a key's content from a remote's annex to a file. -}
|
2013-04-11 21:15:45 +00:00
|
|
|
copyFromRemote :: Remote -> Key -> AssociatedFile -> FilePath -> MeterUpdate -> Annex Bool
|
|
|
|
copyFromRemote r key file dest _p = copyFromRemote' r key file dest
|
|
|
|
copyFromRemote' :: Remote -> Key -> AssociatedFile -> FilePath -> Annex Bool
|
|
|
|
copyFromRemote' r key file dest
|
2013-01-01 17:52:47 +00:00
|
|
|
| not $ Git.repoIsUrl (repo r) = guardUsable (repo r) False $ do
|
|
|
|
let params = rsyncParams r
|
2012-07-01 20:59:54 +00:00
|
|
|
u <- getUUID
|
|
|
|
-- run copy from perspective of remote
|
2013-01-01 17:52:47 +00:00
|
|
|
liftIO $ onLocal (repo r) $ do
|
2012-07-01 20:59:54 +00:00
|
|
|
ensureInitialized
|
2013-01-10 15:52:11 +00:00
|
|
|
v <- Annex.Content.prepSendAnnex key
|
|
|
|
case v of
|
|
|
|
Nothing -> return False
|
|
|
|
Just (object, checksuccess) ->
|
|
|
|
upload u key file noRetry
|
|
|
|
(rsyncOrCopyFile params object dest)
|
|
|
|
<&&> checksuccess
|
2013-01-01 17:52:47 +00:00
|
|
|
| Git.repoIsSsh (repo r) = feedprogressback $ \feeder ->
|
2012-09-22 03:25:06 +00:00
|
|
|
rsyncHelper (Just feeder)
|
2013-01-10 15:52:11 +00:00
|
|
|
=<< rsyncParamsRemote r Download key dest file
|
2013-01-01 17:52:47 +00:00
|
|
|
| Git.repoIsHttp (repo r) = Annex.Content.downloadUrl (keyUrls (repo r) key) dest
|
2011-08-17 01:04:23 +00:00
|
|
|
| otherwise = error "copying from non-ssh, non-http repo not supported"
|
2012-10-29 01:27:15 +00:00
|
|
|
where
|
|
|
|
{- Feed local rsync's progress info back to the remote,
|
|
|
|
- by forking a feeder thread that runs
|
|
|
|
- git-annex-shell transferinfo at the same time
|
|
|
|
- git-annex-shell sendkey is running.
|
|
|
|
-
|
2013-05-14 17:51:14 +00:00
|
|
|
- To avoid extra password prompts, this is only done when ssh
|
|
|
|
- connection caching is supported.
|
2012-10-29 01:27:15 +00:00
|
|
|
- Note that it actually waits for rsync to indicate
|
|
|
|
- progress before starting transferinfo, in order
|
|
|
|
- to ensure ssh connection caching works and reuses
|
|
|
|
- the connection set up for the sendkey.
|
|
|
|
-
|
|
|
|
- Also note that older git-annex-shell does not support
|
|
|
|
- transferinfo, so stderr is dropped and failure ignored.
|
|
|
|
-}
|
2013-05-14 17:51:14 +00:00
|
|
|
feedprogressback a = ifM (isJust <$> sshCacheDir)
|
|
|
|
( feedprogressback' a
|
2013-05-19 22:15:29 +00:00
|
|
|
, a $ const noop
|
2013-05-14 17:52:30 +00:00
|
|
|
)
|
2013-05-14 17:51:14 +00:00
|
|
|
feedprogressback' a = do
|
2012-10-29 01:27:15 +00:00
|
|
|
u <- getUUID
|
|
|
|
let fields = (Fields.remoteUUID, fromUUID u)
|
|
|
|
: maybe [] (\f -> [(Fields.associatedFile, f)]) file
|
2013-01-01 17:52:47 +00:00
|
|
|
Just (cmd, params) <- git_annex_shell (repo r) "transferinfo"
|
2012-10-29 01:27:15 +00:00
|
|
|
[Param $ key2file key] fields
|
2013-03-28 21:03:04 +00:00
|
|
|
v <- liftIO $ (newEmptySV :: IO (MSampleVar Integer))
|
2012-10-29 01:27:15 +00:00
|
|
|
tid <- liftIO $ forkIO $ void $ tryIO $ do
|
|
|
|
bytes <- readSV v
|
|
|
|
p <- createProcess $
|
|
|
|
(proc cmd (toCommand params))
|
|
|
|
{ std_in = CreatePipe
|
|
|
|
, std_err = CreatePipe
|
|
|
|
}
|
|
|
|
hClose $ stderrHandle p
|
|
|
|
let h = stdinHandle p
|
|
|
|
let send b = do
|
|
|
|
hPutStrLn h $ show b
|
|
|
|
hFlush h
|
|
|
|
send bytes
|
|
|
|
forever $
|
|
|
|
send =<< readSV v
|
2013-03-28 21:03:04 +00:00
|
|
|
let feeder = writeSV v . fromBytesProcessed
|
2013-05-23 00:58:27 +00:00
|
|
|
bracketIO noop (const $ tryIO $ killThread tid) (const $ a feeder)
|
2011-08-17 01:04:23 +00:00
|
|
|
|
2013-01-01 17:52:47 +00:00
|
|
|
copyFromRemoteCheap :: Remote -> Key -> FilePath -> Annex Bool
|
2013-08-02 16:27:32 +00:00
|
|
|
#ifndef mingw32_HOST_OS
|
2013-08-04 17:12:18 +00:00
|
|
|
copyFromRemoteCheap r key file
|
2013-01-01 17:52:47 +00:00
|
|
|
| not $ Git.repoIsUrl (repo r) = guardUsable (repo r) False $ do
|
2013-04-04 19:46:33 +00:00
|
|
|
loc <- liftIO $ gitAnnexLocation key (repo r) $
|
|
|
|
fromJust $ remoteGitConfig $ gitconfig r
|
2012-01-20 17:23:11 +00:00
|
|
|
liftIO $ catchBoolIO $ createSymbolicLink loc file >> return True
|
2013-01-01 17:52:47 +00:00
|
|
|
| Git.repoIsSsh (repo r) =
|
2012-03-16 00:39:25 +00:00
|
|
|
ifM (Annex.Content.preseedTmp key file)
|
2013-04-11 21:15:45 +00:00
|
|
|
( copyFromRemote' r key Nothing file
|
2012-03-16 00:39:25 +00:00
|
|
|
, return False
|
|
|
|
)
|
2012-01-20 17:23:11 +00:00
|
|
|
| otherwise = return False
|
2013-08-04 17:12:18 +00:00
|
|
|
#else
|
|
|
|
copyFromRemoteCheap _ _ _ = return False
|
|
|
|
#endif
|
2012-01-20 17:23:11 +00:00
|
|
|
|
2011-03-27 19:56:43 +00:00
|
|
|
{- Tries to copy a key's content to a remote's annex. -}
|
2013-01-01 17:52:47 +00:00
|
|
|
copyToRemote :: Remote -> Key -> AssociatedFile -> MeterUpdate -> Annex Bool
|
2012-09-19 20:08:37 +00:00
|
|
|
copyToRemote r key file p
|
2013-01-01 17:52:47 +00:00
|
|
|
| not $ Git.repoIsUrl (repo r) =
|
2013-01-10 15:45:44 +00:00
|
|
|
guardUsable (repo r) False $ commitOnCleanup r $
|
|
|
|
copylocal =<< Annex.Content.prepSendAnnex key
|
2013-01-01 17:52:47 +00:00
|
|
|
| Git.repoIsSsh (repo r) = commitOnCleanup r $
|
2013-01-09 22:42:29 +00:00
|
|
|
Annex.Content.sendAnnex key noop $ \object ->
|
2013-01-10 15:52:11 +00:00
|
|
|
rsyncHelper (Just p) =<< rsyncParamsRemote r Upload key object file
|
2012-12-08 21:03:39 +00:00
|
|
|
| otherwise = error "copying to non-ssh repo not supported"
|
|
|
|
where
|
2013-01-10 15:45:44 +00:00
|
|
|
copylocal Nothing = return False
|
|
|
|
copylocal (Just (object, checksuccess)) = do
|
2013-03-12 20:41:54 +00:00
|
|
|
-- The checksuccess action is going to be run in
|
|
|
|
-- the remote's Annex, but it needs access to the current
|
|
|
|
-- Annex monad's state.
|
|
|
|
checksuccessio <- Annex.withCurrentState checksuccess
|
2013-01-01 17:52:47 +00:00
|
|
|
let params = rsyncParams r
|
2012-07-01 20:59:54 +00:00
|
|
|
u <- getUUID
|
2011-03-27 19:56:43 +00:00
|
|
|
-- run copy from perspective of remote
|
2013-01-01 17:52:47 +00:00
|
|
|
liftIO $ onLocal (repo r) $ ifM (Annex.Content.inAnnex key)
|
2013-03-10 21:54:27 +00:00
|
|
|
( return True
|
2012-09-18 17:59:03 +00:00
|
|
|
, do
|
|
|
|
ensureInitialized
|
2013-04-11 21:15:45 +00:00
|
|
|
download u key file noRetry $ const $
|
2012-09-18 17:59:03 +00:00
|
|
|
Annex.Content.saveState True `after`
|
2013-03-12 20:41:54 +00:00
|
|
|
Annex.Content.getViaTmpChecked (liftIO checksuccessio) key
|
2012-12-08 21:03:39 +00:00
|
|
|
(\d -> rsyncOrCopyFile params object d p)
|
2012-09-18 17:59:03 +00:00
|
|
|
)
|
2011-03-27 19:56:43 +00:00
|
|
|
|
2012-09-21 18:50:14 +00:00
|
|
|
rsyncHelper :: Maybe MeterUpdate -> [CommandParam] -> Annex Bool
|
2012-09-19 20:55:08 +00:00
|
|
|
rsyncHelper callback params = do
|
2011-07-19 18:07:23 +00:00
|
|
|
showOutput -- make way for progress bar
|
2012-09-19 20:55:08 +00:00
|
|
|
ifM (liftIO $ (maybe rsync rsyncProgress callback) params)
|
2012-03-16 00:39:25 +00:00
|
|
|
( return True
|
|
|
|
, do
|
2011-03-27 19:56:43 +00:00
|
|
|
showLongNote "rsync failed -- run git annex again to resume file transfer"
|
2012-03-16 00:39:25 +00:00
|
|
|
return False
|
|
|
|
)
|
2011-03-27 19:56:43 +00:00
|
|
|
|
2011-06-14 00:23:47 +00:00
|
|
|
{- Copys a file with rsync unless both locations are on the same
|
|
|
|
- filesystem. Then cp could be faster. -}
|
2012-09-21 18:50:14 +00:00
|
|
|
rsyncOrCopyFile :: [CommandParam] -> FilePath -> FilePath -> MeterUpdate -> Annex Bool
|
2012-09-19 20:08:37 +00:00
|
|
|
rsyncOrCopyFile rsyncparams src dest p =
|
2013-08-02 16:27:32 +00:00
|
|
|
#ifdef mingw32_HOST_OS
|
2013-05-11 20:03:00 +00:00
|
|
|
dorsync
|
|
|
|
where
|
|
|
|
#else
|
2012-09-22 00:24:08 +00:00
|
|
|
ifM (sameDeviceIds src dest) (docopy, dorsync)
|
2012-10-29 01:27:15 +00:00
|
|
|
where
|
|
|
|
sameDeviceIds a b = (==) <$> (getDeviceId a) <*> (getDeviceId b)
|
|
|
|
getDeviceId f = deviceID <$> liftIO (getFileStatus $ parentDir f)
|
|
|
|
docopy = liftIO $ bracket
|
2013-03-28 21:03:04 +00:00
|
|
|
(forkIO $ watchfilesize zeroBytesProcessed)
|
2012-10-29 01:27:15 +00:00
|
|
|
(void . tryIO . killThread)
|
|
|
|
(const $ copyFileExternal src dest)
|
|
|
|
watchfilesize oldsz = do
|
|
|
|
threadDelay 500000 -- 0.5 seconds
|
|
|
|
v <- catchMaybeIO $
|
2013-03-28 21:03:04 +00:00
|
|
|
toBytesProcessed . fileSize
|
2012-10-29 01:27:15 +00:00
|
|
|
<$> getFileStatus dest
|
|
|
|
case v of
|
|
|
|
Just sz
|
|
|
|
| sz /= oldsz -> do
|
|
|
|
p sz
|
|
|
|
watchfilesize sz
|
|
|
|
_ -> watchfilesize oldsz
|
2013-05-11 20:03:00 +00:00
|
|
|
#endif
|
|
|
|
dorsync = rsyncHelper (Just p) $
|
2013-05-14 17:24:15 +00:00
|
|
|
rsyncparams ++ [File src, File dest]
|
2011-06-14 00:23:47 +00:00
|
|
|
|
2011-03-27 19:56:43 +00:00
|
|
|
{- Generates rsync parameters that ssh to the remote and asks it
|
|
|
|
- to either receive or send the key's content. -}
|
2013-01-10 15:52:11 +00:00
|
|
|
rsyncParamsRemote :: Remote -> Direction -> Key -> FilePath -> AssociatedFile -> Annex [CommandParam]
|
|
|
|
rsyncParamsRemote r direction key file afile = do
|
2012-07-02 14:57:51 +00:00
|
|
|
u <- getUUID
|
2013-01-11 19:43:09 +00:00
|
|
|
direct <- isDirect
|
2012-07-02 14:57:51 +00:00
|
|
|
let fields = (Fields.remoteUUID, fromUUID u)
|
2013-01-11 19:43:09 +00:00
|
|
|
: (Fields.direct, if direct then "1" else "")
|
2012-07-02 14:57:51 +00:00
|
|
|
: maybe [] (\f -> [(Fields.associatedFile, f)]) afile
|
2013-01-01 17:52:47 +00:00
|
|
|
Just (shellcmd, shellparams) <- git_annex_shell (repo r)
|
2013-01-10 15:52:11 +00:00
|
|
|
(if direction == Download then "sendkey" else "recvkey")
|
2012-08-08 20:06:01 +00:00
|
|
|
[ Param $ key2file key ]
|
2012-07-02 14:57:51 +00:00
|
|
|
fields
|
2011-03-27 19:56:43 +00:00
|
|
|
-- Convert the ssh command into rsync command line.
|
|
|
|
let eparam = rsyncShell (Param shellcmd:shellparams)
|
2013-01-01 17:52:47 +00:00
|
|
|
let o = rsyncParams r
|
2013-01-10 15:52:11 +00:00
|
|
|
if direction == Download
|
2012-07-02 14:57:51 +00:00
|
|
|
then return $ o ++ rsyncopts eparam dummy (File file)
|
|
|
|
else return $ o ++ rsyncopts eparam (File file) dummy
|
2012-10-29 01:27:15 +00:00
|
|
|
where
|
|
|
|
rsyncopts ps source dest
|
|
|
|
| end ps == [dashdash] = ps ++ [source, dest]
|
|
|
|
| otherwise = ps ++ [dashdash, source, dest]
|
|
|
|
dashdash = Param "--"
|
|
|
|
{- The rsync shell parameter controls where rsync
|
|
|
|
- goes, so the source/dest parameter can be a dummy value,
|
|
|
|
- that just enables remote rsync mode.
|
|
|
|
- For maximum compatability with some patched rsyncs,
|
|
|
|
- the dummy value needs to still contain a hostname,
|
|
|
|
- even though this hostname will never be used. -}
|
|
|
|
dummy = Param "dummy:"
|
2011-06-14 00:23:47 +00:00
|
|
|
|
2013-01-01 17:52:47 +00:00
|
|
|
-- --inplace to resume partial files
|
|
|
|
rsyncParams :: Remote -> [CommandParam]
|
2013-02-22 19:23:29 +00:00
|
|
|
rsyncParams r = [Params "--progress --inplace"] ++
|
2013-01-01 17:52:47 +00:00
|
|
|
map Param (remoteAnnexRsyncOptions $ gitconfig r)
|
2012-02-25 22:02:49 +00:00
|
|
|
|
2013-01-01 17:52:47 +00:00
|
|
|
commitOnCleanup :: Remote -> Annex a -> Annex a
|
2012-02-25 22:02:49 +00:00
|
|
|
commitOnCleanup r a = go `after` a
|
2012-10-29 01:27:15 +00:00
|
|
|
where
|
2013-01-01 17:52:47 +00:00
|
|
|
go = Annex.addCleanup (Git.repoLocation $ repo r) cleanup
|
2012-10-29 01:27:15 +00:00
|
|
|
cleanup
|
2013-01-01 17:52:47 +00:00
|
|
|
| not $ Git.repoIsUrl (repo r) = liftIO $ onLocal (repo r) $
|
2012-10-29 01:27:15 +00:00
|
|
|
doQuietSideAction $
|
|
|
|
Annex.Branch.commit "update"
|
|
|
|
| otherwise = void $ do
|
|
|
|
Just (shellcmd, shellparams) <-
|
2013-01-01 17:52:47 +00:00
|
|
|
git_annex_shell (repo r) "commit" [] []
|
2012-10-29 01:27:15 +00:00
|
|
|
|
|
|
|
-- Throw away stderr, since the remote may not
|
|
|
|
-- have a new enough git-annex shell to
|
|
|
|
-- support committing.
|
|
|
|
liftIO $ catchMaybeIO $ do
|
|
|
|
withQuietOutput createProcessSuccess $
|
|
|
|
proc shellcmd $
|
|
|
|
toCommand shellparams
|