git-annex/Remotes.hs

286 lines
8.9 KiB
Haskell
Raw Normal View History

2010-10-27 20:53:54 +00:00
{- git-annex remote repositories
-
- Copyright 2010 Joey Hess <joey@kitenet.net>
-
- Licensed under the GNU GPL version 3 or higher.
-}
module Remotes (
2010-10-14 06:41:54 +00:00
list,
keyPossibilities,
tryGitConfigRead,
2010-10-23 18:14:36 +00:00
inAnnex,
same,
2010-10-23 18:14:36 +00:00
commandLineRemote,
byName,
2010-10-23 18:58:14 +00:00
copyFromRemote,
copyToRemote,
runCmd
) where
2010-11-22 21:51:55 +00:00
import Control.Exception.Extensible
2010-10-14 01:28:47 +00:00
import Control.Monad.State (liftIO)
2010-10-14 02:59:43 +00:00
import qualified Data.Map as Map
2010-10-14 03:18:58 +00:00
import Data.String.Utils
import System.Directory hiding (copyFile)
import System.Posix.Directory
2010-11-22 21:51:55 +00:00
import Data.List
import Control.Monad (when, unless, filterM)
2010-10-16 20:20:49 +00:00
2010-10-14 07:18:11 +00:00
import Types
2010-10-14 06:36:41 +00:00
import qualified GitRepo as Git
2010-10-14 07:18:11 +00:00
import qualified Annex
import LocationLog
2010-10-14 03:18:58 +00:00
import Locations
import UUID
2010-10-23 18:14:36 +00:00
import Utility
import qualified Core
2010-11-08 19:15:21 +00:00
import Messages
import CopyFile
import qualified SysConfig
{- Human visible list of remotes. -}
2010-10-14 06:41:54 +00:00
list :: [Git.Repo] -> String
2010-10-22 19:21:23 +00:00
list remotes = join ", " $ map Git.repoDescribe remotes
{- Cost ordered list of remotes that the LocationLog indicate may have a key. -}
keyPossibilities :: Key -> Annex [Git.Repo]
keyPossibilities key = do
2010-10-14 07:18:11 +00:00
g <- Annex.gitRepo
2010-10-14 01:28:47 +00:00
uuids <- liftIO $ keyLocations g key
2010-10-14 03:18:58 +00:00
allremotes <- remotesByCost
-- To determine if a remote has a key, its UUID needs to be known.
-- The locally cached UUIDs of remotes can fall out of date if
-- eg, a different drive is mounted at the same location.
-- But, reading the config of remotes can be expensive, so make
-- sure we only do it once per git-annex run.
remotesread <- Annex.flagIsSet "remotesread"
2010-11-22 21:51:55 +00:00
if remotesread
then reposByUUID allremotes uuids
else do
-- We assume that it's cheap to read the config
-- of non-URL remotes, so that is done each time.
-- But reading the config of an URL remote is
-- only done when there is no cached UUID value.
let cheap = filter (not . Git.repoIsUrl) allremotes
let expensive = filter Git.repoIsUrl allremotes
doexpensive <- filterM cachedUUID expensive
2010-11-22 21:51:55 +00:00
unless (null doexpensive) $
2010-11-08 19:15:21 +00:00
showNote $ "getting UUID for " ++
2010-11-22 21:51:55 +00:00
list doexpensive ++ "..."
let todo = cheap ++ doexpensive
2010-11-22 21:51:55 +00:00
if not $ null todo
then do
2010-10-31 18:23:51 +00:00
_ <- mapM tryGitConfigRead todo
Annex.flagChange "remotesread" $ FlagBool True
keyPossibilities key
else reposByUUID allremotes uuids
where
cachedUUID r = do
u <- getUUID r
2010-10-23 00:47:14 +00:00
return $ null u
{- Checks if a given remote has the content for a key inAnnex.
- If the remote cannot be accessed, returns a Left error.
-}
inAnnex :: Git.Repo -> Key -> Annex (Either IOException Bool)
2010-11-22 21:51:55 +00:00
inAnnex r key = if Git.repoIsUrl r
then checkremote
else liftIO (try checklocal ::IO (Either IOException Bool))
where
checklocal = do
-- run a local check by making an Annex monad
-- using the remote
a <- Annex.new r []
2010-11-01 03:24:16 +00:00
Annex.eval a (Core.inAnnex key)
checkremote = do
2010-11-08 19:15:21 +00:00
showNote ("checking " ++ Git.repoDescribe r ++ "...")
2010-11-07 01:12:45 +00:00
inannex <- runCmd r "test" ["-e", annexLocation r key]
-- XXX Note that ssh failing and the file not existing
-- are not currently differentiated.
return $ Right inannex
{- Cost Ordered list of remotes. -}
2010-10-14 06:36:41 +00:00
remotesByCost :: Annex [Git.Repo]
2010-10-14 01:28:47 +00:00
remotesByCost = do
2010-10-14 07:18:11 +00:00
g <- Annex.gitRepo
2010-10-14 06:36:41 +00:00
reposByCost $ Git.remotes g
{- Orders a list of git repos by cost. Throws out ignored ones. -}
2010-10-14 06:36:41 +00:00
reposByCost :: [Git.Repo] -> Annex [Git.Repo]
2010-10-14 01:28:47 +00:00
reposByCost l = do
notignored <- filterM repoNotIgnored l
costpairs <- mapM costpair notignored
2010-11-22 21:51:55 +00:00
return $ fst $ unzip $ sortBy cmpcost costpairs
where
2010-10-14 01:28:47 +00:00
costpair r = do
cost <- repoCost r
return (r, cost)
2010-11-22 21:51:55 +00:00
cmpcost (_, c1) (_, c2) = compare c1 c2
{- Calculates cost for a repo.
-
- The default cost is 100 for local repositories, and 200 for remote
- repositories; it can also be configured by remote.<name>.annex-cost
-}
2010-10-14 06:36:41 +00:00
repoCost :: Git.Repo -> Annex Int
2010-10-14 01:28:47 +00:00
repoCost r = do
cost <- repoConfig r "cost" ""
2010-11-22 21:51:55 +00:00
if not $ null cost
then return $ read cost
2010-11-22 21:51:55 +00:00
else if Git.repoIsUrl r
then return 200
else return 100
2010-10-14 02:59:43 +00:00
{- Checks if a repo should be ignored, based either on annex-ignore
- setting, or on command-line options. Allows command-line to override
- annex-ignore. -}
repoNotIgnored :: Git.Repo -> Annex Bool
repoNotIgnored r = do
ignored <- repoConfig r "ignore" "false"
fromName <- Annex.flagGet "fromrepository"
toName <- Annex.flagGet "torepository"
2010-11-22 21:51:55 +00:00
let name = if null fromName then toName else fromName
if not $ null name
then return $ match name
2010-11-22 21:51:55 +00:00
else return $ not $ Git.configTrue ignored
where
match name = name == Git.repoRemoteName r
{- Checks if two repos are the same, by comparing their remote names. -}
same :: Git.Repo -> Git.Repo -> Bool
same a b = Git.repoRemoteName a == Git.repoRemoteName b
2010-10-23 18:14:36 +00:00
{- Returns the remote specified by --from or --to, may fail with error. -}
commandLineRemote :: Annex Git.Repo
commandLineRemote = do
fromName <- Annex.flagGet "fromrepository"
toName <- Annex.flagGet "torepository"
2010-11-22 21:51:55 +00:00
let name = if null fromName then toName else fromName
byName name
{- Looks up a remote by name. -}
byName :: String -> Annex Git.Repo
byName name = do
2010-10-28 18:20:02 +00:00
when (null name) $ error "no remote specified"
g <- Annex.gitRepo
let match = filter (\r -> name == Git.repoRemoteName r) $
Git.remotes g
when (null match) $ error $
"there is no git remote named \"" ++ name ++ "\""
2010-11-22 21:51:55 +00:00
return $ head match
2010-10-23 18:14:36 +00:00
2010-10-14 02:59:43 +00:00
{- The git configs for the git repo's remotes is not read on startup
- because reading it may be expensive. This function tries to read the
- config for a specified remote, and updates state. If successful, it
- returns the updated git repo. -}
tryGitConfigRead :: Git.Repo -> Annex (Either Git.Repo Git.Repo)
tryGitConfigRead r = do
sshoptions <- repoConfig r "ssh-options" ""
2010-11-22 21:51:55 +00:00
if Map.null $ Git.configMap r
2010-10-14 02:59:43 +00:00
then do
2010-10-16 21:44:59 +00:00
-- configRead can fail due to IO error or
-- for other reasons; catch all possible exceptions
2010-11-22 21:51:55 +00:00
result <- liftIO (try (Git.configRead r $ Just $ words sshoptions)::IO (Either SomeException Git.Repo))
case result of
2010-10-31 18:23:51 +00:00
Left _ -> return $ Left r
Right r' -> do
g <- Annex.gitRepo
let l = Git.remotes g
let g' = Git.remotesAdd g $
exchange l r'
Annex.gitRepoChange g'
return $ Right r'
else return $ Right r -- config already read
2010-10-14 02:59:43 +00:00
where
2010-10-31 18:23:51 +00:00
exchange [] _ = []
2010-10-14 02:59:43 +00:00
exchange (old:ls) new =
2010-11-22 21:51:55 +00:00
if Git.repoRemoteName old == Git.repoRemoteName new
then new : exchange ls new
else old : exchange ls new
2010-10-23 18:14:36 +00:00
2010-10-23 18:58:14 +00:00
{- Tries to copy a key's content from a remote to a file. -}
2010-10-23 18:14:36 +00:00
copyFromRemote :: Git.Repo -> Key -> FilePath -> Annex Bool
2010-11-22 21:51:55 +00:00
copyFromRemote r key file
| not $ Git.repoIsUrl r = getlocal
| Git.repoIsSsh r = getssh
| otherwise = error "copying from non-ssh repo not supported"
2010-10-23 18:14:36 +00:00
where
keyloc = annexLocation r key
getlocal = liftIO $ copyFile keyloc file
getssh = remoteCopyFile r (sshLocation r keyloc) file
2010-10-23 18:58:14 +00:00
{- Tries to copy a key's content to a file on a remote. -}
copyToRemote :: Git.Repo -> Key -> FilePath -> Annex Bool
copyToRemote r key file = do
2010-10-23 18:58:14 +00:00
g <- Annex.gitRepo
let keyloc = annexLocation g key
2010-11-22 21:51:55 +00:00
if not $ Git.repoIsUrl r
then putlocal keyloc
2010-11-22 21:51:55 +00:00
else if Git.repoIsSsh r
then putssh keyloc
2010-10-23 18:58:14 +00:00
else error "copying to non-ssh repo not supported"
where
putlocal src = liftIO $ copyFile src file
putssh src = remoteCopyFile r src (sshLocation r file)
sshLocation :: Git.Repo -> FilePath -> FilePath
2010-11-22 21:51:55 +00:00
sshLocation r file = Git.urlHost r ++ ":" ++ shellEscape file
{- Copys a file from or to a remote, using rsync (when available) or scp. -}
remoteCopyFile :: Git.Repo -> String -> String -> Annex Bool
remoteCopyFile r src dest = do
showProgress -- make way for progress bar
o <- repoConfig r configopt ""
res <- liftIO $ boolSystem cmd $ options ++ words o ++ [src, dest]
if res
then return res
else do
when rsync $
2010-12-02 21:54:08 +00:00
showLongNote "rsync failed -- run git annex again to resume file transfer"
return res
where
cmd
| rsync = "rsync"
| otherwise = "scp"
configopt
| rsync = "rsync-options"
| otherwise = "scp-options"
options
-- inplace makes rsync resume partial files
| rsync = ["-p", "--progress", "--inplace"]
| otherwise = ["-p"]
rsync = SysConfig.rsync
{- Runs a command in a remote, using ssh if necessary.
- (Honors annex-ssh-options.) -}
runCmd :: Git.Repo -> String -> [String] -> Annex Bool
runCmd r command params = do
sshoptions <- repoConfig r "ssh-options" ""
2010-11-22 21:51:55 +00:00
if not $ Git.repoIsUrl r
then do
2010-11-22 21:51:55 +00:00
cwd <- liftIO getCurrentDirectory
liftIO $ bracket_
(changeWorkingDirectory (Git.workTree r))
(changeWorkingDirectory cwd)
(boolSystem command params)
else if Git.repoIsSsh r
then liftIO $ boolSystem "ssh" $
words sshoptions ++ [Git.urlHost r, sshcmd]
else error "running command in non-ssh repo not supported"
2010-11-22 21:51:55 +00:00
where
sshcmd = "cd " ++ shellEscape (Git.workTree r) ++
" && " ++ shellEscape command ++ " " ++
unwords (map shellEscape params)
{- Looks up a per-remote config option in git config.
- Failing that, tries looking for a global config option. -}
repoConfig :: Git.Repo -> String -> String -> Annex String
repoConfig r key def = do
g <- Annex.gitRepo
let def' = Git.configGet g global def
return $ Git.configGet g local def'
where
2010-11-22 21:51:55 +00:00
local = "remote." ++ Git.repoRemoteName r ++ ".annex-" ++ key
global = "annex." ++ key