convert configParser to Annex action and add passthrough option

Needed so Remote.External can query the external program for its
configs. When the external program does not support the query,
the passthrough option will make all input fields be available.
This commit is contained in:
Joey Hess 2020-01-14 13:18:15 -04:00
parent 8f142a9279
commit c498269a88
No known key found for this signature in database
GPG key ID: DB12DB0FF05F8F38
16 changed files with 70 additions and 47 deletions

View file

@ -93,8 +93,8 @@ importTree :: ParsedRemoteConfig -> Bool
importTree = fromMaybe False . getRemoteConfigValue importTreeField importTree = fromMaybe False . getRemoteConfigValue importTreeField
{- Parsers for fields that are common to all special remotes. -} {- Parsers for fields that are common to all special remotes. -}
commonFieldsParser :: [RemoteConfigParser] commonFieldParsers :: [RemoteConfigFieldParser]
commonFieldsParser = commonFieldParsers =
[ optionalStringParser nameField [ optionalStringParser nameField
, optionalStringParser sameasNameField , optionalStringParser sameasNameField
, optionalStringParser sameasUUIDField , optionalStringParser sameasUUIDField
@ -166,11 +166,13 @@ getRemoteConfigValue f m = case M.lookup f m of
] ]
Nothing -> Nothing Nothing -> Nothing
parseRemoteConfig :: RemoteConfig -> [RemoteConfigParser] -> Either String ParsedRemoteConfig parseRemoteConfig :: RemoteConfig -> RemoteConfigParser -> Either String ParsedRemoteConfig
parseRemoteConfig c ps = parseRemoteConfig c rpc =
go [] (M.filterWithKey notaccepted c) (ps ++ commonFieldsParser) go [] (M.filterWithKey notaccepted c) (remoteConfigFieldParsers rpc ++ commonFieldParsers)
where where
go l c' [] go l c' []
| remoteConfigRestPassthrough rpc = Right $ M.fromList $
l ++ map (uncurry passthrough) (M.toList c')
| M.null c' = Right (M.fromList l) | M.null c' = Right (M.fromList l)
| otherwise = Left $ "Unexpected fields: " ++ | otherwise = Left $ "Unexpected fields: " ++
unwords (map fromProposedAccepted (M.keys c')) unwords (map fromProposedAccepted (M.keys c'))
@ -179,19 +181,22 @@ parseRemoteConfig c ps =
case v of case v of
Just v' -> go ((f,v'):l) (M.delete f c') rest Just v' -> go ((f,v'):l) (M.delete f c') rest
Nothing -> go l (M.delete f c') rest Nothing -> go l (M.delete f c') rest
passthrough f v = (f, RemoteConfigValue (fromProposedAccepted v))
notaccepted (Proposed _) _ = True notaccepted (Proposed _) _ = True
notaccepted (Accepted _) _ = False notaccepted (Accepted _) _ = False
optionalStringParser :: RemoteConfigField -> RemoteConfigParser optionalStringParser :: RemoteConfigField -> RemoteConfigFieldParser
optionalStringParser f = (f, p) optionalStringParser f = (f, p)
where where
p (Just v) _c = Right (Just (RemoteConfigValue (fromProposedAccepted v))) p (Just v) _c = Right (Just (RemoteConfigValue (fromProposedAccepted v)))
p Nothing _c = Right Nothing p Nothing _c = Right Nothing
yesNoParser :: RemoteConfigField -> Bool -> RemoteConfigParser yesNoParser :: RemoteConfigField -> Bool -> RemoteConfigFieldParser
yesNoParser = genParser yesNo "yes or no" yesNoParser = genParser yesNo "yes or no"
trueFalseParser :: RemoteConfigField -> Bool -> RemoteConfigParser trueFalseParser :: RemoteConfigField -> Bool -> RemoteConfigFieldParser
trueFalseParser = genParser Git.Config.isTrueFalse "true or false" trueFalseParser = genParser Git.Config.isTrueFalse "true or false"
genParser genParser
@ -200,7 +205,7 @@ genParser
-> String -- ^ description of the value -> String -- ^ description of the value
-> RemoteConfigField -> RemoteConfigField
-> t -- ^ fallback value -> t -- ^ fallback value
-> RemoteConfigParser -> RemoteConfigFieldParser
genParser parse desc f fallback = (f, p) genParser parse desc f fallback = (f, p)
where where
p Nothing _c = Right (Just (RemoteConfigValue fallback)) p Nothing _c = Right (Just (RemoteConfigValue fallback))

View file

@ -1,6 +1,6 @@
{- Credentials storage {- Credentials storage
- -
- Copyright 2012-2014 Joey Hess <id@joeyh.name> - Copyright 2012-2020 Joey Hess <id@joeyh.name>
- -
- Licensed under the GNU AGPL version 3 or higher. - Licensed under the GNU AGPL version 3 or higher.
-} -}
@ -30,7 +30,7 @@ import Utility.FileMode
import Crypto import Crypto
import Types.Remote (RemoteConfig, RemoteConfigField) import Types.Remote (RemoteConfig, RemoteConfigField)
import Types.ProposedAccepted import Types.ProposedAccepted
import Remote.Helper.Encryptable (remoteCipher, remoteCipher', embedCreds, EncryptionIsSetup, extractCipher, encryptionConfigParser) import Remote.Helper.Encryptable (remoteCipher, remoteCipher', embedCreds, EncryptionIsSetup, extractCipher, parseEncryptionConfig)
import Utility.Env (getEnv) import Utility.Env (getEnv)
import qualified Data.ByteString.Lazy.Char8 as L import qualified Data.ByteString.Lazy.Char8 as L
@ -79,8 +79,7 @@ setRemoteCredPair encsetup c gc storage mcreds = case mcreds of
storeconfig creds key Nothing = storeconfig creds key Nothing =
return $ M.insert key (Accepted (toB64 $ encodeCredPair creds)) c return $ M.insert key (Accepted (toB64 $ encodeCredPair creds)) c
pc = either (const mempty) id pc = either (const mempty) id (parseEncryptionConfig c)
(parseRemoteConfig c encryptionConfigParser)
{- Gets a remote's credpair, from the environment if set, otherwise {- Gets a remote's credpair, from the environment if set, otherwise
- from the cache in gitAnnexCredsDir, or failing that, from the - from the cache in gitAnnexCredsDir, or failing that, from the

View file

@ -42,7 +42,8 @@ remote = specialRemoteType $ RemoteType
{ typename = "directory" { typename = "directory"
, enumerate = const (findSpecialRemotes "directory") , enumerate = const (findSpecialRemotes "directory")
, generate = gen , generate = gen
, configParser = [optionalStringParser directoryField] , configParser = mkRemoteConfigParser
[optionalStringParser directoryField]
, setup = directorySetup , setup = directorySetup
, exportSupported = exportIsSupported , exportSupported = exportIsSupported
, importSupported = importIsSupported , importSupported = importIsSupported

View file

@ -66,7 +66,8 @@ remote = specialRemoteType $ RemoteType
-- and will call our gen on them. -- and will call our gen on them.
, enumerate = const (return []) , enumerate = const (return [])
, generate = gen , generate = gen
, configParser = [optionalStringParser gitRepoField] , configParser = mkRemoteConfigParser
[optionalStringParser gitRepoField]
, setup = gCryptSetup , setup = gCryptSetup
, exportSupported = exportUnsupported , exportSupported = exportUnsupported
, importSupported = importUnsupported , importSupported = importUnsupported
@ -104,8 +105,9 @@ gen baser u c gc rs = do
v <- M.lookup u' <$> readRemoteLog v <- M.lookup u' <$> readRemoteLog
case (Git.remoteName baser, v) of case (Git.remoteName baser, v) of
(Just remotename, Just c') -> do (Just remotename, Just c') -> do
pc <- either giveup return $ pc <- either giveup return
parseRemoteConfig c' (configParser remote) . parseRemoteConfig c'
=<< configParser remote
setGcryptEncryption pc remotename setGcryptEncryption pc remotename
storeUUIDIn (remoteConfig baser "uuid") u' storeUUIDIn (remoteConfig baser "uuid") u'
setConfig (Git.GCrypt.remoteConfigKey "gcrypt-id" remotename) gcryptid setConfig (Git.GCrypt.remoteConfigKey "gcrypt-id" remotename) gcryptid
@ -214,8 +216,8 @@ gCryptSetup _ mu _ c gc = go $ fromProposedAccepted <$> M.lookup gitRepoField c
| Git.repoLocation r == url -> noop | Git.repoLocation r == url -> noop
| otherwise -> error "Another remote with the same name already exists." | otherwise -> error "Another remote with the same name already exists."
pc <- either giveup return $ pc <- either giveup return . parseRemoteConfig c'
parseRemoteConfig c' (configParser remote) =<< configParser remote
setGcryptEncryption pc remotename setGcryptEncryption pc remotename
{- Run a git fetch and a push to the git repo in order to get {- Run a git fetch and a push to the git repo in order to get

View file

@ -80,7 +80,8 @@ remote = RemoteType
{ typename = "git" { typename = "git"
, enumerate = list , enumerate = list
, generate = gen , generate = gen
, configParser = [optionalStringParser locationField] , configParser = mkRemoteConfigParser
[optionalStringParser locationField]
, setup = gitSetup , setup = gitSetup
, exportSupported = exportUnsupported , exportSupported = exportUnsupported
, importSupported = importUnsupported , importSupported = importUnsupported

View file

@ -60,7 +60,8 @@ remote = specialRemoteType $ RemoteType
-- and will call our gen on them. -- and will call our gen on them.
, enumerate = const (return []) , enumerate = const (return [])
, generate = gen , generate = gen
, configParser = [optionalStringParser urlField] , configParser = mkRemoteConfigParser
[optionalStringParser urlField]
, setup = mySetup , setup = mySetup
, exportSupported = exportUnsupported , exportSupported = exportUnsupported
, importSupported = importUnsupported , importSupported = importUnsupported
@ -133,7 +134,7 @@ mySetup _ mu _ c gc = do
u <- maybe (liftIO genUUID) return mu u <- maybe (liftIO genUUID) return mu
(c', _encsetup) <- encryptionSetup c gc (c', _encsetup) <- encryptionSetup c gc
pc <- either giveup return $ parseRemoteConfig c' (configParser remote) pc <- either giveup return . parseRemoteConfig c' =<< configParser remote
case (isEncrypted pc, Git.GCrypt.urlPrefix `isPrefixOf` url) of case (isEncrypted pc, Git.GCrypt.urlPrefix `isPrefixOf` url) of
(False, False) -> noop (False, False) -> noop
(True, True) -> Remote.GCrypt.setGcryptEncryption pc remotename (True, True) -> Remote.GCrypt.setGcryptEncryption pc remotename

View file

@ -10,7 +10,7 @@ module Remote.Helper.Chunked (
ChunkConfig(..), ChunkConfig(..),
noChunks, noChunks,
describeChunkConfig, describeChunkConfig,
chunkConfigParser, chunkConfigParsers,
getChunkConfig, getChunkConfig,
storeChunks, storeChunks,
removeChunks, removeChunks,
@ -49,8 +49,8 @@ noChunks :: ChunkConfig -> Bool
noChunks NoChunks = True noChunks NoChunks = True
noChunks _ = False noChunks _ = False
chunkConfigParser :: [RemoteConfigParser] chunkConfigParsers :: [RemoteConfigFieldParser]
chunkConfigParser = chunkConfigParsers =
[ optionalStringParser chunksizeField [ optionalStringParser chunksizeField
, optionalStringParser chunkField , optionalStringParser chunkField
] ]

View file

@ -12,7 +12,7 @@ module Remote.Helper.Encryptable (
encryptionSetup, encryptionSetup,
noEncryptionUsed, noEncryptionUsed,
encryptionAlreadySetup, encryptionAlreadySetup,
encryptionConfigParser, encryptionConfigParsers,
parseEncryptionConfig, parseEncryptionConfig,
remoteCipher, remoteCipher,
remoteCipher', remoteCipher',
@ -51,8 +51,8 @@ noEncryptionUsed = NoEncryption
encryptionAlreadySetup :: EncryptionIsSetup encryptionAlreadySetup :: EncryptionIsSetup
encryptionAlreadySetup = EncryptionIsSetup encryptionAlreadySetup = EncryptionIsSetup
encryptionConfigParser :: [RemoteConfigParser] encryptionConfigParsers :: [RemoteConfigFieldParser]
encryptionConfigParser = encryptionConfigParsers =
[ (encryptionField, \v c -> Just . RemoteConfigValue <$> parseEncryptionMethod (fmap fromProposedAccepted v) c) [ (encryptionField, \v c -> Just . RemoteConfigValue <$> parseEncryptionMethod (fmap fromProposedAccepted v) c)
, optionalStringParser cipherField , optionalStringParser cipherField
, optionalStringParser cipherkeysField , optionalStringParser cipherkeysField
@ -66,11 +66,13 @@ encryptionConfigParser =
] ]
encryptionConfigs :: S.Set RemoteConfigField encryptionConfigs :: S.Set RemoteConfigField
encryptionConfigs = S.fromList (map fst encryptionConfigParser) encryptionConfigs = S.fromList (map fst encryptionConfigParsers)
-- Parse only encryption fields, ignoring all others. -- Parse only encryption fields, ignoring all others.
parseEncryptionConfig :: RemoteConfig -> Either String ParsedRemoteConfig parseEncryptionConfig :: RemoteConfig -> Either String ParsedRemoteConfig
parseEncryptionConfig c = parseRemoteConfig (M.restrictKeys c encryptionConfigs) encryptionConfigParser parseEncryptionConfig c = parseRemoteConfig
(M.restrictKeys c encryptionConfigs)
(RemoteConfigParser encryptionConfigParsers False)
parseEncryptionMethod :: Maybe String -> RemoteConfig -> Either String EncryptionMethod parseEncryptionMethod :: Maybe String -> RemoteConfig -> Either String EncryptionMethod
parseEncryptionMethod (Just "none") _ = Right NoneEncryption parseEncryptionMethod (Just "none") _ = Right NoneEncryption

View file

@ -77,9 +77,10 @@ adjustExportImportRemoteType rt = rt
, configParser = configparser , configParser = configparser
} }
where where
configparser = configParser rt ++ exportImportConfigParser configparser = addRemoteConfigParser exportImportConfigParsers
<$> configParser rt
setup' st mu cp c gc = do setup' st mu cp c gc = do
pc <- either giveup return $ parseRemoteConfig c configparser pc <- either giveup return . parseRemoteConfig c =<< configparser
let checkconfig supported configured configfield cont = let checkconfig supported configured configfield cont =
ifM (supported rt pc gc) ifM (supported rt pc gc)
( case st of ( case st of
@ -87,9 +88,9 @@ adjustExportImportRemoteType rt = rt
| configured pc && isEncrypted pc -> | configured pc && isEncrypted pc ->
giveup $ "cannot enable both encryption and " ++ fromProposedAccepted configfield giveup $ "cannot enable both encryption and " ++ fromProposedAccepted configfield
| otherwise -> cont | otherwise -> cont
Enable oldc -> Enable oldc -> do
let oldpc = either mempty id $ parseRemoteConfig oldc configparser oldpc <- either mempty id . parseRemoteConfig oldc <$> configparser
in if configured pc /= configured oldpc if configured pc /= configured oldpc
then giveup $ "cannot change " ++ fromProposedAccepted configfield ++ " of existing special remote" then giveup $ "cannot change " ++ fromProposedAccepted configfield ++ " of existing special remote"
else cont else cont
, if configured pc , if configured pc
@ -102,8 +103,8 @@ adjustExportImportRemoteType rt = rt
then giveup "cannot enable importtree=yes without also enabling exporttree=yes" then giveup "cannot enable importtree=yes without also enabling exporttree=yes"
else setup rt st mu cp c gc else setup rt st mu cp c gc
exportImportConfigParser :: [RemoteConfigParser] exportImportConfigParsers :: [RemoteConfigFieldParser]
exportImportConfigParser = exportImportConfigParsers =
[ yesNoParser exportTreeField False [ yesNoParser exportTreeField False
, yesNoParser importTreeField False , yesNoParser importTreeField False
] ]

View file

@ -28,7 +28,6 @@ module Remote.Helper.Special (
retreiveKeyFileDummy, retreiveKeyFileDummy,
removeKeyDummy, removeKeyDummy,
checkPresentDummy, checkPresentDummy,
specialRemoteConfigParser,
SpecialRemoteCfg(..), SpecialRemoteCfg(..),
specialRemoteCfg, specialRemoteCfg,
specialRemoteType, specialRemoteType,
@ -170,11 +169,12 @@ specialRemoteCfg c = SpecialRemoteCfg (getChunkConfig c) True
-- Modifies a base RemoteType to support chunking and encryption configs. -- Modifies a base RemoteType to support chunking and encryption configs.
specialRemoteType :: RemoteType -> RemoteType specialRemoteType :: RemoteType -> RemoteType
specialRemoteType r = r specialRemoteType r = r
{ configParser = configParser r ++ specialRemoteConfigParser { configParser = addRemoteConfigParser specialRemoteConfigParsers
<$> configParser r
} }
specialRemoteConfigParser :: [RemoteConfigParser] specialRemoteConfigParsers :: [RemoteConfigFieldParser]
specialRemoteConfigParser = chunkConfigParser ++ encryptionConfigParser specialRemoteConfigParsers = chunkConfigParsers ++ encryptionConfigParsers
-- Modifies a base Remote to support both chunking and encryption, -- Modifies a base Remote to support both chunking and encryption,
-- which special remotes typically should support. -- which special remotes typically should support.

View file

@ -122,7 +122,7 @@ remoteGen m t g = do
let cu = fromMaybe u $ remoteAnnexConfigUUID gc let cu = fromMaybe u $ remoteAnnexConfigUUID gc
let rs = RemoteStateHandle cu let rs = RemoteStateHandle cu
let c = fromMaybe M.empty $ M.lookup cu m let c = fromMaybe M.empty $ M.lookup cu m
let pc = either mempty id (parseRemoteConfig c (configParser t)) pc <- either mempty id . parseRemoteConfig c <$> configParser t
generate t g u pc gc rs >>= \case generate t g u pc gc rs >>= \case
Nothing -> return Nothing Nothing -> return Nothing
Just r -> Just <$> adjustExportImport (adjustReadOnly (addHooks r)) rs Just r -> Just <$> adjustExportImport (adjustReadOnly (addHooks r)) rs

View file

@ -36,7 +36,7 @@ remote = RemoteType
-- and will call chainGen on them. -- and will call chainGen on them.
, enumerate = const (return []) , enumerate = const (return [])
, generate = \_ _ _ _ _ -> return Nothing , generate = \_ _ _ _ _ -> return Nothing
, configParser = [] , configParser = mkRemoteConfigParser []
, setup = error "P2P remotes are set up using git-annex p2p" , setup = error "P2P remotes are set up using git-annex p2p"
, exportSupported = exportUnsupported , exportSupported = exportUnsupported
, importSupported = importUnsupported , importSupported = importUnsupported

View file

@ -51,7 +51,7 @@ remote = specialRemoteType $ RemoteType
{ typename = "rsync" { typename = "rsync"
, enumerate = const (findSpecialRemotes "rsyncurl") , enumerate = const (findSpecialRemotes "rsyncurl")
, generate = gen , generate = gen
, configParser = , configParser = mkRemoteConfigParser
[ yesNoParser shellEscapeField True [ yesNoParser shellEscapeField True
, optionalStringParser rsyncUrlField , optionalStringParser rsyncUrlField
] ]

View file

@ -27,7 +27,7 @@ remote = RemoteType
{ typename = "web" { typename = "web"
, enumerate = list , enumerate = list
, generate = gen , generate = gen
, configParser = [] , configParser = mkRemoteConfigParser []
, setup = error "not supported" , setup = error "not supported"
, exportSupported = exportUnsupported , exportSupported = exportUnsupported
, importSupported = importUnsupported , importSupported = importUnsupported

View file

@ -60,7 +60,7 @@ data RemoteTypeA a = RemoteType
-- generates a remote of this type -- generates a remote of this type
, generate :: Git.Repo -> UUID -> ParsedRemoteConfig -> RemoteGitConfig -> RemoteStateHandle -> a (Maybe (RemoteA a)) , generate :: Git.Repo -> UUID -> ParsedRemoteConfig -> RemoteGitConfig -> RemoteStateHandle -> a (Maybe (RemoteA a))
-- parse configs of remotes of this type -- parse configs of remotes of this type
, configParser :: [RemoteConfigParser] , configParser :: a RemoteConfigParser
-- initializes or enables a remote -- initializes or enables a remote
, setup :: SetupStage -> Maybe UUID -> Maybe CredPair -> RemoteConfig -> RemoteGitConfig -> a (RemoteConfig, UUID) , setup :: SetupStage -> Maybe UUID -> Maybe CredPair -> RemoteConfig -> RemoteGitConfig -> a (RemoteConfig, UUID)
-- check if a remote of this type is able to support export -- check if a remote of this type is able to support export

View file

@ -37,4 +37,15 @@ data RemoteConfigValue where
- Presence of fields that are not included in this list will cause - Presence of fields that are not included in this list will cause
- a parse failure. - a parse failure.
-} -}
type RemoteConfigParser = (RemoteConfigField, Maybe (ProposedAccepted String) -> RemoteConfig -> Either String (Maybe RemoteConfigValue)) type RemoteConfigFieldParser = (RemoteConfigField, Maybe (ProposedAccepted String) -> RemoteConfig -> Either String (Maybe RemoteConfigValue))
data RemoteConfigParser = RemoteConfigParser
{ remoteConfigFieldParsers :: [RemoteConfigFieldParser]
, remoteConfigRestPassthrough :: Bool
}
mkRemoteConfigParser :: Monad m => [RemoteConfigFieldParser] -> m RemoteConfigParser
mkRemoteConfigParser l = pure (RemoteConfigParser l False)
addRemoteConfigParser :: [RemoteConfigFieldParser] -> RemoteConfigParser -> RemoteConfigParser
addRemoteConfigParser l rpc = rpc { remoteConfigFieldParsers = remoteConfigFieldParsers rpc ++ l }