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

MaintainerThomas.DuBuisson@gmail.com
Stabilitybeta
Portabilityportable
Safe HaskellNone
LanguageHaskell98

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 CtrDRBG 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 CtrDRBG
    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 ...

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.

Most likely you will want to automatically reseed using system randomness (via lazy IO). Thus, you are left with a generator that is random, not pseudo random but without the dangerously unsafe IO found in some other RNGs:

    import Crypto.Random.DRBG hiding (genBytes)
    import Crypto.Classes.Exceptions (genBytes)

    -- An AES CTR generator that automatically reseeds.
    getCtrGen :: IO (GenAutoReseed CtrDRBG SystemEntropy)
    getCtrGen = newGenAutoReseedIO

    f = do g1 <- getCtrGen
           let (bytes, g2) = getBytes 1024 g1
           g bytes g2

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 SHA512 Source

An alias for an HMAC DRBG generator using SHA512.

type HashDRBG = State SHA512 Source

An Alias for a Hash DRBG generator using SHA512.

As of 1July2014 this remains the fastest cryptographic RNG on hackage that has been ran against known answer tests.

type CtrDRBG = State AESKey128 Source

The recommended generator which uses AES-128 in counter mode.

This is an alias for a Counter DRBG generator using AES 128.

type HmacDRBGWith = State Source

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

type HashDRBGWith = State Source

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

type CtrDRBGWith = State Source

The AES CTR DRBG state (of kind * -> *) allowing selection of the underlying cipher algorithm.

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.

Constructors

GenXor !a !b 

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 -> Word64 -> 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) => Word64 -> 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