set annex-config-uuid when RemoteConfig contains a sameas-uuid

Initremote sets that, so after both initremote and enableremote,
the git config will be set.

Any remote that does not use Annex.SpecialRemote won't set
annex-config-uuid. But that's only Remote.Git, which doesn't use
RemoteConfig anyway.
This commit is contained in:
Joey Hess 2019-10-10 12:48:26 -04:00
parent 46071a2435
commit 92ff30df70
No known key found for this signature in database
GPG key ID: DB12DB0FF05F8F38
5 changed files with 45 additions and 24 deletions

View file

@ -8,6 +8,7 @@
module Annex.SpecialRemote where
import Annex.Common
import Annex.SpecialRemote.Config
import Remote (remoteTypes, remoteMap)
import Types.Remote (RemoteConfig, RemoteConfigKey, SetupStage(..), typename, setup)
import Types.GitConfig
@ -57,9 +58,6 @@ specialRemoteMap = do
Nothing -> Nothing
Just n -> Just (u, n)
lookupName :: RemoteConfig -> Maybe RemoteName
lookupName c = M.lookup nameKey c <|> M.lookup sameasNameKey c
{- find the remote type -}
findType :: RemoteConfig -> Either String RemoteType
findType config = maybe unspecified specified $ M.lookup typeKey config
@ -70,26 +68,6 @@ findType config = maybe unspecified specified $ M.lookup typeKey config
(t:_) -> Right t
findtype s i = typename i == s
{- The name of a configured remote is stored in its config using this key. -}
nameKey :: RemoteConfigKey
nameKey = "name"
{- The name of a sameas remote is stored using this key instead.
- This prevents old versions of git-annex getting confused. -}
sameasNameKey :: RemoteConfigKey
sameasNameKey = "sameas-name"
{- The uuid that a sameas remote is the same as is stored in this key. -}
sameasUUIDKey :: RemoteConfigKey
sameasUUIDKey = "sameas-uuid"
{- The type of a remote is stored in its config using this key. -}
typeKey :: RemoteConfigKey
typeKey = "type"
autoEnableKey :: RemoteConfigKey
autoEnableKey = "autoenable"
autoEnable :: Annex ()
autoEnable = do
remotemap <- M.filter configured <$> readRemoteLog

View file

@ -0,0 +1,37 @@
{- git-annex special remote configuration
-
- Copyright 2019 Joey Hess <id@joeyh.name>
-
- Licensed under the GNU AGPL version 3 or higher.
-}
module Annex.SpecialRemote.Config where
import Common
import Types.Remote (RemoteConfigKey, RemoteConfig)
import qualified Data.Map as M
{- The name of a configured remote is stored in its config using this key. -}
nameKey :: RemoteConfigKey
nameKey = "name"
{- The name of a sameas remote is stored using this key instead.
- This prevents old versions of git-annex getting confused. -}
sameasNameKey :: RemoteConfigKey
sameasNameKey = "sameas-name"
lookupName :: RemoteConfig -> Maybe String
lookupName c = M.lookup nameKey c <|> M.lookup sameasNameKey c
{- The uuid that a sameas remote is the same as is stored in this key. -}
sameasUUIDKey :: RemoteConfigKey
sameasUUIDKey = "sameas-uuid"
{- The type of a remote is stored in its config using this key. -}
typeKey :: RemoteConfigKey
typeKey = "type"
autoEnableKey :: RemoteConfigKey
autoEnableKey = "autoenable"

View file

@ -19,6 +19,7 @@ import Config.DynamicConfig
import Types.Availability
import Git.Types
import qualified Types.Remote as Remote
import qualified Annex.SpecialRemote.Config as SpecialRemote
import qualified Data.Map as M
@ -62,7 +63,7 @@ instance RemoteNameable Remote where
getRemoteName = Remote.name
instance RemoteNameable Remote.RemoteConfig where
getRemoteName c = fromMaybe "" (M.lookup "name" c)
getRemoteName c = fromMaybe "" (SpecialRemote.lookupName c)
{- A per-remote config setting in git config. -}
remoteConfig :: RemoteNameable r => r -> UnqualifiedConfigKey -> ConfigKey

View file

@ -35,6 +35,7 @@ module Remote.Helper.Special (
import Annex.Common
import qualified Annex
import Annex.SpecialRemote.Config
import Types.StoreRetrieve
import Types.Remote
import Crypto
@ -72,6 +73,9 @@ gitConfigSpecialRemote u c cfgs = do
forM_ cfgs $ \(k, v) ->
setConfig (remoteConfig c k) v
storeUUIDIn (remoteConfig c "uuid") u
case M.lookup sameasUUIDKey c of
Nothing -> noop
Just sameasuuid -> setConfig (remoteConfig c "config-uuid") sameasuuid
-- RetrievalVerifiableKeysSecure unless overridden by git config.
--

View file

@ -653,6 +653,7 @@ Executable git-annex
Annex.ReplaceFile
Annex.RemoteTrackingBranch
Annex.SpecialRemote
Annex.SpecialRemote.Config
Annex.Ssh
Annex.TaggedPush
Annex.Tmp