mwc-random-accelerate-0.2.0.0: Generate Accelerate arrays filled with high quality pseudorandom numbers

Copyright[2014..2020] Trevor L. McDonell
LicenseBSD3
MaintainerTrevor L. McDonell <trevor.mcdonell@gmail.com>
Stabilityexperimental
Portabilitynon-portable (GHC extensions)
Safe HaskellNone
LanguageHaskell2010

Data.Array.Accelerate.System.Random.MWC

Contents

Description

Random number generation backed by MWC.

Example

Create a vector of 100 random uniformly distributed floating-point numbers, where the PRNG is seeded with data from the system's source of pseudo-random numbers (see withSystemRandom):

>>> vs <- randomArray uniform (Z :. 100)           :: IO (Vector Float)

To generate uniformly distributed random variables in the range (-1,1]:

>>> vs <- randomArray (uniformR (-1,1)) (Z:.100)   :: IO (Vector Double)

You can also pass the generator state in explicitly, so that it can be reused:

>>> gen <- create                                  :: IO GenIO
>>> vs  <- randomArrayWith gen uniform (Z :. 100)  :: IO (Vector Int)
Non-uniform distributions

If you require random numbers following other distributions, you can combine this package with the generators from the random-fu package. For example:

import Data.Random                                    hiding ( uniform )
import qualified Data.Random.Distribution.Exponential as R
import qualified Data.Random.Distribution.Poisson     as R

exponential
    :: (Distribution StdUniform e, Floating e, Shape sh, Elt e)
    => e
    -> sh :~> e
exponential beta _sh gen = sampleFrom gen (R.exponential beta)

poisson
    :: (Distribution (R.Poisson b) a, Shape sh, Elt a)
    => b
    -> sh :~> a
poisson lambda _sh gen = sampleFrom gen (R.poisson lambda)

Which can then be used as before:

>>> vs <- randomArray (exponential 5) (Z :. 100)   :: IO (Vector Float)
>>> us <- randomArray (poisson 5)     (Z :. 100)   :: IO (Vector Float)
Synopsis

Generating random arrays

type (:~>) sh e = sh -> GenIO -> IO e Source #

A PRNG from indices to variates

uniform :: (Shape sh, Elt e, Variate e) => sh :~> e Source #

Uniformly distributed random variates.

uniformR :: (Shape sh, Elt e, Variate e) => (e, e) -> sh :~> e Source #

Uniformly distributed random variates in a given range.

randomArray :: (Shape sh, Elt e) => (sh :~> e) -> sh -> IO (Array sh e) Source #

Generate an array of random values. The generator for variates is seeded from the system's fast source of pseudo-random numbers (see: createSystemRandom)

randomArrayWith :: (Shape sh, Elt e) => GenIO -> (sh :~> e) -> sh -> IO (Array sh e) Source #

Generate an array of random values using the supplied generator.

uniformVector :: (PrimMonad m, Variate a, Vector v a) => Gen (PrimState m) -> Int -> m (v a) #

Generate a vector of pseudo-random variates. This is not necessarily faster than invoking uniform repeatedly in a loop, but it may be more convenient to use in some situations.

createSystemRandom :: IO GenIO #

Seed a PRNG with data from the system's fast source of pseudo-random numbers. All the caveats of withSystemRandom apply here as well.

withSystemRandom :: PrimBase m => (Gen (PrimState m) -> m a) -> IO a #

Seed a PRNG with data from the system's fast source of pseudo-random numbers ("/dev/urandom" on Unix-like systems or RtlGenRandom on Windows), then run the given action.

This is a somewhat expensive function, and is intended to be called only occasionally (e.g. once per thread). You should use the Gen it creates to generate many random numbers.

restore :: PrimMonad m => Seed -> m (Gen (PrimState m)) #

Create a new Gen that mirrors the state of a saved Seed.

save :: PrimMonad m => Gen (PrimState m) -> m Seed #

Save the state of a Gen, for later use by restore.

toSeed :: Vector v Word32 => v Word32 -> Seed #

Convert vector to Seed. It acts similarily to initialize and will accept any vector. If you want to pass seed immediately to restore you better call initialize directly since following law holds:

restore (toSeed v) = initialize v

initialize :: (PrimMonad m, Vector v Word32) => v Word32 -> m (Gen (PrimState m)) #

Create a generator for variates using the given seed, of which up to 256 elements will be used. For arrays of less than 256 elements, part of the default seed will be used to finish initializing the generator's state.

Examples:

initialize (singleton 42)
initialize (fromList [4, 8, 15, 16, 23, 42])

If a seed contains fewer than 256 elements, it is first used verbatim, then its elements are xored against elements of the default seed until 256 elements are reached.

If a seed contains exactly 258 elements, then the last two elements are used to set the generator's initial state. This allows for complete generator reproducibility, so that e.g. gen' == gen in the following example:

gen' <- initialize . fromSeed =<< save

In the MWC algorithm, the carry value must be strictly smaller than the multiplicator (see https://en.wikipedia.org/wiki/Multiply-with-carry). Hence, if a seed contains exactly 258 elements, the carry value, which is the last of the 258 values, is moduloed by the multiplicator.

Note that if the first carry value is strictly smaller than the multiplicator, all subsequent carry values are also strictly smaller than the multiplicator (a proof of this is in the comments of the code of uniformWord32), hence when restoring a saved state, we have the guarantee that moduloing the saved carry won't modify its value.

create :: PrimMonad m => m (Gen (PrimState m)) #

Create a generator for variates using a fixed seed.

asGenST :: (GenST s -> ST s a) -> GenST s -> ST s a #

Constrain the type of an action to run in the ST monad.

asGenIO :: (GenIO -> IO a) -> GenIO -> IO a #

Constrain the type of an action to run in the IO monad.

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
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) #

data Gen s #

State of the pseudo-random number generator. It uses mutable state so same generator shouldn't be used from the different threads simultaneously.

type GenIO = Gen (PrimState IO) #

A shorter name for PRNG state in the IO monad.

type GenST s = Gen (PrimState (ST s)) #

A shorter name for PRNG state in the ST monad.

data Seed #

An immutable snapshot of the state of a Gen.

Instances
Eq Seed 
Instance details

Defined in System.Random.MWC

Methods

(==) :: Seed -> Seed -> Bool #

(/=) :: Seed -> Seed -> Bool #

Show Seed 
Instance details

Defined in System.Random.MWC

Methods

showsPrec :: Int -> Seed -> ShowS #

show :: Seed -> String #

showList :: [Seed] -> ShowS #