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
26
Crypto.hs
26
Crypto.hs
|
@ -3,7 +3,7 @@
|
|||
- Currently using gpg; could later be modified to support different
|
||||
- crypto backends if neccessary.
|
||||
-
|
||||
- Copyright 2011-2016 Joey Hess <id@joeyh.name>
|
||||
- Copyright 2011-2020 Joey Hess <id@joeyh.name>
|
||||
-
|
||||
- Licensed under the GNU AGPL version 3 or higher.
|
||||
-}
|
||||
|
@ -13,6 +13,7 @@
|
|||
{-# LANGUAGE Rank2Types #-}
|
||||
|
||||
module Crypto (
|
||||
EncryptionMethod(..),
|
||||
Cipher,
|
||||
KeyIds(..),
|
||||
EncKey,
|
||||
|
@ -37,17 +38,24 @@ module Crypto (
|
|||
import qualified Data.ByteString as S
|
||||
import qualified Data.ByteString.Lazy as L
|
||||
import Data.ByteString.UTF8 (fromString)
|
||||
import qualified Data.Map as M
|
||||
import Control.Monad.IO.Class
|
||||
import Data.Typeable
|
||||
|
||||
import Annex.Common
|
||||
import qualified Utility.Gpg as Gpg
|
||||
import Types.Crypto
|
||||
import Types.Remote
|
||||
import Types.Key
|
||||
import Types.ProposedAccepted
|
||||
import Annex.SpecialRemote.Config
|
||||
|
||||
data EncryptionMethod
|
||||
= NoneEncryption
|
||||
| SharedEncryption
|
||||
| PubKeyEncryption
|
||||
| SharedPubKeyEncryption
|
||||
| HybridEncryption
|
||||
deriving (Typeable, Eq)
|
||||
|
||||
{- The beginning of a Cipher is used for MAC'ing; the remainder is used
|
||||
- as the GPG symmetric encryption passphrase when using the hybrid
|
||||
- scheme. Note that the cipher itself is base-64 encoded, hence the
|
||||
|
@ -233,14 +241,18 @@ class LensGpgEncParams a where
|
|||
|
||||
{- Extract the GnuPG options from a pair of a Remote Config and a Remote
|
||||
- Git Config. -}
|
||||
instance LensGpgEncParams (RemoteConfig, RemoteGitConfig) where
|
||||
instance LensGpgEncParams (ParsedRemoteConfig, RemoteGitConfig) where
|
||||
getGpgEncParamsBase (_c,gc) = map Param (remoteAnnexGnupgOptions gc)
|
||||
getGpgEncParams (c,gc) = getGpgEncParamsBase (c,gc) ++
|
||||
{- When the remote is configured to use public-key encryption,
|
||||
- look up the recipient keys and add them to the option list. -}
|
||||
case fromProposedAccepted <$> M.lookup encryptionField c of
|
||||
Just "pubkey" -> Gpg.pkEncTo $ maybe [] (splitc ',' . fromProposedAccepted) $ M.lookup cipherkeysField c
|
||||
Just "sharedpubkey" -> Gpg.pkEncTo $ maybe [] (splitc ',' . fromProposedAccepted) $ M.lookup pubkeysField c
|
||||
case getRemoteConfigValue encryptionField c of
|
||||
Just PubKeyEncryption ->
|
||||
Gpg.pkEncTo $ maybe [] (splitc ',') $
|
||||
getRemoteConfigValue cipherkeysField c
|
||||
Just SharedPubKeyEncryption ->
|
||||
Gpg.pkEncTo $ maybe [] (splitc ',') $
|
||||
getRemoteConfigValue pubkeysField c
|
||||
_ -> []
|
||||
getGpgDecParams (_c,gc) = map Param (remoteAnnexGnupgDecryptOptions gc)
|
||||
|
||||
|
|
Loading…
Add table
Add a link
Reference in a new issue