Copyright | (c) Leo D 2023 |
---|---|
License | BSD-3-Clause |
Maintainer | leo@apotheca.io |
Stability | experimental |
Portability | POSIX |
Safe Haskell | None |
Language | Haskell2010 |
A module for the common task of random number generation.
Synopsis
- type RNG = RNG
- data RNGType
- = System
- | Autoseeded
- | RDRand
- newRNG :: MonadIO m => RNGType -> m RNG
- systemRNG :: RNG
- getRandomBytesRNG :: MonadIO m => Int -> RNG -> m ByteString
- unsafeGetRandomBytesRNG :: Int -> RNG -> ByteString
- addEntropyRNG :: MonadIO m => ByteString -> RNG -> m ()
- reseedRNG :: MonadIO m => Int -> RNG -> m ()
- reseedRNGFrom :: MonadIO m => Int -> RNG -> RNG -> m ()
- class MonadIO m => MonadRandomIO (m :: Type -> Type) where
- getRandomBytes :: MonadRandomIO m => Int -> m ByteString
- getSystemRandomBytes :: MonadIO m => Int -> m ByteString
- reseed :: MonadRandomIO m => Int -> m ()
- reseedFrom :: MonadRandomIO m => Int -> RNG -> m ()
- addEntropy :: MonadRandomIO m => ByteString -> m ()
- type RandomIO = ReaderT RNG IO
- runRandomIO :: RandomIO a -> RNG -> IO a
- type RandomT (m :: Type -> Type) = ReaderT RNG m
- runRandomT :: MonadIO m => RandomT m a -> RNG -> m a
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:
- Directly using an
RNG
context - Implicit access to an
RNG
context usingMonadRandomIO
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
The random number generator context.
NOTE: This data type is an instance of Stateful
Available RNGs
The random generator type.
Custom RNG are not yet supported at this time.
System | System random |
Autoseeded | User-threadsafe autoseeded random |
RDRand | Hardware random |
Initializing a random number generator
newRNG :: MonadIO m => RNGType -> m RNG Source #
Initialize a random number generator object
NOTE: This is not newRNG
Getting random bytes directly
:: 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 #
:: 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
Reseed a random number generator.
Uses the System_RNG as a seed generator.
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
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
Getting random bytes
getRandomBytes :: MonadRandomIO m => Int -> m ByteString Source #
Get random bytes from the current random number generator
:: 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.
:: MonadRandomIO m | |
=> Int | n number of bits |
-> RNG | src |
-> m () |
Reseed the current random number generator using another generator.
:: MonadRandomIO m | |
=> ByteString | entropy |
-> m () |
Add some seed material to the current random number generator
RandomIO monad
RandomT monad transformer
runRandomT :: MonadIO m => RandomT m a -> RNG -> m a Source #
Runs a MonadRandomIO
action in MonadIO
using the specified generator.
Orphan instances
MonadIO m => StatefulGen RNG m Source # | |
uniformWord32R :: Word32 -> RNG -> m Word32 # uniformWord64R :: Word64 -> RNG -> m Word64 # uniformWord8 :: RNG -> m Word8 # uniformWord16 :: RNG -> m Word16 # uniformWord32 :: RNG -> m Word32 # uniformWord64 :: RNG -> m Word64 # uniformShortByteString :: Int -> RNG -> m ShortByteString # |