summaryrefslogtreecommitdiff
diff options
context:
space:
mode:
authorJoe Crayne <joe@jerkface.net>2019-07-04 17:22:43 -0400
committerJoe Crayne <joe@jerkface.net>2019-07-04 17:22:43 -0400
commit730cf4755596090a214075e05e92d70f3f6ea69e (patch)
tree3520bc9f3462908f759bd09ffa9799a691ed0050
parentace402f21e0d42801aeda2411e2487235027bd34 (diff)
refactor
-rw-r--r--Data/OpenPGP.hs28
1 files changed, 10 insertions, 18 deletions
diff --git a/Data/OpenPGP.hs b/Data/OpenPGP.hs
index 0165a97..a297c34 100644
--- a/Data/OpenPGP.hs
+++ b/Data/OpenPGP.hs
@@ -1,4 +1,5 @@
1{-# LANGUAGE CPP #-} 1{-# LANGUAGE CPP #-}
2{-# LANGUAGE PatternGuards #-}
2-- | Main implementation of the OpenPGP message format <http://tools.ietf.org/html/rfc4880> 3-- | Main implementation of the OpenPGP message format <http://tools.ietf.org/html/rfc4880>
3-- 4--
4-- The recommended way to import this module is: 5-- The recommended way to import this module is:
@@ -1051,23 +1052,14 @@ signatures (Message ps) =
1051 1052
1052-- TODO: UserAttribute 1053-- TODO: UserAttribute
1053paired_sigs :: Maybe Packet -> [Packet] -> [SignatureOver] 1054paired_sigs :: Maybe Packet -> [Packet] -> [SignatureOver]
1054paired_sigs _ [] = [] 1055paired_sigs _ [] = []
1055paired_sigs _ (p@(PublicKeyPacket {is_subkey = False}):ps) = 1056paired_sigs mk (p:ps) = ($ span isSignaturePacket ps) $ case p of
1056 KeySignature p (takeWhile isSignaturePacket ps) : 1057 PublicKeyPacket {is_subkey = False} -> \(ss,qs) -> KeySignature p ss : paired_sigs (Just p) qs
1057 paired_sigs (Just p) (dropWhile isSignaturePacket ps) 1058 SecretKeyPacket {is_subkey = False} -> \(ss,qs) -> KeySignature p ss : paired_sigs (Just p) qs
1058paired_sigs _ (p@(SecretKeyPacket {is_subkey = False}):ps) = 1059 PublicKeyPacket {is_subkey = True} | Just k <- mk -> \(ss,qs) -> SubkeySignature k p ss : paired_sigs mk qs
1059 KeySignature p (takeWhile isSignaturePacket ps) : 1060 SecretKeyPacket {is_subkey = True} | Just k <- mk -> \(ss,qs) -> SubkeySignature k p ss : paired_sigs mk qs
1060 paired_sigs (Just p) (dropWhile isSignaturePacket ps) 1061 UserIDPacket {} | Just k <- mk -> \(ss,qs) -> CertificationSignature k p ss : paired_sigs mk qs
1061paired_sigs (Just k) (p@(PublicKeyPacket {is_subkey = True}):ps) = 1062 _ -> \_ -> paired_sigs mk ps
1062 SubkeySignature k p (takeWhile isSignaturePacket ps) :
1063 paired_sigs (Just k) (dropWhile isSignaturePacket ps)
1064paired_sigs (Just k) (p@(SecretKeyPacket {is_subkey = True}):ps) =
1065 SubkeySignature k p (takeWhile isSignaturePacket ps) :
1066 paired_sigs (Just k) (dropWhile isSignaturePacket ps)
1067paired_sigs (Just k) (p@(UserIDPacket {}):ps) =
1068 CertificationSignature k p (takeWhile isSignaturePacket ps) :
1069 paired_sigs (Just k) (dropWhile isSignaturePacket ps)
1070paired_sigs k (_:ps) = paired_sigs k ps
1071 1063
1072-- | <http://tools.ietf.org/html/rfc4880#section-3.2> 1064-- | <http://tools.ietf.org/html/rfc4880#section-3.2>
1073newtype MPI = MPI Integer deriving (Show, Read, Eq, Ord) 1065newtype MPI = MPI Integer deriving (Show, Read, Eq, Ord)