convert StorableCipher to ByteString

This allows getting rid of the ugly and error prone handling of
"bag of bytes" String in Remote.Helper.Encryptable.
Avoiding breakage like that dealt with by commit
9862d64bf9

And allows converting Utility.Gpg to use ByteString for IO, which is
a welcome change.

Tested the new git-annex interoperability with old, using all 3
encryption= types.

Sponsored-By: the NIH-funded NICEMAN (ReproNim TR&D3) project
This commit is contained in:
Joey Hess 2023-11-01 14:27:22 -04:00
parent be6b56df4c
commit c41ca6c832
No known key found for this signature in database
GPG key ID: DB12DB0FF05F8F38
5 changed files with 45 additions and 68 deletions

View file

@ -3,7 +3,7 @@
- Currently using gpg; could later be modified to support different - Currently using gpg; could later be modified to support different
- crypto backends if necessary. - crypto backends if necessary.
- -
- Copyright 2011-2022 Joey Hess <id@joeyh.name> - Copyright 2011-2023 Joey Hess <id@joeyh.name>
- -
- Licensed under the GNU AGPL version 3 or higher. - Licensed under the GNU AGPL version 3 or higher.
-} -}
@ -39,7 +39,6 @@ module Crypto (
import qualified Data.ByteString as S import qualified Data.ByteString as S
import qualified Data.ByteString.Lazy as L import qualified Data.ByteString.Lazy as L
import Data.ByteString.UTF8 (fromString)
import Control.Monad.IO.Class import Control.Monad.IO.Class
import Annex.Common import Annex.Common
@ -71,12 +70,12 @@ cipherBeginning = 256
cipherSize :: Int cipherSize :: Int
cipherSize = 512 cipherSize = 512
cipherPassphrase :: Cipher -> String cipherPassphrase :: Cipher -> S.ByteString
cipherPassphrase (Cipher c) = drop cipherBeginning c cipherPassphrase (Cipher c) = S.drop cipherBeginning c
cipherPassphrase (MacOnlyCipher _) = giveup "MAC-only cipher" cipherPassphrase (MacOnlyCipher _) = giveup "MAC-only cipher"
cipherMac :: Cipher -> String cipherMac :: Cipher -> S.ByteString
cipherMac (Cipher c) = take cipherBeginning c cipherMac (Cipher c) = S.take cipherBeginning c
cipherMac (MacOnlyCipher c) = c cipherMac (MacOnlyCipher c) = c
{- Creates a new Cipher, encrypted to the specified key id. -} {- Creates a new Cipher, encrypted to the specified key id. -}
@ -168,7 +167,7 @@ type EncKey = Key -> Key
- on content. It does need to be repeatable. -} - on content. It does need to be repeatable. -}
encryptKey :: Mac -> Cipher -> EncKey encryptKey :: Mac -> Cipher -> EncKey
encryptKey mac c k = mkKey $ \d -> d encryptKey mac c k = mkKey $ \d -> d
{ keyName = S.toShort $ encodeBS $ macWithCipher mac c (serializeKey k) { keyName = S.toShort $ encodeBS $ macWithCipher mac c (serializeKey' k)
, keyVariety = OtherKey $ , keyVariety = OtherKey $
encryptedBackendNamePrefix <> encodeBS (showMac mac) encryptedBackendNamePrefix <> encodeBS (showMac mac)
} }
@ -225,10 +224,10 @@ decrypt cmd c cipher = case cipher of
where where
params = Param "--decrypt" : getGpgDecParams c params = Param "--decrypt" : getGpgDecParams c
macWithCipher :: Mac -> Cipher -> String -> String macWithCipher :: Mac -> Cipher -> S.ByteString -> String
macWithCipher mac c = macWithCipher' mac (cipherMac c) macWithCipher mac c = macWithCipher' mac (cipherMac c)
macWithCipher' :: Mac -> String -> String -> String macWithCipher' :: Mac -> S.ByteString -> S.ByteString -> String
macWithCipher' mac c s = calcMac mac (fromString c) (fromString s) macWithCipher' mac c s = calcMac mac c s
{- Ensure that macWithCipher' returns the same thing forevermore. -} {- Ensure that macWithCipher' returns the same thing forevermore. -}
prop_HmacSha1WithCipher_sane :: Bool prop_HmacSha1WithCipher_sane :: Bool

View file

@ -28,8 +28,6 @@ module Remote.Helper.Encryptable (
import qualified Data.Map as M import qualified Data.Map as M
import qualified Data.Set as S import qualified Data.Set as S
import qualified Data.ByteString as B
import Data.Word
import Control.Concurrent.STM import Control.Concurrent.STM
import Annex.Common import Annex.Common
@ -273,7 +271,7 @@ storeCipher cip = case cip of
(EncryptedCipher t _ ks) -> addcipher t . storekeys ks cipherkeysField (EncryptedCipher t _ ks) -> addcipher t . storekeys ks cipherkeysField
(SharedPubKeyCipher t ks) -> addcipher t . storekeys ks pubkeysField (SharedPubKeyCipher t ks) -> addcipher t . storekeys ks pubkeysField
where where
addcipher t = M.insert cipherField (Accepted (toB64bs t)) addcipher t = M.insert cipherField (Accepted (decodeBS (toB64 t)))
storekeys (KeyIds l) n = M.insert n (Accepted (intercalate "," l)) storekeys (KeyIds l) n = M.insert n (Accepted (intercalate "," l))
{- Extracts an StorableCipher from a remote's configuration. -} {- Extracts an StorableCipher from a remote's configuration. -}
@ -282,13 +280,13 @@ extractCipher c = case (getRemoteConfigValue cipherField c,
(getRemoteConfigValue cipherkeysField c <|> getRemoteConfigValue pubkeysField c), (getRemoteConfigValue cipherkeysField c <|> getRemoteConfigValue pubkeysField c),
getRemoteConfigValue encryptionField c) of getRemoteConfigValue encryptionField c) of
(Just t, Just ks, Just HybridEncryption) -> (Just t, Just ks, Just HybridEncryption) ->
Just $ EncryptedCipher (fromB64bs t) Hybrid (readkeys ks) Just $ EncryptedCipher (fromB64 (encodeBS t)) Hybrid (readkeys ks)
(Just t, Just ks, Just PubKeyEncryption) -> (Just t, Just ks, Just PubKeyEncryption) ->
Just $ EncryptedCipher (fromB64bs t) PubKey (readkeys ks) Just $ EncryptedCipher (fromB64 (encodeBS t)) PubKey (readkeys ks)
(Just t, Just ks, Just SharedPubKeyEncryption) -> (Just t, Just ks, Just SharedPubKeyEncryption) ->
Just $ SharedPubKeyCipher (fromB64bs t) (readkeys ks) Just $ SharedPubKeyCipher (fromB64 (encodeBS t)) (readkeys ks)
(Just t, Nothing, Just SharedEncryption) -> (Just t, Nothing, Just SharedEncryption) ->
Just $ SharedCipher (fromB64bs t) Just $ SharedCipher (fromB64 (encodeBS t))
_ -> Nothing _ -> Nothing
where where
readkeys = KeyIds . splitc ',' readkeys = KeyIds . splitc ','
@ -322,25 +320,3 @@ describeCipher c = case c of
(SharedPubKeyCipher _ ks) -> showkeys ks (SharedPubKeyCipher _ ks) -> showkeys ks
where where
showkeys (KeyIds { keyIds = ks }) = "to gpg keys: " ++ unwords ks showkeys (KeyIds { keyIds = ks }) = "to gpg keys: " ++ unwords ks
{- Not using encodeBS because these "Strings" are really
- bags of bytes and are not encoding with the filesystem encoding.
- So this hack is needed to work on all locales and roundtrip cleanly.
-}
toB64bs :: String -> String
toB64bs = w82s . B.unpack . toB64 . B.pack . s2w8
fromB64bs :: String -> String
fromB64bs = w82s . B.unpack . fromB64 . B.pack . s2w8
c2w8 :: Char -> Word8
c2w8 = fromIntegral . fromEnum
w82c :: Word8 -> Char
w82c = toEnum . fromIntegral
s2w8 :: String -> [Word8]
s2w8 = map c2w8
w82s :: [Word8] -> String
w82s = map w82c

View file

@ -25,6 +25,7 @@ import Utility.Gpg (KeyIds(..))
import Data.Typeable import Data.Typeable
import qualified Data.Map as M import qualified Data.Map as M
import Data.ByteString (ByteString)
data EncryptionMethod data EncryptionMethod
= NoneEncryption = NoneEncryption
@ -35,12 +36,12 @@ data EncryptionMethod
deriving (Typeable, Eq) deriving (Typeable, Eq)
-- XXX ideally, this would be a locked memory region -- XXX ideally, this would be a locked memory region
data Cipher = Cipher String | MacOnlyCipher String data Cipher = Cipher ByteString | MacOnlyCipher ByteString
data StorableCipher data StorableCipher
= EncryptedCipher String EncryptedCipherVariant KeyIds = EncryptedCipher ByteString EncryptedCipherVariant KeyIds
| SharedCipher String | SharedCipher ByteString
| SharedPubKeyCipher String KeyIds | SharedPubKeyCipher ByteString KeyIds
deriving (Ord, Eq) deriving (Ord, Eq)
data EncryptedCipherVariant = Hybrid | PubKey data EncryptedCipherVariant = Hybrid | PubKey
deriving (Ord, Eq) deriving (Ord, Eq)

View file

@ -1,10 +1,11 @@
{- gpg interface {- gpg interface
- -
- Copyright 2011-2022 Joey Hess <id@joeyh.name> - Copyright 2011-2023 Joey Hess <id@joeyh.name>
- -
- License: BSD-2-clause - License: BSD-2-clause
-} -}
{-# LANGUAGE OverloadedStrings #-}
{-# LANGUAGE CPP #-} {-# LANGUAGE CPP #-}
module Utility.Gpg ( module Utility.Gpg (
@ -48,6 +49,7 @@ import Utility.Format (decode_c)
import Control.Concurrent.Async import Control.Concurrent.Async
import Control.Monad.IO.Class import Control.Monad.IO.Class
import qualified Data.ByteString as B
import qualified Data.Map as M import qualified Data.Map as M
import Data.Char import Data.Char
@ -108,10 +110,10 @@ stdEncryptionParams symmetric = enc symmetric ++
] ]
{- Runs gpg with some params and returns its stdout, strictly. -} {- Runs gpg with some params and returns its stdout, strictly. -}
readStrict :: GpgCmd -> [CommandParam] -> IO String readStrict :: GpgCmd -> [CommandParam] -> IO B.ByteString
readStrict c p = readStrict' c p Nothing readStrict c p = readStrict' c p Nothing
readStrict' :: GpgCmd -> [CommandParam] -> Maybe [(String, String)] -> IO String readStrict' :: GpgCmd -> [CommandParam] -> Maybe [(String, String)] -> IO B.ByteString
readStrict' (GpgCmd cmd) params environ = do readStrict' (GpgCmd cmd) params environ = do
params' <- stdParams params params' <- stdParams params
let p = (proc cmd params') let p = (proc cmd params')
@ -120,17 +122,16 @@ readStrict' (GpgCmd cmd) params environ = do
} }
withCreateProcess p (go p) withCreateProcess p (go p)
where where
go p _ (Just hout) _ pid = do go p _ (Just hout) _ pid =
hSetBinaryMode hout True forceSuccessProcess p pid `after` B.hGetContents hout
forceSuccessProcess p pid `after` hGetContentsStrict hout
go _ _ _ _ _ = error "internal" go _ _ _ _ _ = error "internal"
{- Runs gpg, piping an input value to it, and returning its stdout, {- Runs gpg, piping an input value to it, and returning its stdout,
- strictly. -} - strictly. -}
pipeStrict :: GpgCmd -> [CommandParam] -> String -> IO String pipeStrict :: GpgCmd -> [CommandParam] -> B.ByteString -> IO B.ByteString
pipeStrict c p i = pipeStrict' c p Nothing i pipeStrict c p i = pipeStrict' c p Nothing i
pipeStrict' :: GpgCmd -> [CommandParam] -> Maybe [(String, String)] -> String -> IO String pipeStrict' :: GpgCmd -> [CommandParam] -> Maybe [(String, String)] -> B.ByteString -> IO B.ByteString
pipeStrict' (GpgCmd cmd) params environ input = do pipeStrict' (GpgCmd cmd) params environ input = do
params' <- stdParams params params' <- stdParams params
let p = (proc cmd params') let p = (proc cmd params')
@ -141,11 +142,9 @@ pipeStrict' (GpgCmd cmd) params environ input = do
withCreateProcess p (go p) withCreateProcess p (go p)
where where
go p (Just to) (Just from) _ pid = do go p (Just to) (Just from) _ pid = do
hSetBinaryMode to True B.hPutStr to input
hSetBinaryMode from True
hPutStr to input
hClose to hClose to
forceSuccessProcess p pid `after` hGetContentsStrict from forceSuccessProcess p pid `after` B.hGetContents from
go _ _ _ _ _ = error "internal" go _ _ _ _ _ = error "internal"
{- Runs gpg with some parameters. First sends it a passphrase (unless it {- Runs gpg with some parameters. First sends it a passphrase (unless it
@ -158,7 +157,7 @@ pipeStrict' (GpgCmd cmd) params environ input = do
- the passphrase. - the passphrase.
- -
- Note that the reader must fully consume gpg's input before returning. -} - Note that the reader must fully consume gpg's input before returning. -}
feedRead :: (MonadIO m, MonadMask m) => GpgCmd -> [CommandParam] -> String -> (Handle -> IO ()) -> (Handle -> m a) -> m a feedRead :: (MonadIO m, MonadMask m) => GpgCmd -> [CommandParam] -> B.ByteString -> (Handle -> IO ()) -> (Handle -> m a) -> m a
feedRead cmd params passphrase feeder reader = do feedRead cmd params passphrase feeder reader = do
#ifndef mingw32_HOST_OS #ifndef mingw32_HOST_OS
let setup = liftIO $ do let setup = liftIO $ do
@ -166,7 +165,7 @@ feedRead cmd params passphrase feeder reader = do
(frompipe, topipe) <- System.Posix.IO.createPipe (frompipe, topipe) <- System.Posix.IO.createPipe
toh <- fdToHandle topipe toh <- fdToHandle topipe
t <- async $ do t <- async $ do
hPutStrLn toh passphrase B.hPutStr toh (passphrase <> "\n")
hClose toh hClose toh
let Fd pfd = frompipe let Fd pfd = frompipe
let passphrasefd = [Param "--passphrase-fd", Param $ show pfd] let passphrasefd = [Param "--passphrase-fd", Param $ show pfd]
@ -180,7 +179,7 @@ feedRead cmd params passphrase feeder reader = do
#else #else
-- store the passphrase in a temp file for gpg -- store the passphrase in a temp file for gpg
withTmpFile "gpg" $ \tmpfile h -> do withTmpFile "gpg" $ \tmpfile h -> do
liftIO $ hPutStr h passphrase liftIO $ B.hPutStr h passphrase
liftIO $ hClose h liftIO $ hClose h
let passphrasefile = [Param "--passphrase-file", File tmpfile] let passphrasefile = [Param "--passphrase-file", File tmpfile]
go $ passphrasefile ++ params go $ passphrasefile ++ params
@ -223,7 +222,8 @@ findPubKeys' cmd environ for
-- pass forced subkey through as-is rather than -- pass forced subkey through as-is rather than
-- looking up the master key. -- looking up the master key.
| isForcedSubKey for = return $ KeyIds [for] | isForcedSubKey for = return $ KeyIds [for]
| otherwise = KeyIds . parse . lines <$> readStrict' cmd params environ | otherwise = KeyIds . parse . lines . decodeBS
<$> readStrict' cmd params environ
where where
params = [Param "--with-colons", Param "--list-public-keys", Param for] params = [Param "--with-colons", Param "--list-public-keys", Param for]
parse = mapMaybe (keyIdField . splitc ':') parse = mapMaybe (keyIdField . splitc ':')
@ -241,7 +241,8 @@ type UserId = String
secretKeys :: GpgCmd -> IO (M.Map KeyId UserId) secretKeys :: GpgCmd -> IO (M.Map KeyId UserId)
secretKeys cmd = catchDefaultIO M.empty makemap secretKeys cmd = catchDefaultIO M.empty makemap
where where
makemap = M.fromList . parse . lines <$> readStrict cmd params makemap = M.fromList . parse . lines . decodeBS
<$> readStrict cmd params
params = [Param "--with-colons", Param "--list-secret-keys", Param "--fixed-list-mode"] params = [Param "--with-colons", Param "--list-secret-keys", Param "--fixed-list-mode"]
parse = extract [] Nothing . map (splitc ':') parse = extract [] Nothing . map (splitc ':')
extract c (Just keyid) (("uid":_:_:_:_:_:_:_:_:userid:_):rest) = extract c (Just keyid) (("uid":_:_:_:_:_:_:_:_:userid:_):rest) =
@ -301,7 +302,7 @@ genSecretKey (GpgCmd cmd) keytype passphrase userid keysize =
{- Creates a block of high-quality random data suitable to use as a cipher. {- Creates a block of high-quality random data suitable to use as a cipher.
- It is armored, to avoid newlines, since gpg only reads ciphers up to the - It is armored, to avoid newlines, since gpg only reads ciphers up to the
- first newline. -} - first newline. -}
genRandom :: GpgCmd -> Bool -> Size -> IO String genRandom :: GpgCmd -> Bool -> Size -> IO B.ByteString
genRandom cmd highQuality size = do genRandom cmd highQuality size = do
s <- readStrict cmd params s <- readStrict cmd params
checksize s checksize s
@ -327,7 +328,7 @@ genRandom cmd highQuality size = do
- entropy. -} - entropy. -}
expectedlength = size * 8 `div` 6 expectedlength = size * 8 `div` 6
checksize s = let len = length s in checksize s = let len = B.length s in
unless (len >= expectedlength) $ unless (len >= expectedlength) $
shortread len shortread len
@ -439,8 +440,8 @@ testHarness tmpdir cmd a = ifM (inSearchPath (unGpgCmd cmd))
liftIO $ void $ tryIO $ modifyFileMode (toRawFilePath subdir) $ liftIO $ void $ tryIO $ modifyFileMode (toRawFilePath subdir) $
removeModes $ otherGroupModes removeModes $ otherGroupModes
-- For some reason, recent gpg needs a trustdb to be set up. -- For some reason, recent gpg needs a trustdb to be set up.
_ <- pipeStrict' cmd [Param "--trust-model", Param "auto", Param "--update-trustdb"] (Just environ) [] _ <- pipeStrict' cmd [Param "--trust-model", Param "auto", Param "--update-trustdb"] (Just environ) mempty
_ <- pipeStrict' cmd [Param "--import", Param "-q"] (Just environ) $ unlines _ <- pipeStrict' cmd [Param "--import", Param "-q"] (Just environ) $ encodeBS $ unlines
[testSecretKey, testKey] [testSecretKey, testKey]
return environ return environ
@ -470,7 +471,7 @@ checkEncryptionFile cmd environ filename keys =
where where
params = [Param "--list-packets", Param "--list-only", File filename] params = [Param "--list-packets", Param "--list-only", File filename]
checkEncryptionStream :: GpgCmd -> Maybe [(String, String)] -> String -> Maybe KeyIds -> IO Bool checkEncryptionStream :: GpgCmd -> Maybe [(String, String)] -> B.ByteString -> Maybe KeyIds -> IO Bool
checkEncryptionStream cmd environ stream keys = checkEncryptionStream cmd environ stream keys =
checkGpgPackets cmd environ keys =<< pipeStrict' cmd params environ stream checkGpgPackets cmd environ keys =<< pipeStrict' cmd params environ stream
where where
@ -480,13 +481,13 @@ checkEncryptionStream cmd environ stream keys =
- symmetrically encrypted (keys is Nothing), or encrypted to some - symmetrically encrypted (keys is Nothing), or encrypted to some
- public key(s). - public key(s).
- /!\ The key needs to be in the keyring! -} - /!\ The key needs to be in the keyring! -}
checkGpgPackets :: GpgCmd -> Maybe [(String, String)] -> Maybe KeyIds -> String -> IO Bool checkGpgPackets :: GpgCmd -> Maybe [(String, String)] -> Maybe KeyIds -> B.ByteString -> IO Bool
checkGpgPackets cmd environ keys str = do checkGpgPackets cmd environ keys str = do
let (asym,sym) = partition (pubkeyEncPacket `isPrefixOf`) $ let (asym,sym) = partition (pubkeyEncPacket `isPrefixOf`) $
filter (\l' -> pubkeyEncPacket `isPrefixOf` l' || filter (\l' -> pubkeyEncPacket `isPrefixOf` l' ||
symkeyEncPacket `isPrefixOf` l') $ symkeyEncPacket `isPrefixOf` l') $
takeWhile (/= ":encrypted data packet:") $ takeWhile (/= ":encrypted data packet:") $
lines str lines (decodeBS str)
case (keys,asym,sym) of case (keys,asym,sym) of
(Nothing, [], [_]) -> return True (Nothing, [], [_]) -> return True
(Just (KeyIds ks), ls, []) -> do (Just (KeyIds ks), ls, []) -> do

View file

@ -30,4 +30,4 @@ cron-20231027/build-ubuntu.yaml-1289-1c03c8fd-failed/0_test-annex (normal, ubunt
[[!meta author=yoh]] [[!meta author=yoh]]
[[!tag projects/repronim]] [[!tag projects/repronim]]
> [[fixed|done]] --[[Joey]]