1-- | 2-- Module : Crypto.PubKey.DSA 3-- License : BSD-style 4-- Maintainer : Vincent Hanquez <vincent@snarc.org> 5-- Stability : experimental 6-- Portability : Good 7-- 8-- An implementation of the Digital Signature Algorithm (DSA) 9{-# LANGUAGE DeriveDataTypeable #-} 10module Crypto.PubKey.DSA 11 ( Params(..) 12 , Signature(..) 13 , PublicKey(..) 14 , PrivateKey(..) 15 , PublicNumber 16 , PrivateNumber 17 -- * Generation 18 , generatePrivate 19 , calculatePublic 20 -- * Signature primitive 21 , sign 22 , signWith 23 -- * Verification primitive 24 , verify 25 -- * Key pair 26 , KeyPair(..) 27 , toPublicKey 28 , toPrivateKey 29 ) where 30 31 32import Data.Data 33import Data.Maybe 34 35import Crypto.Number.ModArithmetic (expFast, expSafe, inverse) 36import Crypto.Number.Generate 37import Crypto.Internal.ByteArray (ByteArrayAccess) 38import Crypto.Internal.Imports 39import Crypto.Hash 40import Crypto.PubKey.Internal (dsaTruncHash) 41import Crypto.Random.Types 42 43-- | DSA Public Number, usually embedded in DSA Public Key 44type PublicNumber = Integer 45 46-- | DSA Private Number, usually embedded in DSA Private Key 47type PrivateNumber = Integer 48 49-- | Represent DSA parameters namely P, G, and Q. 50data Params = Params 51 { params_p :: Integer -- ^ DSA p 52 , params_g :: Integer -- ^ DSA g 53 , params_q :: Integer -- ^ DSA q 54 } deriving (Show,Read,Eq,Data) 55 56instance NFData Params where 57 rnf (Params p g q) = p `seq` g `seq` q `seq` () 58 59-- | Represent a DSA signature namely R and S. 60data Signature = Signature 61 { sign_r :: Integer -- ^ DSA r 62 , sign_s :: Integer -- ^ DSA s 63 } deriving (Show,Read,Eq,Data) 64 65instance NFData Signature where 66 rnf (Signature r s) = r `seq` s `seq` () 67 68-- | Represent a DSA public key. 69data PublicKey = PublicKey 70 { public_params :: Params -- ^ DSA parameters 71 , public_y :: PublicNumber -- ^ DSA public Y 72 } deriving (Show,Read,Eq,Data) 73 74instance NFData PublicKey where 75 rnf (PublicKey params y) = y `seq` params `seq` () 76 77-- | Represent a DSA private key. 78-- 79-- Only x need to be secret. 80-- the DSA parameters are publicly shared with the other side. 81data PrivateKey = PrivateKey 82 { private_params :: Params -- ^ DSA parameters 83 , private_x :: PrivateNumber -- ^ DSA private X 84 } deriving (Show,Read,Eq,Data) 85 86instance NFData PrivateKey where 87 rnf (PrivateKey params x) = x `seq` params `seq` () 88 89-- | Represent a DSA key pair 90data KeyPair = KeyPair Params PublicNumber PrivateNumber 91 deriving (Show,Read,Eq,Data) 92 93instance NFData KeyPair where 94 rnf (KeyPair params y x) = x `seq` y `seq` params `seq` () 95 96-- | Public key of a DSA Key pair 97toPublicKey :: KeyPair -> PublicKey 98toPublicKey (KeyPair params pub _) = PublicKey params pub 99 100-- | Private key of a DSA Key pair 101toPrivateKey :: KeyPair -> PrivateKey 102toPrivateKey (KeyPair params _ priv) = PrivateKey params priv 103 104-- | generate a private number with no specific property 105-- this number is usually called X in DSA text. 106generatePrivate :: MonadRandom m => Params -> m PrivateNumber 107generatePrivate (Params _ _ q) = generateMax q 108 109-- | Calculate the public number from the parameters and the private key 110calculatePublic :: Params -> PrivateNumber -> PublicNumber 111calculatePublic (Params p g _) x = expSafe g x p 112 113-- | sign message using the private key and an explicit k number. 114signWith :: (ByteArrayAccess msg, HashAlgorithm hash) 115 => Integer -- ^ k random number 116 -> PrivateKey -- ^ private key 117 -> hash -- ^ hash function 118 -> msg -- ^ message to sign 119 -> Maybe Signature 120signWith k pk hashAlg msg 121 | r == 0 || s == 0 = Nothing 122 | otherwise = Just $ Signature r s 123 where -- parameters 124 (Params p g q) = private_params pk 125 x = private_x pk 126 -- compute r,s 127 kInv = fromJust $ inverse k q 128 hm = dsaTruncHash hashAlg msg q 129 r = expSafe g k p `mod` q 130 s = (kInv * (hm + x * r)) `mod` q 131 132-- | sign message using the private key. 133sign :: (ByteArrayAccess msg, HashAlgorithm hash, MonadRandom m) => PrivateKey -> hash -> msg -> m Signature 134sign pk hashAlg msg = do 135 k <- generateMax q 136 case signWith k pk hashAlg msg of 137 Nothing -> sign pk hashAlg msg 138 Just sig -> return sig 139 where 140 (Params _ _ q) = private_params pk 141 142-- | verify a bytestring using the public key. 143verify :: (ByteArrayAccess msg, HashAlgorithm hash) => hash -> PublicKey -> Signature -> msg -> Bool 144verify hashAlg pk (Signature r s) m 145 -- Reject the signature if either 0 < r < q or 0 < s < q is not satisfied. 146 | r <= 0 || r >= q || s <= 0 || s >= q = False 147 | otherwise = v == r 148 where (Params p g q) = public_params pk 149 y = public_y pk 150 hm = dsaTruncHash hashAlg m q 151 w = fromJust $ inverse s q 152 u1 = (hm*w) `mod` q 153 u2 = (r*w) `mod` q 154 v = ((expFast g u1 p) * (expFast y u2 p)) `mod` p `mod` q 155