botan-0.0.1.0: High-level Botan bindings
Copyright(c) Leo D 2023
LicenseBSD-3-Clause
Maintainerleo@apotheca.io
Stabilityexperimental
PortabilityPOSIX
Safe HaskellNone
LanguageHaskell2010

Botan.RNG

Description

A module for the common task of random number generation.

Synopsis

Random Number Generators

Random number generators (RNG) are applicable to a wide variety of fields, including cryptography and statistics. They tend to come in two basic varieties: "true" random generators (TRNG) that obtain entropy by measuring some physical random process, and pseudo- random generators (PRNG) that produce long sequences of unpredictable values based on permutations of a much shorter initial key.

Most practical systems take a hybrid approach that involves reseeding a cryptographically secure pseudo-random generator (CSPRNG) periodically from some a source of true entropy, which is the approach that the Botan C++ library takes.

NOTE: Be forewarned that virtual machines usually lack access to a source of true entropy.

Usage

This module provides two methods of using the random number generator, which are repeated throughout other modules in the rest of the library, thus affecting their design:

Use of MonadRandomIO is preferred.

Directly using an RNG context

Direct usage is very simple: an RNG context is created, and must be passed around manually.

main = do
    rng <- newRNG Autoseeded
    addEntropyRNG "Fee fi fo fum!" rng
    reseedRNG 32 rng
    x <- getRandomBytesRNG 12 rng
    print x

Implicit access to an RNG context using MonadRandomIO

Monadic usage is very simple: IO is itself a convenient instance of MonadRandomIO that uses the systemRNG:

main = do
    x <- getRandomBytes 12
    print x

The runRandomIO function is used to run a MonadRandomIO action in RandomIO with a specific RNG:

main = do
    rng <- newRNG Autoseeded
    flip runRandomIO rng $ do
        addEntropy "Fee fi fo fum!"
        x <- getRandomBytes 12
        liftIO $ print x

The RandomT transformer and runRandomT functions can also be run with any MonadIO, since RandomIO and RandomT are both instances of MonadRandomIO.

getSomeBytes :: (MonadIO m) => RandomT (ReaderT Int m) ByteString
getSomeBytes = do
    n <- lift ask
    getRandomBytes n

The RNG data type

type RNG = RNG Source #

The random number generator context.

NOTE: This data type is an instance of Stateful

Available RNGs

data RNGType Source #

The random generator type.

Custom RNG are not yet supported at this time.

Constructors

System

System random System_RNG

Autoseeded

User-threadsafe autoseeded random AutoSeeded_RNG

RDRand

Hardware random Processor_RNG, may be unavailable

Instances

Instances details
Show RNGType Source # 
Instance details

Defined in Botan.RNG

Eq RNGType Source # 
Instance details

Defined in Botan.RNG

Methods

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

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

Initializing a random number generator

newRNG :: MonadIO m => RNGType -> m RNG Source #

Initialize a random number generator object

NOTE: This is not newRNG

systemRNG :: RNG Source #

The System_RNG generator

Getting random bytes directly

getRandomBytesRNG Source #

Arguments

:: MonadIO m 
=> Int

n number of bytes

-> RNG

rng random generator

-> m ByteString

A random bytestring of length n

Get random bytes from a random number generator

unsafeGetRandomBytesRNG Source #

Arguments

:: Int

n number of bytes

-> RNG

rng random generator

-> ByteString

A random bytestring of length n

Get random bytes from a random number generator, unsafely.

This uses unsafePerformIO, and thus requires caution.

Adding entropy directly

addEntropyRNG :: MonadIO m => ByteString -> RNG -> m () Source #

Add some seed material to a random number generator

reseedRNG Source #

Arguments

:: MonadIO m 
=> Int

n number of bits

-> RNG

rng random generator

-> m () 

Reseed a random number generator.

Uses the System_RNG as a seed generator.

reseedRNGFrom Source #

Arguments

:: MonadIO m 
=> Int

n

-> RNG

src

-> RNG

rng

-> m () 

Reseed a random number generator using another generator.

NOTE: The arguments are in a different order than Botan.Low.RNG.rngReseedFromRNG

IO with implicit RNG

class MonadIO m => MonadRandomIO (m :: Type -> Type) where Source #

A typeclass for any monad that has access to a hidden RNG context

Methods

getRNG :: m RNG Source #

Access the hidden RNG context

This can be used to turn any direct RNG function into a MonadRandomIO function

getRandomBytes :: MonadRandomIO m => Int -> m ByteString
getRandomBytes n = getRNG >>= getRandomBytesRNG n

Instances

Instances details
MonadRandomIO IO Source # 
Instance details

Defined in Botan.RNG

Methods

getRNG :: IO RNG Source #

MonadIO m => MonadRandomIO (ReaderT RNG m) Source # 
Instance details

Defined in Botan.RNG

Getting random bytes

getRandomBytes :: MonadRandomIO m => Int -> m ByteString Source #

Get random bytes from the current random number generator

getSystemRandomBytes Source #

Arguments

:: MonadIO m 
=> Int

n number of bytes

-> m ByteString

A random bytestring of length n

Get random bytes from system random number generator

Adding entropy

reseed :: MonadRandomIO m => Int -> m () Source #

Reseed the current random number generator.

Uses the System_RNG as a seed generator.

reseedFrom Source #

Arguments

:: MonadRandomIO m 
=> Int

n number of bits

-> RNG

src

-> m () 

Reseed the current random number generator using another generator.

addEntropy Source #

Arguments

:: MonadRandomIO m 
=> ByteString

entropy

-> m () 

Add some seed material to the current random number generator

RandomIO monad

type RandomIO = ReaderT RNG IO Source #

Random generator monad

runRandomIO :: RandomIO a -> RNG -> IO a Source #

Runs a RandomIO action in IO using the specified generator.

RandomT monad transformer

type RandomT (m :: Type -> Type) = ReaderT RNG m Source #

Random generator monad transformer

runRandomT :: MonadIO m => RandomT m a -> RNG -> m a Source #

Runs a MonadRandomIO action in MonadIO using the specified generator.

Orphan instances