crypto-rng-0.2.0.1: Cryptographic random number generator.
Safe HaskellNone
LanguageHaskell2010

Crypto.RNG

Description

Support for generation of cryptographically secure random numbers, based on the DRBG package.

This is a convenience layer on top of DRBG, which allows you to pull random values by means of the method random, while keeping the state of the random number generator (RNG) inside a monad. The state is protected by an MVar, which means that concurrent generation of random values from several threads works straight out of the box.

The access to the RNG state is captured by a class. By making instances of this class, client code can enjoy RNG generation from their own monads.

Synopsis

CryptoRNG class

Generation of strings and numbers

data CryptoRNGState Source #

The random number generator state.

newCryptoRNGState :: MonadIO m => m CryptoRNGState Source #

Create a new CryptoRNGState, based on system entropy.

newCryptoRNGStateSized Source #

Arguments

:: MonadIO m 
=> Int

Pool size.

-> m CryptoRNGState 

Create a new CryptoRNGState, based on system entropy with the pool of a specific size.

Note: making the pool bigger than the number of capabilities will not affect anything.

unsafeCryptoRNGState Source #

Arguments

:: MonadIO m 
=> [ByteString]

Seeds for each generator from the pool.

-> m CryptoRNGState 

Create a new CryptoRNGState, based on a bytestring seed. Should only be used for testing.

randomBytesIO Source #

Arguments

:: ByteLength

number of bytes to generate

-> CryptoRNGState 
-> IO ByteString 

Generate given number of cryptographically secure random bytes.

Monad transformer for carrying rng state

data CryptoRNGT m a Source #

Monad transformer with RNG state.

Instances

Instances details
MonadTrans CryptoRNGT Source # 
Instance details

Defined in Crypto.RNG

Methods

lift :: Monad m => m a -> CryptoRNGT m a #

MonadTransControl CryptoRNGT Source # 
Instance details

Defined in Crypto.RNG

Associated Types

type StT CryptoRNGT a #

Methods

liftWith :: Monad m => (Run CryptoRNGT -> m a) -> CryptoRNGT m a #

restoreT :: Monad m => m (StT CryptoRNGT a) -> CryptoRNGT m a #

MonadBase b m => MonadBase b (CryptoRNGT m) Source # 
Instance details

Defined in Crypto.RNG

Methods

liftBase :: b α -> CryptoRNGT m α #

MonadBaseControl b m => MonadBaseControl b (CryptoRNGT m) Source # 
Instance details

Defined in Crypto.RNG

Associated Types

type StM (CryptoRNGT m) a #

Methods

liftBaseWith :: (RunInBase (CryptoRNGT m) b -> b a) -> CryptoRNGT m a #

restoreM :: StM (CryptoRNGT m) a -> CryptoRNGT m a #

MonadError e m => MonadError e (CryptoRNGT m) Source # 
Instance details

Defined in Crypto.RNG

Methods

throwError :: e -> CryptoRNGT m a #

catchError :: CryptoRNGT m a -> (e -> CryptoRNGT m a) -> CryptoRNGT m a #

Monad m => Monad (CryptoRNGT m) Source # 
Instance details

Defined in Crypto.RNG

Methods

(>>=) :: CryptoRNGT m a -> (a -> CryptoRNGT m b) -> CryptoRNGT m b #

(>>) :: CryptoRNGT m a -> CryptoRNGT m b -> CryptoRNGT m b #

return :: a -> CryptoRNGT m a #

Functor m => Functor (CryptoRNGT m) Source # 
Instance details

Defined in Crypto.RNG

Methods

fmap :: (a -> b) -> CryptoRNGT m a -> CryptoRNGT m b #

(<$) :: a -> CryptoRNGT m b -> CryptoRNGT m a #

MonadFail m => MonadFail (CryptoRNGT m) Source # 
Instance details

Defined in Crypto.RNG

Methods

fail :: String -> CryptoRNGT m a #

Applicative m => Applicative (CryptoRNGT m) Source # 
Instance details

Defined in Crypto.RNG

Methods

pure :: a -> CryptoRNGT m a #

(<*>) :: CryptoRNGT m (a -> b) -> CryptoRNGT m a -> CryptoRNGT m b #

liftA2 :: (a -> b -> c) -> CryptoRNGT m a -> CryptoRNGT m b -> CryptoRNGT m c #

(*>) :: CryptoRNGT m a -> CryptoRNGT m b -> CryptoRNGT m b #

(<*) :: CryptoRNGT m a -> CryptoRNGT m b -> CryptoRNGT m a #

MonadIO m => MonadIO (CryptoRNGT m) Source # 
Instance details

Defined in Crypto.RNG

Methods

liftIO :: IO a -> CryptoRNGT m a #

Alternative m => Alternative (CryptoRNGT m) Source # 
Instance details

Defined in Crypto.RNG

Methods

empty :: CryptoRNGT m a #

(<|>) :: CryptoRNGT m a -> CryptoRNGT m a -> CryptoRNGT m a #

some :: CryptoRNGT m a -> CryptoRNGT m [a] #

many :: CryptoRNGT m a -> CryptoRNGT m [a] #

MonadPlus m => MonadPlus (CryptoRNGT m) Source # 
Instance details

Defined in Crypto.RNG

Methods

mzero :: CryptoRNGT m a #

mplus :: CryptoRNGT m a -> CryptoRNGT m a -> CryptoRNGT m a #

MonadThrow m => MonadThrow (CryptoRNGT m) Source # 
Instance details

Defined in Crypto.RNG

Methods

throwM :: Exception e => e -> CryptoRNGT m a #

MonadCatch m => MonadCatch (CryptoRNGT m) Source # 
Instance details

Defined in Crypto.RNG

Methods

catch :: Exception e => CryptoRNGT m a -> (e -> CryptoRNGT m a) -> CryptoRNGT m a #

MonadMask m => MonadMask (CryptoRNGT m) Source # 
Instance details

Defined in Crypto.RNG

Methods

mask :: ((forall a. CryptoRNGT m a -> CryptoRNGT m a) -> CryptoRNGT m b) -> CryptoRNGT m b #

uninterruptibleMask :: ((forall a. CryptoRNGT m a -> CryptoRNGT m a) -> CryptoRNGT m b) -> CryptoRNGT m b #

generalBracket :: CryptoRNGT m a -> (a -> ExitCase b -> CryptoRNGT m c) -> (a -> CryptoRNGT m b) -> CryptoRNGT m (b, c) #

MonadIO m => CryptoRNG (CryptoRNGT m) Source # 
Instance details

Defined in Crypto.RNG

type StT CryptoRNGT a Source # 
Instance details

Defined in Crypto.RNG

type StM (CryptoRNGT m) a Source # 
Instance details

Defined in Crypto.RNG

mapCryptoRNGT :: (m a -> n b) -> CryptoRNGT m a -> CryptoRNGT n b Source #