diff --git a/Crypto/Number/Basic.hs b/Crypto/Number/Basic.hs index 52b6e4e..d0c8dca 100644 --- a/Crypto/Number/Basic.hs +++ b/Crypto/Number/Basic.hs @@ -13,8 +13,11 @@ module Crypto.Number.Basic , log2 , numBits , numBytes + , asPowerOf2AndOdd ) where +import Data.Bits + import Crypto.Number.Compat -- | @sqrti@ returns two integers @(l,b)@ so that @l <= sqrt i <= b@. @@ -98,3 +101,16 @@ numBits n = gmpSizeInBits n `onGmpUnsupported` (if n == 0 then 1 else computeBit -- | Compute the number of bytes for an integer numBytes :: Integer -> Int numBytes n = gmpSizeInBytes n `onGmpUnsupported` ((numBits n + 7) `div` 8) + +-- | Express an integer as a odd number and a power of 2 +asPowerOf2AndOdd :: Integer -> (Int, Integer) +asPowerOf2AndOdd a + | a == 0 = (0, 0) + | odd a = (0, a) + | a < 0 = let (e, a1) = asPowerOf2AndOdd $ abs a in (e, -a1) + | isPowerOf2 a = (log2 a, 1) + | otherwise = loop a 0 + where + isPowerOf2 n = (n /= 0) && ((n .&. (n - 1)) == 0) + loop n pw = if n `mod` 2 == 0 then loop (n `div` 2) (pw + 1) + else (pw, n) \ No newline at end of file diff --git a/Crypto/Number/ModArithmetic.hs b/Crypto/Number/ModArithmetic.hs index 4ca6317..02729c6 100644 --- a/Crypto/Number/ModArithmetic.hs +++ b/Crypto/Number/ModArithmetic.hs @@ -15,6 +15,7 @@ module Crypto.Number.ModArithmetic -- * Inverse computing , inverse , inverseCoprimes + , jacobi ) where import Control.Exception (throw, Exception) @@ -95,3 +96,29 @@ inverseCoprimes g m = case inverse g m of Nothing -> throw CoprimesAssertionError Just i -> i + +-- | Computes the Jacobi symbol (a/n). +-- 0 = a < n; n = 3 and odd. +-- +-- The Legendre and Jacobi symbols are indistinguishable exactly when the +-- lower argument is an odd prime, in which case they have the same value. +-- +-- See algorithm 2.149 in "Handbook of Applied Cryptography" by Alfred J. Menezes et al. +jacobi :: Integer -> Integer -> Maybe Integer +jacobi a n + | n < 3 || even n = Nothing + | a == 0 || a == 1 = Just a + | n <= a = jacobi (a `mod` n) n + | a < 0 = + let b = if n `mod` 4 == 1 then 1 else -1 + in fmap (*b) (jacobi (-a) n) + | otherwise = + let (e, a1) = asPowerOf2AndOdd a + nMod8 = n `mod` 8 + nMod4 = n `mod` 4 + a1Mod4 = a1 `mod` 4 + s' = if even e || nMod8 == 1 || nMod8 == 7 then 1 else -1 + s = if nMod4 == 3 && a1Mod4 == 3 then -s' else s' + n1 = n `mod` a1 + in if a1 == 1 then Just s + else fmap (*s) (jacobi n1 a1) \ No newline at end of file diff --git a/Crypto/PubKey/Rabin/Basic.hs b/Crypto/PubKey/Rabin/Basic.hs new file mode 100644 index 0000000..f82d5a3 --- /dev/null +++ b/Crypto/PubKey/Rabin/Basic.hs @@ -0,0 +1,174 @@ +-- | +-- Module : Crypto.PubKey.Rabin.Basic +-- License : BSD-style +-- Maintainer : Carlos Rodrigue-Vega +-- Stability : experimental +-- Portability : unknown +-- +-- Rabin cryptosystem for public-key cryptography and digital signature. +-- +{-# LANGUAGE DeriveDataTypeable #-} +module Crypto.PubKey.Rabin.Basic + ( PublicKey(..) + , PrivateKey(..) + , generate + , encrypt + , decrypt + , sign + , verify + ) where + +import System.Random (getStdGen, randomRs) + +import Data.ByteString (ByteString) +import qualified Data.ByteString as B +import Data.Data + +import Crypto.Hash +import Crypto.Number.Basic (gcde, asPowerOf2AndOdd) +import Crypto.Number.ModArithmetic (expSafe, jacobi) +import Crypto.Number.Prime (isProbablyPrime) +import Crypto.Number.Serialize (i2osp, os2ip) +import Crypto.PubKey.Rabin.Types +import Crypto.Random (MonadRandom, getRandomBytes) + +-- | Represent a Rabin public key. +data PublicKey = PublicKey + { public_size :: Int -- ^ size of key in bytes + , public_n :: Integer -- ^ public p*q + } deriving (Show, Read, Eq, Data, Typeable) + +-- | Represent a Rabin private key. +data PrivateKey = PrivateKey + { private_pub :: PublicKey + , private_p :: Integer -- ^ p prime number + , private_q :: Integer -- ^ q prime number + , private_a :: Integer + , private_b :: Integer + } deriving (Show, Read, Eq, Data, Typeable) + +-- | Rabin Signature. +data Signature = Signature (Integer, Integer) + +-- | Generate a pair of (private, public) key of size in bytes. +-- Primes p and q are both congruent 3 mod 4. +-- +-- See algorithm 8.11 in "Handbook of Applied Cryptography" by Alfred J. Menezes et al. +generate :: MonadRandom m + => Int + -> m (PublicKey, PrivateKey) +generate size = do + (p, q) <- generatePrimes size (\p -> p `mod` 4 == 3) (\q -> q `mod` 4 == 3) + return (generateKeys p q) + where + generateKeys p q = + let n = p*q + (a, b, _) = gcde p q + publicKey = PublicKey { public_size = size + , public_n = n } + privateKey = PrivateKey { private_pub = publicKey + , private_p = p + , private_q = q + , private_a = a + , private_b = b } + in (publicKey, privateKey) + +-- | Encrypt plaintext using public key. +-- +-- See algorithm 8.11 in "Handbook of Applied Cryptography" by Alfred J. Menezes et al. +encrypt :: PublicKey -- ^ public key + -> ByteString -- ^ plaintext + -> Either Error ByteString +encrypt pk m = + let m' = os2ip m + n = public_n pk + in if m' < 0 then Left InvalidParameters + else if m' >= n then Left MessageTooLong + else Right $ i2osp $ expSafe m' 2 n + +-- | Decrypt ciphertext using private key. +-- +-- See algorithm 8.12 in "Handbook of Applied Cryptography" by Alfred J. Menezes et al. +decrypt :: PrivateKey -- ^ private key + -> ByteString -- ^ ciphertext + -> (ByteString, ByteString, ByteString, ByteString) +decrypt pk c = + let p = private_p pk + q = private_q pk + a = private_a pk + b = private_b pk + n = public_n $ private_pub pk + c' = os2ip c + in mapTuple i2osp $ sqroot' c' p q a b n + where mapTuple f (w, x, y, z) = (f w, f x, f y, f z) + +-- | Sign message using hash algorithm and private key. +-- +-- See https://en.wikipedia.org/wiki/Rabin_signature_algorithm. +sign :: (MonadRandom m, HashAlgorithm hash) + => PrivateKey -- ^ private key + -> hash -- ^ hash function + -> ByteString -- ^ message to sign + -> m (Either Error Signature) +sign pk hashAlg m = + let p = private_p pk + q = private_q pk + a = private_a pk + b = private_b pk + n = public_n $ private_pub pk + in do + (padding, h) <- loop p q + return (if h >= n then Left MessageTooLong + else let (r, _, _, _) = sqroot' h p q a b n + in Right $ Signature (os2ip padding, r)) + where + loop p q = do + padding <- getRandomBytes 8 + let h = os2ip $ hashWith hashAlg $ B.append m padding + case (jacobi (h `mod` p) p, jacobi (h `mod` q) q) of + (Just 1, Just 1) -> return (padding, h) + _ -> loop p q + +-- | Verify signature using hash algorithm and public key. +-- +-- See https://en.wikipedia.org/wiki/Rabin_signature_algorithm. +verify :: (HashAlgorithm hash) + => PublicKey -- ^ private key + -> hash -- ^ hash function + -> ByteString -- ^ message + -> Signature -- ^ signature + -> Bool +verify pk hashAlg m (Signature (padding, x)) = + let n = public_n pk + h = os2ip $ hashWith hashAlg $ B.append m $ i2osp padding + h' = expSafe x 2 n + in h' == h + +-- | Square roots modulo prime p where p is congruent 3 mod 4 +-- Value a must be a quadratic residue modulo p (i.e. jacobi symbol (a/n) = 1). +-- +-- See algorithm 3.36 in "Handbook of Applied Cryptography" by Alfred J. Menezes et al. +sqroot :: Integer + -> Integer -- ^ prime p + -> (Integer, Integer) +sqroot a p = + let r = expSafe a ((p + 1) `div` 4) p + in (r, -r) + +-- | Square roots modulo n given its prime factors p and q (both congruent 3 mod 4) +-- Value a must be a quadratic residue of both modulo p and modulo q (i.e. jacobi symbols (a/p) = (a/q) = 1). +-- +-- See algorithm 3.44 in "Handbook of Applied Cryptography" by Alfred J. Menezes et al. +sqroot' :: Integer + -> Integer -- ^ prime p + -> Integer -- ^ prime q + -> Integer -- ^ c such that c*p + d*q = 1 + -> Integer -- ^ d such that c*p + d*q = 1 + -> Integer -- ^ n = p*q + -> (Integer, Integer, Integer, Integer) +sqroot' a p q c d n = + let (r, _) = sqroot a p + (s, _) = sqroot a q + x = (r*d*q + s*c*p) `mod` n + y = (r*d*q - s*c*p) `mod` n + in (x, (-x) `mod` n, y, (-y) `mod` n) diff --git a/Crypto/PubKey/Rabin/Modified.hs b/Crypto/PubKey/Rabin/Modified.hs new file mode 100644 index 0000000..67c652f --- /dev/null +++ b/Crypto/PubKey/Rabin/Modified.hs @@ -0,0 +1,104 @@ +-- | +-- Module : Crypto.PubKey.Rabin.Modified +-- License : BSD-style +-- Maintainer : Carlos Rodrigue-Vega +-- Stability : experimental +-- Portability : unknown +-- +-- Modified-Rabin public-key digital signature algorithm. +-- See algorithm 11.30 in "Handbook of Applied Cryptography" by Alfred J. Menezes et al. +-- +{-# LANGUAGE DeriveDataTypeable #-} +module Crypto.PubKey.Rabin.Modified + ( PublicKey(..) + , PrivateKey(..) + , generate + , sign + , verify + ) where + +import Data.ByteString +import qualified Data.ByteString as B +import Data.Data + +import Crypto.Hash +import Crypto.Number.Basic (gcde) +import Crypto.Number.ModArithmetic (expSafe, jacobi) +import Crypto.Number.Serialize (i2osp, os2ip) +import Crypto.PubKey.Rabin.Types +import Crypto.Random.Types + +-- | Represent a Modified-Rabin public key. +data PublicKey = PublicKey + { public_size :: Int -- ^ size of key in bytes + , public_n :: Integer -- ^ public p*q + } deriving (Show, Read, Eq, Data, Typeable) + +-- | Represent a Modified-Rabin private key. +data PrivateKey = PrivateKey + { private_pub :: PublicKey + , private_p :: Integer -- ^ p prime number + , private_q :: Integer -- ^ q prime number + , private_d :: Integer + } deriving (Show, Read, Eq, Data, Typeable) + +-- | Generate a pair of (private, public) key of size in bytes. +-- Prime p is congruent 3 mod 8 and prime q is congruent 7 mod 8. +generate :: MonadRandom m + => Int + -> m (PublicKey, PrivateKey) +generate size = do + (p, q) <- generatePrimes size (\p -> p `mod` 8 == 3) (\q -> q `mod` 8 == 7) + return (generateKeys p q) + where + generateKeys p q = + let n = p*q + d = (n - p - q + 5) `div` 8 + publicKey = PublicKey { public_size = size + , public_n = n } + privateKey = PrivateKey { private_pub = publicKey + , private_p = p + , private_q = q + , private_d = d } + in (publicKey, privateKey) + +-- | Sign message using hash algorithm and private key. +sign :: (HashAlgorithm hash) + => PrivateKey -- ^ private key + -> hash -- ^ hash function + -> ByteString -- ^ message to sign + -> Either Error ByteString +sign pk hashAlg m = + let d = private_d pk + n = public_n $ private_pub pk + h = os2ip $ hashWith hashAlg m + limit = (n - 6) `div` 16 + in if h > limit then Left MessageTooLong + else let h' = 16*h + 6 + in case jacobi h' n of + Just 1 -> Right $ i2osp $ expSafe h' d n + Just (-1) -> Right $ i2osp $ expSafe (h' `div` 2) d n + _ -> Left InvalidParameters + +-- | Verify signature using hash algorithm and public key. +verify :: (HashAlgorithm hash) + => PublicKey -- ^ public key + -> hash -- ^ hash function + -> ByteString -- ^ message + -> ByteString -- ^ signature + -> Bool +verify pk hashAlg m s = + let n = public_n pk + h = os2ip $ hashWith hashAlg m + s' = os2ip s + s'' = expSafe s' 2 n + s''' = case s'' `mod` 8 of + 6 -> s'' + 3 -> 2*s'' + 7 -> n - s'' + 2 -> 2*(n - s'') + _ -> 0 + in case s''' `mod` 16 of + 6 -> let h' = (s''' - 6) `div` 16 + in h' == h + _ -> False diff --git a/Crypto/PubKey/Rabin/RW.hs b/Crypto/PubKey/Rabin/RW.hs new file mode 100644 index 0000000..2ad85a3 --- /dev/null +++ b/Crypto/PubKey/Rabin/RW.hs @@ -0,0 +1,140 @@ +-- | +-- Module : Crypto.PubKey.Rabin.RW +-- License : BSD-style +-- Maintainer : Carlos Rodrigue-Vega +-- Stability : experimental +-- Portability : unknown +-- +-- Rabin-Williams cryptosystem for public-key encryption and digital signature. +-- See pages 323 - 324 in "Computational Number Theory and Modern Cryptography" by Song Y. Yan. +-- Also inspired by https://github.com/vanilala/vncrypt/blob/master/vncrypt/vnrw_gmp.c. +-- +{-# LANGUAGE DeriveDataTypeable #-} +module Crypto.PubKey.Rabin.RW + ( PublicKey(..) + , PrivateKey(..) + , generate + , encrypt + , decrypt + , sign + , verify + ) where + +import Data.ByteString +import qualified Data.ByteString as B +import Data.Data + +import Crypto.Hash +import Crypto.Number.Basic (gcde) +import Crypto.Number.ModArithmetic (expSafe, jacobi) +import Crypto.Number.Serialize (i2osp, os2ip) +import Crypto.PubKey.Rabin.Types +import Crypto.Random.Types + +-- | Represent a Rabin-Williams public key. +data PublicKey = PublicKey + { public_size :: Int -- ^ size of key in bytes + , public_n :: Integer -- ^ public p*q + } deriving (Show, Read, Eq, Data, Typeable) + +-- | Represent a Rabin-Williams private key. +data PrivateKey = PrivateKey + { private_pub :: PublicKey + , private_p :: Integer -- ^ p prime number + , private_q :: Integer -- ^ q prime number + , private_d :: Integer + } deriving (Show, Read, Eq, Data, Typeable) + +-- | Generate a pair of (private, public) key of size in bytes. +-- Prime p is congruent 3 mod 8 and prime q is congruent 7 mod 8. +generate :: MonadRandom m + => Int + -> m (PublicKey, PrivateKey) +generate size = do + (p, q) <- generatePrimes size (\p -> p `mod` 8 == 3) (\q -> q `mod` 8 == 7) + return (generateKeys p q) + where + generateKeys p q = + let n = p*q + d = ((p - 1)*(q - 1) `div` 4 + 1) `div` 2 + publicKey = PublicKey { public_size = size + , public_n = n } + privateKey = PrivateKey { private_pub = publicKey + , private_p = p + , private_q = q + , private_d = d } + in (publicKey, privateKey) + +-- | Encrypt plaintext using public key. +encrypt :: PublicKey -- ^ public key + -> ByteString -- ^ plaintext + -> Either Error ByteString +encrypt pk m = + let n = public_n pk + in case ep1 n $ os2ip m of + Right m' -> Right $ i2osp $ ep2 n m' + Left err -> Left err + +-- | Decrypt ciphertext using private key. +decrypt :: PrivateKey -- ^ private key + -> ByteString -- ^ ciphertext + -> ByteString +decrypt pk c = + let d = private_d pk + n = public_n $ private_pub pk + in i2osp $ dp2 n $ dp1 d n $ os2ip c + +-- | Sign message using hash algorithm and private key. +sign :: (HashAlgorithm hash) + => PrivateKey -- ^ private key + -> hash -- ^ hash function + -> ByteString -- ^ message to sign + -> Either Error ByteString +sign pk hashAlg m = + let d = private_d pk + n = public_n $ private_pub pk + in case ep1 n $ os2ip $ hashWith hashAlg m of + Right m' -> Right (i2osp $ dp1 d n m') + Left err -> Left err + +-- | Verify signature using hash algorithm and public key. +verify :: (HashAlgorithm hash) + => PublicKey -- ^ public key + -> hash -- ^ hash function + -> ByteString -- ^ message + -> ByteString -- ^ signature + -> Bool +verify pk hashAlg m s = + let n = public_n pk + h = os2ip $ hashWith hashAlg m + h' = dp2 n $ ep2 n $ os2ip s + in h' == h + +-- | Encryption primitive 1 +ep1 :: Integer -> Integer -> Either Error Integer +ep1 n m = + let m' = 2*m + 1 + m'' = 2*m' + m''' = 2*m'' + in case jacobi m' n of + Just (-1) | m'' < n -> Right m'' + Just 1 | m''' < n -> Right m''' + _ -> Left InvalidParameters + +-- | Encryption primitive 2 +ep2 :: Integer -> Integer -> Integer +ep2 n m = expSafe m 2 n + +-- | Decryption primitive 1 +dp1 :: Integer -> Integer -> Integer -> Integer +dp1 d n c = expSafe c d n + +-- | Decryption primitive 2 +dp2 :: Integer -> Integer -> Integer +dp2 n c = let c' = c `div` 2 + c'' = (n - c) `div` 2 + in case c `mod` 4 of + 0 -> ((c' `div` 2 - 1) `div` 2) + 1 -> ((c'' `div` 2 - 1) `div` 2) + 2 -> ((c' - 1) `div` 2) + _ -> ((c'' - 1) `div` 2) diff --git a/Crypto/PubKey/Rabin/Types.hs b/Crypto/PubKey/Rabin/Types.hs new file mode 100644 index 0000000..a2bfe14 --- /dev/null +++ b/Crypto/PubKey/Rabin/Types.hs @@ -0,0 +1,42 @@ +-- | +-- Module : Crypto.PubKey.Rabin.Types +-- License : BSD-style +-- Maintainer : Carlos Rodrigue-Vega +-- Stability : experimental +-- Portability : unknown +-- +module Crypto.PubKey.Rabin.Types + ( Error(..) + , generatePrimes + ) where + +import Crypto.Number.Basic (numBits) +import Crypto.Number.Prime (generatePrime, findPrimeFromWith) +import Crypto.Random.Types + +type PrimeCondition = Integer -> Bool + +-- | Error possible during encryption, decryption or signing. +data Error = MessageTooLong -- ^ the message to encrypt is too long + | InvalidParameters -- ^ some parameters lead to breaking assumptions + deriving (Show, Eq) + +-- | Generate primes p & q +generatePrimes :: MonadRandom m + => Int -- ^ size in bytes + -> PrimeCondition -- ^ condition prime p must satisfy + -> PrimeCondition -- ^ condition prime q must satisfy + -> m (Integer, Integer) -- ^ chosen distinct primes p and q +generatePrimes size pCond qCond = + let pBits = (8*(size `div` 2)) + qBits = (8*(size - (size `div` 2))) + in do + p <- generatePrime' pBits pCond + q <- generatePrime' qBits qCond + return (p, q) + where + generatePrime' bits cond = do + pr' <- generatePrime bits + let pr = findPrimeFromWith cond pr' + if numBits pr == bits then return pr + else generatePrime' bits cond diff --git a/cryptonite.cabal b/cryptonite.cabal index bbfebac..2673891 100644 --- a/cryptonite.cabal +++ b/cryptonite.cabal @@ -162,6 +162,10 @@ Library Crypto.PubKey.RSA.PSS Crypto.PubKey.RSA.OAEP Crypto.PubKey.RSA.Types + Crypto.PubKey.Rabin.Basic + Crypto.PubKey.Rabin.Modified + Crypto.PubKey.Rabin.RW + Crypto.PubKey.Rabin.Types Crypto.Random Crypto.Random.Types Crypto.Random.Entropy @@ -231,6 +235,7 @@ Library Build-depends: bytestring , memory >= 0.14.14 + , random , basement >= 0.0.6 , ghc-prim ghc-options: -Wall -fwarn-tabs -optc-O3 -fno-warn-unused-imports @@ -406,6 +411,7 @@ Test-Suite test-cryptonite KAT_PubKey.OAEP KAT_PubKey.PSS KAT_PubKey.P256 + KAT_PubKey.Rabin KAT_PubKey KAT_RC4 KAT_Scrypt diff --git a/tests/KAT_PubKey.hs b/tests/KAT_PubKey.hs index 13dd71e..b87404e 100644 --- a/tests/KAT_PubKey.hs +++ b/tests/KAT_PubKey.hs @@ -16,6 +16,7 @@ import KAT_PubKey.PSS import KAT_PubKey.DSA import KAT_PubKey.ECC import KAT_PubKey.ECDSA +import KAT_PubKey.Rabin import Utils import qualified KAT_PubKey.P256 as P256 @@ -41,6 +42,7 @@ tests = testGroup "PubKey" , eccTests , ecdsaTests , P256.tests + , rabinTests ] --newKats = [ eccKatTests ] diff --git a/tests/KAT_PubKey/Rabin.hs b/tests/KAT_PubKey/Rabin.hs new file mode 100644 index 0000000..e1d6ab3 --- /dev/null +++ b/tests/KAT_PubKey/Rabin.hs @@ -0,0 +1,89 @@ +{-# LANGUAGE OverloadedStrings #-} +module KAT_PubKey.Rabin (rabinTests) where + +import Imports +import Crypto.Hash +import qualified Crypto.PubKey.Rabin.Basic as Basic +import qualified Crypto.PubKey.Rabin.Modified as ModRabin +import qualified Crypto.PubKey.Rabin.RW as RW + +data VectorRabin = VectorRabin + { msg :: ByteString + , size :: Int + } + +vectors = + [ VectorRabin + { msg = "\xd4\x36\xe9\x95\x69\xfd\x32\xa7\xc8\xa0\x5b\xbc\x90\xd3\x2c\x49" + , size = 32 + } + , VectorRabin + { msg = "\x52\xe6\x50\xd9\x8e\x7f\x2a\x04\x8b\x4f\x86\x85\x21\x53\xb9\x7e\x01\xdd\x31\x6f\x34\x6a\x19\xf6\x7a\x85" + , size = 64 + } + , VectorRabin + { msg = "\x66\x28\x19\x4e\x12\x07\x3d\xb0\x3b\xa9\x4c\xda\x9e\xf9\x53\x23\x97\xd5\x0d\xba\x79\xb9\x87\x00\x4a\xfe\xfe\x34" + , size = 128 + } + ] + +doBasicEncryptionTest (i, vector) = testCase (show i) (do + let message = msg vector + (pubKey, privKey) <- Basic.generate (size vector) + let cipherText = Basic.encrypt pubKey message + actual = case cipherText of + Left _ -> False + Right c -> let (p, p', p'', p''') = Basic.decrypt privKey c + in elem message [p, p', p'', p'''] + (True @=? actual)) + +doBasicSignatureTest (i, vector) = testCase (show i) (do + let message = msg vector + (pubKey, privKey) <- Basic.generate (size vector) + signature <- Basic.sign privKey SHA1 message + let actual = case signature of + Left _ -> False + Right s -> Basic.verify pubKey SHA1 message s + (True @=? actual)) + +doModifiedSignatureTest (i, vector) = testCase (show i) (do + let message = msg vector + (pubKey, privKey) <- ModRabin.generate (size vector) + let signature = ModRabin.sign privKey SHA1 message + actual = case signature of + Left _ -> False + Right s -> ModRabin.verify pubKey SHA1 message s + (True @=? actual)) + +doRwEncryptionTest (i, vector) = testCase (show i) (do + let message = msg vector + (pubKey, privKey) <- RW.generate (size vector) + let cipherText = RW.encrypt pubKey message + actual = case cipherText of + Left _ -> False + Right c -> let p = RW.decrypt privKey c + in message == p + (True @=? actual)) + +doRwSignatureTest (i, vector) = testCase (show i) (do + let message = msg vector + (pubKey, privKey) <- RW.generate (size vector) + let signature = RW.sign privKey SHA1 message + actual = case signature of + Left _ -> False + Right s -> RW.verify pubKey SHA1 message s + (True @=? actual)) + +rabinTests = testGroup "Rabin" + [ testGroup "Basic" + [ testGroup "encryption" $ map doBasicEncryptionTest (zip [katZero..] vectors) + , testGroup "signature" $ map doBasicSignatureTest (zip [katZero..] vectors) + ] + , testGroup "Modified" + [ testGroup "signature" $ map doModifiedSignatureTest (zip [katZero..] vectors) + ] + , testGroup "RW" + [ testGroup "encryption" $ map doRwEncryptionTest (zip [katZero..] vectors) + , testGroup "signature" $ map doRwSignatureTest (zip [katZero..] vectors) + ] + ] diff --git a/tests/Number.hs b/tests/Number.hs index 8016e70..fd77fa7 100644 --- a/tests/Number.hs +++ b/tests/Number.hs @@ -52,6 +52,9 @@ tests = testGroup "number" in bits == numBits prime , testProperty "marshalling" $ \qaInt -> getQAInteger qaInt == os2ip (i2osp (getQAInteger qaInt) :: Bytes) + , testProperty "as-power-of-2-and-odd" $ \n -> + let (e, a1) = asPowerOf2AndOdd n + in n == (2^e)*a1 , testGroup "marshalling-kat-to-bytearray" $ map toSerializationKat $ zip [katZero..] serializationVectors , testGroup "marshalling-kat-to-integer" $ map toSerializationKatInteger $ zip [katZero..] serializationVectors ]