2011-04-17 04:40:23 +00:00
|
|
|
{- common functions for encryptable remotes
|
2011-04-16 17:25:27 +00:00
|
|
|
-
|
2020-01-13 16:35:39 +00:00
|
|
|
- Copyright 2011-2020 Joey Hess <id@joeyh.name>
|
2011-04-16 17:25:27 +00:00
|
|
|
-
|
2019-03-13 19:48:14 +00:00
|
|
|
- Licensed under the GNU AGPL version 3 or higher.
|
2011-04-16 17:25:27 +00:00
|
|
|
-}
|
|
|
|
|
2020-01-13 16:35:39 +00:00
|
|
|
{-# LANGUAGE FlexibleContexts, ScopedTypeVariables #-}
|
|
|
|
|
glacier, S3: Fix bug that caused embedded creds to not be encypted using the remote's key.
encryptionSetup must be called before setRemoteCredPair. Otherwise,
the RemoteConfig doesn't have the cipher in it, and so no cipher is used to
encrypt the embedded creds.
This is a security fix for non-shared encryption methods!
For encryption=shared, there's no security problem, just an
inconsistentency in whether the embedded creds are encrypted.
This is very important to get right, so used some types to help ensure that
setRemoteCredPair is only run after encryptionSetup. Note that the external
special remote bypasses the type safety, since creds can be set after the
initial remote config, if the external special remote program requests it.
Also note that IA remotes never use encryption, so encryptionSetup is not
run for them at all, and again the type safety is bypassed.
This leaves two open questions:
1. What to do about S3 and glacier remotes that were set up
using encryption=pubkey/hybrid with embedcreds?
Such a git repo has a security hole embedded in it, and this needs to be
communicated to the user. Is the changelog enough?
2. enableremote won't work in such a repo, because git-annex will
try to decrypt the embedded creds, which are not encrypted, so fails.
This needs to be dealt with, especially for ecryption=shared repos,
which are not really broken, just inconsistently configured.
Noticing that problem for encryption=shared is what led to commit
fbdeeeed5fa276d94be587c8916d725eddcaf546, which tried to
fix the problem by not decrypting the embedded creds.
This commit was sponsored by Josh Taylor.
2014-09-18 21:07:17 +00:00
|
|
|
module Remote.Helper.Encryptable (
|
|
|
|
EncryptionIsSetup,
|
|
|
|
encryptionSetup,
|
|
|
|
noEncryptionUsed,
|
|
|
|
encryptionAlreadySetup,
|
2020-01-14 17:18:15 +00:00
|
|
|
encryptionConfigParsers,
|
2020-01-14 16:35:08 +00:00
|
|
|
parseEncryptionConfig,
|
glacier, S3: Fix bug that caused embedded creds to not be encypted using the remote's key.
encryptionSetup must be called before setRemoteCredPair. Otherwise,
the RemoteConfig doesn't have the cipher in it, and so no cipher is used to
encrypt the embedded creds.
This is a security fix for non-shared encryption methods!
For encryption=shared, there's no security problem, just an
inconsistentency in whether the embedded creds are encrypted.
This is very important to get right, so used some types to help ensure that
setRemoteCredPair is only run after encryptionSetup. Note that the external
special remote bypasses the type safety, since creds can be set after the
initial remote config, if the external special remote program requests it.
Also note that IA remotes never use encryption, so encryptionSetup is not
run for them at all, and again the type safety is bypassed.
This leaves two open questions:
1. What to do about S3 and glacier remotes that were set up
using encryption=pubkey/hybrid with embedcreds?
Such a git repo has a security hole embedded in it, and this needs to be
communicated to the user. Is the changelog enough?
2. enableremote won't work in such a repo, because git-annex will
try to decrypt the embedded creds, which are not encrypted, so fails.
This needs to be dealt with, especially for ecryption=shared repos,
which are not really broken, just inconsistently configured.
Noticing that problem for encryption=shared is what led to commit
fbdeeeed5fa276d94be587c8916d725eddcaf546, which tried to
fix the problem by not decrypting the embedded creds.
This commit was sponsored by Josh Taylor.
2014-09-18 21:07:17 +00:00
|
|
|
remoteCipher,
|
2014-09-18 21:58:03 +00:00
|
|
|
remoteCipher',
|
glacier, S3: Fix bug that caused embedded creds to not be encypted using the remote's key.
encryptionSetup must be called before setRemoteCredPair. Otherwise,
the RemoteConfig doesn't have the cipher in it, and so no cipher is used to
encrypt the embedded creds.
This is a security fix for non-shared encryption methods!
For encryption=shared, there's no security problem, just an
inconsistentency in whether the embedded creds are encrypted.
This is very important to get right, so used some types to help ensure that
setRemoteCredPair is only run after encryptionSetup. Note that the external
special remote bypasses the type safety, since creds can be set after the
initial remote config, if the external special remote program requests it.
Also note that IA remotes never use encryption, so encryptionSetup is not
run for them at all, and again the type safety is bypassed.
This leaves two open questions:
1. What to do about S3 and glacier remotes that were set up
using encryption=pubkey/hybrid with embedcreds?
Such a git repo has a security hole embedded in it, and this needs to be
communicated to the user. Is the changelog enough?
2. enableremote won't work in such a repo, because git-annex will
try to decrypt the embedded creds, which are not encrypted, so fails.
This needs to be dealt with, especially for ecryption=shared repos,
which are not really broken, just inconsistently configured.
Noticing that problem for encryption=shared is what led to commit
fbdeeeed5fa276d94be587c8916d725eddcaf546, which tried to
fix the problem by not decrypting the embedded creds.
This commit was sponsored by Josh Taylor.
2014-09-18 21:07:17 +00:00
|
|
|
embedCreds,
|
|
|
|
cipherKey,
|
|
|
|
extractCipher,
|
2017-09-04 16:40:33 +00:00
|
|
|
isEncrypted,
|
2014-10-21 18:36:09 +00:00
|
|
|
describeEncryption,
|
2020-01-15 15:30:45 +00:00
|
|
|
encryptionField,
|
|
|
|
highRandomQualityField
|
glacier, S3: Fix bug that caused embedded creds to not be encypted using the remote's key.
encryptionSetup must be called before setRemoteCredPair. Otherwise,
the RemoteConfig doesn't have the cipher in it, and so no cipher is used to
encrypt the embedded creds.
This is a security fix for non-shared encryption methods!
For encryption=shared, there's no security problem, just an
inconsistentency in whether the embedded creds are encrypted.
This is very important to get right, so used some types to help ensure that
setRemoteCredPair is only run after encryptionSetup. Note that the external
special remote bypasses the type safety, since creds can be set after the
initial remote config, if the external special remote program requests it.
Also note that IA remotes never use encryption, so encryptionSetup is not
run for them at all, and again the type safety is bypassed.
This leaves two open questions:
1. What to do about S3 and glacier remotes that were set up
using encryption=pubkey/hybrid with embedcreds?
Such a git repo has a security hole embedded in it, and this needs to be
communicated to the user. Is the changelog enough?
2. enableremote won't work in such a repo, because git-annex will
try to decrypt the embedded creds, which are not encrypted, so fails.
This needs to be dealt with, especially for ecryption=shared repos,
which are not really broken, just inconsistently configured.
Noticing that problem for encryption=shared is what led to commit
fbdeeeed5fa276d94be587c8916d725eddcaf546, which tried to
fix the problem by not decrypting the embedded creds.
This commit was sponsored by Josh Taylor.
2014-09-18 21:07:17 +00:00
|
|
|
) where
|
2011-04-16 17:25:27 +00:00
|
|
|
|
|
|
|
import qualified Data.Map as M
|
2020-01-14 16:35:08 +00:00
|
|
|
import qualified Data.Set as S
|
2015-05-07 22:07:13 +00:00
|
|
|
import qualified "sandi" Codec.Binary.Base64 as B64
|
|
|
|
import qualified Data.ByteString as B
|
2011-04-16 17:25:27 +00:00
|
|
|
|
2016-01-20 20:36:33 +00:00
|
|
|
import Annex.Common
|
2011-06-02 01:56:04 +00:00
|
|
|
import Types.Remote
|
2011-04-16 17:25:27 +00:00
|
|
|
import Crypto
|
2013-03-29 16:06:02 +00:00
|
|
|
import Types.Crypto
|
2020-01-10 18:10:20 +00:00
|
|
|
import Types.ProposedAccepted
|
2011-04-16 22:22:52 +00:00
|
|
|
import qualified Annex
|
2019-10-10 19:46:12 +00:00
|
|
|
import Annex.SpecialRemote.Config
|
2011-04-16 17:25:27 +00:00
|
|
|
|
glacier, S3: Fix bug that caused embedded creds to not be encypted using the remote's key.
encryptionSetup must be called before setRemoteCredPair. Otherwise,
the RemoteConfig doesn't have the cipher in it, and so no cipher is used to
encrypt the embedded creds.
This is a security fix for non-shared encryption methods!
For encryption=shared, there's no security problem, just an
inconsistentency in whether the embedded creds are encrypted.
This is very important to get right, so used some types to help ensure that
setRemoteCredPair is only run after encryptionSetup. Note that the external
special remote bypasses the type safety, since creds can be set after the
initial remote config, if the external special remote program requests it.
Also note that IA remotes never use encryption, so encryptionSetup is not
run for them at all, and again the type safety is bypassed.
This leaves two open questions:
1. What to do about S3 and glacier remotes that were set up
using encryption=pubkey/hybrid with embedcreds?
Such a git repo has a security hole embedded in it, and this needs to be
communicated to the user. Is the changelog enough?
2. enableremote won't work in such a repo, because git-annex will
try to decrypt the embedded creds, which are not encrypted, so fails.
This needs to be dealt with, especially for ecryption=shared repos,
which are not really broken, just inconsistently configured.
Noticing that problem for encryption=shared is what led to commit
fbdeeeed5fa276d94be587c8916d725eddcaf546, which tried to
fix the problem by not decrypting the embedded creds.
This commit was sponsored by Josh Taylor.
2014-09-18 21:07:17 +00:00
|
|
|
-- Used to ensure that encryption has been set up before trying to
|
|
|
|
-- eg, store creds in the remote config that would need to use the
|
|
|
|
-- encryption setup.
|
|
|
|
data EncryptionIsSetup = EncryptionIsSetup | NoEncryption
|
|
|
|
|
|
|
|
-- Remotes that don't use encryption can use this instead of
|
|
|
|
-- encryptionSetup.
|
|
|
|
noEncryptionUsed :: EncryptionIsSetup
|
|
|
|
noEncryptionUsed = NoEncryption
|
|
|
|
|
|
|
|
-- Using this avoids the type-safe check, so you'd better be sure
|
|
|
|
-- of what you're doing.
|
|
|
|
encryptionAlreadySetup :: EncryptionIsSetup
|
|
|
|
encryptionAlreadySetup = EncryptionIsSetup
|
|
|
|
|
2020-01-14 17:18:15 +00:00
|
|
|
encryptionConfigParsers :: [RemoteConfigFieldParser]
|
|
|
|
encryptionConfigParsers =
|
2020-01-20 17:49:30 +00:00
|
|
|
[ encryptionFieldParser
|
2020-01-20 19:20:04 +00:00
|
|
|
, optionalStringParser cipherField HiddenField
|
|
|
|
, optionalStringParser cipherkeysField HiddenField
|
|
|
|
, optionalStringParser pubkeysField HiddenField
|
2020-06-16 21:59:55 +00:00
|
|
|
, yesNoParser embedCredsField Nothing
|
2020-01-20 19:20:04 +00:00
|
|
|
(FieldDesc "embed credentials into git repository")
|
2020-01-20 17:49:30 +00:00
|
|
|
, macFieldParser
|
2020-01-14 16:35:08 +00:00
|
|
|
, optionalStringParser (Accepted "keyid")
|
2020-01-20 19:20:04 +00:00
|
|
|
(FieldDesc "gpg key id")
|
2020-01-14 16:35:08 +00:00
|
|
|
, optionalStringParser (Accepted "keyid+")
|
2020-01-20 19:20:04 +00:00
|
|
|
(FieldDesc "add additional gpg key")
|
2020-01-14 16:35:08 +00:00
|
|
|
, optionalStringParser (Accepted "keyid-")
|
2020-01-20 19:20:04 +00:00
|
|
|
(FieldDesc "remove gpg key")
|
2020-01-20 17:49:30 +00:00
|
|
|
, highRandomQualityFieldParser
|
2020-01-13 16:35:39 +00:00
|
|
|
]
|
|
|
|
|
2020-01-14 16:35:08 +00:00
|
|
|
encryptionConfigs :: S.Set RemoteConfigField
|
2020-01-20 17:49:30 +00:00
|
|
|
encryptionConfigs = S.fromList (map parserForField encryptionConfigParsers)
|
2020-01-14 16:35:08 +00:00
|
|
|
|
|
|
|
-- Parse only encryption fields, ignoring all others.
|
|
|
|
parseEncryptionConfig :: RemoteConfig -> Either String ParsedRemoteConfig
|
2020-01-14 17:18:15 +00:00
|
|
|
parseEncryptionConfig c = parseRemoteConfig
|
|
|
|
(M.restrictKeys c encryptionConfigs)
|
2020-01-20 20:23:35 +00:00
|
|
|
(RemoteConfigParser encryptionConfigParsers Nothing)
|
2020-01-14 16:35:08 +00:00
|
|
|
|
2020-01-20 17:49:30 +00:00
|
|
|
encryptionFieldParser :: RemoteConfigFieldParser
|
|
|
|
encryptionFieldParser = RemoteConfigFieldParser
|
|
|
|
{ parserForField = encryptionField
|
|
|
|
, valueParser = \v c -> Just . RemoteConfigValue
|
|
|
|
<$> parseEncryptionMethod (fmap fromProposedAccepted v) c
|
2020-01-20 19:20:04 +00:00
|
|
|
, fieldDesc = FieldDesc "how to encrypt data stored in the special remote"
|
|
|
|
, valueDesc = Just $ ValueDesc $
|
|
|
|
intercalate " or " (M.keys encryptionMethods)
|
2020-01-20 17:49:30 +00:00
|
|
|
}
|
|
|
|
|
2020-01-20 19:20:04 +00:00
|
|
|
encryptionMethods :: M.Map String EncryptionMethod
|
|
|
|
encryptionMethods = M.fromList
|
|
|
|
[ ("none", NoneEncryption)
|
|
|
|
, ("shared", SharedEncryption)
|
|
|
|
, ("hybrid", HybridEncryption)
|
|
|
|
, ("pubkey", PubKeyEncryption)
|
|
|
|
, ("sharedpubkey", SharedPubKeyEncryption)
|
|
|
|
]
|
|
|
|
|
2020-01-13 16:35:39 +00:00
|
|
|
parseEncryptionMethod :: Maybe String -> RemoteConfig -> Either String EncryptionMethod
|
2020-01-20 19:20:04 +00:00
|
|
|
parseEncryptionMethod (Just s) _ = case M.lookup s encryptionMethods of
|
|
|
|
Just em -> Right em
|
|
|
|
Nothing -> Left badEncryptionMethod
|
2020-01-13 16:35:39 +00:00
|
|
|
-- Hybrid encryption is the default when a keyid is specified without
|
|
|
|
-- an encryption field, or when there's a cipher already but no encryption
|
|
|
|
-- field.
|
|
|
|
parseEncryptionMethod Nothing c
|
|
|
|
| M.member (Accepted "keyid") c || M.member cipherField c = Right HybridEncryption
|
2020-01-20 19:20:04 +00:00
|
|
|
| otherwise = Left badEncryptionMethod
|
|
|
|
|
|
|
|
badEncryptionMethod :: String
|
|
|
|
badEncryptionMethod = "Specify " ++ intercalate " or "
|
|
|
|
(map ((fromProposedAccepted encryptionField ++ "=") ++)
|
|
|
|
(M.keys encryptionMethods))
|
|
|
|
++ "."
|
|
|
|
|
|
|
|
highRandomQualityField :: RemoteConfigField
|
|
|
|
highRandomQualityField = Accepted "highRandomQuality"
|
2020-01-20 17:49:30 +00:00
|
|
|
|
|
|
|
highRandomQualityFieldParser :: RemoteConfigFieldParser
|
|
|
|
highRandomQualityFieldParser = RemoteConfigFieldParser
|
|
|
|
{ parserForField = highRandomQualityField
|
|
|
|
, valueParser = \v _c -> Just . RemoteConfigValue
|
|
|
|
<$> parseHighRandomQuality (fmap fromProposedAccepted v)
|
2020-01-20 19:20:04 +00:00
|
|
|
, fieldDesc = HiddenField
|
|
|
|
, valueDesc = Nothing
|
2020-01-20 17:49:30 +00:00
|
|
|
}
|
2020-01-13 16:35:39 +00:00
|
|
|
|
|
|
|
parseHighRandomQuality :: Maybe String -> Either String Bool
|
|
|
|
parseHighRandomQuality Nothing = Right True
|
|
|
|
parseHighRandomQuality (Just "false") = Right False
|
|
|
|
parseHighRandomQuality (Just "true") = Right True
|
|
|
|
parseHighRandomQuality _ = Left "expected highRandomQuality=true/false"
|
2020-01-20 17:49:30 +00:00
|
|
|
|
|
|
|
macFieldParser :: RemoteConfigFieldParser
|
|
|
|
macFieldParser = RemoteConfigFieldParser
|
|
|
|
{ parserForField = macField
|
|
|
|
, valueParser = \v _c -> Just . RemoteConfigValue <$> parseMac v
|
2020-01-20 19:20:04 +00:00
|
|
|
, fieldDesc = FieldDesc "how to encrypt filenames used on the remote"
|
|
|
|
, valueDesc = Just $ ValueDesc $
|
|
|
|
intercalate " or " (M.keys macMap)
|
2020-01-20 17:49:30 +00:00
|
|
|
}
|
2020-01-13 16:35:39 +00:00
|
|
|
|
|
|
|
parseMac :: Maybe (ProposedAccepted String) -> Either String Mac
|
|
|
|
parseMac Nothing = Right defaultMac
|
|
|
|
parseMac (Just (Accepted s)) = Right $ fromMaybe defaultMac (readMac s)
|
|
|
|
parseMac (Just (Proposed s)) = case readMac s of
|
|
|
|
Just mac -> Right mac
|
|
|
|
Nothing -> Left "bad mac value"
|
|
|
|
|
2011-04-16 17:25:27 +00:00
|
|
|
{- Encryption setup for a remote. The user must specify whether to use
|
|
|
|
- an encryption key, or not encrypt. An encrypted cipher is created, or is
|
2012-04-29 18:02:18 +00:00
|
|
|
- updated to be accessible to an additional encryption key. Or the user
|
|
|
|
- could opt to use a shared cipher, which is stored unencrypted. -}
|
2016-05-23 21:27:15 +00:00
|
|
|
encryptionSetup :: RemoteConfig -> RemoteGitConfig -> Annex (RemoteConfig, EncryptionIsSetup)
|
|
|
|
encryptionSetup c gc = do
|
2020-01-14 16:35:08 +00:00
|
|
|
pc <- either giveup return $ parseEncryptionConfig c
|
2015-09-09 22:06:49 +00:00
|
|
|
cmd <- gpgCmd <$> Annex.getGitConfig
|
2020-01-13 16:35:39 +00:00
|
|
|
maybe (genCipher pc cmd) (updateCipher pc cmd) (extractCipher pc)
|
2012-11-11 04:51:07 +00:00
|
|
|
where
|
2013-08-28 02:24:14 +00:00
|
|
|
-- The type of encryption
|
2020-01-13 16:35:39 +00:00
|
|
|
encryption = parseEncryptionMethod (fromProposedAccepted <$> M.lookup encryptionField c) c
|
2013-08-28 02:24:14 +00:00
|
|
|
-- Generate a new cipher, depending on the chosen encryption scheme
|
2020-01-13 16:35:39 +00:00
|
|
|
genCipher pc cmd = case encryption of
|
|
|
|
Right NoneEncryption -> return (c, NoEncryption)
|
|
|
|
Right SharedEncryption -> encsetup $ genSharedCipher cmd
|
|
|
|
Right HybridEncryption -> encsetup $ genEncryptedCipher cmd (pc, gc) key Hybrid
|
|
|
|
Right PubKeyEncryption -> encsetup $ genEncryptedCipher cmd (pc, gc) key PubKey
|
|
|
|
Right SharedPubKeyEncryption -> encsetup $ genSharedPubKeyCipher cmd key
|
|
|
|
Left err -> giveup err
|
2020-01-10 18:10:20 +00:00
|
|
|
key = maybe (giveup "Specify keyid=...") fromProposedAccepted $
|
|
|
|
M.lookup (Accepted "keyid") c
|
|
|
|
newkeys = maybe [] (\k -> [(True,fromProposedAccepted k)]) (M.lookup (Accepted "keyid+") c) ++
|
|
|
|
maybe [] (\k -> [(False,fromProposedAccepted k)]) (M.lookup (Accepted "keyid-") c)
|
2016-11-16 01:29:54 +00:00
|
|
|
cannotchange = giveup "Cannot set encryption type of existing remotes."
|
2013-08-28 02:24:14 +00:00
|
|
|
-- Update an existing cipher if possible.
|
2020-01-13 16:35:39 +00:00
|
|
|
updateCipher pc cmd v = case v of
|
|
|
|
SharedCipher _ | encryption == Right SharedEncryption ->
|
|
|
|
return (c', EncryptionIsSetup)
|
|
|
|
EncryptedCipher _ variant _ | sameasencryption variant ->
|
|
|
|
use "encryption update" $ updateCipherKeyIds cmd (pc, gc) newkeys v
|
2016-05-10 20:50:31 +00:00
|
|
|
SharedPubKeyCipher _ _ ->
|
2020-01-13 16:35:39 +00:00
|
|
|
use "encryption update" $ updateCipherKeyIds cmd (pc, gc) newkeys v
|
2013-09-01 18:12:00 +00:00
|
|
|
_ -> cannotchange
|
2020-01-13 16:35:39 +00:00
|
|
|
sameasencryption variant = case encryption of
|
|
|
|
Right HybridEncryption -> variant == Hybrid
|
|
|
|
Right PubKeyEncryption -> variant == PubKey
|
|
|
|
Right _ -> False
|
|
|
|
Left _ -> True
|
2016-05-10 20:50:31 +00:00
|
|
|
encsetup a = use "encryption setup" . a =<< highRandomQuality
|
2012-11-11 04:51:07 +00:00
|
|
|
use m a = do
|
2013-05-18 23:30:52 +00:00
|
|
|
showNote m
|
2012-11-11 04:51:07 +00:00
|
|
|
cipher <- liftIO a
|
2016-05-11 20:09:39 +00:00
|
|
|
showNote (describeCipher cipher)
|
2016-05-10 20:50:31 +00:00
|
|
|
return (storeCipher cipher c', EncryptionIsSetup)
|
2020-01-13 16:35:39 +00:00
|
|
|
highRandomQuality = ifM (Annex.getState Annex.fast)
|
|
|
|
( return False
|
2020-01-15 15:30:45 +00:00
|
|
|
, case parseHighRandomQuality (fromProposedAccepted <$> M.lookup highRandomQualityField c) of
|
2020-01-13 16:35:39 +00:00
|
|
|
Left err -> giveup err
|
|
|
|
Right v -> return v
|
|
|
|
)
|
2013-09-01 18:12:00 +00:00
|
|
|
c' = foldr M.delete c
|
2020-01-13 16:35:39 +00:00
|
|
|
-- Remove configs that are only used in here to generate
|
|
|
|
-- the encryption keys, and should not be stored in
|
|
|
|
-- remote.log.
|
|
|
|
-- Older versions used to remove 'encryption' as well, since
|
2014-10-09 19:09:26 +00:00
|
|
|
-- it was redundant; we now need to keep it for
|
|
|
|
-- public-key encryption, hence we leave it on newer
|
|
|
|
-- remotes (while being backward-compatible).
|
2020-01-13 16:35:39 +00:00
|
|
|
(map Accepted ["keyid", "keyid+", "keyid-", "highRandomQuality"])
|
2011-04-16 22:22:52 +00:00
|
|
|
|
2020-01-13 16:35:39 +00:00
|
|
|
remoteCipher :: ParsedRemoteConfig -> RemoteGitConfig -> Annex (Maybe Cipher)
|
2016-05-23 21:27:15 +00:00
|
|
|
remoteCipher c gc = fmap fst <$> remoteCipher' c gc
|
2014-09-18 21:58:03 +00:00
|
|
|
|
2011-12-08 20:01:46 +00:00
|
|
|
{- Gets encryption Cipher. The decrypted Ciphers are cached in the Annex
|
2011-05-01 18:05:10 +00:00
|
|
|
- state. -}
|
2020-01-13 16:35:39 +00:00
|
|
|
remoteCipher' :: ParsedRemoteConfig -> RemoteGitConfig -> Annex (Maybe (Cipher, StorableCipher))
|
2016-05-23 21:27:15 +00:00
|
|
|
remoteCipher' c gc = go $ extractCipher c
|
2012-11-11 04:51:07 +00:00
|
|
|
where
|
|
|
|
go Nothing = return Nothing
|
|
|
|
go (Just encipher) = do
|
|
|
|
cache <- Annex.getState Annex.ciphers
|
|
|
|
case M.lookup encipher cache of
|
2014-09-18 21:58:03 +00:00
|
|
|
Just cipher -> return $ Just (cipher, encipher)
|
2012-11-18 19:27:44 +00:00
|
|
|
Nothing -> do
|
2015-09-09 22:06:49 +00:00
|
|
|
cmd <- gpgCmd <$> Annex.getGitConfig
|
2016-05-23 21:27:15 +00:00
|
|
|
cipher <- liftIO $ decryptCipher cmd (c, gc) encipher
|
2012-11-18 19:27:44 +00:00
|
|
|
Annex.changeState (\s -> s { Annex.ciphers = M.insert encipher cipher cache })
|
2014-09-18 21:58:03 +00:00
|
|
|
return $ Just (cipher, encipher)
|
2011-05-01 18:05:10 +00:00
|
|
|
|
2012-11-19 21:32:58 +00:00
|
|
|
{- Checks if the remote's config allows storing creds in the remote's config.
|
|
|
|
-
|
|
|
|
- embedcreds=yes allows this, and embedcreds=no prevents it.
|
|
|
|
-
|
|
|
|
- If not set, the default is to only store creds when it's surely safe:
|
2016-05-10 20:50:31 +00:00
|
|
|
- When gpg encryption is used and the creds are encrypted using it.
|
|
|
|
- Not when a shared cipher is used.
|
2012-11-19 21:32:58 +00:00
|
|
|
-}
|
2020-01-13 16:35:39 +00:00
|
|
|
embedCreds :: ParsedRemoteConfig -> Bool
|
|
|
|
embedCreds c = case getRemoteConfigValue embedCredsField c of
|
2018-10-10 15:07:49 +00:00
|
|
|
Just v -> v
|
2020-01-13 16:35:39 +00:00
|
|
|
Nothing -> case (getRemoteConfigValue cipherkeysField c, getRemoteConfigValue cipherField c) of
|
2020-06-16 22:14:36 +00:00
|
|
|
(Just (_ :: String), Just (_ :: String)) -> True
|
2020-01-13 16:35:39 +00:00
|
|
|
_ -> False
|
2012-09-26 16:06:44 +00:00
|
|
|
|
2014-07-27 00:14:09 +00:00
|
|
|
{- Gets encryption Cipher, and key encryptor. -}
|
2020-01-13 16:35:39 +00:00
|
|
|
cipherKey :: ParsedRemoteConfig -> RemoteGitConfig -> Annex (Maybe (Cipher, EncKey))
|
2016-05-23 21:27:15 +00:00
|
|
|
cipherKey c gc = fmap make <$> remoteCipher c gc
|
2012-11-11 04:51:07 +00:00
|
|
|
where
|
2014-07-27 00:14:09 +00:00
|
|
|
make ciphertext = (ciphertext, encryptKey mac ciphertext)
|
2020-01-13 16:35:39 +00:00
|
|
|
mac = fromMaybe defaultMac $ getRemoteConfigValue macField c
|
2012-04-29 18:31:34 +00:00
|
|
|
|
|
|
|
{- Stores an StorableCipher in a remote's configuration. -}
|
2016-05-10 20:50:31 +00:00
|
|
|
storeCipher :: StorableCipher -> RemoteConfig -> RemoteConfig
|
|
|
|
storeCipher cip = case cip of
|
|
|
|
(SharedCipher t) -> addcipher t
|
2019-10-10 20:10:12 +00:00
|
|
|
(EncryptedCipher t _ ks) -> addcipher t . storekeys ks cipherkeysField
|
|
|
|
(SharedPubKeyCipher t ks) -> addcipher t . storekeys ks pubkeysField
|
2012-11-11 04:51:07 +00:00
|
|
|
where
|
2020-01-10 18:10:20 +00:00
|
|
|
addcipher t = M.insert cipherField (Accepted (toB64bs t))
|
|
|
|
storekeys (KeyIds l) n = M.insert n (Accepted (intercalate "," l))
|
2012-04-29 18:31:34 +00:00
|
|
|
|
|
|
|
{- Extracts an StorableCipher from a remote's configuration. -}
|
2020-01-13 16:35:39 +00:00
|
|
|
extractCipher :: ParsedRemoteConfig -> Maybe StorableCipher
|
|
|
|
extractCipher c = case (getRemoteConfigValue cipherField c,
|
|
|
|
(getRemoteConfigValue cipherkeysField c <|> getRemoteConfigValue pubkeysField c),
|
|
|
|
getRemoteConfigValue encryptionField c) of
|
|
|
|
(Just t, Just ks, Just HybridEncryption) ->
|
metadata: Fix encoding problem that led to mojibake when storing metadata strings that contained both unicode characters and a space (or '!') character.
The fix is to stop using w82s, which does not properly reconstitute unicode
strings. Instrad, use utf8 bytestring to get the [Word8] to base64. This
passes unicode through perfectly, including any invalid filesystem encoded
characters.
Note that toB64 / fromB64 are also used for creds and cipher
embedding. It would be unfortunate if this change broke those uses.
For cipher embedding, note that ciphers can contain arbitrary bytes (should
really be using ByteString.Char8 there). Testing indicated it's not safe to
use the new fromB64 there; I think that characters were incorrectly
combined.
For credpair embedding, the username or password could contain unicode.
Before, that unicode would fail to round-trip through the b64.
So, I guess this is not going to break any embedded creds that worked
before.
This bug may have affected some creds before, and if so,
this change will not fix old ones, but should fix new ones at least.
2015-03-04 15:16:03 +00:00
|
|
|
Just $ EncryptedCipher (fromB64bs t) Hybrid (readkeys ks)
|
2020-01-13 16:35:39 +00:00
|
|
|
(Just t, Just ks, Just PubKeyEncryption) ->
|
metadata: Fix encoding problem that led to mojibake when storing metadata strings that contained both unicode characters and a space (or '!') character.
The fix is to stop using w82s, which does not properly reconstitute unicode
strings. Instrad, use utf8 bytestring to get the [Word8] to base64. This
passes unicode through perfectly, including any invalid filesystem encoded
characters.
Note that toB64 / fromB64 are also used for creds and cipher
embedding. It would be unfortunate if this change broke those uses.
For cipher embedding, note that ciphers can contain arbitrary bytes (should
really be using ByteString.Char8 there). Testing indicated it's not safe to
use the new fromB64 there; I think that characters were incorrectly
combined.
For credpair embedding, the username or password could contain unicode.
Before, that unicode would fail to round-trip through the b64.
So, I guess this is not going to break any embedded creds that worked
before.
This bug may have affected some creds before, and if so,
this change will not fix old ones, but should fix new ones at least.
2015-03-04 15:16:03 +00:00
|
|
|
Just $ EncryptedCipher (fromB64bs t) PubKey (readkeys ks)
|
2020-01-13 16:35:39 +00:00
|
|
|
(Just t, Just ks, Just SharedPubKeyEncryption) ->
|
2016-05-10 20:50:31 +00:00
|
|
|
Just $ SharedPubKeyCipher (fromB64bs t) (readkeys ks)
|
2020-01-13 16:35:39 +00:00
|
|
|
(Just t, Nothing, Just SharedEncryption) ->
|
metadata: Fix encoding problem that led to mojibake when storing metadata strings that contained both unicode characters and a space (or '!') character.
The fix is to stop using w82s, which does not properly reconstitute unicode
strings. Instrad, use utf8 bytestring to get the [Word8] to base64. This
passes unicode through perfectly, including any invalid filesystem encoded
characters.
Note that toB64 / fromB64 are also used for creds and cipher
embedding. It would be unfortunate if this change broke those uses.
For cipher embedding, note that ciphers can contain arbitrary bytes (should
really be using ByteString.Char8 there). Testing indicated it's not safe to
use the new fromB64 there; I think that characters were incorrectly
combined.
For credpair embedding, the username or password could contain unicode.
Before, that unicode would fail to round-trip through the b64.
So, I guess this is not going to break any embedded creds that worked
before.
This bug may have affected some creds before, and if so,
this change will not fix old ones, but should fix new ones at least.
2015-03-04 15:16:03 +00:00
|
|
|
Just $ SharedCipher (fromB64bs t)
|
2013-09-01 18:12:00 +00:00
|
|
|
_ -> Nothing
|
2012-11-11 04:51:07 +00:00
|
|
|
where
|
2017-01-31 22:40:42 +00:00
|
|
|
readkeys = KeyIds . splitc ','
|
2014-10-21 18:36:09 +00:00
|
|
|
|
2020-01-13 16:35:39 +00:00
|
|
|
isEncrypted :: ParsedRemoteConfig -> Bool
|
|
|
|
isEncrypted = isJust . extractCipher
|
2017-09-04 16:40:33 +00:00
|
|
|
|
2020-01-13 16:35:39 +00:00
|
|
|
describeEncryption :: ParsedRemoteConfig -> String
|
2014-10-21 18:36:09 +00:00
|
|
|
describeEncryption c = case extractCipher c of
|
2020-02-26 19:02:23 +00:00
|
|
|
Nothing -> "none"
|
2016-05-11 20:09:39 +00:00
|
|
|
Just cip -> nameCipher cip ++ " (" ++ describeCipher cip ++ ")"
|
|
|
|
|
|
|
|
nameCipher :: StorableCipher -> String
|
|
|
|
nameCipher (SharedCipher _) = "shared"
|
|
|
|
nameCipher (EncryptedCipher _ PubKey _) = "pubkey"
|
|
|
|
nameCipher (EncryptedCipher _ Hybrid _) = "hybrid"
|
|
|
|
nameCipher (SharedPubKeyCipher _ _) = "sharedpubkey"
|
2016-05-10 20:50:31 +00:00
|
|
|
|
2016-05-11 20:09:39 +00:00
|
|
|
describeCipher :: StorableCipher -> String
|
2016-05-10 20:50:31 +00:00
|
|
|
describeCipher c = case c of
|
2016-05-11 20:09:39 +00:00
|
|
|
(SharedCipher _) -> "encryption key stored in git repository"
|
|
|
|
(EncryptedCipher _ _ ks) -> showkeys ks
|
|
|
|
(SharedPubKeyCipher _ ks) -> showkeys ks
|
2016-05-10 20:50:31 +00:00
|
|
|
where
|
|
|
|
showkeys (KeyIds { keyIds = ks }) = "to gpg keys: " ++ unwords ks
|
metadata: Fix encoding problem that led to mojibake when storing metadata strings that contained both unicode characters and a space (or '!') character.
The fix is to stop using w82s, which does not properly reconstitute unicode
strings. Instrad, use utf8 bytestring to get the [Word8] to base64. This
passes unicode through perfectly, including any invalid filesystem encoded
characters.
Note that toB64 / fromB64 are also used for creds and cipher
embedding. It would be unfortunate if this change broke those uses.
For cipher embedding, note that ciphers can contain arbitrary bytes (should
really be using ByteString.Char8 there). Testing indicated it's not safe to
use the new fromB64 there; I think that characters were incorrectly
combined.
For credpair embedding, the username or password could contain unicode.
Before, that unicode would fail to round-trip through the b64.
So, I guess this is not going to break any embedded creds that worked
before.
This bug may have affected some creds before, and if so,
this change will not fix old ones, but should fix new ones at least.
2015-03-04 15:16:03 +00:00
|
|
|
|
|
|
|
{- Not using Utility.Base64 because these "Strings" are really
|
2015-05-07 22:07:13 +00:00
|
|
|
- bags of bytes and that would convert to unicode and not round-trip
|
metadata: Fix encoding problem that led to mojibake when storing metadata strings that contained both unicode characters and a space (or '!') character.
The fix is to stop using w82s, which does not properly reconstitute unicode
strings. Instrad, use utf8 bytestring to get the [Word8] to base64. This
passes unicode through perfectly, including any invalid filesystem encoded
characters.
Note that toB64 / fromB64 are also used for creds and cipher
embedding. It would be unfortunate if this change broke those uses.
For cipher embedding, note that ciphers can contain arbitrary bytes (should
really be using ByteString.Char8 there). Testing indicated it's not safe to
use the new fromB64 there; I think that characters were incorrectly
combined.
For credpair embedding, the username or password could contain unicode.
Before, that unicode would fail to round-trip through the b64.
So, I guess this is not going to break any embedded creds that worked
before.
This bug may have affected some creds before, and if so,
this change will not fix old ones, but should fix new ones at least.
2015-03-04 15:16:03 +00:00
|
|
|
- cleanly. -}
|
|
|
|
toB64bs :: String -> String
|
2015-05-07 22:07:13 +00:00
|
|
|
toB64bs = w82s . B.unpack . B64.encode . B.pack . s2w8
|
metadata: Fix encoding problem that led to mojibake when storing metadata strings that contained both unicode characters and a space (or '!') character.
The fix is to stop using w82s, which does not properly reconstitute unicode
strings. Instrad, use utf8 bytestring to get the [Word8] to base64. This
passes unicode through perfectly, including any invalid filesystem encoded
characters.
Note that toB64 / fromB64 are also used for creds and cipher
embedding. It would be unfortunate if this change broke those uses.
For cipher embedding, note that ciphers can contain arbitrary bytes (should
really be using ByteString.Char8 there). Testing indicated it's not safe to
use the new fromB64 there; I think that characters were incorrectly
combined.
For credpair embedding, the username or password could contain unicode.
Before, that unicode would fail to round-trip through the b64.
So, I guess this is not going to break any embedded creds that worked
before.
This bug may have affected some creds before, and if so,
this change will not fix old ones, but should fix new ones at least.
2015-03-04 15:16:03 +00:00
|
|
|
|
|
|
|
fromB64bs :: String -> String
|
2015-05-07 22:07:13 +00:00
|
|
|
fromB64bs s = either (const bad) (w82s . B.unpack) (B64.decode $ B.pack $ s2w8 s)
|
metadata: Fix encoding problem that led to mojibake when storing metadata strings that contained both unicode characters and a space (or '!') character.
The fix is to stop using w82s, which does not properly reconstitute unicode
strings. Instrad, use utf8 bytestring to get the [Word8] to base64. This
passes unicode through perfectly, including any invalid filesystem encoded
characters.
Note that toB64 / fromB64 are also used for creds and cipher
embedding. It would be unfortunate if this change broke those uses.
For cipher embedding, note that ciphers can contain arbitrary bytes (should
really be using ByteString.Char8 there). Testing indicated it's not safe to
use the new fromB64 there; I think that characters were incorrectly
combined.
For credpair embedding, the username or password could contain unicode.
Before, that unicode would fail to round-trip through the b64.
So, I guess this is not going to break any embedded creds that worked
before.
This bug may have affected some creds before, and if so,
this change will not fix old ones, but should fix new ones at least.
2015-03-04 15:16:03 +00:00
|
|
|
where
|
|
|
|
bad = error "bad base64 encoded data"
|