-- |
-- Module      : Crypto.PubKey.RSA
-- License     : BSD-style
-- Maintainer  : Vincent Hanquez <vincent@snarc.org>
-- Stability   : experimental
-- Portability : Good
--
module Crypto.PubKey.RSA
    ( Error(..)
    , PublicKey(..)
    , PrivateKey(..)
    , Blinder(..)
    -- * generation function
    , generateWith
    , generate
    , generateBlinder
    ) where

import Crypto.Random.API
import Crypto.Types.PubKey.RSA
import Crypto.Number.ModArithmetic (inverse, inverseCoprimes)
import Crypto.Number.Generate (generateMax)
import Crypto.Number.Prime (generatePrime)
import Crypto.PubKey.RSA.Types

-- | Generate a key pair given p and q.
--
-- p and q need to be distinct prime numbers.
--
-- e need to be coprime to phi=(p-1)*(q-1). If that's not the
-- case, the function will not return a key pair.
-- A small hamming weight results in better performance.
--
-- * e=0x10001 is a popular choice
--
-- * e=3 is popular as well, but proven to not be as secure for some cases.
--
generateWith :: (Integer, Integer) -- ^ chosen distinct primes p and q
             -> Int                -- ^ size in bytes
             -> Integer            -- ^ RSA public exponant 'e'
             -> Maybe (PublicKey, PrivateKey)
generateWith (p,q) size e =
    case inverse e phi of
        Nothing -> Nothing
        Just d  -> Just (pub,priv d)
  where n   = p*q
        phi = (p-1)*(q-1)
        -- q and p should be *distinct* *prime* numbers, hence always coprime
        qinv = inverseCoprimes q p
        pub = PublicKey { public_size = size
                        , public_n    = n
                        , public_e    = e
                        }
        priv d = PrivateKey { private_pub  = pub
                            , private_d    = d
                            , private_p    = p
                            , private_q    = q
                            , private_dP   = d `mod` (p-1)
                            , private_dQ   = d `mod` (q-1)
                            , private_qinv = qinv
                            }

-- | generate a pair of (private, public) key of size in bytes.
generate :: CPRG g
         => g       -- ^ CPRG
         -> Int     -- ^ size in bytes
         -> Integer -- ^ RSA public exponant 'e'
         -> ((PublicKey, PrivateKey), g)
generate rng size e = loop rng
  where loop g = -- loop until we find a valid key pair given e
            let (pq, g') = generatePQ g
             in case generateWith pq size e of
                    Nothing -> loop g'
                    Just pp -> (pp, g')
        generatePQ g =
            let (p, g')  = generatePrime g (8 * (size `div` 2))
                (q, g'') = generateQ p g'
             in ((p,q), g'')
        generateQ p h =
            let (q, h') = generatePrime h (8 * (size - (size `div` 2)))
             in if p == q then generateQ p h' else (q, h')

-- | Generate a blinder to use with decryption and signing operation
--
-- the unique parameter apart from the random number generator is the
-- public key value N.
generateBlinder :: CPRG g
                => g       -- ^ CPRG to use.
                -> Integer -- ^ RSA public N parameter.
                -> (Blinder, g)
generateBlinder rng n = (Blinder r (inverseCoprimes r n), rng')
  where (r, rng') = generateMax rng n