summaryrefslogtreecommitdiff
path: root/Data/OpenPGP/Util/DecryptSecretKey.hs
diff options
context:
space:
mode:
Diffstat (limited to 'Data/OpenPGP/Util/DecryptSecretKey.hs')
-rw-r--r--Data/OpenPGP/Util/DecryptSecretKey.hs25
1 files changed, 9 insertions, 16 deletions
diff --git a/Data/OpenPGP/Util/DecryptSecretKey.hs b/Data/OpenPGP/Util/DecryptSecretKey.hs
index 57dd8c3..9f9e42a 100644
--- a/Data/OpenPGP/Util/DecryptSecretKey.hs
+++ b/Data/OpenPGP/Util/DecryptSecretKey.hs
@@ -4,10 +4,11 @@
4module Data.OpenPGP.Util.DecryptSecretKey where 4module Data.OpenPGP.Util.DecryptSecretKey where
5 5
6import qualified Data.OpenPGP as OpenPGP 6import qualified Data.OpenPGP as OpenPGP
7import Data.OpenPGP.Internal (decode_s2k_count) 7import Data.OpenPGP.Internal (decode_s2k_count,checksumForKey)
8import qualified Data.ByteString as BS 8import qualified Data.ByteString as BS
9import qualified Data.ByteString.Lazy as LZ 9import qualified Data.ByteString.Lazy as LZ
10import Data.Word (Word16) 10import Data.Word
11import Data.Int
11import Data.Maybe 12import Data.Maybe
12import Control.Monad (foldM) 13import Control.Monad (foldM)
13import Data.Binary (get,Binary,Get,encode,put) 14import Data.Binary (get,Binary,Get,encode,put)
@@ -53,7 +54,7 @@ data Enciphered =
53withIV :: forall k. (Vincent.BlockCipher k) => (Vincent.IV k -> LZ.ByteString -> LZ.ByteString) -> Enciphered -> LZ.ByteString 54withIV :: forall k. (Vincent.BlockCipher k) => (Vincent.IV k -> LZ.ByteString -> LZ.ByteString) -> Enciphered -> LZ.ByteString
54withIV f (EncipheredWithIV s) = f iv bs 55withIV f (EncipheredWithIV s) = f iv bs
55 where 56 where
56 Just iv = Vincent.makeIV (toStrictBS ivbs) 57 Just iv = Vincent.makeIV (LZ.toStrict ivbs)
57 (ivbs,bs) = LZ.splitAt (fromIntegral ivlen) s 58 (ivbs,bs) = LZ.splitAt (fromIntegral ivlen) s
58#if defined(VERSION_cryptonite) 59#if defined(VERSION_cryptonite)
59 ivlen = Bytes.length (Vincent.nullIV :: Vincent.IV k) 60 ivlen = Bytes.length (Vincent.nullIV :: Vincent.IV k)
@@ -64,6 +65,7 @@ withIV f (EncipheredWithIV s) = f iv bs
64#endif 65#endif
65withIV f (EncipheredZeroIV s) = f Vincent.nullIV s 66withIV f (EncipheredZeroIV s) = f Vincent.nullIV s
66 67
68
67decryptSecretKey :: 69decryptSecretKey ::
68 BS.ByteString -- ^ Passphrase 70 BS.ByteString -- ^ Passphrase
69 -> OpenPGP.Packet -- ^ Encrypted SecretKeyPacket 71 -> OpenPGP.Packet -- ^ Encrypted SecretKeyPacket
@@ -74,7 +76,7 @@ decryptSecretKey pass k@(OpenPGP.SecretKeyPacket {
74 OpenPGP.version = 4, OpenPGP.key_algorithm = kalgo, 76 OpenPGP.version = 4, OpenPGP.key_algorithm = kalgo,
75 OpenPGP.s2k = s2k, OpenPGP.symmetric_algorithm = salgo, 77 OpenPGP.s2k = s2k, OpenPGP.symmetric_algorithm = salgo,
76 OpenPGP.key = existing, OpenPGP.encrypted_data = encd 78 OpenPGP.key = existing, OpenPGP.encrypted_data = encd
77 }) | chkF material == toStrictBS chk = 79 }) | chkF material == LZ.toStrict chk =
78 fmap (\m -> k { 80 fmap (\m -> k {
79 OpenPGP.s2k_useage = 0, 81 OpenPGP.s2k_useage = 0,
80 OpenPGP.symmetric_algorithm = OpenPGP.Unencrypted, 82 OpenPGP.symmetric_algorithm = OpenPGP.Unencrypted,
@@ -87,18 +89,9 @@ decryptSecretKey pass k@(OpenPGP.SecretKeyPacket {
87 (foldM (\m f -> do {mpi <- get; return $ (f,mpi):m}) existing 89 (foldM (\m f -> do {mpi <- get; return $ (f,mpi):m}) existing
88 (OpenPGP.secret_key_fields kalgo)) material 90 (OpenPGP.secret_key_fields kalgo)) material
89 (material, chk) = LZ.splitAt (LZ.length decd - chkSize) decd 91 (material, chk) = LZ.splitAt (LZ.length decd - chkSize) decd
90 (chkSize, chkF) 92 (chkSize, chkF) = checksumForKey (OpenPGP.s2k_useage k)
91 | OpenPGP.s2k_useage k == 254 = (20, sha1 . toStrictBS)
92 | otherwise = (2, toStrictBS . encode . checksum . toStrictBS)
93 -- Words16s are written as 2 bytes in big-endian (network) order
94 decd = withS2K simpleUnCFB salgo (Just s2k) (toLazyBS pass) (EncipheredWithIV encd) 93 decd = withS2K simpleUnCFB salgo (Just s2k) (toLazyBS pass) (EncipheredWithIV encd)
95 94
96#if defined(VERSION_cryptonite)
97 sha1 x = Bytes.convert (hash x :: Digest SHA1)
98#else
99 sha1 = SHA1.hash
100#endif
101
102decryptSecretKey _ _ = Nothing 95decryptSecretKey _ _ = Nothing
103 96
104checksum :: BS.ByteString -> Word16 97checksum :: BS.ByteString -> Word16
@@ -133,7 +126,7 @@ withS2K codec OpenPGP.CAST5 s2k s = withIV $ codec (string2key s2k s :: Thoma
133withS2K codec algo _ _ = error $ "Unsupported symmetric algorithm : " ++ show algo ++ " in Data.OpenPGP.CryptoAPI.withS2K" 126withS2K codec algo _ _ = error $ "Unsupported symmetric algorithm : " ++ show algo ++ " in Data.OpenPGP.CryptoAPI.withS2K"
134 127
135simpleCFB :: forall k g. (Vincent.BlockCipher k, RG g) => g -> k -> LZ.ByteString -> (LZ.ByteString, g) 128simpleCFB :: forall k g. (Vincent.BlockCipher k, RG g) => g -> k -> LZ.ByteString -> (LZ.ByteString, g)
136simpleCFB g k bs = ( padThenUnpad k (LZ.fromChunks . (ivbs:) . (:[]) . Vincent.cfbEncrypt k iv . toStrictBS) bs 129simpleCFB g k bs = ( padThenUnpad k (LZ.fromChunks . (ivbs:) . (:[]) . Vincent.cfbEncrypt k iv . LZ.toStrict) bs
137 , g' ) 130 , g' )
138 where 131 where
139 Just iv = Vincent.makeIV ivbs 132 Just iv = Vincent.makeIV ivbs
@@ -180,7 +173,7 @@ encryptSecretKey passphrase s2k salgo plain = do
180 -- two-octet checksum is required. 173 -- two-octet checksum is required.
181 s2k_usage_octet = 255 174 s2k_usage_octet = 255
182 -- chkSize = 2 175 -- chkSize = 2
183 chkF = toStrictBS . encode . checksum . toStrictBS 176 chkF = LZ.toStrict . encode . checksum . LZ.toStrict
184 177
185 178
186 -- k = string2key s2k passphrase -- OpenPGP.string2key hashBySymbol s2k passphrase 179 -- k = string2key s2k passphrase -- OpenPGP.string2key hashBySymbol s2k passphrase