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.hs65
1 files changed, 64 insertions, 1 deletions
diff --git a/Data/OpenPGP/Util/Base.hs b/Data/OpenPGP/Util/Base.hs
index ed0e32c..c1088d8 100644
--- a/Data/OpenPGP/Util/Base.hs
+++ b/Data/OpenPGP/Util/Base.hs
@@ -1,10 +1,22 @@
1{-# LANGUAGE CPP #-}
2{-# LANGUAGE ExistentialQuantification #-}
3{-# LANGUAGE ConstraintKinds #-}
1module Data.OpenPGP.Util.Base where 4module Data.OpenPGP.Util.Base where
2 5
3import qualified Data.ByteString as BS 6import qualified Data.ByteString as BS
4import qualified Data.ByteString.Lazy as LZ 7import qualified Data.ByteString.Lazy as LZ
5import Data.Binary (encode) 8import Data.Binary (encode)
9import Data.Word
6 10
7import Data.OpenPGP as OpenPGP 11import Data.OpenPGP as OpenPGP
12#if defined(VERSION_cryptonite)
13import Crypto.Hash
14import Crypto.Hash.Algorithms as Vincent
15import qualified Crypto.PubKey.ECC.Types as Vincent.ECDSA
16import qualified Data.ByteArray as Bytes
17import qualified Crypto.PubKey.ECC.ECDSA as Vincent.ECDSA
18import Crypto.PubKey.RSA.PKCS15 (HashAlgorithmASN1)
19#else
8import Crypto.Hash.MD5 as MD5 20import Crypto.Hash.MD5 as MD5
9import Crypto.Hash.SHA1 as SHA1 21import Crypto.Hash.SHA1 as SHA1
10import Crypto.Hash.SHA256 as SHA256 22import Crypto.Hash.SHA256 as SHA256
@@ -12,13 +24,34 @@ import Crypto.Hash.SHA384 as SHA384
12import Crypto.Hash.SHA512 as SHA512 24import Crypto.Hash.SHA512 as SHA512
13import Crypto.Hash.SHA224 as SHA224 25import Crypto.Hash.SHA224 as SHA224
14import Crypto.Hash.RIPEMD160 as RIPEMD160 26import Crypto.Hash.RIPEMD160 as RIPEMD160
15import qualified Crypto.PubKey.RSA as Vincent.RSA
16import Crypto.PubKey.HashDescr as Vincent 27import Crypto.PubKey.HashDescr as Vincent
17import qualified Crypto.Types.PubKey.ECC as Vincent.ECDSA 28import qualified Crypto.Types.PubKey.ECC as Vincent.ECDSA
18import qualified Crypto.Types.PubKey.ECDSA as Vincent.ECDSA 29import qualified Crypto.Types.PubKey.ECDSA as Vincent.ECDSA
30#endif
31import qualified Crypto.PubKey.RSA as Vincent.RSA
32import qualified Crypto.Random as Vincent
19 33
20import Data.OpenPGP.Util.Fingerprint (fingerprint) 34import Data.OpenPGP.Util.Fingerprint (fingerprint)
21 35
36#if defined(VERSION_cryptonite)
37import Data.Hourglass
38import System.Hourglass
39import Control.Arrow (second)
40import Data.Binary (decode)
41#else
42import qualified Data.Time.Clock.POSIX
43#endif
44
45hashBySymbol :: OpenPGP.HashAlgorithm -> LZ.ByteString -> BS.ByteString
46#if defined(VERSION_cryptonite)
47hashBySymbol OpenPGP.MD5 x = Bytes.convert (hashlazy x :: Digest MD5)
48hashBySymbol OpenPGP.SHA1 x = Bytes.convert (hashlazy x :: Digest SHA1)
49hashBySymbol OpenPGP.SHA256 x = Bytes.convert (hashlazy x :: Digest SHA256)
50hashBySymbol OpenPGP.SHA384 x = Bytes.convert (hashlazy x :: Digest SHA384)
51hashBySymbol OpenPGP.SHA512 x = Bytes.convert (hashlazy x :: Digest SHA512)
52hashBySymbol OpenPGP.SHA224 x = Bytes.convert (hashlazy x :: Digest SHA224)
53hashBySymbol OpenPGP.RIPEMD160 x = Bytes.convert (hashlazy x :: Digest RIPEMD160)
54#else
22hashBySymbol OpenPGP.MD5 = MD5.hashlazy 55hashBySymbol OpenPGP.MD5 = MD5.hashlazy
23hashBySymbol OpenPGP.SHA1 = SHA1.hashlazy 56hashBySymbol OpenPGP.SHA1 = SHA1.hashlazy
24hashBySymbol OpenPGP.SHA256 = SHA256.hashlazy 57hashBySymbol OpenPGP.SHA256 = SHA256.hashlazy
@@ -26,6 +59,7 @@ hashBySymbol OpenPGP.SHA384 = SHA384.hashlazy
26hashBySymbol OpenPGP.SHA512 = SHA512.hashlazy 59hashBySymbol OpenPGP.SHA512 = SHA512.hashlazy
27hashBySymbol OpenPGP.SHA224 = SHA224.hashlazy 60hashBySymbol OpenPGP.SHA224 = SHA224.hashlazy
28hashBySymbol OpenPGP.RIPEMD160 = RIPEMD160.hashlazy 61hashBySymbol OpenPGP.RIPEMD160 = RIPEMD160.hashlazy
62#endif
29 63
30curveFromOID :: Integer -> Vincent.ECDSA.Curve 64curveFromOID :: Integer -> Vincent.ECDSA.Curve
31curveFromOID 0x2a8648ce3d030107 = Vincent.ECDSA.getCurveByName Vincent.ECDSA.SEC_p256r1 -- NIST P-256 65curveFromOID 0x2a8648ce3d030107 = Vincent.ECDSA.getCurveByName Vincent.ECDSA.SEC_p256r1 -- NIST P-256
@@ -74,6 +108,17 @@ rsaKey k =
74 108
75-- http://tools.ietf.org/html/rfc3447#page-43 109-- http://tools.ietf.org/html/rfc3447#page-43
76-- http://tools.ietf.org/html/rfc4880#section-5.2.2 110-- http://tools.ietf.org/html/rfc4880#section-5.2.2
111#if defined(VERSION_cryptonite)
112data HashDescr = forall hashAlg. HashAlgorithmASN1 hashAlg => HashDescr hashAlg
113
114hashAlgoDesc OpenPGP.MD5 = HashDescr Vincent.MD5
115hashAlgoDesc OpenPGP.SHA1 = HashDescr Vincent.SHA1
116hashAlgoDesc OpenPGP.RIPEMD160 = HashDescr Vincent.RIPEMD160
117hashAlgoDesc OpenPGP.SHA256 = HashDescr Vincent.SHA256
118hashAlgoDesc OpenPGP.SHA384 = HashDescr Vincent.SHA384
119hashAlgoDesc OpenPGP.SHA512 = HashDescr Vincent.SHA512
120hashAlgoDesc OpenPGP.SHA224 = HashDescr Vincent.SHA224
121#else
77hashAlgoDesc OpenPGP.MD5 = Vincent.hashDescrMD5 122hashAlgoDesc OpenPGP.MD5 = Vincent.hashDescrMD5
78hashAlgoDesc OpenPGP.SHA1 = Vincent.hashDescrSHA1 123hashAlgoDesc OpenPGP.SHA1 = Vincent.hashDescrSHA1
79hashAlgoDesc OpenPGP.RIPEMD160 = Vincent.hashDescrRIPEMD160 124hashAlgoDesc OpenPGP.RIPEMD160 = Vincent.hashDescrRIPEMD160
@@ -81,7 +126,25 @@ hashAlgoDesc OpenPGP.SHA256 = Vincent.hashDescrSHA256
81hashAlgoDesc OpenPGP.SHA384 = Vincent.hashDescrSHA384 126hashAlgoDesc OpenPGP.SHA384 = Vincent.hashDescrSHA384
82hashAlgoDesc OpenPGP.SHA512 = Vincent.hashDescrSHA512 127hashAlgoDesc OpenPGP.SHA512 = Vincent.hashDescrSHA512
83hashAlgoDesc OpenPGP.SHA224 = Vincent.hashDescrSHA224 128hashAlgoDesc OpenPGP.SHA224 = Vincent.hashDescrSHA224
129#endif
84hashAlgoDesc _ = 130hashAlgoDesc _ =
85 error "Unsupported HashAlgorithm in hashAlgoDesc" 131 error "Unsupported HashAlgorithm in hashAlgoDesc"
86 132
87 133
134currentTime :: Integral b => IO b
135#if defined(VERSION_hourglass)
136currentTime = fromIntegral . toSeconds <$> dateCurrent
137 where
138 toSeconds vincentTime = t
139 where (Elapsed (Seconds t)) = timeGetElapsed vincentTime
140#else
141currentTime = floor <$> Data.Time.Clock.POSIX.getPOSIXTime
142#endif
143
144
145#if defined(VERSION_cryptonite)
146type RG = Vincent.DRG
147#else
148type RG = Vincent.CPRG
149#endif
150