{-# LANGUAGE DeriveDataTypeable #-}
module Crypto.PubKey.Rabin.RW
( PublicKey(..)
, PrivateKey(..)
, generate
, encrypt
, encryptWithSeed
, decrypt
, sign
, verify
) where
import Data.ByteString
import Data.Data
import Crypto.Hash
import Crypto.Number.Basic (numBytes)
import Crypto.Number.ModArithmetic (expSafe, jacobi)
import Crypto.Number.Serialize (i2osp, i2ospOf_, os2ip)
import Crypto.PubKey.Rabin.OAEP
import Crypto.PubKey.Rabin.Types
import Crypto.Random.Types
data PublicKey = PublicKey
{ public_size :: Int
, public_n :: Integer
} deriving (Show, Read, Eq, Data)
data PrivateKey = PrivateKey
{ private_pub :: PublicKey
, private_p :: Integer
, private_q :: Integer
, private_d :: Integer
} deriving (Show, Read, Eq, Data)
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)
encryptWithSeed :: HashAlgorithm hash
=> ByteString
-> OAEPParams hash ByteString ByteString
-> PublicKey
-> ByteString
-> Either Error ByteString
encryptWithSeed seed oaep pk m =
let n = public_n pk
k = numBytes n
in do
m' <- pad seed oaep k m
m'' <- ep1 n $ os2ip m'
return $ i2osp $ ep2 n m''
encrypt :: (HashAlgorithm hash, MonadRandom m)
=> OAEPParams hash ByteString ByteString
-> PublicKey
-> ByteString
-> m (Either Error ByteString)
encrypt oaep pk m = do
seed <- getRandomBytes hashLen
return $ encryptWithSeed seed oaep pk m
where
hashLen = hashDigestSize (oaepHash oaep)
decrypt :: HashAlgorithm hash
=> OAEPParams hash ByteString ByteString
-> PrivateKey
-> ByteString
-> Maybe ByteString
decrypt oaep pk c =
let d = private_d pk
n = public_n $ private_pub pk
k = numBytes n
c' = i2ospOf_ k $ dp2 n $ dp1 d n $ os2ip c
in case unpad oaep k c' of
Left _ -> Nothing
Right p -> Just p
sign :: HashAlgorithm hash
=> PrivateKey
-> hash
-> ByteString
-> Either Error Integer
sign pk hashAlg m =
let d = private_d pk
n = public_n $ private_pub pk
in do
m' <- ep1 n $ os2ip $ hashWith hashAlg m
return $ dp1 d n m'
verify :: HashAlgorithm hash
=> PublicKey
-> hash
-> ByteString
-> Integer
-> Bool
verify pk hashAlg m s =
let n = public_n pk
h = os2ip $ hashWith hashAlg m
h' = dp2 n $ ep2 n s
in h' == h
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
ep2 :: Integer -> Integer -> Integer
ep2 n m = expSafe m 2 n
dp1 :: Integer -> Integer -> Integer -> Integer
dp1 d n c = expSafe c d n
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)