summaryrefslogtreecommitdiff
path: root/Data
diff options
context:
space:
mode:
authorStephen Paul Weber <singpolyma@singpolyma.net>2013-01-01 13:08:12 -0500
committerStephen Paul Weber <singpolyma@singpolyma.net>2013-01-01 13:08:12 -0500
commit9e4f996c68c3901bab4a5e1e70638c2531a85994 (patch)
tree38b7e03b2208d56e3e19652335fda7d4f327b901 /Data
parent06f96ec8d862e43d12cfb4c3ad8650395cfc662c (diff)
Proper S2K type
S2K is a seperate concept and is used in both secret key packets and SymmetricallyEncryptedSessionKey packets. It should have its own parser and thus its own type. This also cleans up the SecretKeyPacket record considerably (the many Maybe fields were a smell). SecretKeyPacket.s2k should be set to (Just $ SimpleS2K MD5) in fallback cases. symmetric_algorithm should be set to Unencrypted when s2k_useage is 0. s2k_useage itself is only needed for the different between 255 and 254 (different checksum). Round trip encode/decode tests for S2K work.
Diffstat (limited to 'Data')
-rw-r--r--Data/OpenPGP.hs86
1 files changed, 43 insertions, 43 deletions
diff --git a/Data/OpenPGP.hs b/Data/OpenPGP.hs
index 4dad404..5e62d1a 100644
--- a/Data/OpenPGP.hs
+++ b/Data/OpenPGP.hs
@@ -34,14 +34,11 @@ module Data.OpenPGP (
34 message, 34 message,
35 nested, 35 nested,
36 private_hash, 36 private_hash,
37 s2k_count,
38 s2k_hash_algorithm,
39 s2k_salt,
40 s2k_type,
41 s2k_useage, 37 s2k_useage,
38 s2k,
42 signature, 39 signature,
43 signature_type, 40 signature_type,
44 symmetric_type, 41 symmetric_algorithm,
45 timestamp, 42 timestamp,
46 trailer, 43 trailer,
47 unhashed_subpackets, 44 unhashed_subpackets,
@@ -51,6 +48,7 @@ module Data.OpenPGP (
51 signaturePacket, 48 signaturePacket,
52 Message(..), 49 Message(..),
53 SignatureSubpacket(..), 50 SignatureSubpacket(..),
51 S2K(..),
54 HashAlgorithm(..), 52 HashAlgorithm(..),
55 KeyAlgorithm(..), 53 KeyAlgorithm(..),
56 SymmetricAlgorithm(..), 54 SymmetricAlgorithm(..),
@@ -211,12 +209,9 @@ data Packet =
211 timestamp::Word32, 209 timestamp::Word32,
212 key_algorithm::KeyAlgorithm, 210 key_algorithm::KeyAlgorithm,
213 key::[(Char,MPI)], 211 key::[(Char,MPI)],
214 s2k_useage::Word8, -- ^ determines if the 'Maybe's are 'Just' or 'Nothing' 212 s2k_useage::Word8,
215 symmetric_type::Maybe Word8, 213 s2k::Maybe S2K,
216 s2k_type::Maybe Word8, 214 symmetric_algorithm::SymmetricAlgorithm,
217 s2k_hash_algorithm::Maybe HashAlgorithm,
218 s2k_salt::Maybe Word64,
219 s2k_count::Maybe Word32,
220 encrypted_data::B.ByteString, 215 encrypted_data::B.ByteString,
221 private_hash::Maybe B.ByteString, -- ^ the hash may be in the encrypted data 216 private_hash::Maybe B.ByteString, -- ^ the hash may be in the encrypted data
222 is_subkey::Bool 217 is_subkey::Bool
@@ -436,23 +431,16 @@ put_packet (OnePassSignaturePacket { version = version,
436 ], 4) 431 ], 4)
437put_packet (SecretKeyPacket { version = version, timestamp = timestamp, 432put_packet (SecretKeyPacket { version = version, timestamp = timestamp,
438 key_algorithm = algorithm, key = key, 433 key_algorithm = algorithm, key = key,
439 s2k_useage = s2k_useage, 434 s2k_useage = s2k_useage, s2k = s2k,
440 symmetric_type = symmetric_type, 435 symmetric_algorithm = symmetric_algorithm,
441 s2k_type = s2k_type,
442 s2k_hash_algorithm = s2k_hash_algo,
443 s2k_salt = s2k_salt,
444 s2k_count = s2k_count,
445 encrypted_data = encrypted_data, 436 encrypted_data = encrypted_data,
446 is_subkey = is_subkey }) = 437 is_subkey = is_subkey }) =
447 (B.concat $ [p, encode s2k_useage] ++ 438 (B.concat $ p :
448 (if s2k_useage `elem` [255, 254] then 439 (case s2k of
449 [encode $ fromJust symmetric_type, encode s2k_t, 440 Just s2k -> [encode s2k_useage, encode symmetric_algorithm, encode s2k]
450 encode $ fromJust s2k_hash_algo] ++ 441 Nothing -> [encode symmetric_algorithm]
451 (if s2k_t `elem` [1,3] then [encode $ fromJust s2k_salt] else []) ++ 442 ) ++
452 if s2k_t == 3 then 443 (if symmetric_algorithm /= Unencrypted then
453 [encode $ encode_s2k_count $ fromJust s2k_count] else []
454 else []) ++
455 (if s2k_useage > 0 then
456 [encrypted_data] 444 [encrypted_data]
457 else s ++ 445 else s ++
458 -- XXX: Checksum is part of encrypted_data for V4 ONLY 446 -- XXX: Checksum is part of encrypted_data for V4 ONLY
@@ -464,7 +452,6 @@ put_packet (SecretKeyPacket { version = version, timestamp = timestamp,
464 (0::Integer) (B.concat s) :: Word16)]), 452 (0::Integer) (B.concat s) :: Word16)]),
465 if is_subkey then 7 else 5) 453 if is_subkey then 7 else 5)
466 where 454 where
467 (Just s2k_t) = s2k_type
468 p = fst (put_packet $ 455 p = fst (put_packet $
469 PublicKeyPacket version timestamp algorithm key False Nothing) 456 PublicKeyPacket version timestamp algorithm key False Nothing)
470 s = map (encode . (key !)) (secret_key_fields algorithm) 457 s = map (encode . (key !)) (secret_key_fields algorithm)
@@ -592,31 +579,22 @@ parse_packet 5 = do
592 }) <- parse_packet 6 579 }) <- parse_packet 6
593 s2k_useage <- get :: Get Word8 580 s2k_useage <- get :: Get Word8
594 let k = SecretKeyPacket version timestamp algorithm key s2k_useage 581 let k = SecretKeyPacket version timestamp algorithm key s2k_useage
595 k' <- case s2k_useage of 582 (symmetric_algorithm, s2k) <- case () of
596 _ | s2k_useage `elem` [255, 254] -> do 583 _ | s2k_useage `elem` [255, 254] -> (,) <$> get <*> fmap Just get
597 symmetric_type <- get
598 s2k_type <- get
599 s2k_hash_algorithm <- get
600 s2k_salt <- if s2k_type `elem` [1, 3] then get
601 else return undefined
602 s2k_count <- if s2k_type == 3 then fmap decode_s2k_count get else
603 return undefined
604 return (k (Just symmetric_type) (Just s2k_type)
605 (Just s2k_hash_algorithm) (Just s2k_salt) (Just s2k_count))
606 _ | s2k_useage > 0 -> 584 _ | s2k_useage > 0 ->
607 -- s2k_useage is symmetric_type in this case 585 -- s2k_useage is symmetric_type in this case
608 return (k (Just s2k_useage) Nothing Nothing Nothing Nothing) 586 return (decode $ encode s2k_useage, Just $ SimpleS2K MD5)
609 _ -> 587 _ ->
610 return (k Nothing Nothing Nothing Nothing Nothing) 588 return (Unencrypted, Nothing)
611 if s2k_useage > 0 then do { 589 if symmetric_algorithm /= Unencrypted then do {
612 encrypted <- getRemainingByteString; 590 encrypted <- getRemainingByteString;
613 return (k' encrypted Nothing False) 591 return (k s2k symmetric_algorithm encrypted Nothing False)
614 } else do 592 } else do
615 key <- foldM (\m f -> do 593 key <- foldM (\m f -> do
616 mpi <- get :: Get MPI 594 mpi <- get :: Get MPI
617 return $ (f,mpi):m) key (secret_key_fields algorithm) 595 return $ (f,mpi):m) key (secret_key_fields algorithm)
618 private_hash <- getRemainingByteString 596 private_hash <- getRemainingByteString
619 return ((k' B.empty (Just private_hash) False) {key = key}) 597 return ((k s2k symmetric_algorithm B.empty (Just private_hash) False) {key = key})
620-- PublicKeyPacket, http://tools.ietf.org/html/rfc4880#section-5.5.2 598-- PublicKeyPacket, http://tools.ietf.org/html/rfc4880#section-5.5.2
621parse_packet 6 = do 599parse_packet 6 = do
622 version <- get :: Get Word8 600 version <- get :: Get Word8
@@ -718,6 +696,28 @@ enum_to_word8 = fromIntegral . fromEnum
718enum_from_word8 :: (Enum a) => Word8 -> a 696enum_from_word8 :: (Enum a) => Word8 -> a
719enum_from_word8 = toEnum . fromIntegral 697enum_from_word8 = toEnum . fromIntegral
720 698
699data S2K =
700 SimpleS2K HashAlgorithm |
701 SaltedS2K HashAlgorithm Word64 |
702 IteratedSaltedS2K HashAlgorithm Word64 Word32 |
703 S2K Word8 B.ByteString
704 deriving (Show, Read, Eq)
705
706instance BINARY_CLASS S2K where
707 put (SimpleS2K halgo) = put (0::Word8) >> put halgo
708 put (SaltedS2K halgo salt) = put (1::Word8) >> put halgo >> put salt
709 put (IteratedSaltedS2K halgo salt count) = put (3::Word8) >> put halgo
710 >> put salt >> put (encode_s2k_count count)
711 put (S2K t body) = put t >> putSomeByteString body
712
713 get = do
714 t <- get :: Get Word8
715 case t of
716 0 -> SimpleS2K <$> get
717 1 -> SaltedS2K <$> get <*> get
718 3 -> IteratedSaltedS2K <$> get <*> get <*> (decode_s2k_count <$> get)
719 _ -> S2K t <$> getRemainingByteString
720
721data HashAlgorithm = MD5 | SHA1 | RIPEMD160 | SHA256 | SHA384 | SHA512 | SHA224 | HashAlgorithm Word8 721data HashAlgorithm = MD5 | SHA1 | RIPEMD160 | SHA256 | SHA384 | SHA512 | SHA224 | HashAlgorithm Word8
722 deriving (Show, Read, Eq) 722 deriving (Show, Read, Eq)
723 723