rename RemoteConfigKey to RemoteConfigField

And some associated renames.
I was going to have some values named fooKeyKey otherwise..
This commit is contained in:
Joey Hess 2019-10-10 15:31:10 -04:00
parent d1130ea04a
commit 59908586f4
No known key found for this signature in database
GPG key ID: DB12DB0FF05F8F38
11 changed files with 39 additions and 39 deletions

View file

@ -10,7 +10,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.Remote (RemoteConfig, SetupStage(..), typename, setup)
import Types.GitConfig
import Logs.Remote
import Logs.Trust
@ -34,10 +34,10 @@ findExisting name = do
<$> Logs.Remote.readRemoteLog
newConfig :: RemoteName -> Maybe (Sameas UUID) -> RemoteConfig
newConfig name Nothing = M.singleton nameKey name
newConfig name Nothing = M.singleton nameField name
newConfig name (Just (Sameas u)) = M.fromList
[ (sameasNameKey, name)
, (sameasUUIDKey, fromUUID u)
[ (sameasNameField, name)
, (sameasUUIDField, fromUUID u)
]
findByName :: RemoteName -> M.Map UUID RemoteConfig -> [(UUID, RemoteConfig)]
@ -60,7 +60,7 @@ specialRemoteMap = do
{- find the remote type -}
findType :: RemoteConfig -> Either String RemoteType
findType config = maybe unspecified specified $ M.lookup typeKey config
findType config = maybe unspecified specified $ M.lookup typeField config
where
unspecified = Left "Specify the type of remote with type="
specified s = case filter (findtype s) remoteTypes of
@ -83,5 +83,5 @@ autoEnable = do
_ -> return ()
where
configured rc = fromMaybe False $
Git.Config.isTrue =<< M.lookup autoEnableKey rc
Git.Config.isTrue =<< M.lookup autoEnableField rc
canenable u = (/= DeadTrusted) <$> lookupTrust u

View file

@ -8,30 +8,30 @@
module Annex.SpecialRemote.Config where
import Common
import Types.Remote (RemoteConfigKey, RemoteConfig)
import Types.Remote (RemoteConfigField, 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"
nameField :: RemoteConfigField
nameField = "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"
sameasNameField :: RemoteConfigField
sameasNameField = "sameas-name"
lookupName :: RemoteConfig -> Maybe String
lookupName c = M.lookup nameKey c <|> M.lookup sameasNameKey c
lookupName c = M.lookup nameField c <|> M.lookup sameasNameField c
{- The uuid that a sameas remote is the same as is stored in this key. -}
sameasUUIDKey :: RemoteConfigKey
sameasUUIDKey = "sameas-uuid"
sameasUUIDField :: RemoteConfigField
sameasUUIDField = "sameas-uuid"
{- The type of a remote is stored in its config using this key. -}
typeKey :: RemoteConfigKey
typeKey = "type"
typeField :: RemoteConfigField
typeField = "type"
autoEnableKey :: RemoteConfigKey
autoEnableKey = "autoenable"
autoEnableField :: RemoteConfigField
autoEnableField = "autoenable"

View file

@ -9,7 +9,7 @@ module Assistant.Gpg where
import Utility.Gpg
import Utility.UserInfo
import Types.Remote (RemoteConfigKey)
import Types.Remote (RemoteConfigField)
import qualified Data.Map as M
import Control.Applicative
@ -30,7 +30,7 @@ data EnableEncryption = HybridEncryption | SharedEncryption | NoEncryption
deriving (Eq)
{- Generates Remote configuration for encryption. -}
configureEncryption :: EnableEncryption -> (RemoteConfigKey, String)
configureEncryption :: EnableEncryption -> (RemoteConfigField, String)
configureEncryption SharedEncryption = ("encryption", "shared")
configureEncryption NoEncryption = ("encryption", "none")
configureEncryption HybridEncryption = ("encryption", "hybrid")

View file

@ -547,9 +547,9 @@ makeSshRepo rs sshdata
let c = fromMaybe M.empty (M.lookup (Remote.uuid r) m)
let c' = M.insert "location" (genSshUrl sshdata) $
M.insert "type" "git" $
case M.lookup nameKey c of
case M.lookup nameField c of
Just _ -> c
Nothing -> M.insert nameKey (Remote.name r) c
Nothing -> M.insert nameField (Remote.name r) c
configSet (Remote.uuid r) c'
makeSshRepoConnection :: RepoStatus -> Annex RemoteName -> (Remote -> Annex ()) -> Handler Html

View file

@ -9,7 +9,7 @@ module Command.RenameRemote where
import Command
import qualified Annex.SpecialRemote
import Annex.SpecialRemote.Config (nameKey, sameasNameKey)
import Annex.SpecialRemote.Config (nameField, sameasNameField)
import qualified Logs.Remote
import qualified Types.Remote as R
import qualified Remote
@ -47,9 +47,9 @@ start _ = giveup "Specify an old name (or uuid or description) and a new name."
perform :: UUID -> R.RemoteConfig -> String -> CommandPerform
perform u cfg newname = do
let namekey = case M.lookup sameasNameKey cfg of
Just _ -> sameasNameKey
Nothing -> nameKey
Logs.Remote.configSet u (M.insert namekey newname cfg)
let namefield = case M.lookup sameasNameField cfg of
Just _ -> sameasNameField
Nothing -> nameField
Logs.Remote.configSet u (M.insert namefield newname cfg)
next $ return True

View file

@ -26,7 +26,7 @@ import Types.Creds
import Annex.Perms
import Utility.FileMode
import Crypto
import Types.Remote (RemoteConfig, RemoteConfigKey)
import Types.Remote (RemoteConfig, RemoteConfigField)
import Remote.Helper.Encryptable (remoteCipher, remoteCipher', embedCreds, EncryptionIsSetup, extractCipher)
import Utility.Env (getEnv)
@ -39,7 +39,7 @@ import Utility.Base64
data CredPairStorage = CredPairStorage
{ credPairFile :: FilePath
, credPairEnvironment :: (String, String)
, credPairRemoteKey :: RemoteConfigKey
, credPairRemoteField :: RemoteConfigField
}
{- Stores creds in a remote's configuration, if the remote allows
@ -58,7 +58,7 @@ setRemoteCredPair encsetup c gc storage mcreds = case mcreds of
=<< getRemoteCredPair c gc storage
Just creds
| embedCreds c ->
let key = credPairRemoteKey storage
let key = credPairRemoteField storage
in storeconfig creds key =<< flip remoteCipher gc =<< localcache creds
| otherwise -> localcache creds
where
@ -84,7 +84,7 @@ getRemoteCredPair c gc storage = maybe fromcache (return . Just) =<< fromenv
fromenv = liftIO $ getEnvCredPair storage
fromcache = maybe fromconfig (return . Just) =<< readCacheCredPair storage
fromconfig = do
let key = credPairRemoteKey storage
let key = credPairRemoteField storage
mcipher <- remoteCipher' c gc
case (M.lookup key c, mcipher) of
(Nothing, _) -> return Nothing
@ -190,7 +190,7 @@ includeCredsInfo c storage info = do
Just _ -> do
let (uenv, penv) = credPairEnvironment storage
ret $ "from environment variables (" ++ unwords [uenv, penv] ++ ")"
Nothing -> case (`M.lookup` c) (credPairRemoteKey storage) of
Nothing -> case (`M.lookup` c) (credPairRemoteField storage) of
Nothing -> ifM (existsCacheCredPair storage)
( ret "stored locally"
, ret "not available"

View file

@ -442,7 +442,7 @@ handleRequest' st external req mp responsehandler
credstorage setting = CredPairStorage
{ credPairFile = base
, credPairEnvironment = (base ++ "login", base ++ "password")
, credPairRemoteKey = setting
, credPairRemoteField = setting
}
where
base = replace "/" "_" $ fromUUID (externalUUID external) ++ "-" ++ setting

View file

@ -23,7 +23,7 @@ creds :: UUID -> CredPairStorage
creds u = CredPairStorage
{ credPairFile = fromUUID u
, credPairEnvironment = ("AWS_ACCESS_KEY_ID", "AWS_SECRET_ACCESS_KEY")
, credPairRemoteKey = "s3creds"
, credPairRemoteField = "s3creds"
}
data Service = S3 | Glacier

View file

@ -74,7 +74,7 @@ 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
case M.lookup sameasUUIDField c of
Nothing -> noop
Just sameasuuid -> setConfig (remoteConfig c "config-uuid") sameasuuid

View file

@ -341,7 +341,7 @@ davCreds :: UUID -> CredPairStorage
davCreds u = CredPairStorage
{ credPairFile = fromUUID u
, credPairEnvironment = ("WEBDAV_USERNAME", "WEBDAV_PASSWORD")
, credPairRemoteKey = "davcreds"
, credPairRemoteField = "davcreds"
}
{- Content-Type to use for files uploaded to WebDAV. -}

View file

@ -10,7 +10,7 @@
{-# LANGUAGE RankNTypes #-}
module Types.Remote
( RemoteConfigKey
( RemoteConfigField
, RemoteConfig
, RemoteTypeA(..)
, RemoteA(..)
@ -47,9 +47,9 @@ import Utility.SafeCommand
import Utility.Url
import Utility.DataUnits
type RemoteConfigKey = String
type RemoteConfigField = String
type RemoteConfig = M.Map RemoteConfigKey String
type RemoteConfig = M.Map RemoteConfigField String
data SetupStage = Init | Enable RemoteConfig