git-annex/Crypto.hs

154 lines
4.9 KiB
Haskell
Raw Normal View History

2011-04-15 22:18:39 +00:00
{- git-annex crypto
-
- Currently using gpg; could later be modified to support different
- crypto backends if neccessary.
2011-04-15 22:18:39 +00:00
-
- Copyright 2011-2012 Joey Hess <joey@kitenet.net>
2011-04-15 22:18:39 +00:00
-
- Licensed under the GNU GPL version 3 or higher.
-}
module Crypto (
Cipher,
2012-04-29 18:31:34 +00:00
KeyIds(..),
StorableCipher(..),
genEncryptedCipher,
genSharedCipher,
updateEncryptedCipher,
2011-04-17 22:18:27 +00:00
describeCipher,
2011-04-15 22:18:39 +00:00
decryptCipher,
encryptKey,
feedFile,
feedBytes,
readBytes,
encrypt,
decrypt,
2011-04-21 20:56:24 +00:00
prop_hmacWithCipher_sane
2011-04-15 22:18:39 +00:00
) where
import qualified Data.ByteString.Lazy as L
import Data.ByteString.Lazy.UTF8 (fromString)
import Data.Digest.Pure.SHA
import Control.Applicative
2011-04-15 22:18:39 +00:00
2011-10-05 20:02:51 +00:00
import Common.Annex
import qualified Utility.Gpg as Gpg
import Types.Key
import Types.Crypto
2011-04-15 22:18:39 +00:00
{- The beginning of a Cipher is used for HMAC; the remainder
- is used as the GPG symmetric encryption passphrase.
-
- HMAC SHA1 needs only 64 bytes. The rest of the HMAC key is for expansion,
2011-04-17 15:13:54 +00:00
- perhaps to HMAC SHA512, which needs 128 bytes (ideally).
- It also provides room the Cipher to contain data in a form like base64,
- which does not pack a full byte of entropy into a byte of data.
2011-04-17 15:13:54 +00:00
-
- 256 bytes is enough for gpg's symetric cipher; unlike weaker public key
- crypto, the key does not need to be too large.
-}
cipherBeginning :: Int
cipherBeginning = 256
cipherSize :: Int
cipherSize = 512
cipherPassphrase :: Cipher -> String
cipherPassphrase (Cipher c) = drop cipherBeginning c
cipherHmac :: Cipher -> String
cipherHmac (Cipher c) = take cipherBeginning c
{- Creates a new Cipher, encrypted to the specified key id. -}
genEncryptedCipher :: String -> IO StorableCipher
genEncryptedCipher keyid = do
ks <- Gpg.findPubKeys keyid
random <- Gpg.genRandom cipherSize
encryptCipher (Cipher random) ks
{- Creates a new, shared Cipher. -}
genSharedCipher :: IO StorableCipher
genSharedCipher = SharedCipher <$> Gpg.genRandom cipherSize
{- Updates an existing Cipher, re-encrypting it to add a keyid. -}
updateEncryptedCipher :: String -> StorableCipher -> IO StorableCipher
updateEncryptedCipher _ (SharedCipher _) = undefined
updateEncryptedCipher keyid encipher@(EncryptedCipher _ ks) = do
ks' <- Gpg.findPubKeys keyid
cipher <- decryptCipher encipher
encryptCipher cipher (merge ks ks')
where
merge (KeyIds a) (KeyIds b) = KeyIds $ a ++ b
2011-04-15 22:18:39 +00:00
describeCipher :: StorableCipher -> String
describeCipher (SharedCipher _) = "shared cipher"
2011-04-17 22:18:27 +00:00
describeCipher (EncryptedCipher _ (KeyIds ks)) =
"with gpg " ++ keys ks ++ " " ++ unwords ks
where
keys [_] = "key"
keys _ = "keys"
2011-04-17 22:18:27 +00:00
{- Encrypts a Cipher to the specified KeyIds. -}
encryptCipher :: Cipher -> KeyIds -> IO StorableCipher
encryptCipher (Cipher c) (KeyIds ks) = do
let ks' = nub $ sort ks -- gpg complains about duplicate recipient keyids
encipher <- Gpg.pipeStrict ([ Params "--encrypt" ] ++ recipients ks') c
return $ EncryptedCipher encipher (KeyIds ks')
2012-12-13 04:45:27 +00:00
where
recipients l = force_recipients :
concatMap (\k -> [Param "--recipient", Param k]) l
-- Force gpg to only encrypt to the specified
-- recipients, not configured defaults.
force_recipients = Params "--no-encrypt-to --no-default-recipient"
2011-04-15 22:18:39 +00:00
{- Decrypting an EncryptedCipher is expensive; the Cipher should be cached. -}
decryptCipher :: StorableCipher -> IO Cipher
decryptCipher (SharedCipher t) = return $ Cipher t
decryptCipher (EncryptedCipher t _) =
Cipher <$> Gpg.pipeStrict [ Param "--decrypt" ] t
2011-04-15 22:18:39 +00:00
{- Generates an encrypted form of a Key. The encryption does not need to be
2011-04-15 22:18:39 +00:00
- reversable, nor does it need to be the same type of encryption used
- on content. It does need to be repeatable. -}
2011-10-11 18:43:45 +00:00
encryptKey :: Cipher -> Key -> Key
encryptKey c k = Key
{ keyName = hmacWithCipher c (key2file k)
2011-10-11 18:43:45 +00:00
, keyBackendName = "GPGHMACSHA1"
, keySize = Nothing -- size and mtime omitted
, keyMtime = Nothing -- to avoid leaking data
}
2011-04-15 22:18:39 +00:00
type Feeder = Handle -> IO ()
type Reader a = Handle -> IO a
feedFile :: FilePath -> Feeder
feedFile f h = L.hPut h =<< L.readFile f
feedBytes :: L.ByteString -> Feeder
feedBytes = flip L.hPut
readBytes :: (L.ByteString -> IO a) -> Reader a
readBytes a h = L.hGetContents h >>= a
{- Runs a Feeder action, that generates content that is encrypted with the
- Cipher, and read by the Reader action. -}
encrypt :: Cipher -> Feeder -> Reader a -> IO a
encrypt = Gpg.feedRead [Params "--symmetric --force-mdc"] . cipherPassphrase
{- Runs a Feeder action, that generates content that is decrypted with the
- Cipher, and read by the Reader action. -}
decrypt :: Cipher -> Feeder -> Reader a -> IO a
decrypt = Gpg.feedRead [Param "--decrypt"] . cipherPassphrase
2011-04-15 22:18:39 +00:00
2011-04-21 20:56:24 +00:00
hmacWithCipher :: Cipher -> String -> String
hmacWithCipher c = hmacWithCipher' (cipherHmac c)
hmacWithCipher' :: String -> String -> String
hmacWithCipher' c s = showDigest $ hmacSha1 (fromString c) (fromString s)
2011-04-21 20:56:24 +00:00
{- Ensure that hmacWithCipher' returns the same thing forevermore. -}
prop_hmacWithCipher_sane :: Bool
prop_hmacWithCipher_sane = known_good == hmacWithCipher' "foo" "bar"
where
known_good = "46b4ec586117154dacd49d664e5d63fdc88efb51"