summaryrefslogtreecommitdiff
path: root/Data/OpenPGP/Util/Verify.hs
blob: fd834855b9281c82b0a7c27bf18ed320898206dd (plain)
1
2
3
4
5
6
7
8
9
10
11
12
13
14
15
16
17
18
19
20
21
22
23
24
25
26
27
28
29
30
31
32
33
34
35
36
37
38
39
40
41
42
43
44
45
46
47
48
49
50
51
52
53
54
55
56
57
58
59
60
61
62
63
64
65
66
67
68
69
70
71
72
73
74
75
76
77
78
79
80
81
82
83
84
85
86
87
88
89
90
91
92
93
94
95
96
97
98
99
100
{-# LANGUAGE OverloadedStrings #-}
{-# LANGUAGE CPP #-}
module Data.OpenPGP.Util.Verify where

import Debug.Trace
import qualified Data.OpenPGP as OpenPGP
import Data.Maybe
import Data.Binary (encode)
import Control.Monad
import qualified Data.ByteString as BS
import qualified Data.ByteString.Lazy as LZ

import qualified Crypto.PubKey.DSA as Vincent.DSA
import qualified Crypto.PubKey.RSA.PKCS15 as Vincent.RSA
import qualified Crypto.PubKey.ECC.ECDSA as Vincent.ECDSA
-- import Math.NumberTheory.Moduli
#if !defined(VERSION_cryptonite)
import Crypto.PubKey.HashDescr
#endif

import Data.OpenPGP.Util.Base


dsaKey :: OpenPGP.Packet -> Vincent.DSA.PublicKey
dsaKey k = Vincent.DSA.PublicKey
    (Vincent.DSA.Params (keyParam 'p' k) (keyParam 'g' k) (keyParam 'q' k))
    (keyParam 'y' k)


{-
applyCurve :: Vincent.ECDSA.CurveCommon -> Integer -> Integer
applyCurve curve x = x*x*x + x*a + b
 where
    a = Vincent.ECDSA.ecc_a curve
    b = Vincent.ECDSA.ecc_b curve
-}

-- | Verify a message signature
verify ::
    OpenPGP.Message          -- ^ Keys that may have made the signature
    -> OpenPGP.SignatureOver -- ^ Signatures to verify
    -> OpenPGP.SignatureOver -- ^ Will only contain signatures that passed
verify keys over =
    over {OpenPGP.signatures_over = mapMaybe (uncurry $ verifyOne keys) sigs}
    where
    sigs = map (\s -> (s, toStrictBS $ encode over `LZ.append` OpenPGP.trailer s))
        (OpenPGP.signatures_over over)

verifyOne :: OpenPGP.Message -> OpenPGP.Packet -> BS.ByteString -> Maybe OpenPGP.Packet
verifyOne keys sig over = fmap (const sig) $ maybeKey >>= verification >>= guard
    where
    verification = case OpenPGP.key_algorithm sig of
        OpenPGP.DSA -> dsaVerify
        OpenPGP.ECDSA -> ecdsaVerify
        alg | alg `elem` [OpenPGP.RSA,OpenPGP.RSA_S] -> rsaVerify
            | otherwise -> const Nothing

#if defined(VERSION_cryptonite)
    dsaVerify k = let k' = dsaKey k in
        -- XXX: What happened to dsaTruncate?
        Just $ case desc of HashDescr h -> Vincent.DSA.verify h k' dsaSig over
#else
    dsaVerify k = let k' = dsaKey k in
        Just $ Vincent.DSA.verify (dsaTruncate k' . bhash) k' dsaSig over
#endif

    ecdsaVerify k = let k' = ecdsaKey k
#if defined(VERSION_cryptonite)
                        r = Just $ case desc of
                                      HashDescr h -> Vincent.ECDSA.verify h k' ecdsaSig over
#else
                        r = Just $ Vincent.ECDSA.verify bhash k' ecdsaSig over
#endif
                    in r -- trace ("ecdsaVerify: "++show r) r
#if defined(VERSION_cryptonite)
    rsaVerify k = Just $ case desc of
                            HashDescr h -> Vincent.RSA.verify (Just h) (rsaKey k) over rsaSig
#else
    rsaVerify k = Just $ Vincent.RSA.verify desc (rsaKey k) over rsaSig
#endif
    [rsaSig] = map (toStrictBS . LZ.drop 2 . encode) (OpenPGP.signature sig)
    dsaSig = let [OpenPGP.MPI r, OpenPGP.MPI s] = OpenPGP.signature sig in
        Vincent.DSA.Signature r s
    ecdsaSig = let [OpenPGP.MPI r, OpenPGP.MPI s] = OpenPGP.signature sig in
        Vincent.ECDSA.Signature r s
    dsaTruncate (Vincent.DSA.PublicKey (Vincent.DSA.Params _ _ q) _) = BS.take (integerBytesize q)
    {-
    ecdsaTruncate (Vincent.ECDSA.PublicKey _ (Vincent.ECDSA.Point x y)) = BS.take (integerBytesize x
                                                                                  + integerBytesize y )
    -}
#if defined(VERSION_cryptonite)
    -- bhash = case desc of HashDescr alg -> alg
#else
    bhash = hashFunction desc
#endif
    desc = hashAlgoDesc hash_algo
    hash_algo = OpenPGP.hash_algorithm sig
    maybeKey = OpenPGP.signature_issuer sig >>= find_key keys
               -- in trace ("maybeKey="++show (fmap OpenPGP.key_algorithm r)) r