crypto-random-effect-0.2.0.1: A random effect using crypto-random

Safe HaskellNone

Crypto.Random.Effect

Contents

Description

An effect that can generate random bytes.

It is essentially a State monad with a given CPRG.

Synopsis

Documentation

data RNG Source

Type marker to ensure that there is only one RNG.

Instances

SetMember * * RNG (State gen) (:> * (State gen) a) 

runSystemRNG :: SetMember Lift (Lift IO) r => Eff (State SystemRNG :> (Reader EntropyPool :> r)) a -> Eff r aSource

Run the effect using SystemRNG.

runRNGWithPool :: (SetMember Lift (Lift IO) r, Typeable gen, CPRG gen) => EntropyPool -> Eff (State gen :> (Reader EntropyPool :> r)) a -> Eff r aSource

Run the effect with a given EntropyPool.

runRNG :: (SetMember Lift (Lift IO) r, Typeable gen, CPRG gen) => Eff (State gen :> (Reader EntropyPool :> r)) a -> Eff r aSource

Run the effect without specifying the CPRG.

This is only useful when the type of the CPRG is bound by an explicit type annotation (see runSystemRNG which is runRNG with bound type) or any function within the effect binds it.

withRNG :: (SetMember RNG (State gen) r, Typeable gen) => (gen -> Eff r (a, gen)) -> Eff r aSource

Wrap an effect that uses the CPRG directly.

withRNGIO :: (SetMember Lift (Lift IO) r, SetMember RNG (State gen) r, Typeable gen) => (gen -> IO (a, gen)) -> Eff r aSource

Wrap an IO action that uses the CPRG directly.

rngFork :: (SetMember RNG (State gen) r, CPRG gen, Typeable gen) => Eff r genSource

Fork a CPRG into a new independent CPRG.

As entropy is mixed to generate safely a new generator, 2 calls with the same CPRG will not produce the same output.

randomBytes :: (SetMember RNG (State gen) r, CPRG gen, Typeable gen) => Int -> Eff r ByteStringSource

Generate a number of bytes using the CPRG.

randomBytesWithEntropy :: (SetMember RNG (State gen) r, CPRG gen, Typeable gen) => Int -> Eff r ByteStringSource

Similar to randomBytes except that the random data is mixed with pure entropy, so the result is not reproducible after use, but it provides more guarantee, theorically speaking, in term of the randomness generated.

withRandomBytes :: (SetMember RNG (State gen) r, CPRG gen, Typeable gen) => Int -> (ByteString -> a) -> Eff r aSource

Consume a number of random bytes with a pure function.

Note, that this is simply

 randomBytes cnt >>= return . f

grabEntropy :: (SetMember Lift (Lift IO) r, Member (Reader EntropyPool) r) => Int -> Eff r SecureMemSource

Grab a chunk of entropy from the entropy pool.

unsafeGrabEntropy :: Member (Reader EntropyPool) r => Int -> Eff r SecureMemSource

Grab a chunk of entropy from the entropy pool.

Beware: uses unsafePerformIO under the hood.

Re-exports

class CPRG gen

Cryptographic Pseudo Random Generator

Instances

data SystemRNG

System entropy generator.

This generator doesn't use the entropy reseed level, as the only bytes generated are comping from the entropy pool already.

This generator doesn't create reproducible output, and might be difficult to use for testing and debugging purpose, but otherwise for real world use case should be fine.

data EntropyPool

Pool of Entropy. contains a self mutating pool of entropy, that is always guarantee to contains data.