License | BSD-style |
---|---|
Maintainer | Vincent Hanquez <vincent@snarc.org> |
Stability | stable |
Portability | good |
Safe Haskell | None |
Language | Haskell2010 |
- data ChaChaDRG
- data SystemDRG
- data Seed
- seedNew :: MonadRandom randomly => randomly Seed
- seedFromInteger :: Integer -> Seed
- seedToInteger :: Seed -> Integer
- seedFromBinary :: ByteArrayAccess b => b -> CryptoFailable Seed
- getSystemDRG :: IO SystemDRG
- drgNew :: MonadRandom randomly => randomly ChaChaDRG
- drgNewSeed :: Seed -> ChaChaDRG
- drgNewTest :: (Word64, Word64, Word64, Word64, Word64) -> ChaChaDRG
- withDRG :: DRG gen => gen -> MonadPseudoRandom gen a -> (a, gen)
- withRandomBytes :: (ByteArray ba, DRG g) => g -> Int -> (ba -> a) -> (a, g)
- class DRG gen where
- class (Functor m, Monad m) => MonadRandom m where
- data MonadPseudoRandom gen a
Deterministic instances
ChaCha Deterministic Random Generator
A referentially transparent System representation of the random evaluated out of the system.
Holding onto a specific DRG means that all the already evaluated bytes will be consistently replayed.
There's no need to reseed this DRG, as only pure entropy is represented here.
Seed
seedNew :: MonadRandom randomly => randomly Seed Source #
Create a new Seed from system entropy
seedFromInteger :: Integer -> Seed Source #
Convert an integer to a Seed
seedToInteger :: Seed -> Integer Source #
Convert a Seed to an integer
seedFromBinary :: ByteArrayAccess b => b -> CryptoFailable Seed Source #
Convert a binary to a seed
Deterministic Random class
getSystemDRG :: IO SystemDRG Source #
Grab one instance of the System DRG
drgNew :: MonadRandom randomly => randomly ChaChaDRG Source #
Create a new DRG from system entropy
drgNewSeed :: Seed -> ChaChaDRG Source #
Create a new DRG from a seed
drgNewTest :: (Word64, Word64, Word64, Word64, Word64) -> ChaChaDRG Source #
Create a new DRG from 5 Word64.
This is a convenient interface to create deterministic interface for quickcheck style testing.
It can also be used in other contexts provided the input has been properly randomly generated.
withDRG :: DRG gen => gen -> MonadPseudoRandom gen a -> (a, gen) Source #
Run a pure computation with a Deterministic Random Generator
in the MonadPseudoRandom
withRandomBytes :: (ByteArray ba, DRG g) => g -> Int -> (ba -> a) -> (a, g) Source #
Generate len random bytes and mapped the bytes to the function
f.
This is equivalent to use Control.Arrow first
with randomBytesGenerate
A Deterministic Random Generator (DRG) class
randomBytesGenerate :: ByteArray byteArray => Int -> gen -> (byteArray, gen) Source #
Generate N bytes of randomness from a DRG
Random abstraction
class (Functor m, Monad m) => MonadRandom m where Source #
A monad constraint that allows to generate random bytes
getRandomBytes :: ByteArray byteArray => Int -> m byteArray Source #
MonadRandom IO Source # | |
DRG gen => MonadRandom (MonadPseudoRandom gen) Source # | |
data MonadPseudoRandom gen a Source #
A simple Monad class very similar to a State Monad with the state being a DRG.
DRG gen => Monad (MonadPseudoRandom gen) Source # | |
DRG gen => Functor (MonadPseudoRandom gen) Source # | |
DRG gen => Applicative (MonadPseudoRandom gen) Source # | |
DRG gen => MonadRandom (MonadPseudoRandom gen) Source # | |