pcg-random-0.1.1.0: Haskell bindings to the PCG random number generator.

CopyrightCopyright (c) 2014-2015, Christopher Chalmers <c.chalmers@me.com>
LicenseBSD3
MaintainerChristopher Chalmers <c.chalmers@me.com>
Stabilityexperimental
PortabilityCPP, FFI
Safe HaskellNone
LanguageHaskell2010

System.Random.PCG.Unique

Contents

Description

Unique variant of the PCG random number generator. Guarantees the sequence to be unique by using the pointer address to select the output sequence.

There is no way to freeze the state because then it wouldn't be unique anymore. Also, generators can't be initialized in ST because we don't know what pointer reference they'll get.

See http://www.pcg-random.org for details.

import System.Random.PCG.Unique

three :: IO [Double]
three = do
  g <- create
  a <- uniform g
  b <- uniform g
  c <- uniform g
  return [a,b,c]

Synopsis

Gen

data Gen Source

State of the random number generator

Instances

create :: IO Gen Source

Create a Gen from a fixed initial seed.

createSystemRandom :: IO Gen 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.

initialize :: Word64 -> IO Gen Source

Create a generator from two words. Note: this is not the same as the two words in a Seed.

withSystemRandom :: (Gen -> IO a) -> IO a Source

Seed with system random number. ("/dev/urandom" on Unix-like systems, time otherwise).

Getting random numbers

class Variate a where Source

Methods

uniform :: Generator g m => g -> m a Source

Generate a uniformly distributed random vairate.

  • Use entire range for integral types.
  • Use (0,1] range for floating types.

uniformR :: Generator g m => (a, a) -> g -> m a Source

Generate a uniformly distributed random vairate in the given range.

  • Use inclusive range for integral types.
  • Use (a,b] range for floating types.

uniformB :: Generator g m => a -> g -> m a Source

Generate a uniformly distributed random vairate in the range [0,b). For integral types the bound must be less than the max bound of Word32 (4294967295). Behaviour is undefined for negative bounds.

advance :: Word64 -> Gen -> IO () Source

Advance the given generator n steps in log(n) time.

retract :: Word64 -> Gen -> IO () Source

Retract the given generator n steps in log(2^64-n) time. This is just advance (-n).

Type restricted versions

uniform

uniformW8 :: Generator g m => g -> m Word8 Source

uniformI8 :: Generator g m => g -> m Int8 Source

uniformI16 :: Generator g m => g -> m Int16 Source

uniformI32 :: Generator g m => g -> m Int32 Source

uniformI64 :: Generator g m => g -> m Int64 Source

uniformF :: Generator g m => g -> m Float Source

uniformD :: Generator g m => g -> m Double Source

uniformBool :: Generator g m => g -> m Bool Source

uniformR

uniformRW8 :: Generator g m => (Word8, Word8) -> g -> m Word8 Source

uniformRI8 :: Generator g m => (Int8, Int8) -> g -> m Int8 Source

uniformRI16 :: Generator g m => (Int16, Int16) -> g -> m Int16 Source

uniformRI32 :: Generator g m => (Int32, Int32) -> g -> m Int32 Source

uniformRI64 :: Generator g m => (Int64, Int64) -> g -> m Int64 Source

uniformRF :: Generator g m => (Float, Float) -> g -> m Float Source

uniformRD :: Generator g m => (Double, Double) -> g -> m Double Source

uniformRBool :: Generator g m => (Bool, Bool) -> g -> m Bool Source

uniformB

uniformBW8 :: Generator g m => Word8 -> g -> m Word8 Source

uniformBI8 :: Generator g m => Int8 -> g -> m Int8 Source

uniformBI16 :: Generator g m => Int16 -> g -> m Int16 Source

uniformBI32 :: Generator g m => Int32 -> g -> m Int32 Source

uniformBI64 :: Generator g m => Int64 -> g -> m Int64 Source

uniformBF :: Generator g m => Float -> g -> m Float Source

uniformBD :: Generator g m => Double -> g -> m Double Source

uniformBBool :: Generator g m => Bool -> g -> m Bool Source