implemented remotes config caching

This commit is contained in:
Joey Hess 2010-10-13 22:59:43 -04:00
parent 89654751da
commit 912d10e78b
3 changed files with 74 additions and 34 deletions

View file

@ -43,16 +43,20 @@ copyKeyFile key file = do
if (0 == length remotes) if (0 == length remotes)
then error $ "no known remotes have: " ++ (keyFile key) ++ "\n" ++ then error $ "no known remotes have: " ++ (keyFile key) ++ "\n" ++
"(Perhaps you need to git remote add a repository?)" "(Perhaps you need to git remote add a repository?)"
else liftIO $ trycopy remotes remotes else trycopy remotes remotes
where where
trycopy full [] = error $ "unable to get: " ++ (keyFile key) ++ "\n" ++ trycopy full [] = error $ "unable to get: " ++ (keyFile key) ++ "\n" ++
"To get that file, need access to one of these remotes: " ++ "To get that file, need access to one of these remotes: " ++
(remotesList full) (remotesList full)
trycopy full (r:rs) = do trycopy full (r:rs) = do
result <- try (copyFromRemote r key file)::IO (Either SomeException ()) -- annexLocation needs the git config to have been
-- read for a remote, so do that now,
-- if it hasn't been already
r' <- remoteEnsureGitConfigRead r
result <- liftIO $ (try (copyFromRemote r' key file)::IO (Either SomeException ()))
case (result) of case (result) of
Left err -> do Left err -> do
hPutStrLn stderr (show err) liftIO $ hPutStrLn stderr (show err)
trycopy full rs trycopy full rs
Right succ -> return True Right succ -> return True
@ -61,19 +65,11 @@ copyFromRemote :: GitRepo -> Key -> FilePath -> IO ()
copyFromRemote r key file = do copyFromRemote r key file = do
putStrLn $ "copy from " ++ (gitRepoDescribe r ) ++ " " ++ file putStrLn $ "copy from " ++ (gitRepoDescribe r ) ++ " " ++ file
-- annexLocation needs the git config read for the remote first. if (gitRepoIsLocal r)
-- FIXME: Having this here means git-config is run repeatedly when then getlocal
-- copying a series of files; need to use state monad to avoid else getremote
-- this.
r' <- gitConfigRead r
_ <- if (gitRepoIsLocal r')
then getlocal r'
else getremote r'
return () return ()
where where
getlocal r = do getlocal = rawSystem "cp" ["-a", location, file]
rawSystem "cp" ["-a", location r, file] getremote = error "get via network not yet implemented!"
getremote r = do location = annexLocation r backend key
error "get via network not yet implemented!"
location r = annexLocation r backend key

View file

@ -12,15 +12,17 @@ module GitRepo (
gitRepoFromUrl, gitRepoFromUrl,
gitRepoIsLocal, gitRepoIsLocal,
gitRepoIsRemote, gitRepoIsRemote,
gitConfigRemotes,
gitRepoDescribe, gitRepoDescribe,
gitWorkTree, gitWorkTree,
gitDir, gitDir,
gitRelative, gitRelative,
gitConfig, gitConfig,
gitConfigMap,
gitConfigRead, gitConfigRead,
gitRun, gitRun,
gitAttributes, gitAttributes,
gitRepoRemotes,
gitRepoRemotesAdd,
gitRepoRemoteName gitRepoRemoteName
) where ) where
@ -46,12 +48,14 @@ data GitRepo =
LocalGitRepo { LocalGitRepo {
top :: FilePath, top :: FilePath,
config :: Map String String, config :: Map String String,
remotes :: [GitRepo],
-- remoteName holds the name used for this repo in remotes -- remoteName holds the name used for this repo in remotes
remoteName :: Maybe String remoteName :: Maybe String
} | RemoteGitRepo { } | RemoteGitRepo {
url :: String, url :: String,
top :: FilePath, top :: FilePath,
config :: Map String String, config :: Map String String,
remotes :: [GitRepo],
remoteName :: Maybe String remoteName :: Maybe String
} deriving (Show, Read, Eq) } deriving (Show, Read, Eq)
@ -61,6 +65,7 @@ gitRepoFromPath dir =
LocalGitRepo { LocalGitRepo {
top = dir, top = dir,
config = Map.empty, config = Map.empty,
remotes = [],
remoteName = Nothing remoteName = Nothing
} }
@ -71,6 +76,7 @@ gitRepoFromUrl url =
url = url, url = url,
top = path url, top = path url,
config = Map.empty, config = Map.empty,
remotes = [],
remoteName = Nothing remoteName = Nothing
} }
where path url = uriPath $ fromJust $ parseURI url where path url = uriPath $ fromJust $ parseURI url
@ -83,6 +89,15 @@ gitRepoDescribe repo =
then top repo then top repo
else url repo else url repo
{- Returns the list of a repo's remotes. -}
gitRepoRemotes :: GitRepo -> [GitRepo]
gitRepoRemotes r = remotes r
{- Constructs and returns an updated version of a repo with
- different remotes list. -}
gitRepoRemotesAdd :: GitRepo -> [GitRepo] -> GitRepo
gitRepoRemotesAdd repo rs = repo { remotes = rs }
{- Returns the name of the remote that corresponds to the repo, if {- Returns the name of the remote that corresponds to the repo, if
- it is a remote. Otherwise, "" -} - it is a remote. Otherwise, "" -}
gitRepoRemoteName r = gitRepoRemoteName r =
@ -169,10 +184,24 @@ gitConfigRead repo = assertlocal repo $ do
been already read. Instead, chdir to the repo. -} been already read. Instead, chdir to the repo. -}
cwd <- getCurrentDirectory cwd <- getCurrentDirectory
bracket_ (changeWorkingDirectory (top repo)) bracket_ (changeWorkingDirectory (top repo))
(\_ -> changeWorkingDirectory cwd) $ do (\_ -> changeWorkingDirectory cwd) $
pOpen ReadFromPipe "git" ["config", "--list"] $ \h -> do pOpen ReadFromPipe "git" ["config", "--list"] $ \h -> do
val <- hGetContentsStrict h val <- hGetContentsStrict h
return repo { config = gitConfigParse val } let r = repo { config = gitConfigParse val }
return r { remotes = gitConfigRemotes r }
{- Calculates a list of a repo's configured remotes, by parsing its config. -}
gitConfigRemotes :: GitRepo -> [GitRepo]
gitConfigRemotes repo = map construct remotes
where
remotes = toList $ filter $ config repo
filter = filterWithKey (\k _ -> isremote k)
isremote k = (startswith "remote." k) && (endswith ".url" k)
remotename k = (split "." k) !! 1
construct (k,v) = (gen v) { remoteName = Just $ remotename k }
gen v = if (isURI v)
then gitRepoFromUrl v
else gitRepoFromPath v
{- Parses git config --list output into a config map. -} {- Parses git config --list output into a config map. -}
gitConfigParse :: String -> Map.Map String String gitConfigParse :: String -> Map.Map String String
@ -189,18 +218,9 @@ gitConfig :: GitRepo -> String -> String -> String
gitConfig repo key defaultValue = gitConfig repo key defaultValue =
Map.findWithDefault defaultValue key (config repo) Map.findWithDefault defaultValue key (config repo)
{- Returns a list of a repo's configured remotes. -} {- Access to raw config Map -}
gitConfigRemotes :: GitRepo -> [GitRepo] gitConfigMap :: GitRepo -> Map String String
gitConfigRemotes repo = map construct remotes gitConfigMap repo = config repo
where
remotes = toList $ filter $ config repo
filter = filterWithKey (\k _ -> isremote k)
isremote k = (startswith "remote." k) && (endswith ".url" k)
remotename k = (split "." k) !! 1
construct (k,v) = (gen v) { remoteName = Just $ remotename k }
gen v = if (isURI v)
then gitRepoFromUrl v
else gitRepoFromPath v
{- Finds the current git repository, which may be in a parent directory. -} {- Finds the current git repository, which may be in a parent directory. -}
gitRepoFromCwd :: IO GitRepo gitRepoFromCwd :: IO GitRepo

View file

@ -2,10 +2,12 @@
module Remotes ( module Remotes (
remotesList, remotesList,
remotesWithKey remotesWithKey,
remoteEnsureGitConfigRead
) where ) where
import Control.Monad.State (liftIO) import Control.Monad.State (liftIO)
import qualified Data.Map as Map
import Types import Types
import GitRepo import GitRepo
import LocationLog import LocationLog
@ -29,7 +31,7 @@ remotesWithKey key = do
remotesByCost :: Annex [GitRepo] remotesByCost :: Annex [GitRepo]
remotesByCost = do remotesByCost = do
g <- gitAnnex g <- gitAnnex
reposByCost $ gitConfigRemotes g reposByCost $ gitRepoRemotes g
{- Orders a list of git repos by cost. -} {- Orders a list of git repos by cost. -}
reposByCost :: [GitRepo] -> Annex [GitRepo] reposByCost :: [GitRepo] -> Annex [GitRepo]
@ -58,3 +60,25 @@ repoCost r = do
where where
config g r = gitConfig g (configkey r) "" config g r = gitConfig g (configkey r) ""
configkey r = "remote." ++ (gitRepoRemoteName r) ++ ".annex-cost" configkey r = "remote." ++ (gitRepoRemoteName r) ++ ".annex-cost"
{- The git configs for the git repo's remotes is not read on startup
- because reading it may be expensive. This function ensures that it is
- read for a specified remote, and updates state. It returns the
- updated git repo also. -}
remoteEnsureGitConfigRead :: GitRepo -> Annex GitRepo
remoteEnsureGitConfigRead r = do
if (Map.null $ gitConfigMap r)
then do
r' <- liftIO $ gitConfigRead r
g <- gitAnnex
let l = gitRepoRemotes g
let g' = gitRepoRemotesAdd g $ exchange l r'
gitAnnexChange g'
return r'
else return r
where
exchange [] new = []
exchange (old:ls) new =
if ((gitRepoRemoteName old) == (gitRepoRemoteName new))
then new:(exchange ls new)
else old:(exchange ls new)