2020-01-13 16:35:39 +00:00
|
|
|
{- git-annex remote config types
|
|
|
|
-
|
|
|
|
- Copyright 2020 Joey Hess <id@joeyh.name>
|
|
|
|
-
|
|
|
|
- Licensed under the GNU AGPL version 3 or higher.
|
|
|
|
-}
|
|
|
|
|
|
|
|
{-# LANGUAGE GADTs #-}
|
|
|
|
|
|
|
|
module Types.RemoteConfig where
|
|
|
|
|
|
|
|
import qualified Data.Map as M
|
2020-01-17 21:11:55 +00:00
|
|
|
import qualified Data.Set as S
|
2020-01-13 16:35:39 +00:00
|
|
|
import Data.Typeable
|
|
|
|
|
|
|
|
import Types.ProposedAccepted
|
|
|
|
|
|
|
|
type RemoteConfigField = ProposedAccepted String
|
|
|
|
|
|
|
|
{- What the user provides to configure the remote, and what is stored for
|
|
|
|
- later; a bunch of fields and values. -}
|
|
|
|
type RemoteConfig = M.Map RemoteConfigField (ProposedAccepted String)
|
|
|
|
|
|
|
|
{- Before being used a RemoteConfig has to be parsed. -}
|
fix encryption of content to gcrypt and git-lfs
Fix serious regression in gcrypt and encrypted git-lfs remotes.
Since version 7.20200202.7, git-annex incorrectly stored content
on those remotes without encrypting it.
Problem was, Remote.Git enumerates all git remotes, including git-lfs
and gcrypt. It then dispatches to those. So, Remote.List used the
RemoteConfigParser from Remote.Git, instead of from git-lfs or gcrypt,
and that parser does not know about encryption fields, so did not
include them in the ParsedRemoteConfig. (Also didn't include other
fields specific to those remotes, perhaps chunking etc also didn't
get through.)
To fix, had to move RemoteConfig parsing down into the generate methods
of each remote, rather than doing it in Remote.List.
And a consequence of that was that ParsedRemoteConfig had to change to
include the RemoteConfig that got parsed, so that testremote can
generate a new remote based on an existing remote.
(I would have rather fixed this just inside Remote.Git, but that was not
practical, at least not w/o re-doing work that Remote.List already did.
Big ugly mostly mechanical patch seemed preferable to making git-annex
slower.)
2020-02-26 21:20:56 +00:00
|
|
|
data ParsedRemoteConfig = ParsedRemoteConfig
|
2020-03-09 16:38:04 +00:00
|
|
|
{ parsedRemoteConfigMap :: M.Map RemoteConfigField RemoteConfigValue
|
|
|
|
, unparsedRemoteConfig :: RemoteConfig
|
|
|
|
}
|
2020-01-13 16:35:39 +00:00
|
|
|
|
|
|
|
{- Remotes can have configuration values of many types, so use Typeable
|
|
|
|
- to let them all be stored in here. -}
|
|
|
|
data RemoteConfigValue where
|
|
|
|
RemoteConfigValue :: Typeable v => v -> RemoteConfigValue
|
|
|
|
|
|
|
|
{- Parse a field's value provided by the user into a RemoteConfigValue.
|
|
|
|
-
|
|
|
|
- The RemoteConfig is provided to the parser function for cases
|
|
|
|
- where multiple fields need to be looked at. However, it's important
|
|
|
|
- that, when a parser looks at an additional field in that way, the
|
|
|
|
- parser list contains a dedicated parser for that field as well.
|
|
|
|
- Presence of fields that are not included in this list will cause
|
|
|
|
- a parse failure.
|
|
|
|
-}
|
2020-01-20 17:49:30 +00:00
|
|
|
data RemoteConfigFieldParser = RemoteConfigFieldParser
|
|
|
|
{ parserForField :: RemoteConfigField
|
|
|
|
, valueParser :: Maybe (ProposedAccepted String) -> RemoteConfig -> Either String (Maybe RemoteConfigValue)
|
2020-01-20 19:20:04 +00:00
|
|
|
, fieldDesc :: FieldDesc
|
|
|
|
, valueDesc :: Maybe ValueDesc
|
2020-01-20 17:49:30 +00:00
|
|
|
}
|
2020-01-14 17:18:15 +00:00
|
|
|
|
2020-01-20 19:20:04 +00:00
|
|
|
data FieldDesc
|
|
|
|
= FieldDesc String
|
|
|
|
| HiddenField
|
|
|
|
|
|
|
|
newtype ValueDesc = ValueDesc String
|
|
|
|
|
2020-01-14 17:18:15 +00:00
|
|
|
data RemoteConfigParser = RemoteConfigParser
|
|
|
|
{ remoteConfigFieldParsers :: [RemoteConfigFieldParser]
|
2020-01-20 20:23:35 +00:00
|
|
|
, remoteConfigRestPassthrough :: Maybe (RemoteConfigField -> Bool, [(String, FieldDesc)])
|
2020-01-14 17:18:15 +00:00
|
|
|
}
|
|
|
|
|
add LISTCONFIGS to external special remote protocol
Special remote programs that use GETCONFIG/SETCONFIG are recommended
to implement it.
The description is not yet used, but will be useful later when adding a way
to make initremote list all accepted configs.
configParser now takes a RemoteConfig parameter. Normally, that's not
needed, because configParser returns a parter, it does not parse it
itself. But, it's needed to look at externaltype and work out what
external remote program to run for LISTCONFIGS.
Note that, while externalUUID is changed to a Maybe UUID, checkExportSupported
used to use NoUUID. The code that now checks for Nothing used to behave
in some undefined way if the external program made requests that
triggered it.
Also, note that in externalSetup, once it generates external,
it parses the RemoteConfig strictly. That generates a
ParsedRemoteConfig, which is thrown away. The reason it's ok to throw
that away, is that, if the strict parse succeeded, the result must be
the same as the earlier, lenient parse.
initremote of an external special remote now runs the program three
times. First for LISTCONFIGS, then EXPORTSUPPORTED, and again
LISTCONFIGS+INITREMOTE. It would not be hard to eliminate at least
one of those, and it should be possible to only run the program once.
2020-01-17 19:30:14 +00:00
|
|
|
mkRemoteConfigParser :: Monad m => [RemoteConfigFieldParser] -> RemoteConfig -> m RemoteConfigParser
|
2020-01-20 20:23:35 +00:00
|
|
|
mkRemoteConfigParser l _ = pure (RemoteConfigParser l Nothing)
|
2020-01-14 17:18:15 +00:00
|
|
|
|
|
|
|
addRemoteConfigParser :: [RemoteConfigFieldParser] -> RemoteConfigParser -> RemoteConfigParser
|
2020-01-17 21:11:55 +00:00
|
|
|
addRemoteConfigParser l rpc = rpc
|
|
|
|
{ remoteConfigFieldParsers =
|
|
|
|
remoteConfigFieldParsers rpc ++ filter isnew l
|
|
|
|
}
|
|
|
|
where
|
2020-01-20 17:49:30 +00:00
|
|
|
s = S.fromList (map parserForField (remoteConfigFieldParsers rpc))
|
|
|
|
isnew p = not (S.member (parserForField p) s)
|