use git-annex-shell configlist

This commit is contained in:
Joey Hess 2010-12-31 15:46:33 -04:00
parent 60df4e5728
commit eac433a84a
4 changed files with 66 additions and 48 deletions

View file

@ -47,7 +47,7 @@ new gitrepo allbackends = do
where where
prep = do prep = do
-- read git config and update state -- read git config and update state
gitrepo' <- liftIO $ Git.configRead gitrepo Nothing gitrepo' <- liftIO $ Git.configRead gitrepo
Annex.gitRepoChange gitrepo' Annex.gitRepoChange gitrepo'
{- performs an action in the Annex monad -} {- performs an action in the Annex monad -}
@ -136,5 +136,5 @@ setConfig key value = do
g <- Annex.gitRepo g <- Annex.gitRepo
liftIO $ Git.run g ["config", key, value] liftIO $ Git.run g ["config", key, value]
-- re-read git config and update the repo's state -- re-read git config and update the repo's state
g' <- liftIO $ Git.configRead g Nothing g' <- liftIO $ Git.configRead g
Annex.gitRepoChange g' Annex.gitRepoChange g'

View file

@ -7,6 +7,7 @@
module Command.Move where module Command.Move where
import Control.Monad (when)
import Control.Monad.State (liftIO) import Control.Monad.State (liftIO)
import Command import Command
@ -20,6 +21,7 @@ import qualified GitRepo as Git
import qualified Remotes import qualified Remotes
import UUID import UUID
import Messages import Messages
import Utility
command :: [Command] command :: [Command]
command = [Command "move" paramPath seek command = [Command "move" paramPath seek
@ -134,10 +136,11 @@ fromPerform move key = do
else return Nothing -- fail else return Nothing -- fail
fromCleanup :: Bool -> Git.Repo -> Key -> CommandCleanup fromCleanup :: Bool -> Git.Repo -> Key -> CommandCleanup
fromCleanup True remote key = do fromCleanup True remote key = do
ok <- Remotes.onRemote remote "dropkey" ok <- Remotes.onRemote remote boolSystem False "dropkey"
["--quiet", "--force", ["--quiet", "--force",
"--backend=" ++ backendName key, "--backend=" ++ backendName key,
keyName key] keyName key]
remoteHasKey remote key False when ok $
remoteHasKey remote key False
return ok return ok
fromCleanup False _ _ = return True fromCleanup False _ _ = return True

View file

@ -24,6 +24,8 @@ module GitRepo (
configGet, configGet,
configMap, configMap,
configRead, configRead,
hConfigRead,
configStore,
configTrue, configTrue,
gitCommandLine, gitCommandLine,
run, run,
@ -141,11 +143,7 @@ assertUrl repo action =
then action then action
else error $ "acting on local git repo " ++ repoDescribe repo ++ else error $ "acting on local git repo " ++ repoDescribe repo ++
" not supported" " not supported"
assertSsh :: Repo -> a -> a
assertSsh repo action =
if repoIsSsh repo
then action
else error $ "unsupported url in repo " ++ repoDescribe repo
bare :: Repo -> Bool bare :: Repo -> Bool
bare repo = case Map.lookup "core.bare" $ config repo of bare repo = case Map.lookup "core.bare" $ config repo of
Just v -> configTrue v Just v -> configTrue v
@ -276,11 +274,9 @@ pipeNullSplit repo params = do
where where
split0 s = filter (not . null) $ split "\0" s split0 s = filter (not . null) $ split "\0" s
{- Runs git config and populates a repo with its config. {- Runs git config and populates a repo with its config. -}
- configRead :: Repo -> IO Repo
- For a ssh repository, a list of ssh options may optionally be specified. -} configRead repo@(Repo { location = Dir d }) = do
configRead :: Repo -> Maybe [String] -> IO Repo
configRead repo@(Repo { location = Dir d }) _ = do
{- Cannot use pipeRead because it relies on the config having {- Cannot use pipeRead because it relies on the config having
been already read. Instead, chdir to the repo. -} been already read. Instead, chdir to the repo. -}
cwd <- getCurrentDirectory cwd <- getCurrentDirectory
@ -288,19 +284,18 @@ configRead repo@(Repo { location = Dir d }) _ = do
(\_ -> changeWorkingDirectory cwd) $ (\_ -> changeWorkingDirectory cwd) $
pOpen ReadFromPipe "git" ["config", "--list"] $ pOpen ReadFromPipe "git" ["config", "--list"] $
hConfigRead repo hConfigRead repo
configRead repo sshopts = assertSsh repo $ do configRead r = assertLocal r $ error "internal"
pOpen ReadFromPipe "ssh" params $ hConfigRead repo
where {- Reads git config from a handle and populates a repo with it. -}
params = case sshopts of
Nothing -> [urlHost repo, command]
Just l -> l ++ [urlHost repo, command]
command = "cd " ++ shellEscape (urlPath repo) ++
" && git config --list"
hConfigRead :: Repo -> Handle -> IO Repo hConfigRead :: Repo -> Handle -> IO Repo
hConfigRead repo h = do hConfigRead repo h = do
val <- hGetContentsStrict h val <- hGetContentsStrict h
let r = repo { config = configParse val } return $ configStore repo val
return r { remotes = configRemotes r }
{- Parses a git config and returns a version of the repo using it. -}
configStore :: Repo -> String -> Repo
configStore repo s = r { remotes = configRemotes r }
where r = repo { config = configParse s }
{- Checks if a string fron git config is a true value. -} {- Checks if a string fron git config is a true value. -}
configTrue :: String -> Bool configTrue :: String -> Bool

View file

@ -25,6 +25,7 @@ import qualified Data.Map as Map
import Data.String.Utils import Data.String.Utils
import System.Directory hiding (copyFile) import System.Directory hiding (copyFile)
import System.Posix.Directory import System.Posix.Directory
import System.Cmd.Utils
import Data.List (intersect, sortBy) import Data.List (intersect, sortBy)
import Control.Monad (when, unless, filterM) import Control.Monad (when, unless, filterM)
@ -112,16 +113,14 @@ inAnnex r key = if Git.repoIsUrl r
else liftIO (try checklocal ::IO (Either IOException Bool)) else liftIO (try checklocal ::IO (Either IOException Bool))
where where
checklocal = do checklocal = do
-- run a local check by making an Annex monad -- run a local check inexpensively,
-- using the remote -- by making an Annex monad using the remote
a <- Annex.new r [] a <- Annex.new r []
Annex.eval a (Core.inAnnex key) Annex.eval a (Core.inAnnex key)
checkremote = do checkremote = do
showNote ("checking " ++ Git.repoDescribe r ++ "...") showNote ("checking " ++ Git.repoDescribe r ++ "...")
inannex <- onRemote r "inannex" inannex <- onRemote r boolSystem False "inannex"
["--backend=" ++ backendName key, keyName key] ["--backend=" ++ backendName key, keyName key]
-- XXX Note that ssh failing and the file not existing
-- are not currently differentiated.
return $ Right inannex return $ Right inannex
{- Cost Ordered list of remotes. -} {- Cost Ordered list of remotes. -}
@ -199,24 +198,29 @@ byName name = do
- config for a specified remote, and updates state. If successful, it - config for a specified remote, and updates state. If successful, it
- returns the updated git repo. -} - returns the updated git repo. -}
tryGitConfigRead :: Git.Repo -> Annex (Either Git.Repo Git.Repo) tryGitConfigRead :: Git.Repo -> Annex (Either Git.Repo Git.Repo)
tryGitConfigRead r = do tryGitConfigRead r
sshoptions <- repoConfig r "ssh-options" "" | not $ Map.null $ Git.configMap r = return $ Right r -- already read
if Map.null $ Git.configMap r | Git.repoIsSsh r = store $ onRemote r pipedconfig r "configlist" []
then do | Git.repoIsUrl r = return $ Left r
-- configRead can fail due to IO error or | otherwise = store $ safely $ Git.configRead r
-- for other reasons; catch all possible exceptions where
result <- liftIO (try (Git.configRead r $ Just $ words sshoptions)::IO (Either SomeException Git.Repo)) -- Reading config can fail due to IO error or
-- for other reasons; catch all possible exceptions.
safely a = do
result <- liftIO (try (a)::IO (Either SomeException Git.Repo))
case result of case result of
Left _ -> return $ Left r Left _ -> return r
Right r' -> do Right r' -> return r'
g <- Annex.gitRepo pipedconfig cmd params = safely $
let l = Git.remotes g pOpen ReadFromPipe cmd params $
let g' = Git.remotesAdd g $ Git.hConfigRead r
exchange l r' store a = do
Annex.gitRepoChange g' r' <- a
return $ Right r' g <- Annex.gitRepo
else return $ Right r -- config already read let l = Git.remotes g
where let g' = Git.remotesAdd g $ exchange l r'
Annex.gitRepoChange g'
return $ Right r'
exchange [] _ = [] exchange [] _ = []
exchange (old:ls) new = exchange (old:ls) new =
if Git.repoRemoteName old == Git.repoRemoteName new if Git.repoRemoteName old == Git.repoRemoteName new
@ -268,10 +272,26 @@ remoteCopyFile recv r src dest = do
-- inplace makes rsync resume partial files -- inplace makes rsync resume partial files
options = ["-p", "--progress", "--inplace"] options = ["-p", "--progress", "--inplace"]
onRemote :: Git.Repo -> String -> [String] -> Annex Bool {- Uses a supplied function to run a git-annex-shell command on a remote. -}
onRemote r command params = runCmd r "git-annex-shell" (command:dir:params) onRemote
:: Git.Repo
-> (String -> [String] -> IO a)
-> a
-> String
-> [String]
-> Annex a
onRemote r with errorval command params
| not $ Git.repoIsUrl r = liftIO $ with shellcmd shellopts
| Git.repoIsSsh r = do
sshoptions <- repoConfig r "ssh-options" ""
liftIO $ with "ssh" $
words sshoptions ++ [Git.urlHost r, sshcmd]
| otherwise = return errorval
where where
dir = Git.workTree r dir = Git.workTree r
shellcmd = "git-annex-shell"
shellopts = command:dir:params
sshcmd = shellcmd ++ " " ++ unwords (map shellEscape shellopts)
{- Runs a command in a remote, using ssh if necessary. {- Runs a command in a remote, using ssh if necessary.
- (Honors annex-ssh-options.) -} - (Honors annex-ssh-options.) -}