DRBG-0.3: Deterministic random bit generator (aka RNG, PRNG) based HMACs, Hashes, and Ciphers.

Portabilityportable
Stabilitybeta
MaintainerThomas.DuBuisson@gmail.com
Safe HaskellNone

Crypto.Random.DRBG

Contents

Description

This module is the convenience interface for the DRBG (NIST standardized number-theoretically secure random number generator). Everything is setup for using the crypto-api CryptoRandomGen type class.

To instantiate the base types of HmacDRBG, HashDRBG, or GenAES just use the CryptoRandomGen primitives of newGen or newGenIO.

For example, to seed a new generator with the system secure random (Entropy) and generate some bytes (stepping the generator along the way) one would do:

    gen <- newGenIO :: IO HashDRBG
    let Right (randomBytes, newGen) = genBytes 1024 gen

or the same thing with your own entropy (throwing exceptions instead of dealing with Either this time):

    let gen = throwLeft (newGen entropy)
        (bytes,gen') = throwLeft (genBytes 1024 gen)
    in ...

Selecting the underlying hash algorithm is supporting using *DRBGWith types:

    gen <- newGenIO :: IO (HmacDRBGWith SHA224)

There are several modifiers that allow you to compose generators together, producing generators with modified security, reseed, and performance properties. GenXor will xor the random bytes of two generators. GenBuffered will spark off work to generate several megabytes of random data and keep that data buffered for quick use. GenAutoReseed will use one generator to automatically reseed another after every 32 kilobytes of requested randoms.

For a complex example, here is a generator that buffers several megabytes of random values which are an Xor of AES with a SHA384 hash that are each reseeded every 32kb with the output of a SHA512 HMAC generator. (Not to claim this has any enhanced security properties, but just to show the composition can be nested).

    gen <- newGenIO :: IO (GenBuffered (GenAutoReseed (GenXor AesCntDRBG (HashDRBGWith SHA384)) HmacDRBG))

Synopsis

Basic Hash-based Generators

type HmacDRBG = State SHA512Source

An alias for an HMAC DRBG generator using SHA512.

type HashDRBG = State SHA512Source

An Alias for a Hash DRBG generator using SHA512.

type HmacDRBGWith = StateSource

The HMAC DRBG state (of kind * -> *) allowing selection of the underlying hash algorithm (SHA1, SHA224 ... SHA512)

type HashDRBGWith = StateSource

The Hash DRBG state (of kind * -> *) allowing selection of the underlying hash algorithm.

Basic Cipher-based Generator

type GenAES = GenCounter AESKeySource

A random number generator using AESKey in ctr mode.

data GenCounter a Source

GenCounter k is a cryptographic BlockCipher with key k being used in ctr mode to generate random bytes.

CryptoRandomGen Transformers

data GenXor a b Source

g :: GenXor a b generates bytes with sub-generators a and b and exclusive-or's the outputs to produce the resulting bytes.

data GenBuffered g Source

g :: GenBuffered a is a generator of type a that attempts to maintain a buffer of random values size >= 1MB and <= 5MB at any time.

data GenAutoReseed a b Source

g :: GenAutoReseed a b is a generator of type a that gets automatically reseeded by generator b upon every 32kB generated.

reseed g ent will reseed both the component generators by breaking ent up into two parts determined by the genSeedLength of each generator.

genBytes will generate the requested bytes with generator a and reseed a using generator b if there has been 32KB of generated data since the last reseed. Note a request for > 32KB of data will be filled in one request to generator a before a is reseeded by b.

genBytesWithEntropy is lifted into the same call for generator a, but it will still reseed from generator b if the limit is hit.

Reseed interval: If generator a needs a genSeedLength a = a' and generator B needs reseeded every 2^b bytes then a GenAutoReseed a b will need reseeded every 2^15 * (2^b / a') bytes. For the common values of a' = 128 and 2^b = 2^48 this means reseeding every 2^56 byte. For the example numbers this translates to about 200 years of continually generating random values at a rate of 10MB/s.

AutoReseed generator construction with custom reseed interval

newGenAutoReseed :: (CryptoRandomGen a, CryptoRandomGen b) => ByteString -> Int -> Either GenError (GenAutoReseed a b)Source

newGenAutoReseed bs i creates a new GenAutoReseed with a custom interval of i bytes using the provided entropy in bs.

This is for extremely long running uses of CryptoRandomGen instances that can't explicitly reseed as often as a single underlying generator would need (usually every 2^48 bytes).

For example:

 newGenAutoReseedIO (2^48) :: IO (Either GenError (GenAutoReseed HashDRBG HashDRBG))

Will last for 2^48 * 2^41 bytes of randomly generated data. That's 2^49 terabytes of random values (128 byte reseeds every 2^48 bytes generated).

newGenAutoReseedIO :: (CryptoRandomGen a, CryptoRandomGen b) => Int -> IO (GenAutoReseed a b)Source

newGenAutoReseedIO i creates a new GenAutoReseed with a custom interval of i bytes, using the system random number generator as a seed.

See newGenAutoReseed.

Helper Re-exports