crypto-rng-effectful-1.0.0.0: Adaptation of the crypto-rng library for the effectful ecosystem.
Safe HaskellNone
LanguageHaskell2010

Effectful.Crypto.RNG

Description

Generation of random numbers via Crypto.RNG.

Synopsis

Effect

data RNG :: Effect where Source #

Provide the ability to generate random numbers.

Constructors

RandomBytes :: Int -> RNG m ByteString 
Random :: Uniform a => RNG m a 
RandomR :: UniformRange a => (a, a) -> RNG m a 

Instances

Instances details
type DispatchOf RNG Source # 
Instance details

Defined in Effectful.Crypto.RNG.Effect

class Monad m => CryptoRNG (m :: Type -> Type) where #

Monads carrying around the RNG state.

Methods

randomBytes :: Int -> m ByteString #

Generate a given number of cryptographically secure random bytes.

random :: Uniform a => m a #

Generate a cryptographically secure value uniformly distributed over all possible values of that type.

randomR :: UniformRange a => (a, a) -> m a #

Generate a cryptographically secure value in a given, closed range.

Instances

Instances details
(Monad (t m), MonadTrans t, CryptoRNG m) => CryptoRNG (t m)

Generic, overlapping instance.

Instance details

Defined in Crypto.RNG.Class

Methods

randomBytes :: Int -> t m ByteString #

random :: Uniform a => t m a #

randomR :: UniformRange a => (a, a) -> t m a #

MonadIO m => CryptoRNG (RNGT m) 
Instance details

Defined in Crypto.RNG.Unsafe

Methods

randomBytes :: Int -> RNGT m ByteString #

random :: Uniform a => RNGT m a #

randomR :: UniformRange a => (a, a) -> RNGT m a #

MonadIO m => CryptoRNG (CryptoRNGT m) 
Instance details

Defined in Crypto.RNG

RNG :> es => CryptoRNG (Eff es) Source # 
Instance details

Defined in Effectful.Crypto.RNG.Effect

Methods

randomBytes :: Int -> Eff es ByteString #

random :: Uniform a => Eff es a #

randomR :: UniformRange a => (a, a) -> Eff es a #

Handlers

runCryptoRNG :: IOE :> es => CryptoRNGState -> Eff (RNG ': es) a -> Eff es a Source #

Generate cryptographically secure random numbers.

Instantiation of the initial RNG state

newCryptoRNGState :: MonadIO m => m CryptoRNGState #

Create a new CryptoRNGState based on system entropy with a buffer size of 32KB.

One buffer per capability is created.

newCryptoRNGStateSized #

Arguments

:: MonadIO m 
=> Int

Buffer size.

-> m CryptoRNGState 

Create a new CryptoRNGState based on system entropy with buffers of specified size.

One buffer per capability is created.