pcg-random-0.1.3.7: Haskell bindings to the PCG random number generator.
CopyrightCopyright (c) 2015 Christopher Chalmers <c.chalmers@me.com>
LicenseBSD3
MaintainerChristopher Chalmers <c.chalmers@me.com>
Stabilityexperimental
PortabilityCPP
Safe HaskellNone
LanguageHaskell2010

System.Random.PCG.Pure

Description

Standard PCG Random Number Generator with chosen streams, written in pure haskell. See http://www.pcg-random.org for details.

import Control.Monad.ST
import System.Random.PCG.Pure

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

Gen

data Gen s Source #

State of the random number generator

Instances

Instances details
(PrimMonad m, s ~ PrimState m) => Generator (Gen s) m Source # 
Instance details

Defined in System.Random.PCG.Pure

Methods

uniform1 :: (Word32 -> a) -> Gen s -> m a Source #

uniform2 :: (Word32 -> Word32 -> a) -> Gen s -> m a Source #

uniform1B :: Integral a => (Word32 -> a) -> Word32 -> Gen s -> m a Source #

type GenST = Gen Source #

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

Create a Gen from a fixed initial seed.

createSystemRandom :: IO GenIO Source #

Seed with system random number. (/dev/urandom on Unix-like systems and CryptAPI on Windows).

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

Initialize a generator a single word.

>>> Pure.initialize 0 0 >>= Pure.save
SetSeq 6364136223846793006 1

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

Seed with system random number. (/dev/urandom on Unix-like systems and CryptAPI on Windows).

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.

Instances

Instances details
Variate Bool Source # 
Instance details

Defined in System.Random.PCG.Class

Methods

uniform :: Generator g m => g -> m Bool Source #

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

uniformB :: Generator g m => Bool -> g -> m Bool Source #

Variate Double Source # 
Instance details

Defined in System.Random.PCG.Class

Methods

uniform :: Generator g m => g -> m Double Source #

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

uniformB :: Generator g m => Double -> g -> m Double Source #

Variate Float Source # 
Instance details

Defined in System.Random.PCG.Class

Methods

uniform :: Generator g m => g -> m Float Source #

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

uniformB :: Generator g m => Float -> g -> m Float Source #

Variate Int Source # 
Instance details

Defined in System.Random.PCG.Class

Methods

uniform :: Generator g m => g -> m Int Source #

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

uniformB :: Generator g m => Int -> g -> m Int Source #

Variate Int8 Source # 
Instance details

Defined in System.Random.PCG.Class

Methods

uniform :: Generator g m => g -> m Int8 Source #

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

uniformB :: Generator g m => Int8 -> g -> m Int8 Source #

Variate Int16 Source # 
Instance details

Defined in System.Random.PCG.Class

Methods

uniform :: Generator g m => g -> m Int16 Source #

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

uniformB :: Generator g m => Int16 -> g -> m Int16 Source #

Variate Int32 Source # 
Instance details

Defined in System.Random.PCG.Class

Methods

uniform :: Generator g m => g -> m Int32 Source #

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

uniformB :: Generator g m => Int32 -> g -> m Int32 Source #

Variate Int64 Source # 
Instance details

Defined in System.Random.PCG.Class

Methods

uniform :: Generator g m => g -> m Int64 Source #

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

uniformB :: Generator g m => Int64 -> g -> m Int64 Source #

Variate Word Source # 
Instance details

Defined in System.Random.PCG.Class

Methods

uniform :: Generator g m => g -> m Word Source #

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

uniformB :: Generator g m => Word -> g -> m Word Source #

Variate Word8 Source # 
Instance details

Defined in System.Random.PCG.Class

Methods

uniform :: Generator g m => g -> m Word8 Source #

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

uniformB :: Generator g m => Word8 -> g -> m Word8 Source #

Variate Word16 Source # 
Instance details

Defined in System.Random.PCG.Class

Methods

uniform :: Generator g m => g -> m Word16 Source #

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

uniformB :: Generator g m => Word16 -> g -> m Word16 Source #

Variate Word32 Source # 
Instance details

Defined in System.Random.PCG.Class

Methods

uniform :: Generator g m => g -> m Word32 Source #

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

uniformB :: Generator g m => Word32 -> g -> m Word32 Source #

Variate Word64 Source # 
Instance details

Defined in System.Random.PCG.Class

Methods

uniform :: Generator g m => g -> m Word64 Source #

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

uniformB :: Generator g m => Word64 -> g -> m Word64 Source #

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

Defined in System.Random.PCG.Class

Methods

uniform :: Generator g m => g -> m (a, b) Source #

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

uniformB :: Generator g m => (a, b) -> g -> m (a, b) Source #

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

Defined in System.Random.PCG.Class

Methods

uniform :: Generator g m => g -> m (a, b, c) Source #

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

uniformB :: Generator g m => (a, b, c) -> g -> m (a, b, c) Source #

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

Defined in System.Random.PCG.Class

Methods

uniform :: Generator g m => g -> m (a, b, c, d) Source #

uniformR :: Generator g m => ((a, b, c, d), (a, b, c, d)) -> g -> m (a, b, c, d) Source #

uniformB :: Generator g m => (a, b, c, d) -> g -> m (a, b, c, d) Source #

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

Advance the given generator n steps in log(n) time. (Note that a "step" is a single random 32-bit (or less) Variate. Data types such as Double or Word64 require two "steps".)

>>> Pure.create >>= \g -> replicateM_ 1000 (uniformW32 g) >> uniformW32 g
3640764222
>>> Pure.create >>= \g -> replicateM_ 500 (uniformD g) >> uniformW32 g
3640764222
>>> Pure.create >>= \g -> Pure.advance 1000 g >> uniformW32 g
3640764222

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

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

>>> Pure.create >>= \g -> replicateM 3 (uniformW32 g)
[355248013,41705475,3406281715]
>>> Pure.create >>= \g -> Pure.retract 1 g >> replicateM 3 (uniformW32 g)
[19683962,355248013,41705475]

Seeds

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

Save the state of a Gen in a Seed.

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

Restore a Gen from a Seed.

seed :: SetSeq Source #

Fixed seed.

initFrozen :: Word64 -> Word64 -> SetSeq Source #

Create a new generator from two words.

>>> Pure.initFrozen 0 0
SetSeq 6364136223846793006 1

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 #

Pure

data SetSeq Source #

The multiple sequence varient of the pcg random number generator.

Instances

Instances details
Eq SetSeq Source # 
Instance details

Defined in System.Random.PCG.Pure

Methods

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

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

Data SetSeq Source # 
Instance details

Defined in System.Random.PCG.Pure

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> SetSeq -> c SetSeq #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c SetSeq #

toConstr :: SetSeq -> Constr #

dataTypeOf :: SetSeq -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c SetSeq) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c SetSeq) #

gmapT :: (forall b. Data b => b -> b) -> SetSeq -> SetSeq #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> SetSeq -> r #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> SetSeq -> r #

gmapQ :: (forall d. Data d => d -> u) -> SetSeq -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> SetSeq -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> SetSeq -> m SetSeq #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> SetSeq -> m SetSeq #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> SetSeq -> m SetSeq #

Ord SetSeq Source # 
Instance details

Defined in System.Random.PCG.Pure

Show SetSeq Source # 
Instance details

Defined in System.Random.PCG.Pure

Generic SetSeq Source # 
Instance details

Defined in System.Random.PCG.Pure

Associated Types

type Rep SetSeq :: Type -> Type #

Methods

from :: SetSeq -> Rep SetSeq x #

to :: Rep SetSeq x -> SetSeq #

Storable SetSeq Source # 
Instance details

Defined in System.Random.PCG.Pure

RandomGen FrozenGen Source # 
Instance details

Defined in System.Random.PCG.Pure

type Rep SetSeq Source # 
Instance details

Defined in System.Random.PCG.Pure

type Rep SetSeq = D1 ('MetaData "SetSeq" "System.Random.PCG.Pure" "pcg-random-0.1.3.7-DaQwXu1Wgdb4qv3RWR9wAF" 'False) (C1 ('MetaCons "SetSeq" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'SourceUnpack 'SourceStrict 'DecidedStrict) (Rec0 Word64) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'SourceUnpack 'SourceStrict 'DecidedStrict) (Rec0 Word64)))

next' :: SetSeq -> (Word32, SetSeq) Source #

Version of next that returns a Word32.