-- | /WARNING:/ Signature operations may leak the private key. Signature verification
-- should be safe.
{-# LANGUAGE DeriveDataTypeable #-}
module Crypto.PubKey.ECC.ECDSA
    ( Signature(..)
    , PublicPoint
    , PublicKey(..)
    , PrivateNumber
    , PrivateKey(..)
    , KeyPair(..)
    , toPublicKey
    , toPrivateKey
    , signWith
    , signDigestWith
    , sign
    , signDigest
    , verify
    , verifyDigest
    ) where

import Control.Monad
import Data.Data

import Crypto.Hash
import Crypto.Internal.ByteArray (ByteArrayAccess)
import Crypto.Number.ModArithmetic (inverse)
import Crypto.Number.Generate
import Crypto.PubKey.ECC.Types
import Crypto.PubKey.ECC.Prim
import Crypto.PubKey.Internal (dsaTruncHashDigest)
import Crypto.Random.Types

-- | Represent a ECDSA signature namely R and S.
data Signature = Signature
    { Signature -> Integer
sign_r :: Integer -- ^ ECDSA r
    , Signature -> Integer
sign_s :: Integer -- ^ ECDSA s
    } deriving (Int -> Signature -> ShowS
[Signature] -> ShowS
Signature -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [Signature] -> ShowS
$cshowList :: [Signature] -> ShowS
show :: Signature -> String
$cshow :: Signature -> String
showsPrec :: Int -> Signature -> ShowS
$cshowsPrec :: Int -> Signature -> ShowS
Show,ReadPrec [Signature]
ReadPrec Signature
Int -> ReadS Signature
ReadS [Signature]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [Signature]
$creadListPrec :: ReadPrec [Signature]
readPrec :: ReadPrec Signature
$creadPrec :: ReadPrec Signature
readList :: ReadS [Signature]
$creadList :: ReadS [Signature]
readsPrec :: Int -> ReadS Signature
$creadsPrec :: Int -> ReadS Signature
Read,Signature -> Signature -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: Signature -> Signature -> Bool
$c/= :: Signature -> Signature -> Bool
== :: Signature -> Signature -> Bool
$c== :: Signature -> Signature -> Bool
Eq,Typeable Signature
Signature -> DataType
Signature -> Constr
(forall b. Data b => b -> b) -> Signature -> Signature
forall a.
Typeable a
-> (forall (c :: * -> *).
    (forall d b. Data d => c (d -> b) -> d -> c b)
    -> (forall g. g -> c g) -> a -> c a)
-> (forall (c :: * -> *).
    (forall b r. Data b => c (b -> r) -> c r)
    -> (forall r. r -> c r) -> Constr -> c a)
-> (a -> Constr)
-> (a -> DataType)
-> (forall (t :: * -> *) (c :: * -> *).
    Typeable t =>
    (forall d. Data d => c (t d)) -> Maybe (c a))
-> (forall (t :: * -> * -> *) (c :: * -> *).
    Typeable t =>
    (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c a))
-> ((forall b. Data b => b -> b) -> a -> a)
-> (forall r r'.
    (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> a -> r)
-> (forall r r'.
    (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> a -> r)
-> (forall u. (forall d. Data d => d -> u) -> a -> [u])
-> (forall u. Int -> (forall d. Data d => d -> u) -> a -> u)
-> (forall (m :: * -> *).
    Monad m =>
    (forall d. Data d => d -> m d) -> a -> m a)
-> (forall (m :: * -> *).
    MonadPlus m =>
    (forall d. Data d => d -> m d) -> a -> m a)
-> (forall (m :: * -> *).
    MonadPlus m =>
    (forall d. Data d => d -> m d) -> a -> m a)
-> Data a
forall u. Int -> (forall d. Data d => d -> u) -> Signature -> u
forall u. (forall d. Data d => d -> u) -> Signature -> [u]
forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> Signature -> r
forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> Signature -> r
forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> Signature -> m Signature
forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> Signature -> m Signature
forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c Signature
forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> Signature -> c Signature
forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c Signature)
forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Signature)
gmapMo :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> Signature -> m Signature
$cgmapMo :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> Signature -> m Signature
gmapMp :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> Signature -> m Signature
$cgmapMp :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> Signature -> m Signature
gmapM :: forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> Signature -> m Signature
$cgmapM :: forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> Signature -> m Signature
gmapQi :: forall u. Int -> (forall d. Data d => d -> u) -> Signature -> u
$cgmapQi :: forall u. Int -> (forall d. Data d => d -> u) -> Signature -> u
gmapQ :: forall u. (forall d. Data d => d -> u) -> Signature -> [u]
$cgmapQ :: forall u. (forall d. Data d => d -> u) -> Signature -> [u]
gmapQr :: forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> Signature -> r
$cgmapQr :: forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> Signature -> r
gmapQl :: forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> Signature -> r
$cgmapQl :: forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> Signature -> r
gmapT :: (forall b. Data b => b -> b) -> Signature -> Signature
$cgmapT :: (forall b. Data b => b -> b) -> Signature -> Signature
dataCast2 :: forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Signature)
$cdataCast2 :: forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Signature)
dataCast1 :: forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c Signature)
$cdataCast1 :: forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c Signature)
dataTypeOf :: Signature -> DataType
$cdataTypeOf :: Signature -> DataType
toConstr :: Signature -> Constr
$ctoConstr :: Signature -> Constr
gunfold :: forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c Signature
$cgunfold :: forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c Signature
gfoldl :: forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> Signature -> c Signature
$cgfoldl :: forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> Signature -> c Signature
Data)

-- | ECDSA Private Key.
data PrivateKey = PrivateKey
    { PrivateKey -> Curve
private_curve :: Curve
    , PrivateKey -> Integer
private_d     :: PrivateNumber
    } deriving (Int -> PrivateKey -> ShowS
[PrivateKey] -> ShowS
PrivateKey -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [PrivateKey] -> ShowS
$cshowList :: [PrivateKey] -> ShowS
show :: PrivateKey -> String
$cshow :: PrivateKey -> String
showsPrec :: Int -> PrivateKey -> ShowS
$cshowsPrec :: Int -> PrivateKey -> ShowS
Show,ReadPrec [PrivateKey]
ReadPrec PrivateKey
Int -> ReadS PrivateKey
ReadS [PrivateKey]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [PrivateKey]
$creadListPrec :: ReadPrec [PrivateKey]
readPrec :: ReadPrec PrivateKey
$creadPrec :: ReadPrec PrivateKey
readList :: ReadS [PrivateKey]
$creadList :: ReadS [PrivateKey]
readsPrec :: Int -> ReadS PrivateKey
$creadsPrec :: Int -> ReadS PrivateKey
Read,PrivateKey -> PrivateKey -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: PrivateKey -> PrivateKey -> Bool
$c/= :: PrivateKey -> PrivateKey -> Bool
== :: PrivateKey -> PrivateKey -> Bool
$c== :: PrivateKey -> PrivateKey -> Bool
Eq,Typeable PrivateKey
PrivateKey -> DataType
PrivateKey -> Constr
(forall b. Data b => b -> b) -> PrivateKey -> PrivateKey
forall a.
Typeable a
-> (forall (c :: * -> *).
    (forall d b. Data d => c (d -> b) -> d -> c b)
    -> (forall g. g -> c g) -> a -> c a)
-> (forall (c :: * -> *).
    (forall b r. Data b => c (b -> r) -> c r)
    -> (forall r. r -> c r) -> Constr -> c a)
-> (a -> Constr)
-> (a -> DataType)
-> (forall (t :: * -> *) (c :: * -> *).
    Typeable t =>
    (forall d. Data d => c (t d)) -> Maybe (c a))
-> (forall (t :: * -> * -> *) (c :: * -> *).
    Typeable t =>
    (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c a))
-> ((forall b. Data b => b -> b) -> a -> a)
-> (forall r r'.
    (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> a -> r)
-> (forall r r'.
    (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> a -> r)
-> (forall u. (forall d. Data d => d -> u) -> a -> [u])
-> (forall u. Int -> (forall d. Data d => d -> u) -> a -> u)
-> (forall (m :: * -> *).
    Monad m =>
    (forall d. Data d => d -> m d) -> a -> m a)
-> (forall (m :: * -> *).
    MonadPlus m =>
    (forall d. Data d => d -> m d) -> a -> m a)
-> (forall (m :: * -> *).
    MonadPlus m =>
    (forall d. Data d => d -> m d) -> a -> m a)
-> Data a
forall u. Int -> (forall d. Data d => d -> u) -> PrivateKey -> u
forall u. (forall d. Data d => d -> u) -> PrivateKey -> [u]
forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> PrivateKey -> r
forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> PrivateKey -> r
forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> PrivateKey -> m PrivateKey
forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> PrivateKey -> m PrivateKey
forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c PrivateKey
forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> PrivateKey -> c PrivateKey
forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c PrivateKey)
forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c PrivateKey)
gmapMo :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> PrivateKey -> m PrivateKey
$cgmapMo :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> PrivateKey -> m PrivateKey
gmapMp :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> PrivateKey -> m PrivateKey
$cgmapMp :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> PrivateKey -> m PrivateKey
gmapM :: forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> PrivateKey -> m PrivateKey
$cgmapM :: forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> PrivateKey -> m PrivateKey
gmapQi :: forall u. Int -> (forall d. Data d => d -> u) -> PrivateKey -> u
$cgmapQi :: forall u. Int -> (forall d. Data d => d -> u) -> PrivateKey -> u
gmapQ :: forall u. (forall d. Data d => d -> u) -> PrivateKey -> [u]
$cgmapQ :: forall u. (forall d. Data d => d -> u) -> PrivateKey -> [u]
gmapQr :: forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> PrivateKey -> r
$cgmapQr :: forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> PrivateKey -> r
gmapQl :: forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> PrivateKey -> r
$cgmapQl :: forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> PrivateKey -> r
gmapT :: (forall b. Data b => b -> b) -> PrivateKey -> PrivateKey
$cgmapT :: (forall b. Data b => b -> b) -> PrivateKey -> PrivateKey
dataCast2 :: forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c PrivateKey)
$cdataCast2 :: forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c PrivateKey)
dataCast1 :: forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c PrivateKey)
$cdataCast1 :: forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c PrivateKey)
dataTypeOf :: PrivateKey -> DataType
$cdataTypeOf :: PrivateKey -> DataType
toConstr :: PrivateKey -> Constr
$ctoConstr :: PrivateKey -> Constr
gunfold :: forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c PrivateKey
$cgunfold :: forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c PrivateKey
gfoldl :: forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> PrivateKey -> c PrivateKey
$cgfoldl :: forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> PrivateKey -> c PrivateKey
Data)

-- | ECDSA Public Key.
data PublicKey = PublicKey
    { PublicKey -> Curve
public_curve :: Curve
    , PublicKey -> PublicPoint
public_q     :: PublicPoint
    } deriving (Int -> PublicKey -> ShowS
[PublicKey] -> ShowS
PublicKey -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [PublicKey] -> ShowS
$cshowList :: [PublicKey] -> ShowS
show :: PublicKey -> String
$cshow :: PublicKey -> String
showsPrec :: Int -> PublicKey -> ShowS
$cshowsPrec :: Int -> PublicKey -> ShowS
Show,ReadPrec [PublicKey]
ReadPrec PublicKey
Int -> ReadS PublicKey
ReadS [PublicKey]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [PublicKey]
$creadListPrec :: ReadPrec [PublicKey]
readPrec :: ReadPrec PublicKey
$creadPrec :: ReadPrec PublicKey
readList :: ReadS [PublicKey]
$creadList :: ReadS [PublicKey]
readsPrec :: Int -> ReadS PublicKey
$creadsPrec :: Int -> ReadS PublicKey
Read,PublicKey -> PublicKey -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: PublicKey -> PublicKey -> Bool
$c/= :: PublicKey -> PublicKey -> Bool
== :: PublicKey -> PublicKey -> Bool
$c== :: PublicKey -> PublicKey -> Bool
Eq,Typeable PublicKey
PublicKey -> DataType
PublicKey -> Constr
(forall b. Data b => b -> b) -> PublicKey -> PublicKey
forall a.
Typeable a
-> (forall (c :: * -> *).
    (forall d b. Data d => c (d -> b) -> d -> c b)
    -> (forall g. g -> c g) -> a -> c a)
-> (forall (c :: * -> *).
    (forall b r. Data b => c (b -> r) -> c r)
    -> (forall r. r -> c r) -> Constr -> c a)
-> (a -> Constr)
-> (a -> DataType)
-> (forall (t :: * -> *) (c :: * -> *).
    Typeable t =>
    (forall d. Data d => c (t d)) -> Maybe (c a))
-> (forall (t :: * -> * -> *) (c :: * -> *).
    Typeable t =>
    (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c a))
-> ((forall b. Data b => b -> b) -> a -> a)
-> (forall r r'.
    (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> a -> r)
-> (forall r r'.
    (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> a -> r)
-> (forall u. (forall d. Data d => d -> u) -> a -> [u])
-> (forall u. Int -> (forall d. Data d => d -> u) -> a -> u)
-> (forall (m :: * -> *).
    Monad m =>
    (forall d. Data d => d -> m d) -> a -> m a)
-> (forall (m :: * -> *).
    MonadPlus m =>
    (forall d. Data d => d -> m d) -> a -> m a)
-> (forall (m :: * -> *).
    MonadPlus m =>
    (forall d. Data d => d -> m d) -> a -> m a)
-> Data a
forall u. Int -> (forall d. Data d => d -> u) -> PublicKey -> u
forall u. (forall d. Data d => d -> u) -> PublicKey -> [u]
forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> PublicKey -> r
forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> PublicKey -> r
forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> PublicKey -> m PublicKey
forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> PublicKey -> m PublicKey
forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c PublicKey
forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> PublicKey -> c PublicKey
forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c PublicKey)
forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c PublicKey)
gmapMo :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> PublicKey -> m PublicKey
$cgmapMo :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> PublicKey -> m PublicKey
gmapMp :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> PublicKey -> m PublicKey
$cgmapMp :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> PublicKey -> m PublicKey
gmapM :: forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> PublicKey -> m PublicKey
$cgmapM :: forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> PublicKey -> m PublicKey
gmapQi :: forall u. Int -> (forall d. Data d => d -> u) -> PublicKey -> u
$cgmapQi :: forall u. Int -> (forall d. Data d => d -> u) -> PublicKey -> u
gmapQ :: forall u. (forall d. Data d => d -> u) -> PublicKey -> [u]
$cgmapQ :: forall u. (forall d. Data d => d -> u) -> PublicKey -> [u]
gmapQr :: forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> PublicKey -> r
$cgmapQr :: forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> PublicKey -> r
gmapQl :: forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> PublicKey -> r
$cgmapQl :: forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> PublicKey -> r
gmapT :: (forall b. Data b => b -> b) -> PublicKey -> PublicKey
$cgmapT :: (forall b. Data b => b -> b) -> PublicKey -> PublicKey
dataCast2 :: forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c PublicKey)
$cdataCast2 :: forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c PublicKey)
dataCast1 :: forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c PublicKey)
$cdataCast1 :: forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c PublicKey)
dataTypeOf :: PublicKey -> DataType
$cdataTypeOf :: PublicKey -> DataType
toConstr :: PublicKey -> Constr
$ctoConstr :: PublicKey -> Constr
gunfold :: forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c PublicKey
$cgunfold :: forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c PublicKey
gfoldl :: forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> PublicKey -> c PublicKey
$cgfoldl :: forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> PublicKey -> c PublicKey
Data)

-- | ECDSA Key Pair.
data KeyPair = KeyPair Curve PublicPoint PrivateNumber
    deriving (Int -> KeyPair -> ShowS
[KeyPair] -> ShowS
KeyPair -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [KeyPair] -> ShowS
$cshowList :: [KeyPair] -> ShowS
show :: KeyPair -> String
$cshow :: KeyPair -> String
showsPrec :: Int -> KeyPair -> ShowS
$cshowsPrec :: Int -> KeyPair -> ShowS
Show,ReadPrec [KeyPair]
ReadPrec KeyPair
Int -> ReadS KeyPair
ReadS [KeyPair]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [KeyPair]
$creadListPrec :: ReadPrec [KeyPair]
readPrec :: ReadPrec KeyPair
$creadPrec :: ReadPrec KeyPair
readList :: ReadS [KeyPair]
$creadList :: ReadS [KeyPair]
readsPrec :: Int -> ReadS KeyPair
$creadsPrec :: Int -> ReadS KeyPair
Read,KeyPair -> KeyPair -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: KeyPair -> KeyPair -> Bool
$c/= :: KeyPair -> KeyPair -> Bool
== :: KeyPair -> KeyPair -> Bool
$c== :: KeyPair -> KeyPair -> Bool
Eq,Typeable KeyPair
KeyPair -> DataType
KeyPair -> Constr
(forall b. Data b => b -> b) -> KeyPair -> KeyPair
forall a.
Typeable a
-> (forall (c :: * -> *).
    (forall d b. Data d => c (d -> b) -> d -> c b)
    -> (forall g. g -> c g) -> a -> c a)
-> (forall (c :: * -> *).
    (forall b r. Data b => c (b -> r) -> c r)
    -> (forall r. r -> c r) -> Constr -> c a)
-> (a -> Constr)
-> (a -> DataType)
-> (forall (t :: * -> *) (c :: * -> *).
    Typeable t =>
    (forall d. Data d => c (t d)) -> Maybe (c a))
-> (forall (t :: * -> * -> *) (c :: * -> *).
    Typeable t =>
    (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c a))
-> ((forall b. Data b => b -> b) -> a -> a)
-> (forall r r'.
    (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> a -> r)
-> (forall r r'.
    (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> a -> r)
-> (forall u. (forall d. Data d => d -> u) -> a -> [u])
-> (forall u. Int -> (forall d. Data d => d -> u) -> a -> u)
-> (forall (m :: * -> *).
    Monad m =>
    (forall d. Data d => d -> m d) -> a -> m a)
-> (forall (m :: * -> *).
    MonadPlus m =>
    (forall d. Data d => d -> m d) -> a -> m a)
-> (forall (m :: * -> *).
    MonadPlus m =>
    (forall d. Data d => d -> m d) -> a -> m a)
-> Data a
forall u. Int -> (forall d. Data d => d -> u) -> KeyPair -> u
forall u. (forall d. Data d => d -> u) -> KeyPair -> [u]
forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> KeyPair -> r
forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> KeyPair -> r
forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> KeyPair -> m KeyPair
forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> KeyPair -> m KeyPair
forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c KeyPair
forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> KeyPair -> c KeyPair
forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c KeyPair)
forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c KeyPair)
gmapMo :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> KeyPair -> m KeyPair
$cgmapMo :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> KeyPair -> m KeyPair
gmapMp :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> KeyPair -> m KeyPair
$cgmapMp :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> KeyPair -> m KeyPair
gmapM :: forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> KeyPair -> m KeyPair
$cgmapM :: forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> KeyPair -> m KeyPair
gmapQi :: forall u. Int -> (forall d. Data d => d -> u) -> KeyPair -> u
$cgmapQi :: forall u. Int -> (forall d. Data d => d -> u) -> KeyPair -> u
gmapQ :: forall u. (forall d. Data d => d -> u) -> KeyPair -> [u]
$cgmapQ :: forall u. (forall d. Data d => d -> u) -> KeyPair -> [u]
gmapQr :: forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> KeyPair -> r
$cgmapQr :: forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> KeyPair -> r
gmapQl :: forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> KeyPair -> r
$cgmapQl :: forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> KeyPair -> r
gmapT :: (forall b. Data b => b -> b) -> KeyPair -> KeyPair
$cgmapT :: (forall b. Data b => b -> b) -> KeyPair -> KeyPair
dataCast2 :: forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c KeyPair)
$cdataCast2 :: forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c KeyPair)
dataCast1 :: forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c KeyPair)
$cdataCast1 :: forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c KeyPair)
dataTypeOf :: KeyPair -> DataType
$cdataTypeOf :: KeyPair -> DataType
toConstr :: KeyPair -> Constr
$ctoConstr :: KeyPair -> Constr
gunfold :: forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c KeyPair
$cgunfold :: forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c KeyPair
gfoldl :: forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> KeyPair -> c KeyPair
$cgfoldl :: forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> KeyPair -> c KeyPair
Data)

-- | Public key of a ECDSA Key pair.
toPublicKey :: KeyPair -> PublicKey
toPublicKey :: KeyPair -> PublicKey
toPublicKey (KeyPair Curve
curve PublicPoint
pub Integer
_) = Curve -> PublicPoint -> PublicKey
PublicKey Curve
curve PublicPoint
pub

-- | Private key of a ECDSA Key pair.
toPrivateKey :: KeyPair -> PrivateKey
toPrivateKey :: KeyPair -> PrivateKey
toPrivateKey (KeyPair Curve
curve PublicPoint
_ Integer
priv) = Curve -> Integer -> PrivateKey
PrivateKey Curve
curve Integer
priv

-- | Sign digest using the private key and an explicit k number.
--
-- /WARNING:/ Vulnerable to timing attacks.
signDigestWith :: HashAlgorithm hash
               => Integer     -- ^ k random number
               -> PrivateKey  -- ^ private key
               -> Digest hash -- ^ digest to sign
               -> Maybe Signature
signDigestWith :: forall hash.
HashAlgorithm hash =>
Integer -> PrivateKey -> Digest hash -> Maybe Signature
signDigestWith Integer
k (PrivateKey Curve
curve Integer
d) Digest hash
digest = do
    let z :: Integer
z = forall hash.
HashAlgorithm hash =>
Digest hash -> Integer -> Integer
dsaTruncHashDigest Digest hash
digest Integer
n
        CurveCommon Integer
_ Integer
_ PublicPoint
g Integer
n Integer
_ = Curve -> CurveCommon
common_curve Curve
curve
    let point :: PublicPoint
point = Curve -> Integer -> PublicPoint -> PublicPoint
pointMul Curve
curve Integer
k PublicPoint
g
    Integer
r <- case PublicPoint
point of
              PublicPoint
PointO    -> forall a. Maybe a
Nothing
              Point Integer
x Integer
_ -> forall (m :: * -> *) a. Monad m => a -> m a
return forall a b. (a -> b) -> a -> b
$ Integer
x forall a. Integral a => a -> a -> a
`mod` Integer
n
    Integer
kInv <- Integer -> Integer -> Maybe Integer
inverse Integer
k Integer
n
    let s :: Integer
s = Integer
kInv forall a. Num a => a -> a -> a
* (Integer
z forall a. Num a => a -> a -> a
+ Integer
r forall a. Num a => a -> a -> a
* Integer
d) forall a. Integral a => a -> a -> a
`mod` Integer
n
    forall (f :: * -> *). Applicative f => Bool -> f () -> f ()
when (Integer
r forall a. Eq a => a -> a -> Bool
== Integer
0 Bool -> Bool -> Bool
|| Integer
s forall a. Eq a => a -> a -> Bool
== Integer
0) forall a. Maybe a
Nothing
    forall (m :: * -> *) a. Monad m => a -> m a
return forall a b. (a -> b) -> a -> b
$ Integer -> Integer -> Signature
Signature Integer
r Integer
s

-- | Sign message using the private key and an explicit k number.
--
-- /WARNING:/ Vulnerable to timing attacks.
signWith :: (ByteArrayAccess msg, HashAlgorithm hash)
         => Integer    -- ^ k random number
         -> PrivateKey -- ^ private key
         -> hash       -- ^ hash function
         -> msg        -- ^ message to sign
         -> Maybe Signature
signWith :: forall msg hash.
(ByteArrayAccess msg, HashAlgorithm hash) =>
Integer -> PrivateKey -> hash -> msg -> Maybe Signature
signWith Integer
k PrivateKey
pk hash
hashAlg msg
msg = forall hash.
HashAlgorithm hash =>
Integer -> PrivateKey -> Digest hash -> Maybe Signature
signDigestWith Integer
k PrivateKey
pk (forall ba alg.
(ByteArrayAccess ba, HashAlgorithm alg) =>
alg -> ba -> Digest alg
hashWith hash
hashAlg msg
msg)

-- | Sign digest using the private key.
--
-- /WARNING:/ Vulnerable to timing attacks.
signDigest :: (HashAlgorithm hash, MonadRandom m)
           => PrivateKey -> Digest hash -> m Signature
signDigest :: forall hash (m :: * -> *).
(HashAlgorithm hash, MonadRandom m) =>
PrivateKey -> Digest hash -> m Signature
signDigest PrivateKey
pk Digest hash
digest = do
    Integer
k <- forall (m :: * -> *).
MonadRandom m =>
Integer -> Integer -> m Integer
generateBetween Integer
1 (Integer
n forall a. Num a => a -> a -> a
- Integer
1)
    case forall hash.
HashAlgorithm hash =>
Integer -> PrivateKey -> Digest hash -> Maybe Signature
signDigestWith Integer
k PrivateKey
pk Digest hash
digest of
         Maybe Signature
Nothing  -> forall hash (m :: * -> *).
(HashAlgorithm hash, MonadRandom m) =>
PrivateKey -> Digest hash -> m Signature
signDigest PrivateKey
pk Digest hash
digest
         Just Signature
sig -> forall (m :: * -> *) a. Monad m => a -> m a
return Signature
sig
  where n :: Integer
n = CurveCommon -> Integer
ecc_n forall b c a. (b -> c) -> (a -> b) -> a -> c
. Curve -> CurveCommon
common_curve forall a b. (a -> b) -> a -> b
$ PrivateKey -> Curve
private_curve PrivateKey
pk

-- | Sign message using the private key.
--
-- /WARNING:/ Vulnerable to timing attacks.
sign :: (ByteArrayAccess msg, HashAlgorithm hash, MonadRandom m)
     => PrivateKey -> hash -> msg -> m Signature
sign :: forall msg hash (m :: * -> *).
(ByteArrayAccess msg, HashAlgorithm hash, MonadRandom m) =>
PrivateKey -> hash -> msg -> m Signature
sign PrivateKey
pk hash
hashAlg msg
msg = forall hash (m :: * -> *).
(HashAlgorithm hash, MonadRandom m) =>
PrivateKey -> Digest hash -> m Signature
signDigest PrivateKey
pk (forall ba alg.
(ByteArrayAccess ba, HashAlgorithm alg) =>
alg -> ba -> Digest alg
hashWith hash
hashAlg msg
msg)

-- | Verify a digest using the public key.
verifyDigest :: HashAlgorithm hash => PublicKey -> Signature -> Digest hash -> Bool
verifyDigest :: forall hash.
HashAlgorithm hash =>
PublicKey -> Signature -> Digest hash -> Bool
verifyDigest (PublicKey Curve
_ PublicPoint
PointO) Signature
_ Digest hash
_ = Bool
False
verifyDigest pk :: PublicKey
pk@(PublicKey Curve
curve PublicPoint
q) (Signature Integer
r Integer
s) Digest hash
digest
    | Integer
r forall a. Ord a => a -> a -> Bool
< Integer
1 Bool -> Bool -> Bool
|| Integer
r forall a. Ord a => a -> a -> Bool
>= Integer
n Bool -> Bool -> Bool
|| Integer
s forall a. Ord a => a -> a -> Bool
< Integer
1 Bool -> Bool -> Bool
|| Integer
s forall a. Ord a => a -> a -> Bool
>= Integer
n = Bool
False
    | Bool
otherwise = forall b a. b -> (a -> b) -> Maybe a -> b
maybe Bool
False (Integer
r forall a. Eq a => a -> a -> Bool
==) forall a b. (a -> b) -> a -> b
$ do
        Integer
w <- Integer -> Integer -> Maybe Integer
inverse Integer
s Integer
n
        let z :: Integer
z  = forall hash.
HashAlgorithm hash =>
Digest hash -> Integer -> Integer
dsaTruncHashDigest Digest hash
digest Integer
n
            u1 :: Integer
u1 = Integer
z forall a. Num a => a -> a -> a
* Integer
w forall a. Integral a => a -> a -> a
`mod` Integer
n
            u2 :: Integer
u2 = Integer
r forall a. Num a => a -> a -> a
* Integer
w forall a. Integral a => a -> a -> a
`mod` Integer
n
            x :: PublicPoint
x  = Curve
-> Integer -> PublicPoint -> Integer -> PublicPoint -> PublicPoint
pointAddTwoMuls Curve
curve Integer
u1 PublicPoint
g Integer
u2 PublicPoint
q
        case PublicPoint
x of
             PublicPoint
PointO     -> forall a. Maybe a
Nothing
             Point Integer
x1 Integer
_ -> forall (m :: * -> *) a. Monad m => a -> m a
return forall a b. (a -> b) -> a -> b
$ Integer
x1 forall a. Integral a => a -> a -> a
`mod` Integer
n
  where n :: Integer
n = CurveCommon -> Integer
ecc_n CurveCommon
cc
        g :: PublicPoint
g = CurveCommon -> PublicPoint
ecc_g CurveCommon
cc
        cc :: CurveCommon
cc = Curve -> CurveCommon
common_curve forall a b. (a -> b) -> a -> b
$ PublicKey -> Curve
public_curve PublicKey
pk

-- | Verify a bytestring using the public key.
verify :: (ByteArrayAccess msg, HashAlgorithm hash) => hash -> PublicKey -> Signature -> msg -> Bool
verify :: forall msg hash.
(ByteArrayAccess msg, HashAlgorithm hash) =>
hash -> PublicKey -> Signature -> msg -> Bool
verify hash
hashAlg PublicKey
pk Signature
sig msg
msg = forall hash.
HashAlgorithm hash =>
PublicKey -> Signature -> Digest hash -> Bool
verifyDigest PublicKey
pk Signature
sig (forall ba alg.
(ByteArrayAccess ba, HashAlgorithm alg) =>
alg -> ba -> Digest alg
hashWith hash
hashAlg msg
msg)