cryptonite-cd-0.29.1: Cryptography Primitives sink
LicenseBSD-style
MaintainerVincent Hanquez <vincent@snarc.org>
Stabilitystable
Portabilitygood
Safe HaskellNone
LanguageHaskell2010

Crypto.Random

Description

 
Synopsis

Deterministic instances

data ChaChaDRG Source #

ChaCha Deterministic Random Generator

Instances

Instances details
NFData ChaChaDRG Source # 
Instance details

Defined in Crypto.Random.ChaChaDRG

Methods

rnf :: ChaChaDRG -> () #

DRG ChaChaDRG Source # 
Instance details

Defined in Crypto.Random.ChaChaDRG

Methods

randomBytesGenerate :: ByteArray byteArray => Int -> ChaChaDRG -> (byteArray, ChaChaDRG) Source #

data SystemDRG Source #

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.

Instances

Instances details
DRG SystemDRG Source # 
Instance details

Defined in Crypto.Random.SystemDRG

Methods

randomBytesGenerate :: ByteArray byteArray => Int -> SystemDRG -> (byteArray, SystemDRG) Source #

data Seed Source #

Instances

Instances details
ByteArrayAccess Seed Source # 
Instance details

Defined in Crypto.Random

Methods

length :: Seed -> Int #

withByteArray :: Seed -> (Ptr p -> IO a) -> IO a #

copyByteArrayToPtr :: Seed -> Ptr p -> IO () #

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.

Note that the Arbitrary instance provided by QuickCheck for Word64 does not have a uniform distribution. It is often better to use instead arbitraryBoundedRandom.

System endianness impacts how the tuple is interpreted and therefore changes the resulting DRG.

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

class DRG gen where Source #

A Deterministic Random Generator (DRG) class

Methods

randomBytesGenerate :: ByteArray byteArray => Int -> gen -> (byteArray, gen) Source #

Generate N bytes of randomness from a DRG

Instances

Instances details
DRG SystemDRG Source # 
Instance details

Defined in Crypto.Random.SystemDRG

Methods

randomBytesGenerate :: ByteArray byteArray => Int -> SystemDRG -> (byteArray, SystemDRG) Source #

DRG ChaChaDRG Source # 
Instance details

Defined in Crypto.Random.ChaChaDRG

Methods

randomBytesGenerate :: ByteArray byteArray => Int -> ChaChaDRG -> (byteArray, ChaChaDRG) Source #

Random abstraction

class Monad m => MonadRandom m where Source #

A monad constraint that allows to generate random bytes

Methods

getRandomBytes :: ByteArray byteArray => Int -> m byteArray Source #

Instances

Instances details
MonadRandom IO Source # 
Instance details

Defined in Crypto.Random.Types

Methods

getRandomBytes :: ByteArray byteArray => Int -> IO byteArray Source #

DRG gen => MonadRandom (MonadPseudoRandom gen) Source # 
Instance details

Defined in Crypto.Random.Types

Methods

getRandomBytes :: ByteArray byteArray => Int -> MonadPseudoRandom gen byteArray Source #

data MonadPseudoRandom gen a Source #

A simple Monad class very similar to a State Monad with the state being a DRG.

Instances

Instances details
DRG gen => Monad (MonadPseudoRandom gen) Source # 
Instance details

Defined in Crypto.Random.Types

Methods

(>>=) :: MonadPseudoRandom gen a -> (a -> MonadPseudoRandom gen b) -> MonadPseudoRandom gen b #

(>>) :: MonadPseudoRandom gen a -> MonadPseudoRandom gen b -> MonadPseudoRandom gen b #

return :: a -> MonadPseudoRandom gen a #

DRG gen => Functor (MonadPseudoRandom gen) Source # 
Instance details

Defined in Crypto.Random.Types

Methods

fmap :: (a -> b) -> MonadPseudoRandom gen a -> MonadPseudoRandom gen b #

(<$) :: a -> MonadPseudoRandom gen b -> MonadPseudoRandom gen a #

DRG gen => Applicative (MonadPseudoRandom gen) Source # 
Instance details

Defined in Crypto.Random.Types

Methods

pure :: a -> MonadPseudoRandom gen a #

(<*>) :: MonadPseudoRandom gen (a -> b) -> MonadPseudoRandom gen a -> MonadPseudoRandom gen b #

liftA2 :: (a -> b -> c) -> MonadPseudoRandom gen a -> MonadPseudoRandom gen b -> MonadPseudoRandom gen c #

(*>) :: MonadPseudoRandom gen a -> MonadPseudoRandom gen b -> MonadPseudoRandom gen b #

(<*) :: MonadPseudoRandom gen a -> MonadPseudoRandom gen b -> MonadPseudoRandom gen a #

DRG gen => MonadRandom (MonadPseudoRandom gen) Source # 
Instance details

Defined in Crypto.Random.Types

Methods

getRandomBytes :: ByteArray byteArray => Int -> MonadPseudoRandom gen byteArray Source #