DSA-1.0.2: Implementation of DSA, based on the description of FIPS 186-4

Safe HaskellNone
LanguageHaskell98

Codec.Crypto.DSA.Exceptions

Contents

Synopsis

Basic DSA Concepts

data Params :: * #

Represent DSA parameters namely P, G, and Q.

Constructors

Params 

Fields

Instances

Eq Params 

Methods

(==) :: Params -> Params -> Bool #

(/=) :: Params -> Params -> Bool #

Data Params 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Params -> c Params #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c Params #

toConstr :: Params -> Constr #

dataTypeOf :: Params -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c Params) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Params) #

gmapT :: (forall b. Data b => b -> b) -> Params -> Params #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Params -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Params -> r #

gmapQ :: (forall d. Data d => d -> u) -> Params -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> Params -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> Params -> m Params #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Params -> m Params #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Params -> m Params #

Read Params 
Show Params 
ASN1Object Params 

data PublicKey :: * #

Represent a DSA public key.

Constructors

PublicKey 

Fields

Instances

Eq PublicKey 
Data PublicKey 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> PublicKey -> c PublicKey #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c PublicKey #

toConstr :: PublicKey -> Constr #

dataTypeOf :: PublicKey -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c PublicKey) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c PublicKey) #

gmapT :: (forall b. Data b => b -> b) -> PublicKey -> PublicKey #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> PublicKey -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> PublicKey -> r #

gmapQ :: (forall d. Data d => d -> u) -> PublicKey -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> PublicKey -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> PublicKey -> m PublicKey #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> PublicKey -> m PublicKey #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> PublicKey -> m PublicKey #

Read PublicKey 
Show PublicKey 
ASN1Object PublicKey 

data PrivateKey :: * #

Represent a DSA private key.

Only x need to be secret. the DSA parameters are publicly shared with the other side.

Constructors

PrivateKey 

Fields

Instances

Eq PrivateKey 
Data PrivateKey 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> PrivateKey -> c PrivateKey #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c PrivateKey #

toConstr :: PrivateKey -> Constr #

dataTypeOf :: PrivateKey -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c PrivateKey) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c PrivateKey) #

gmapT :: (forall b. Data b => b -> b) -> PrivateKey -> PrivateKey #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> PrivateKey -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> PrivateKey -> r #

gmapQ :: (forall d. Data d => d -> u) -> PrivateKey -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> PrivateKey -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> PrivateKey -> m PrivateKey #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> PrivateKey -> m PrivateKey #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> PrivateKey -> m PrivateKey #

Read PrivateKey 
Show PrivateKey 

data Signature :: * #

Represent a DSA signature namely R and S.

Constructors

Signature 

Fields

Instances

Eq Signature 
Data Signature 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Signature -> c Signature #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c Signature #

toConstr :: Signature -> Constr #

dataTypeOf :: Signature -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c Signature) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Signature) #

gmapT :: (forall b. Data b => b -> b) -> Signature -> Signature #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Signature -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Signature -> r #

gmapQ :: (forall d. Data d => d -> u) -> Signature -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> Signature -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> Signature -> m Signature #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Signature -> m Signature #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Signature -> m Signature #

Read Signature 
Show Signature 
ASN1Object Signature 

getN :: ParameterSizes -> Integer Source #

Get the N parameter, in bits.

getL :: ParameterSizes -> Integer Source #

Get the L parameter, in bits.

DSA Key generation

generateKeyPair :: CryptoRandomGen g => g -> ParameterSizes -> (PublicKey, PrivateKey, ProvablePrimesEvidence, g) Source #

Generate a DSA key pair. This will also generate the p, q, and g parameters using provable and verifiable algorithms, with SHA-256 as the hash function. If you want to use your own p, q, and g values or specify your own generation or hash function,, use the generateKeyPairWithParams function, below.

generateKeyPairWithParams :: CryptoRandomGen g => Params -> g -> (PublicKey, PrivateKey, g) Source #

Generate a key pair given a set of DSA parameters. You really should have validated this set (p, q, and g) using the relevant functions below before you do this. Doing so even if you generated them is probably not a bad practice.

This uses the method using extra random bits from FIPS 186-4. You better be using a good enough random number generator.

DSA Message Signing

Basic, Suggested Mechanisms

signMessage :: PrivateKey -> ByteString -> Signature Source #

Sign a message using DSA. This method utilizes very good defaults for message signing that should be acceptable for most use cases: it uses SHA-256 for the hash function, and generates k using the methods described in RFC 6979. If you wish to change these defaults, please see signMessaage'.

verifyMessage :: PublicKey -> ByteString -> Signature -> Bool Source #

Verify a DSA message signature. This uses the same default mechanisms as signMessage.

Advanced Methods

data HashFunction Source #

The hash to use in generating the signature. We strongly recommend SHA256 or better.

Constructors

SHA1 
SHA224 
SHA256 
SHA384 
SHA512 

signMessage' :: CryptoRandomGen g => HashFunction -> KGenerator g -> g -> PrivateKey -> ByteString -> (Signature, g) Source #

Sign a message given the hash function an k generation routine. Returns either an error the signature generated. You can define your own k generation routine ... but we don't recommend it. Actually, while we're recommending, we recommend you use kViaRFC6979, if you're not sure which to use.

verifyMessage' :: HashFunction -> PublicKey -> ByteString -> Signature -> Bool Source #

Verify a signed message. You need to know what hash algorithm they used to generate the signature, and pass it in. Returns True if the signature was valid.

k Generation Mechanisms

Generation of p and q

Generation via the probable primes method

data ProbablePrimesEvidence Source #

The evidence generated when generating probably primes. This evidence can be used to ensure that the p and q values provided were generated appropriately.

generateProbablePrimes :: CryptoRandomGen g => ParameterSizes -> g -> (ByteString -> ByteString) -> Maybe Integer -> (Integer, Integer, ProbablePrimesEvidence, g) Source #

Using an approved hash function -- at the point of writing, a SHA-2 variant -- generate values of p and q for use in DSA, for which p and q have a very high probability of being prime. In addition to p and q, this routine returns the "domain parameter seed" and "counter" used to generate the primes. These can be supplied to later validation functions; their secrecy is not required for the algorithm to work.

The inputs to the function are the DSA parameters we are generating a key for, a source of entropy, the hash function to use, and (optionally) the length of the domain parameter seed to use. The last item must be greater to or later to the value of n, if supplied, and will be set to (n + 8) if not.

The security of this method depends on the strength of the hash being used. To that end, FIPS 140-2 requires a SHA-2 variant.

validateProbablePrimes Source #

Arguments

:: CryptoRandomGen g 
=> g 
-> Integer

p

-> Integer

q

-> ProbablePrimesEvidence

The evidence

-> (Bool, g) 

Validate that the probable primes that either you generated or that someone provided to you are legitimate.

Generation via the provable primes method

generateProvablePrimes Source #

Arguments

:: CryptoRandomGen g 
=> ParameterSizes

The DSA parameters to use

-> g

source of randomness

-> (ByteString -> ByteString)

Hash function

-> Maybe Integer

Optional seed length, in bits. Must be greater than or equal to N, and divisible by 8.

-> (Integer, Integer, ProvablePrimesEvidence, g) 

Using an approved hash function -- at the point of writing, a SHA-2 variant -- generate values of p and q for use in DSA, for which p and q are provably prime. In addition to p and q, this routine generates a series of additional values that can be used to validate that this algorithm performed correctly.

The inputs to the function are the DSA parameters we are generating key for, a source of entropy, the hash function to use, and (optionally) an initial seed length in bits. The last item, if provided, must be greater than or equal to the N value being tested against, and must be a multiple of 8.

validateProvablePrimes :: Integer -> Integer -> ProvablePrimesEvidence -> Bool Source #

Validate that the provable primes that either you generated or that someone provided to you are legitimate.

Generation of the generator g

generateUnverifiableGenerator :: Integer -> Integer -> Integer Source #

Generate the generator g using a method that is not verifiable to a third party. Quoth FIPS: "[This] method ... may be used when complete validation of the generator g is not required; it is recommended that this method be used only when the party generating g is trusted to not deliberately generate a g that has a potentially exploitable relationship to another generator g'.

The input to this function are a valid p and q, generated using an approved method.

It may be possible (?) that this routine could fail to find a possible generator. In that case, Nothing is returned.

generatorIsValid Source #

Arguments

:: Integer

p

-> Integer

q

-> Integer

g

-> Bool 

Validate that the given generator g works for the values p and q provided.

generateVerifiableGenerator Source #

Arguments

:: GenerationEvidence ev 
=> Integer

p

-> Integer

q

-> ev

The evidence created generating p and q

-> Word8

an index (This allows multiple gs from one pair)

-> Integer 

Generate a generator g, given the values of p, q, the evidence created generating those values, and an index. Quoth FIPS: "This generation method supports the generation of multiple values of g for specific values of p and q. The use of different values of g for the same p and q may be used to support key separation; for example, using the g that is generated with index = 1 for digital signatures and with index = 2 for key establishment."

This method is replicatable, so that given the same inputs it will generate the same outputs. Thus, you can validate that the g generated using this method was generated correctly using validateVerifiableGenerator, which will be nice if you don't trust the person you're talking to.

validateVerifiableGenerator Source #

Arguments

:: GenerationEvidence ev 
=> Integer

p

-> Integer

q

-> ev

The evidence created generating p and q

-> Word8

an index (This allows multiple gs from one pair)

-> Integer

g

-> Bool 

Validate that the value g was generated by generateVerifiableGenerator or someone using the same algorithm. This is probably a good idea if you don't trust your compatriot.