summaryrefslogtreecommitdiff
path: root/Data/OpenPGP/Util/Base.hs
diff options
context:
space:
mode:
Diffstat (limited to 'Data/OpenPGP/Util/Base.hs')
-rw-r--r--Data/OpenPGP/Util/Base.hs83
1 files changed, 83 insertions, 0 deletions
diff --git a/Data/OpenPGP/Util/Base.hs b/Data/OpenPGP/Util/Base.hs
new file mode 100644
index 0000000..aaa02c7
--- /dev/null
+++ b/Data/OpenPGP/Util/Base.hs
@@ -0,0 +1,83 @@
1module Data.OpenPGP.Util.Base where
2
3import qualified Data.ByteString as BS
4import qualified Data.ByteString.Lazy as LZ
5import Data.Binary (encode)
6
7import Data.OpenPGP as OpenPGP
8import Crypto.Hash.MD5 as MD5
9import Crypto.Hash.SHA1 as SHA1
10import Crypto.Hash.SHA256 as SHA256
11import Crypto.Hash.SHA384 as SHA384
12import Crypto.Hash.SHA512 as SHA512
13import Crypto.Hash.SHA224 as SHA224
14import Crypto.Hash.RIPEMD160 as RIPEMD160
15import qualified Crypto.PubKey.RSA as Vincent.RSA
16import Crypto.PubKey.HashDescr as Vincent
17import qualified Crypto.Types.PubKey.ECC as Vincent.ECDSA
18import qualified Crypto.Types.PubKey.ECDSA as Vincent.ECDSA
19
20import Data.OpenPGP.Util.Fingerprint (fingerprint)
21
22hashBySymbol OpenPGP.MD5 = MD5.hashlazy
23hashBySymbol OpenPGP.SHA1 = SHA1.hashlazy
24hashBySymbol OpenPGP.SHA256 = SHA256.hashlazy
25hashBySymbol OpenPGP.SHA384 = SHA384.hashlazy
26hashBySymbol OpenPGP.SHA512 = SHA512.hashlazy
27hashBySymbol OpenPGP.SHA224 = SHA224.hashlazy
28hashBySymbol OpenPGP.RIPEMD160 = RIPEMD160.hashlazy
29
30curveFromOID :: Integer -> Vincent.ECDSA.Curve
31curveFromOID 0x2a8648ce3d030107 = Vincent.ECDSA.getCurveByName Vincent.ECDSA.SEC_p256r1 -- NIST P-256
32curveFromOID 0x2B81040022 = Vincent.ECDSA.getCurveByName Vincent.ECDSA.SEC_p384r1 -- NIST P-384
33curveFromOID 0x2B81040023 = Vincent.ECDSA.getCurveByName Vincent.ECDSA.SEC_p521r1 -- NIST P-521
34curveFromOID 0x2b8104000a = Vincent.ECDSA.getCurveByName Vincent.ECDSA.SEC_p256k1 -- bitcoin curve
35curveFromOID n = error $ "Unknown curve: "++ show n
36
37ecdsaKey k = Vincent.ECDSA.PublicKey curve (Vincent.ECDSA.Point x y)
38 where
39 x = keyParam 'x' k
40 y = keyParam 'y' k
41 curve = curveFromOID (keyParam 'c' k)
42
43
44toStrictBS :: LZ.ByteString -> BS.ByteString
45toStrictBS = BS.concat . LZ.toChunks
46
47toLazyBS :: BS.ByteString -> LZ.ByteString
48toLazyBS = LZ.fromChunks . (:[])
49
50find_key :: OpenPGP.Message -> String -> Maybe OpenPGP.Packet
51find_key = OpenPGP.find_key fingerprint
52
53
54
55keyParam :: Char -> OpenPGP.Packet -> Integer
56keyParam c k = fromJustMPI $ lookup c (OpenPGP.key k)
57 where
58 fromJustMPI :: Maybe OpenPGP.MPI -> Integer
59 fromJustMPI (Just (OpenPGP.MPI x)) = x
60 fromJustMPI _ = error "Not a Just MPI, Data.OpenPGP.CryptoAPI"
61
62integerBytesize :: Integer -> Int
63integerBytesize i = fromIntegral $ LZ.length (encode (OpenPGP.MPI i)) - 2
64
65rsaKey :: OpenPGP.Packet -> Vincent.RSA.PublicKey
66rsaKey k =
67 Vincent.RSA.PublicKey (integerBytesize n) n (keyParam 'e' k)
68 where
69 n = keyParam 'n' k
70
71-- http://tools.ietf.org/html/rfc3447#page-43
72-- http://tools.ietf.org/html/rfc4880#section-5.2.2
73hashAlgoDesc OpenPGP.MD5 = Vincent.hashDescrMD5
74hashAlgoDesc OpenPGP.SHA1 = Vincent.hashDescrSHA1
75hashAlgoDesc OpenPGP.RIPEMD160 = Vincent.hashDescrRIPEMD160
76hashAlgoDesc OpenPGP.SHA256 = Vincent.hashDescrSHA256
77hashAlgoDesc OpenPGP.SHA384 = Vincent.hashDescrSHA384
78hashAlgoDesc OpenPGP.SHA512 = Vincent.hashDescrSHA512
79hashAlgoDesc OpenPGP.SHA224 = Vincent.hashDescrSHA224
80hashAlgoDesc _ =
81 error "Unsupported HashAlgorithm in hashAlgoDesc"
82
83