Safe Haskell | None |
---|---|
Language | Haskell2010 |
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.
- module Crypto.RNG.Class
- data CryptoRNGState
- newCryptoRNGState :: MonadIO m => m CryptoRNGState
- unsafeCryptoRNGState :: MonadIO m => ByteString -> m CryptoRNGState
- randomBytesIO :: ByteLength -> CryptoRNGState -> IO ByteString
- randomR :: (CryptoRNG m, Integral a) => (a, a) -> m a
- class Random a where
- boundedIntegralRandom :: forall m a. (CryptoRNG m, Integral a, Bounded a) => m a
- data CryptoRNGT m a
- mapCryptoRNGT :: (m a -> n b) -> CryptoRNGT m a -> CryptoRNGT n b
- runCryptoRNGT :: CryptoRNGState -> CryptoRNGT m a -> m a
- withCryptoRNGState :: (CryptoRNGState -> m a) -> CryptoRNGT m a
CryproRNG class
module Crypto.RNG.Class
Generation of strings and numbers
data CryptoRNGState Source #
The random number generator state. It sits inside an MVar to support concurrent thread access.
newCryptoRNGState :: MonadIO m => m CryptoRNGState Source #
Create a new CryptoRNGState
, based on system entropy.
unsafeCryptoRNGState :: MonadIO m => ByteString -> m CryptoRNGState Source #
Create a new CryptoRNGState
, based on a bytestring seed.
Should only be used for testing.
:: ByteLength | number of bytes to generate |
-> CryptoRNGState | |
-> IO ByteString |
Generate given number of cryptographically secure random bytes.
randomR :: (CryptoRNG m, Integral a) => (a, a) -> m a Source #
Generate a cryptographically secure random number in given, closed range.
Generation of values in other types
Class for generating cryptographically secure random values.
boundedIntegralRandom :: forall m a. (CryptoRNG m, Integral a, Bounded a) => m a Source #
Helper function for making Random instances.
Monad transformer for carrying rng state
data CryptoRNGT m a Source #
Monad transformer with RNG state.
MonadTrans CryptoRNGT Source # | |
MonadTransControl CryptoRNGT Source # | |
MonadBase b m => MonadBase b (CryptoRNGT m) Source # | |
MonadBaseControl b m => MonadBaseControl b (CryptoRNGT m) Source # | |
Monad m => Monad (CryptoRNGT m) Source # | |
Functor m => Functor (CryptoRNGT m) Source # | |
Applicative m => Applicative (CryptoRNGT m) Source # | |
MonadIO m => MonadIO (CryptoRNGT m) Source # | |
Alternative m => Alternative (CryptoRNGT m) Source # | |
MonadPlus m => MonadPlus (CryptoRNGT m) Source # | |
MonadThrow m => MonadThrow (CryptoRNGT m) Source # | |
MonadCatch m => MonadCatch (CryptoRNGT m) Source # | |
MonadMask m => MonadMask (CryptoRNGT m) Source # | |
MonadIO m => CryptoRNG (CryptoRNGT m) Source # | |
type StT CryptoRNGT a Source # | |
type StM (CryptoRNGT m) a Source # | |
mapCryptoRNGT :: (m a -> n b) -> CryptoRNGT m a -> CryptoRNGT n b Source #
runCryptoRNGT :: CryptoRNGState -> CryptoRNGT m a -> m a Source #
withCryptoRNGState :: (CryptoRNGState -> m a) -> CryptoRNGT m a Source #