fused-effects-mwc-random-0.1.0.0: High-quality random number generation as an effect.
Safe HaskellNone
LanguageHaskell2010

Control.Effect.Random

Description

The Random effect provides access to uniformly distributed random values of user-specified types or from well-known numerical distributions.

This is the “fancy” syntax that hides most details of randomness behind a nice API.

Synopsis

Documentation

data Random (m :: Type -> Type) k where Source #

Constructors

Random :: Distrib a -> Random m a 
Save :: Random m Seed 

Instances

Instances details
(Algebra sig m, Member (Lift n) sig, PrimMonad n) => Algebra (Random :+: sig) (RandomC n m) Source # 
Instance details

Defined in Control.Carrier.Random.Lifted

Methods

alg :: forall ctx (n0 :: Type -> Type) a. Functor ctx => Handler ctx n0 (RandomC n m) -> (Random :+: sig) n0 a -> ctx () -> RandomC n m (ctx a) #

Uniform distributions

uniform :: (Variate a, Has Random sig m) => m a Source #

Generate a single uniformly distributed random variate. The range of values produced varies by type:

  • For fixed-width integral types, the type's entire range is used.
  • For floating point numbers, the range (0,1] is used. Zero is explicitly excluded, to allow variates to be used in statistical calculations that require non-zero values (e.g. uses of the log function).

To generate a Float variate with a range of [0,1), subtract 2**(-33). To do the same with Double variates, subtract 2**(-53).

uniformR :: (Variate a, Has Random sig m) => (a, a) -> m a Source #

Generate single uniformly distributed random variable in a given range.

  • For integral types inclusive range is used.
  • For floating point numbers range (a,b] is used if one ignores rounding errors.

Continuous distributions

normal Source #

Arguments

:: Has Random sig m 
=> Double

Mean

-> Double

Standard deviation

-> m Double 

Generate a normally distributed random variate with given mean and standard deviation.

standard :: Has Random sig m => m Double Source #

Generate a normally distributed random variate with zero mean and unit variance.

exponential Source #

Arguments

:: Has Random sig m 
=> Double

Scale parameter

-> m Double 

Generate an exponentially distributed random variate.

truncatedExp Source #

Arguments

:: Has Random sig m 
=> Double

Scale parameter

-> (Double, Double)

Range to which distribution is truncated. Values may be negative.

-> m Double 

Generate truncated exponentially distributed random variate.

gamma Source #

Arguments

:: Has Random sig m 
=> Double

Shape parameter

-> Double

Scale parameter

-> m Double 

Random variate generator for gamma distribution.

chiSquare Source #

Arguments

:: Has Random sig m 
=> Int

Number of degrees of freedom

-> m Double 

Random variate generator for the chi square distribution.

beta Source #

Arguments

:: Has Random sig m 
=> Double

alpha (>0)

-> Double

beta (>0)

-> m Double 

Random variate generator for Beta distribution

Discrete distributions

categorical Source #

Arguments

:: (Has Random sig m, Vector v Double) 
=> v Double

List of weights [>0]

-> m Int 

Random variate generator for categorical distribution.

logCategorical Source #

Arguments

:: (Has Random sig m, Vector v Double) 
=> v Double

List of logarithms of weights

-> m Int 

Random variate generator for categorical distribution where the weights are in the log domain. It's implemented in terms of categorical.

geometric0 Source #

Arguments

:: Has Random sig m 
=> Double

p success probability lies in (0,1]

-> m Int 

Random variate generator for the geometric distribution, computing the number of failures before success. Distribution's support is [0..].

geometric1 Source #

Arguments

:: Has Random sig m 
=> Double

p success probability lies in (0,1]

-> m Int 

Random variate generator for geometric distribution for number of trials. Distribution's support is [1..] (i.e. just geometric0 shifted by 1).

bernoulli Source #

Arguments

:: Has Random sig m 
=> Double

Probability of success (returning True)

-> m Bool 

Random variate generator for Bernoulli distribution

dirichlet Source #

Arguments

:: (Has Random sig m, Traversable t) 
=> t Double

container of parameters

-> m (t Double) 

Random variate generator for Dirichlet distribution

Permutations

uniformPermutation :: (Has Random sig m, Vector v Int) => Int -> m (v Int) Source #

Random variate generator for uniformly distributed permutations. It returns random permutation of vector [0 .. n-1]. This is the Fisher-Yates shuffle.

uniformShuffle :: (Has Random sig m, Vector v a) => v a -> m (v a) Source #

Random variate generator for a uniformly distributed shuffle (all shuffles are equiprobable) of a vector. It uses Fisher-Yates shuffle algorithm.

Implementation details prevent a native implementation of the uniformShuffleM function. Use the native API if this is required.

Introspection

save :: Has Random sig m => m Seed Source #

Save the state of the random number generator to be used by subsequent carrier invocations.

data Distrib a where Source #

GADT representing the functions provided by mwc-random.

Re-exports

class Variate a #

The class of types for which we can generate uniformly distributed random variates.

The uniform PRNG uses Marsaglia's MWC256 (also known as MWC8222) multiply-with-carry generator, which has a period of 2^8222 and fares well in tests of randomness. It is also extremely fast, between 2 and 3 times faster than the Mersenne Twister.

Note: Marsaglia's PRNG is not known to be cryptographically secure, so you should not use it for cryptographic operations.

Minimal complete definition

uniform, uniformR

Instances

Instances details
Variate Bool 
Instance details

Defined in System.Random.MWC

Methods

uniform :: PrimMonad m => Gen (PrimState m) -> m Bool #

uniformR :: PrimMonad m => (Bool, Bool) -> Gen (PrimState m) -> m Bool #

Variate Double 
Instance details

Defined in System.Random.MWC

Methods

uniform :: PrimMonad m => Gen (PrimState m) -> m Double #

uniformR :: PrimMonad m => (Double, Double) -> Gen (PrimState m) -> m Double #

Variate Float 
Instance details

Defined in System.Random.MWC

Methods

uniform :: PrimMonad m => Gen (PrimState m) -> m Float #

uniformR :: PrimMonad m => (Float, Float) -> Gen (PrimState m) -> m Float #

Variate Int 
Instance details

Defined in System.Random.MWC

Methods

uniform :: PrimMonad m => Gen (PrimState m) -> m Int #

uniformR :: PrimMonad m => (Int, Int) -> Gen (PrimState m) -> m Int #

Variate Int8 
Instance details

Defined in System.Random.MWC

Methods

uniform :: PrimMonad m => Gen (PrimState m) -> m Int8 #

uniformR :: PrimMonad m => (Int8, Int8) -> Gen (PrimState m) -> m Int8 #

Variate Int16 
Instance details

Defined in System.Random.MWC

Methods

uniform :: PrimMonad m => Gen (PrimState m) -> m Int16 #

uniformR :: PrimMonad m => (Int16, Int16) -> Gen (PrimState m) -> m Int16 #

Variate Int32 
Instance details

Defined in System.Random.MWC

Methods

uniform :: PrimMonad m => Gen (PrimState m) -> m Int32 #

uniformR :: PrimMonad m => (Int32, Int32) -> Gen (PrimState m) -> m Int32 #

Variate Int64 
Instance details

Defined in System.Random.MWC

Methods

uniform :: PrimMonad m => Gen (PrimState m) -> m Int64 #

uniformR :: PrimMonad m => (Int64, Int64) -> Gen (PrimState m) -> m Int64 #

Variate Word 
Instance details

Defined in System.Random.MWC

Methods

uniform :: PrimMonad m => Gen (PrimState m) -> m Word #

uniformR :: PrimMonad m => (Word, Word) -> Gen (PrimState m) -> m Word #

Variate Word8 
Instance details

Defined in System.Random.MWC

Methods

uniform :: PrimMonad m => Gen (PrimState m) -> m Word8 #

uniformR :: PrimMonad m => (Word8, Word8) -> Gen (PrimState m) -> m Word8 #

Variate Word16 
Instance details

Defined in System.Random.MWC

Methods

uniform :: PrimMonad m => Gen (PrimState m) -> m Word16 #

uniformR :: PrimMonad m => (Word16, Word16) -> Gen (PrimState m) -> m Word16 #

Variate Word32 
Instance details

Defined in System.Random.MWC

Methods

uniform :: PrimMonad m => Gen (PrimState m) -> m Word32 #

uniformR :: PrimMonad m => (Word32, Word32) -> Gen (PrimState m) -> m Word32 #

Variate Word64 
Instance details

Defined in System.Random.MWC

Methods

uniform :: PrimMonad m => Gen (PrimState m) -> m Word64 #

uniformR :: PrimMonad m => (Word64, Word64) -> Gen (PrimState m) -> m Word64 #

(Variate a, Variate b) => Variate (a, b) 
Instance details

Defined in System.Random.MWC

Methods

uniform :: PrimMonad m => Gen (PrimState m) -> m (a, b) #

uniformR :: PrimMonad m => ((a, b), (a, b)) -> Gen (PrimState m) -> m (a, b) #

(Variate a, Variate b, Variate c) => Variate (a, b, c) 
Instance details

Defined in System.Random.MWC

Methods

uniform :: PrimMonad m => Gen (PrimState m) -> m (a, b, c) #

uniformR :: PrimMonad m => ((a, b, c), (a, b, c)) -> Gen (PrimState m) -> m (a, b, c) #

(Variate a, Variate b, Variate c, Variate d) => Variate (a, b, c, d) 
Instance details

Defined in System.Random.MWC

Methods

uniform :: PrimMonad m => Gen (PrimState m) -> m (a, b, c, d) #

uniformR :: PrimMonad m => ((a, b, c, d), (a, b, c, d)) -> Gen (PrimState m) -> m (a, b, c, d) #

type Has (eff :: (Type -> Type) -> Type -> Type) (sig :: (Type -> Type) -> Type -> Type) (m :: Type -> Type) = (Members eff sig, Algebra sig m) #

m is a carrier for sig containing eff.

Note that if eff is a sum, it will be decomposed into multiple Member constraints. While this technically allows one to combine multiple unrelated effects into a single Has constraint, doing so has two significant drawbacks:

  1. Due to a problem with recursive type families, this can lead to significantly slower compiles.
  2. It defeats ghc’s warnings for redundant constraints, and thus can lead to a proliferation of redundant constraints as code is changed.

Since: fused-effects-1.0.0.0