removal of the rest of remoteGitConfig

In keyUrls, the GitConfig is used only by annexLocations
to support configured Differences. Since such configurations affect all
clones of a repository, the local repo's GitConfig must have the same
information as the remote's GitConfig would have. So, used getGitConfig
to get the local GitConfig, which is cached and so available cheaply.

That actually fixed a bug noone had ever noticed: keyUrls is
used for remotes accessed over http. The full git config of such a
remote is normally not available, so the remoteGitConfig that keyUrls
used would not have the necessary information in it.

In copyFromRemoteCheap', it uses gitAnnexLocation,
which does need the GitConfig of the remote repo itself in order to
check if it's crippled, supports symlinks, etc. So, made the
State include that GitConfig, cached. The use of gitAnnexLocation is
within a (not $ Git.repoIsUrl repo) guard, so it's local, and so
its git config will always be read and available.

(Note that gitAnnexLocation in turn calls annexLocations, so the
Differences config it uses in this case comes from the remote repo's
GitConfig and not from the local repo's GitConfig. As explained above
this is ok since they must have the same value.)

Not very happy with this mess of different GitConfigs not type-safe and
some read only sometimes etc. Very hairy. Think I got it this change
right. Test suite passes..

This commit was sponsored by Ethan Aubin.
This commit is contained in:
Joey Hess 2018-06-05 14:23:34 -04:00
parent a5f598a6aa
commit 0f566ed242
No known key found for this signature in database
GPG key ID: DB12DB0FF05F8F38
6 changed files with 43 additions and 27 deletions

View file

@ -3,8 +3,10 @@ git-annex (6.20180530) UNRELEASED; urgency=medium
* Fix build with ghc 8.4+, which broke due to the Semigroup Monoid change. * Fix build with ghc 8.4+, which broke due to the Semigroup Monoid change.
* version: Show operating system and repository version list * version: Show operating system and repository version list
when run outside a git repo too. when run outside a git repo too.
* Fixed annex-checkuuid implementation, so that remotes configured that * Fix annex-checkuuid implementation, so that remotes configured that
way can be used. way can be used.
* Fix problems accessing repositories over http when annex.tune.*
is configured.
-- Joey Hess <id@joeyh.name> Wed, 30 May 2018 11:49:08 -0400 -- Joey Hess <id@joeyh.name> Wed, 30 May 2018 11:49:08 -0400

View file

@ -124,7 +124,7 @@ gen' r u c gc = do
, config = c , config = c
, localpath = localpathCalc r , localpath = localpathCalc r
, getRepo = return r , getRepo = return r
, gitconfig = gc { remoteGitConfig = extractGitConfig r } , gitconfig = gc
, readonly = Git.repoIsHttp r , readonly = Git.repoIsHttp r
, availability = availabilityCalc r , availability = availabilityCalc r
, remotetype = remote , remotetype = remote

View file

@ -176,7 +176,7 @@ gen r u c gc
, config = c , config = c
, localpath = localpathCalc r , localpath = localpathCalc r
, getRepo = getRepoFromState st , getRepo = getRepoFromState st
, gitconfig = gc { remoteGitConfig = extractGitConfig r } , gitconfig = gc
, readonly = Git.repoIsHttp r , readonly = Git.repoIsHttp r
, availability = availabilityCalc r , availability = availabilityCalc r
, remotetype = remote , remotetype = remote
@ -340,8 +340,9 @@ inAnnex' repo rmt (State connpool duc _) key
where where
checkhttp = do checkhttp = do
showChecking repo showChecking repo
gc <- Annex.getGitConfig
ifM (Url.withUrlOptions $ \uo -> liftIO $ ifM (Url.withUrlOptions $ \uo -> liftIO $
anyM (\u -> Url.checkBoth u (keySize key) uo) (keyUrls repo rmt key)) anyM (\u -> Url.checkBoth u (keySize key) uo) (keyUrls gc repo rmt key))
( return True ( return True
, giveup "not found" , giveup "not found"
) )
@ -355,22 +356,21 @@ inAnnex' repo rmt (State connpool duc _) key
, cantCheck repo , cantCheck repo
) )
keyUrls :: Git.Repo -> Remote -> Key -> [String] keyUrls :: GitConfig -> Git.Repo -> Remote -> Key -> [String]
keyUrls repo r key = map tourl locs' keyUrls gc repo r key = map tourl locs'
where where
tourl l = Git.repoLocation repo ++ "/" ++ l tourl l = Git.repoLocation repo ++ "/" ++ l
-- If the remote is known to not be bare, try the hash locations -- If the remote is known to not be bare, try the hash locations
-- used for non-bare repos first, as an optimisation. -- used for non-bare repos first, as an optimisation.
locs locs
| remoteAnnexBare remoteconfig == Just False = reverse (annexLocations cfg key) | remoteAnnexBare remoteconfig == Just False = reverse (annexLocations gc key)
| otherwise = annexLocations cfg key | otherwise = annexLocations gc key
#ifndef mingw32_HOST_OS #ifndef mingw32_HOST_OS
locs' = locs locs' = locs
#else #else
locs' = map (replace "\\" "/") locs locs' = map (replace "\\" "/") locs
#endif #endif
remoteconfig = gitconfig r remoteconfig = gitconfig r
cfg = remoteGitConfig remoteconfig
dropKey :: Remote -> State -> Key -> Annex Bool dropKey :: Remote -> State -> Key -> Annex Bool
dropKey r st key = do dropKey r st key = do
@ -471,8 +471,9 @@ copyFromRemote' forcersync r st key file dest meterupdate = do
copyFromRemote'' :: Git.Repo -> Bool -> Remote -> State -> Key -> AssociatedFile -> FilePath -> MeterUpdate -> Annex (Bool, Verification) copyFromRemote'' :: Git.Repo -> Bool -> Remote -> State -> Key -> AssociatedFile -> FilePath -> MeterUpdate -> Annex (Bool, Verification)
copyFromRemote'' repo forcersync r (State connpool _ _) key file dest meterupdate copyFromRemote'' repo forcersync r (State connpool _ _) key file dest meterupdate
| Git.repoIsHttp repo = unVerified $ | Git.repoIsHttp repo = unVerified $ do
Annex.Content.downloadUrl key meterupdate (keyUrls repo r key) dest gc <- Annex.getGitConfig
Annex.Content.downloadUrl key meterupdate (keyUrls gc repo r key) dest
| not $ Git.repoIsUrl repo = guardUsable repo (unVerified (return False)) $ do | not $ Git.repoIsUrl repo = guardUsable repo (unVerified (return False)) $ do
params <- Ssh.rsyncParams r Download params <- Ssh.rsyncParams r Download
u <- getUUID u <- getUUID
@ -567,10 +568,10 @@ copyFromRemoteCheap r st key af file = do
copyFromRemoteCheap' :: Git.Repo -> Remote -> State -> Key -> AssociatedFile -> FilePath -> Annex Bool copyFromRemoteCheap' :: Git.Repo -> Remote -> State -> Key -> AssociatedFile -> FilePath -> Annex Bool
#ifndef mingw32_HOST_OS #ifndef mingw32_HOST_OS
copyFromRemoteCheap' repo r st key af file copyFromRemoteCheap' repo r st key af file
| not $ Git.repoIsUrl repo = guardUsable repo (return False) $ liftIO $ do | not $ Git.repoIsUrl repo = guardUsable repo (return False) $ do
loc <- gitAnnexLocation key repo $ gc <- getGitConfigFromState st
remoteGitConfig $ gitconfig r loc <- liftIO $ gitAnnexLocation key repo gc
ifM (doesFileExist loc) liftIO $ ifM (doesFileExist loc)
( do ( do
absloc <- absPath loc absloc <- absPath loc
catchBoolIO $ do catchBoolIO $ do
@ -782,10 +783,14 @@ mkCopier remotewanthardlink rsyncparams = do
- This returns False when the repository UUID is not as expected. -} - This returns False when the repository UUID is not as expected. -}
type DeferredUUIDCheck = Annex Bool type DeferredUUIDCheck = Annex Bool
data State = State Ssh.P2PSshConnectionPool DeferredUUIDCheck (Annex Git.Repo) data State = State Ssh.P2PSshConnectionPool DeferredUUIDCheck (Annex (Git.Repo, GitConfig))
getRepoFromState :: State -> Annex Git.Repo getRepoFromState :: State -> Annex Git.Repo
getRepoFromState (State _ _ a) = a getRepoFromState (State _ _ a) = fst <$> a
{- The config of the remote git repository, cached for speed. -}
getGitConfigFromState :: State -> Annex GitConfig
getGitConfigFromState (State _ _ a) = snd <$> a
mkState :: Git.Repo -> UUID -> RemoteGitConfig -> Annex State mkState :: Git.Repo -> UUID -> RemoteGitConfig -> Annex State
mkState r u gc = do mkState r u gc = do
@ -794,21 +799,23 @@ mkState r u gc = do
return $ State pool duc getrepo return $ State pool duc getrepo
where where
go go
| remoteAnnexCheckUUID gc = return (return True, return r) | remoteAnnexCheckUUID gc = return
(return True, return (r, extractGitConfig r))
| otherwise = do | otherwise = do
rv <- liftIO newEmptyMVar rv <- liftIO newEmptyMVar
let getrepo = ifM (liftIO $ isEmptyMVar rv) let getrepo = ifM (liftIO $ isEmptyMVar rv)
( do ( do
r' <- tryGitConfigRead False r r' <- tryGitConfigRead False r
void $ liftIO $ tryPutMVar rv r' let t = (r', extractGitConfig r')
return r' void $ liftIO $ tryPutMVar rv t
return t
, liftIO $ readMVar rv , liftIO $ readMVar rv
) )
cv <- liftIO newEmptyMVar cv <- liftIO newEmptyMVar
let duc = ifM (liftIO $ isEmptyMVar cv) let duc = ifM (liftIO $ isEmptyMVar cv)
( do ( do
r' <- getrepo r' <- fst <$> getrepo
u' <- getRepoUUID r' u' <- getRepoUUID r'
let ok = u' == u let ok = u' == u
void $ liftIO $ tryPutMVar cv ok void $ liftIO $ tryPutMVar cv ok

View file

@ -65,7 +65,7 @@ chainGen addr r u c gc = do
, config = c , config = c
, localpath = Nothing , localpath = Nothing
, getRepo = return r , getRepo = return r
, gitconfig = gc { remoteGitConfig = extractGitConfig r } , gitconfig = gc
, readonly = False , readonly = False
, availability = GloballyAvailable , availability = GloballyAvailable
, remotetype = remote , remotetype = remote

View file

@ -19,6 +19,7 @@ import Common
import qualified Git import qualified Git
import qualified Git.Config import qualified Git.Config
import qualified Git.Construct import qualified Git.Construct
import Git.Types
import Git.ConfigTypes import Git.ConfigTypes
import Utility.DataUnits import Utility.DataUnits
import Config.Cost import Config.Cost
@ -195,7 +196,12 @@ mergeGitConfig gitconfig repoglobals = gitconfig
{- Per-remote git-annex settings. Each setting corresponds to a git-config {- Per-remote git-annex settings. Each setting corresponds to a git-config
- key such as <remote>.annex-foo, or if that is not set, a default from - key such as <remote>.annex-foo, or if that is not set, a default from
- annex.foo -} - annex.foo.
-
- Note that this is from the perspective of the local repository,
- it is not influenced in any way by the contents of the remote
- repository's git config.
-}
data RemoteGitConfig = RemoteGitConfig data RemoteGitConfig = RemoteGitConfig
{ remoteAnnexCost :: DynamicConfig (Maybe Cost) { remoteAnnexCost :: DynamicConfig (Maybe Cost)
, remoteAnnexIgnore :: DynamicConfig Bool , remoteAnnexIgnore :: DynamicConfig Bool
@ -235,11 +241,11 @@ data RemoteGitConfig = RemoteGitConfig
, remoteAnnexDdarRepo :: Maybe String , remoteAnnexDdarRepo :: Maybe String
, remoteAnnexHookType :: Maybe String , remoteAnnexHookType :: Maybe String
, remoteAnnexExternalType :: Maybe String , remoteAnnexExternalType :: Maybe String
{- A regular git remote's git repository config. -}
, remoteGitConfig :: GitConfig
} }
extractRemoteGitConfig :: Git.Repo -> String -> STM RemoteGitConfig {- The Git.Repo is the local repository, which has the remote with the
- given RemoteName. -}
extractRemoteGitConfig :: Git.Repo -> RemoteName -> STM RemoteGitConfig
extractRemoteGitConfig r remotename = do extractRemoteGitConfig r remotename = do
annexcost <- mkDynamicConfig readCommandRunner annexcost <- mkDynamicConfig readCommandRunner
(notempty $ getmaybe "cost-command") (notempty $ getmaybe "cost-command")
@ -288,7 +294,6 @@ extractRemoteGitConfig r remotename = do
, remoteAnnexDdarRepo = getmaybe "ddarrepo" , remoteAnnexDdarRepo = getmaybe "ddarrepo"
, remoteAnnexHookType = notempty $ getmaybe "hooktype" , remoteAnnexHookType = notempty $ getmaybe "hooktype"
, remoteAnnexExternalType = notempty $ getmaybe "externaltype" , remoteAnnexExternalType = notempty $ getmaybe "externaltype"
, remoteGitConfig = extractGitConfig r
} }
where where
getbool k d = fromMaybe d $ getmaybebool k getbool k d = fromMaybe d $ getmaybebool k

View file

@ -8,3 +8,5 @@ annex-checkuuid=false.
The best thing would be to remove remoteGitConfig, to avoid such problems The best thing would be to remove remoteGitConfig, to avoid such problems
in the future. --[[Joey]] in the future. --[[Joey]]
> [[done]] --[[Joey]]