wip separate RemoteConfig parsing
Remote now contains a ParsedRemoteConfig. The parsing happens when the Remote is constructed, rather than when individual configs are used. This is more efficient, and it lets initremote/enableremote reject configs that have unknown fields or unparsable values. It also allows for improved type safety, as shown in Remote.Helper.Encryptable where things that used to match on string configs now match on data types. This is a work in progress, it does not build yet. The main risk in this conversion is forgetting to add a field to RemoteConfigParser. That will prevent using that field with initremote/enableremote, and will prevent remotes that already are set up from seeing that configuration. So will need to check carefully that every field that getRemoteConfigValue is called on has been added to RemoteConfigParser. (One such case I need to remember is that credPairRemoteField needs to be included in the RemoteConfigParser.)
This commit is contained in:
parent
4a135934ff
commit
71f78fe45d
10 changed files with 266 additions and 101 deletions
|
@ -2,7 +2,7 @@
|
|||
-
|
||||
- Most things should not need this, using Types instead
|
||||
-
|
||||
- Copyright 2011-2019 Joey Hess <id@joeyh.name>
|
||||
- Copyright 2011-2020 Joey Hess <id@joeyh.name>
|
||||
-
|
||||
- Licensed under the GNU AGPL version 3 or higher.
|
||||
-}
|
||||
|
@ -10,8 +10,7 @@
|
|||
{-# LANGUAGE RankNTypes #-}
|
||||
|
||||
module Types.Remote
|
||||
( RemoteConfigField
|
||||
, RemoteConfig
|
||||
( module Types.RemoteConfig
|
||||
, RemoteTypeA(..)
|
||||
, RemoteA(..)
|
||||
, RemoteStateHandle
|
||||
|
@ -28,7 +27,6 @@ module Types.Remote
|
|||
)
|
||||
where
|
||||
|
||||
import qualified Data.Map as M
|
||||
import Data.Ord
|
||||
|
||||
import qualified Git
|
||||
|
@ -42,7 +40,7 @@ import Types.UrlContents
|
|||
import Types.NumCopies
|
||||
import Types.Export
|
||||
import Types.Import
|
||||
import Types.ProposedAccepted
|
||||
import Types.RemoteConfig
|
||||
import Config.Cost
|
||||
import Utility.Metered
|
||||
import Git.Types (RemoteName)
|
||||
|
@ -50,10 +48,6 @@ import Utility.SafeCommand
|
|||
import Utility.Url
|
||||
import Utility.DataUnits
|
||||
|
||||
type RemoteConfigField = ProposedAccepted String
|
||||
|
||||
type RemoteConfig = M.Map RemoteConfigField (ProposedAccepted String)
|
||||
|
||||
data SetupStage = Init | Enable RemoteConfig
|
||||
|
||||
{- There are different types of remotes. -}
|
||||
|
@ -63,14 +57,16 @@ data RemoteTypeA a = RemoteType
|
|||
-- enumerates remotes of this type
|
||||
-- The Bool is True if automatic initialization of remotes is desired
|
||||
, enumerate :: Bool -> a [Git.Repo]
|
||||
-- parse configs of remotes of this type
|
||||
, configParser :: [RemoteConfigParser]
|
||||
-- generates a remote of this type
|
||||
, generate :: Git.Repo -> UUID -> RemoteConfig -> RemoteGitConfig -> RemoteStateHandle -> a (Maybe (RemoteA a))
|
||||
-- initializes or enables a remote
|
||||
, setup :: SetupStage -> Maybe UUID -> Maybe CredPair -> RemoteConfig -> RemoteGitConfig -> a (RemoteConfig, UUID)
|
||||
-- check if a remote of this type is able to support export
|
||||
, exportSupported :: RemoteConfig -> RemoteGitConfig -> a Bool
|
||||
, exportSupported :: ParsedRemoteConfig -> RemoteGitConfig -> a Bool
|
||||
-- check if a remote of this type is able to support import
|
||||
, importSupported :: RemoteConfig -> RemoteGitConfig -> a Bool
|
||||
, importSupported :: ParsedRemoteConfig -> RemoteGitConfig -> a Bool
|
||||
}
|
||||
|
||||
instance Eq (RemoteTypeA a) where
|
||||
|
@ -125,7 +121,7 @@ data RemoteA a = Remote
|
|||
-- Runs an action to repair the remote's git repository.
|
||||
, repairRepo :: Maybe (a Bool -> a (IO Bool))
|
||||
-- a Remote has a persistent configuration store
|
||||
, config :: RemoteConfig
|
||||
, config :: ParsedRemoteConfig
|
||||
-- Get the git repo for the Remote.
|
||||
, getRepo :: a Git.Repo
|
||||
-- a Remote's configuration from git
|
||||
|
|
46
Types/RemoteConfig.hs
Normal file
46
Types/RemoteConfig.hs
Normal file
|
@ -0,0 +1,46 @@
|
|||
{- 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
|
||||
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. -}
|
||||
type ParsedRemoteConfig = M.Map RemoteConfigField RemoteConfigValue
|
||||
|
||||
{- 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
|
||||
|
||||
{- Extracts the value, if the field was parsed to the requested type. -}
|
||||
getRemoteConfigValue :: Typeable v => RemoteConfigField -> ParsedRemoteConfig -> Maybe v
|
||||
getRemoteConfigValue f m = case M.lookup f m of
|
||||
Just (RemoteConfigValue v) -> cast v
|
||||
Nothing -> Nothing
|
||||
|
||||
{- 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.
|
||||
-}
|
||||
type RemoteConfigParser = (RemoteConfigField, Maybe (ProposedAccepted String) -> RemoteConfig -> Either String RemoteConfigValue)
|
Loading…
Add table
Add a link
Reference in a new issue