mwc-random-0.13.5.0: Fast, high quality pseudo random number generation

Copyright(c) 2009-2012 Bryan O'Sullivan
LicenseBSD3
Maintainerbos@serpentine.com
Stabilityexperimental
Portabilityportable
Safe HaskellNone
LanguageHaskell98

System.Random.MWC

Contents

Description

Pseudo-random number generation. This module contains code for generating high quality random numbers that follow a uniform distribution.

For non-uniform distributions, see the Distributions module.

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.

The generator state is stored in the Gen data type. It can be created in several ways:

  1. Using the withSystemRandom call, which creates a random state.
  2. Supply your own seed to initialize function.
  3. Finally, create makes a generator from a fixed seed. Generators created in this way aren't really random.

For repeatability, the state of the generator can be snapshotted and replayed using the save and restore functions.

The simplest use is to generate a vector of uniformly distributed values:

  vs <- withSystemRandom . asGenST $ \gen -> uniformVector gen 100

These values can be of any type which is an instance of the class Variate.

To generate random values on demand, first create a random number generator.

  gen <- create

Hold onto this generator and use it wherever random values are required (creating a new generator is expensive compared to generating a random number, so you don't want to throw them away). Get a random value using uniform or uniformR:

  v <- uniform gen
  v <- uniformR (1, 52) gen

Synopsis

Gen: Pseudo-Random Number Generators

data Gen s Source #

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

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

Create a generator for variates using a fixed seed.

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

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

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

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.

createSystemRandom :: IO GenIO Source #

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

Type helpers

The functions in this package are deliberately written for flexibility, and will run in both the IO and ST monads.

This can defeat the compiler's ability to infer a principal type in simple (and common) cases. For instance, we would like the following to work cleanly:

import System.Random.MWC
import Data.Vector.Unboxed

main = do
  v <- withSystemRandom $ \gen -> uniformVector gen 20
  print (v :: Vector Int)

Unfortunately, the compiler cannot tell what monad uniformVector should execute in. The "fix" of adding explicit type annotations is not pretty:

{-# LANGUAGE ScopedTypeVariables #-}

import Control.Monad.ST

main = do
  vs <- withSystemRandom $
        \(gen::GenST s) -> uniformVector gen 20 :: ST s (Vector Int)
  print vs

As a more readable alternative, this library provides asGenST and asGenIO to constrain the types appropriately. We can get rid of the explicit type annotations as follows:

main = do
  vs <- withSystemRandom . asGenST $ \gen -> uniformVector gen 20
  print (vs :: Vector Int)

This is almost as compact as the original code that the compiler rejected.

type GenIO = Gen (PrimState IO) Source #

A shorter name for PRNG state in the IO monad.

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

A shorter name for PRNG state in the ST monad.

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

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

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

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

Variates: uniformly distributed values

class Variate a where Source #

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

Methods

uniform :: PrimMonad m => Gen (PrimState 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 :: PrimMonad m => (a, a) -> Gen (PrimState m) -> 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.

Instances

Variate Bool Source # 

Methods

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

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

Variate Double Source # 
Variate Float Source # 

Methods

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

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

Variate Int Source # 

Methods

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

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

Variate Int8 Source # 

Methods

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

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

Variate Int16 Source # 

Methods

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

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

Variate Int32 Source # 

Methods

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

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

Variate Int64 Source # 

Methods

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

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

Variate Word Source # 

Methods

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

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

Variate Word8 Source # 

Methods

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

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

Variate Word16 Source # 
Variate Word32 Source # 
Variate Word64 Source # 
(Variate a, Variate b) => Variate (a, b) Source # 

Methods

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

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

(Variate a, Variate b, Variate c) => Variate (a, b, c) Source # 

Methods

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

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

(Variate a, Variate b, Variate c, Variate d) => Variate (a, b, c, d) Source # 

Methods

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

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

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

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.

Seed: state management

data Seed Source #

An immutable snapshot of the state of a Gen.

Instances

Eq Seed Source # 

Methods

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

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

Show Seed Source # 

Methods

showsPrec :: Int -> Seed -> ShowS #

show :: Seed -> String #

showList :: [Seed] -> ShowS #

fromSeed :: Seed -> Vector Word32 Source #

Convert seed into vector.

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

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

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

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

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

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

References