random-1.3.0: Pseudo-random number generation
Copyright(c) The University of Glasgow 2001
LicenseBSD-style (see the file LICENSE in the 'random' repository)
Maintainerlibraries@haskell.org
Stabilitystable
Safe HaskellTrustworthy
LanguageHaskell2010

System.Random

Description

This library deals with the common task of pseudo-random number generation.

Synopsis

Introduction

This module provides type classes and instances for the following concepts:

Pure pseudo-random number generators
RandomGen is an interface to pure pseudo-random number generators.

StdGen, the standard pseudo-random number generator provided in this library, is an instance of RandomGen. It uses the SplitMix implementation provided by the splitmix package. Programmers may, of course, supply their own instances of RandomGen.

Usage

In pure code, use uniform and uniformR to generate pseudo-random values with a pure pseudo-random number generator like StdGen.

>>> :{
let rolls :: RandomGen g => Int -> g -> [Word]
    rolls n = fst . uniformListR n (1, 6)
    pureGen = mkStdGen 137
in
    rolls 10 pureGen :: [Word]
:}
[4,2,6,1,6,6,5,1,1,5]

To run use a monadic pseudo-random computation in pure code with a pure pseudo-random number generator, use runStateGen and its variants.

>>> :{
let rollsM :: StatefulGen g m => Int -> g -> m [Word]
    rollsM n = uniformListRM n (1, 6)
    pureGen = mkStdGen 137
in
    runStateGen_ pureGen (rollsM 10) :: [Word]
:}
[4,2,6,1,6,6,5,1,1,5]

Pure number generator interface

Pseudo-random number generators come in two flavours: pure and monadic.

RandomGen: pure pseudo-random number generators
These generators produce a new pseudo-random value together with a new instance of the pseudo-random number generator.

Pure pseudo-random number generators should implement split if they are splittable, that is, if there is an efficient method to turn one generator into two. The pseudo-random numbers produced by the two resulting generators should not be correlated. See [1] for some background on splittable pseudo-random generators.

StatefulGen: monadic pseudo-random number generators
See System.Random.Stateful module

class RandomGen g where Source #

RandomGen is an interface to pure pseudo-random number generators.

StdGen is the standard RandomGen instance provided by this library.

Since: 1.0.0

Minimal complete definition

(genWord32 | genWord64 | next, genRange)

Methods

genWord8 :: g -> (Word8, g) Source #

Returns a Word8 that is uniformly distributed over the entire Word8 range.

Since: 1.2.0

genWord16 :: g -> (Word16, g) Source #

Returns a Word16 that is uniformly distributed over the entire Word16 range.

Since: 1.2.0

genWord32 :: g -> (Word32, g) Source #

Returns a Word32 that is uniformly distributed over the entire Word32 range.

Since: 1.2.0

genWord64 :: g -> (Word64, g) Source #

Returns a Word64 that is uniformly distributed over the entire Word64 range.

Since: 1.2.0

genWord32R :: Word32 -> g -> (Word32, g) Source #

genWord32R upperBound g returns a Word32 that is uniformly distributed over the range [0, upperBound].

Since: 1.2.0

genWord64R :: Word64 -> g -> (Word64, g) Source #

genWord64R upperBound g returns a Word64 that is uniformly distributed over the range [0, upperBound].

Since: 1.2.0

unsafeUniformFillMutableByteArray Source #

Arguments

:: MutableByteArray s

Mutable array to fill with random bytes

-> Int

Offset into a mutable array from the beginning in number of bytes. Offset must be non-negative, but this will not be checked

-> Int

Number of randomly generated bytes to write into the array. Number of bytes must be non-negative and less then the total size of the array, minus the offset. This also will be checked.

-> g 
-> ST s g 

Fill in the supplied MutableByteArray with uniformly generated random bytes. This function is unsafe because it is not required to do any bounds checking. For a safe variant use uniformFillMutableByteArrayM instead.

Default type class implementation uses defaultUnsafeUniformFillMutableByteArray.

Since: 1.3.0

split :: g -> (g, g) Source #

Deprecated: In favor of splitGen

Returns two distinct pseudo-random number generators.

Implementations should take care to ensure that the resulting generators are not correlated. Some pseudo-random number generators are not splittable. In that case, the split implementation should fail with a descriptive error message.

Since: 1.0.0

default split :: SplitGen g => g -> (g, g) Source #

Instances

Instances details
RandomGen StdGen Source # 
Instance details

Defined in System.Random.Internal

RandomGen SMGen Source # 
Instance details

Defined in System.Random.Internal

RandomGen SMGen Source # 
Instance details

Defined in System.Random.Internal

RandomGen g => RandomGen (StateGen g) Source # 
Instance details

Defined in System.Random.Internal

RandomGen g => RandomGen (AtomicGen g) Source # 
Instance details

Defined in System.Random.Stateful

RandomGen g => RandomGen (IOGen g) Source # 
Instance details

Defined in System.Random.Stateful

RandomGen g => RandomGen (STGen g) Source # 
Instance details

Defined in System.Random.Stateful

RandomGen g => RandomGen (TGen g) Source # 
Instance details

Defined in System.Random.Stateful

class RandomGen g => SplitGen g where Source #

Pseudo-random generators that can be split into two separate and independent psuedo-random generators should provide an instance for this type class.

Historically this functionality was included in the RandomGen type class in the split function, however, few pseudo-random generators possess this property of splittability. This lead the old split function being usually implemented in terms of error.

Since: 1.3.0

Methods

splitGen :: g -> (g, g) Source #

Returns two distinct pseudo-random number generators.

Implementations should take care to ensure that the resulting generators are not correlated.

Since: 1.3.0

Instances

Instances details
SplitGen StdGen Source # 
Instance details

Defined in System.Random.Internal

SplitGen SMGen Source # 
Instance details

Defined in System.Random.Internal

Methods

splitGen :: SMGen -> (SMGen, SMGen) Source #

SplitGen SMGen Source # 
Instance details

Defined in System.Random.Internal

Methods

splitGen :: SMGen -> (SMGen, SMGen) Source #

SplitGen g => SplitGen (AtomicGen g) Source # 
Instance details

Defined in System.Random.Stateful

SplitGen g => SplitGen (IOGen g) Source # 
Instance details

Defined in System.Random.Stateful

Methods

splitGen :: IOGen g -> (IOGen g, IOGen g) Source #

SplitGen g => SplitGen (STGen g) Source # 
Instance details

Defined in System.Random.Stateful

Methods

splitGen :: STGen g -> (STGen g, STGen g) Source #

SplitGen g => SplitGen (TGen g) Source # 
Instance details

Defined in System.Random.Stateful

Methods

splitGen :: TGen g -> (TGen g, TGen g) Source #

uniform :: (Uniform a, RandomGen g) => g -> (a, g) Source #

Generates a value uniformly distributed over all possible values of that type.

This is a pure version of uniformM.

Examples

Expand
>>> import System.Random
>>> let pureGen = mkStdGen 137
>>> uniform pureGen :: (Bool, StdGen)
(True,StdGen {unStdGen = SMGen 11285859549637045894 7641485672361121627})

You can use type applications to disambiguate the type of the generated numbers:

>>> :seti -XTypeApplications
>>> uniform @Bool pureGen
(True,StdGen {unStdGen = SMGen 11285859549637045894 7641485672361121627})

Since: 1.2.0

uniformR :: (UniformRange a, RandomGen g) => (a, a) -> g -> (a, g) Source #

Generates a value uniformly distributed over the provided range, which is interpreted as inclusive in the lower and upper bound.

  • uniformR (1 :: Int, 4 :: Int) generates values uniformly from the set \(\{1,2,3,4\}\)
  • uniformR (1 :: Float, 4 :: Float) generates values uniformly from the set \(\{x\;|\;1 \le x \le 4\}\)

The following law should hold to make the function always defined:

uniformR (a, b) = uniformR (b, a)

This is a pure version of uniformRM.

Examples

Expand
>>> import System.Random
>>> let pureGen = mkStdGen 137
>>> uniformR (1 :: Int, 4 :: Int) pureGen
(4,StdGen {unStdGen = SMGen 11285859549637045894 7641485672361121627})

You can use type applications to disambiguate the type of the generated numbers:

>>> :seti -XTypeApplications
>>> uniformR @Int (1, 4) pureGen
(4,StdGen {unStdGen = SMGen 11285859549637045894 7641485672361121627})

Since: 1.2.0

class Random a where Source #

The class of types for which random values can be generated. Most instances of Random will produce values that are uniformly distributed on the full range, but for those types without a well-defined "full range" some sensible default subrange will be selected.

Random exists primarily for backwards compatibility with version 1.1 of this library. In new code, use the better specified Uniform and UniformRange instead.

Since: 1.0.0

Minimal complete definition

Nothing

Methods

randomR :: RandomGen g => (a, a) -> g -> (a, g) Source #

Takes a range (lo,hi) and a pseudo-random number generator g, and returns a pseudo-random value uniformly distributed over the closed interval [lo,hi], together with a new generator. It is unspecified what happens if lo>hi, but usually the values will simply get swapped.

>>> let gen = mkStdGen 26
>>> fst $ randomR ('a', 'z') gen
'z'
>>> fst $ randomR ('a', 'z') gen
'z'

For continuous types there is no requirement that the values lo and hi are ever produced, but they may be, depending on the implementation and the interval.

There is no requirement to follow the Ord instance and the concept of range can be defined on per type basis. For example product types will treat their values independently:

>>> fst $ randomR (('a', 5.0), ('z', 10.0)) $ mkStdGen 26
('z',5.22694980853051)

In case when a lawful range is desired uniformR should be used instead.

Since: 1.0.0

default randomR :: (RandomGen g, UniformRange a) => (a, a) -> g -> (a, g) Source #

random :: RandomGen g => g -> (a, g) Source #

The same as randomR, but using a default range determined by the type:

  • For bounded types (instances of Bounded, such as Char), the range is normally the whole type.
  • For floating point types, the range is normally the closed interval [0,1].
  • For Integer, the range is (arbitrarily) the range of Int.

Since: 1.0.0

default random :: (RandomGen g, Uniform a) => g -> (a, g) Source #

randomRs :: RandomGen g => (a, a) -> g -> [a] Source #

Plural variant of randomR, producing an infinite list of pseudo-random values instead of returning a new generator.

Since: 1.0.0

randoms :: RandomGen g => g -> [a] Source #

Plural variant of random, producing an infinite list of pseudo-random values instead of returning a new generator.

Since: 1.0.0

Instances

Instances details
Random CBool Source # 
Instance details

Defined in System.Random

Methods

randomR :: RandomGen g => (CBool, CBool) -> g -> (CBool, g) Source #

random :: RandomGen g => g -> (CBool, g) Source #

randomRs :: RandomGen g => (CBool, CBool) -> g -> [CBool] Source #

randoms :: RandomGen g => g -> [CBool] Source #

Random CChar Source # 
Instance details

Defined in System.Random

Methods

randomR :: RandomGen g => (CChar, CChar) -> g -> (CChar, g) Source #

random :: RandomGen g => g -> (CChar, g) Source #

randomRs :: RandomGen g => (CChar, CChar) -> g -> [CChar] Source #

randoms :: RandomGen g => g -> [CChar] Source #

Random CDouble Source #

Note - random produces values in the closed range [0,1].

Instance details

Defined in System.Random

Methods

randomR :: RandomGen g => (CDouble, CDouble) -> g -> (CDouble, g) Source #

random :: RandomGen g => g -> (CDouble, g) Source #

randomRs :: RandomGen g => (CDouble, CDouble) -> g -> [CDouble] Source #

randoms :: RandomGen g => g -> [CDouble] Source #

Random CFloat Source #

Note - random produces values in the closed range [0,1].

Instance details

Defined in System.Random

Methods

randomR :: RandomGen g => (CFloat, CFloat) -> g -> (CFloat, g) Source #

random :: RandomGen g => g -> (CFloat, g) Source #

randomRs :: RandomGen g => (CFloat, CFloat) -> g -> [CFloat] Source #

randoms :: RandomGen g => g -> [CFloat] Source #

Random CInt Source # 
Instance details

Defined in System.Random

Methods

randomR :: RandomGen g => (CInt, CInt) -> g -> (CInt, g) Source #

random :: RandomGen g => g -> (CInt, g) Source #

randomRs :: RandomGen g => (CInt, CInt) -> g -> [CInt] Source #

randoms :: RandomGen g => g -> [CInt] Source #

Random CIntMax Source # 
Instance details

Defined in System.Random

Methods

randomR :: RandomGen g => (CIntMax, CIntMax) -> g -> (CIntMax, g) Source #

random :: RandomGen g => g -> (CIntMax, g) Source #

randomRs :: RandomGen g => (CIntMax, CIntMax) -> g -> [CIntMax] Source #

randoms :: RandomGen g => g -> [CIntMax] Source #

Random CIntPtr Source # 
Instance details

Defined in System.Random

Methods

randomR :: RandomGen g => (CIntPtr, CIntPtr) -> g -> (CIntPtr, g) Source #

random :: RandomGen g => g -> (CIntPtr, g) Source #

randomRs :: RandomGen g => (CIntPtr, CIntPtr) -> g -> [CIntPtr] Source #

randoms :: RandomGen g => g -> [CIntPtr] Source #

Random CLLong Source # 
Instance details

Defined in System.Random

Methods

randomR :: RandomGen g => (CLLong, CLLong) -> g -> (CLLong, g) Source #

random :: RandomGen g => g -> (CLLong, g) Source #

randomRs :: RandomGen g => (CLLong, CLLong) -> g -> [CLLong] Source #

randoms :: RandomGen g => g -> [CLLong] Source #

Random CLong Source # 
Instance details

Defined in System.Random

Methods

randomR :: RandomGen g => (CLong, CLong) -> g -> (CLong, g) Source #

random :: RandomGen g => g -> (CLong, g) Source #

randomRs :: RandomGen g => (CLong, CLong) -> g -> [CLong] Source #

randoms :: RandomGen g => g -> [CLong] Source #

Random CPtrdiff Source # 
Instance details

Defined in System.Random

Methods

randomR :: RandomGen g => (CPtrdiff, CPtrdiff) -> g -> (CPtrdiff, g) Source #

random :: RandomGen g => g -> (CPtrdiff, g) Source #

randomRs :: RandomGen g => (CPtrdiff, CPtrdiff) -> g -> [CPtrdiff] Source #

randoms :: RandomGen g => g -> [CPtrdiff] Source #

Random CSChar Source # 
Instance details

Defined in System.Random

Methods

randomR :: RandomGen g => (CSChar, CSChar) -> g -> (CSChar, g) Source #

random :: RandomGen g => g -> (CSChar, g) Source #

randomRs :: RandomGen g => (CSChar, CSChar) -> g -> [CSChar] Source #

randoms :: RandomGen g => g -> [CSChar] Source #

Random CShort Source # 
Instance details

Defined in System.Random

Methods

randomR :: RandomGen g => (CShort, CShort) -> g -> (CShort, g) Source #

random :: RandomGen g => g -> (CShort, g) Source #

randomRs :: RandomGen g => (CShort, CShort) -> g -> [CShort] Source #

randoms :: RandomGen g => g -> [CShort] Source #

Random CSigAtomic Source # 
Instance details

Defined in System.Random

Random CSize Source # 
Instance details

Defined in System.Random

Methods

randomR :: RandomGen g => (CSize, CSize) -> g -> (CSize, g) Source #

random :: RandomGen g => g -> (CSize, g) Source #

randomRs :: RandomGen g => (CSize, CSize) -> g -> [CSize] Source #

randoms :: RandomGen g => g -> [CSize] Source #

Random CUChar Source # 
Instance details

Defined in System.Random

Methods

randomR :: RandomGen g => (CUChar, CUChar) -> g -> (CUChar, g) Source #

random :: RandomGen g => g -> (CUChar, g) Source #

randomRs :: RandomGen g => (CUChar, CUChar) -> g -> [CUChar] Source #

randoms :: RandomGen g => g -> [CUChar] Source #

Random CUInt Source # 
Instance details

Defined in System.Random

Methods

randomR :: RandomGen g => (CUInt, CUInt) -> g -> (CUInt, g) Source #

random :: RandomGen g => g -> (CUInt, g) Source #

randomRs :: RandomGen g => (CUInt, CUInt) -> g -> [CUInt] Source #

randoms :: RandomGen g => g -> [CUInt] Source #

Random CUIntMax Source # 
Instance details

Defined in System.Random

Methods

randomR :: RandomGen g => (CUIntMax, CUIntMax) -> g -> (CUIntMax, g) Source #

random :: RandomGen g => g -> (CUIntMax, g) Source #

randomRs :: RandomGen g => (CUIntMax, CUIntMax) -> g -> [CUIntMax] Source #

randoms :: RandomGen g => g -> [CUIntMax] Source #

Random CUIntPtr Source # 
Instance details

Defined in System.Random

Methods

randomR :: RandomGen g => (CUIntPtr, CUIntPtr) -> g -> (CUIntPtr, g) Source #

random :: RandomGen g => g -> (CUIntPtr, g) Source #

randomRs :: RandomGen g => (CUIntPtr, CUIntPtr) -> g -> [CUIntPtr] Source #

randoms :: RandomGen g => g -> [CUIntPtr] Source #

Random CULLong Source # 
Instance details

Defined in System.Random

Methods

randomR :: RandomGen g => (CULLong, CULLong) -> g -> (CULLong, g) Source #

random :: RandomGen g => g -> (CULLong, g) Source #

randomRs :: RandomGen g => (CULLong, CULLong) -> g -> [CULLong] Source #

randoms :: RandomGen g => g -> [CULLong] Source #

Random CULong Source # 
Instance details

Defined in System.Random

Methods

randomR :: RandomGen g => (CULong, CULong) -> g -> (CULong, g) Source #

random :: RandomGen g => g -> (CULong, g) Source #

randomRs :: RandomGen g => (CULong, CULong) -> g -> [CULong] Source #

randoms :: RandomGen g => g -> [CULong] Source #

Random CUShort Source # 
Instance details

Defined in System.Random

Methods

randomR :: RandomGen g => (CUShort, CUShort) -> g -> (CUShort, g) Source #

random :: RandomGen g => g -> (CUShort, g) Source #

randomRs :: RandomGen g => (CUShort, CUShort) -> g -> [CUShort] Source #

randoms :: RandomGen g => g -> [CUShort] Source #

Random CWchar Source # 
Instance details

Defined in System.Random

Methods

randomR :: RandomGen g => (CWchar, CWchar) -> g -> (CWchar, g) Source #

random :: RandomGen g => g -> (CWchar, g) Source #

randomRs :: RandomGen g => (CWchar, CWchar) -> g -> [CWchar] Source #

randoms :: RandomGen g => g -> [CWchar] Source #

Random Int16 Source # 
Instance details

Defined in System.Random

Methods

randomR :: RandomGen g => (Int16, Int16) -> g -> (Int16, g) Source #

random :: RandomGen g => g -> (Int16, g) Source #

randomRs :: RandomGen g => (Int16, Int16) -> g -> [Int16] Source #

randoms :: RandomGen g => g -> [Int16] Source #

Random Int32 Source # 
Instance details

Defined in System.Random

Methods

randomR :: RandomGen g => (Int32, Int32) -> g -> (Int32, g) Source #

random :: RandomGen g => g -> (Int32, g) Source #

randomRs :: RandomGen g => (Int32, Int32) -> g -> [Int32] Source #

randoms :: RandomGen g => g -> [Int32] Source #

Random Int64 Source # 
Instance details

Defined in System.Random

Methods

randomR :: RandomGen g => (Int64, Int64) -> g -> (Int64, g) Source #

random :: RandomGen g => g -> (Int64, g) Source #

randomRs :: RandomGen g => (Int64, Int64) -> g -> [Int64] Source #

randoms :: RandomGen g => g -> [Int64] Source #

Random Int8 Source # 
Instance details

Defined in System.Random

Methods

randomR :: RandomGen g => (Int8, Int8) -> g -> (Int8, g) Source #

random :: RandomGen g => g -> (Int8, g) Source #

randomRs :: RandomGen g => (Int8, Int8) -> g -> [Int8] Source #

randoms :: RandomGen g => g -> [Int8] Source #

Random Word16 Source # 
Instance details

Defined in System.Random

Methods

randomR :: RandomGen g => (Word16, Word16) -> g -> (Word16, g) Source #

random :: RandomGen g => g -> (Word16, g) Source #

randomRs :: RandomGen g => (Word16, Word16) -> g -> [Word16] Source #

randoms :: RandomGen g => g -> [Word16] Source #

Random Word32 Source # 
Instance details

Defined in System.Random

Methods

randomR :: RandomGen g => (Word32, Word32) -> g -> (Word32, g) Source #

random :: RandomGen g => g -> (Word32, g) Source #

randomRs :: RandomGen g => (Word32, Word32) -> g -> [Word32] Source #

randoms :: RandomGen g => g -> [Word32] Source #

Random Word64 Source # 
Instance details

Defined in System.Random

Methods

randomR :: RandomGen g => (Word64, Word64) -> g -> (Word64, g) Source #

random :: RandomGen g => g -> (Word64, g) Source #

randomRs :: RandomGen g => (Word64, Word64) -> g -> [Word64] Source #

randoms :: RandomGen g => g -> [Word64] Source #

Random Word8 Source # 
Instance details

Defined in System.Random

Methods

randomR :: RandomGen g => (Word8, Word8) -> g -> (Word8, g) Source #

random :: RandomGen g => g -> (Word8, g) Source #

randomRs :: RandomGen g => (Word8, Word8) -> g -> [Word8] Source #

randoms :: RandomGen g => g -> [Word8] Source #

Random Integer Source #

Note - random generates values in the Int range

Instance details

Defined in System.Random

Methods

randomR :: RandomGen g => (Integer, Integer) -> g -> (Integer, g) Source #

random :: RandomGen g => g -> (Integer, g) Source #

randomRs :: RandomGen g => (Integer, Integer) -> g -> [Integer] Source #

randoms :: RandomGen g => g -> [Integer] Source #

Random Bool Source # 
Instance details

Defined in System.Random

Methods

randomR :: RandomGen g => (Bool, Bool) -> g -> (Bool, g) Source #

random :: RandomGen g => g -> (Bool, g) Source #

randomRs :: RandomGen g => (Bool, Bool) -> g -> [Bool] Source #

randoms :: RandomGen g => g -> [Bool] Source #

Random Char Source # 
Instance details

Defined in System.Random

Methods

randomR :: RandomGen g => (Char, Char) -> g -> (Char, g) Source #

random :: RandomGen g => g -> (Char, g) Source #

randomRs :: RandomGen g => (Char, Char) -> g -> [Char] Source #

randoms :: RandomGen g => g -> [Char] Source #

Random Double Source #

Note - random produces values in the closed range [0,1].

Instance details

Defined in System.Random

Methods

randomR :: RandomGen g => (Double, Double) -> g -> (Double, g) Source #

random :: RandomGen g => g -> (Double, g) Source #

randomRs :: RandomGen g => (Double, Double) -> g -> [Double] Source #

randoms :: RandomGen g => g -> [Double] Source #

Random Float Source #

Note - random produces values in the closed range [0,1].

Instance details

Defined in System.Random

Methods

randomR :: RandomGen g => (Float, Float) -> g -> (Float, g) Source #

random :: RandomGen g => g -> (Float, g) Source #

randomRs :: RandomGen g => (Float, Float) -> g -> [Float] Source #

randoms :: RandomGen g => g -> [Float] Source #

Random Int Source # 
Instance details

Defined in System.Random

Methods

randomR :: RandomGen g => (Int, Int) -> g -> (Int, g) Source #

random :: RandomGen g => g -> (Int, g) Source #

randomRs :: RandomGen g => (Int, Int) -> g -> [Int] Source #

randoms :: RandomGen g => g -> [Int] Source #

Random Word Source # 
Instance details

Defined in System.Random

Methods

randomR :: RandomGen g => (Word, Word) -> g -> (Word, g) Source #

random :: RandomGen g => g -> (Word, g) Source #

randomRs :: RandomGen g => (Word, Word) -> g -> [Word] Source #

randoms :: RandomGen g => g -> [Word] Source #

(Random a, Random b) => Random (a, b) Source #

Note - randomR treats a and b types independently

Instance details

Defined in System.Random

Methods

randomR :: RandomGen g => ((a, b), (a, b)) -> g -> ((a, b), g) Source #

random :: RandomGen g => g -> ((a, b), g) Source #

randomRs :: RandomGen g => ((a, b), (a, b)) -> g -> [(a, b)] Source #

randoms :: RandomGen g => g -> [(a, b)] Source #

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

Note - randomR treats a, b and c types independently

Instance details

Defined in System.Random

Methods

randomR :: RandomGen g => ((a, b, c), (a, b, c)) -> g -> ((a, b, c), g) Source #

random :: RandomGen g => g -> ((a, b, c), g) Source #

randomRs :: RandomGen g => ((a, b, c), (a, b, c)) -> g -> [(a, b, c)] Source #

randoms :: RandomGen g => g -> [(a, b, c)] Source #

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

Note - randomR treats a, b, c and d types independently

Instance details

Defined in System.Random

Methods

randomR :: RandomGen g => ((a, b, c, d), (a, b, c, d)) -> g -> ((a, b, c, d), g) Source #

random :: RandomGen g => g -> ((a, b, c, d), g) Source #

randomRs :: RandomGen g => ((a, b, c, d), (a, b, c, d)) -> g -> [(a, b, c, d)] Source #

randoms :: RandomGen g => g -> [(a, b, c, d)] Source #

(Random a, Random b, Random c, Random d, Random e) => Random (a, b, c, d, e) Source #

Note - randomR treats a, b, c, d and e types independently

Instance details

Defined in System.Random

Methods

randomR :: RandomGen g => ((a, b, c, d, e), (a, b, c, d, e)) -> g -> ((a, b, c, d, e), g) Source #

random :: RandomGen g => g -> ((a, b, c, d, e), g) Source #

randomRs :: RandomGen g => ((a, b, c, d, e), (a, b, c, d, e)) -> g -> [(a, b, c, d, e)] Source #

randoms :: RandomGen g => g -> [(a, b, c, d, e)] Source #

(Random a, Random b, Random c, Random d, Random e, Random f) => Random (a, b, c, d, e, f) Source #

Note - randomR treats a, b, c, d, e and f types independently

Instance details

Defined in System.Random

Methods

randomR :: RandomGen g => ((a, b, c, d, e, f), (a, b, c, d, e, f)) -> g -> ((a, b, c, d, e, f), g) Source #

random :: RandomGen g => g -> ((a, b, c, d, e, f), g) Source #

randomRs :: RandomGen g => ((a, b, c, d, e, f), (a, b, c, d, e, f)) -> g -> [(a, b, c, d, e, f)] Source #

randoms :: RandomGen g => g -> [(a, b, c, d, e, f)] Source #

(Random a, Random b, Random c, Random d, Random e, Random f, Random g) => Random (a, b, c, d, e, f, g) Source #

Note - randomR treats a, b, c, d, e, f and g types independently

Instance details

Defined in System.Random

Methods

randomR :: RandomGen g0 => ((a, b, c, d, e, f, g), (a, b, c, d, e, f, g)) -> g0 -> ((a, b, c, d, e, f, g), g0) Source #

random :: RandomGen g0 => g0 -> ((a, b, c, d, e, f, g), g0) Source #

randomRs :: RandomGen g0 => ((a, b, c, d, e, f, g), (a, b, c, d, e, f, g)) -> g0 -> [(a, b, c, d, e, f, g)] Source #

randoms :: RandomGen g0 => g0 -> [(a, b, c, d, e, f, g)] Source #

class Uniform a Source #

The class of types for which a uniformly distributed value can be drawn from all possible values of the type.

Since: 1.2.0

Instances

Instances details
Uniform CBool Source # 
Instance details

Defined in System.Random.Internal

Methods

uniformM :: StatefulGen g m => g -> m CBool Source #

Uniform CChar Source # 
Instance details

Defined in System.Random.Internal

Methods

uniformM :: StatefulGen g m => g -> m CChar Source #

Uniform CInt Source # 
Instance details

Defined in System.Random.Internal

Methods

uniformM :: StatefulGen g m => g -> m CInt Source #

Uniform CIntMax Source # 
Instance details

Defined in System.Random.Internal

Methods

uniformM :: StatefulGen g m => g -> m CIntMax Source #

Uniform CIntPtr Source # 
Instance details

Defined in System.Random.Internal

Methods

uniformM :: StatefulGen g m => g -> m CIntPtr Source #

Uniform CLLong Source # 
Instance details

Defined in System.Random.Internal

Methods

uniformM :: StatefulGen g m => g -> m CLLong Source #

Uniform CLong Source # 
Instance details

Defined in System.Random.Internal

Methods

uniformM :: StatefulGen g m => g -> m CLong Source #

Uniform CPtrdiff Source # 
Instance details

Defined in System.Random.Internal

Methods

uniformM :: StatefulGen g m => g -> m CPtrdiff Source #

Uniform CSChar Source # 
Instance details

Defined in System.Random.Internal

Methods

uniformM :: StatefulGen g m => g -> m CSChar Source #

Uniform CShort Source # 
Instance details

Defined in System.Random.Internal

Methods

uniformM :: StatefulGen g m => g -> m CShort Source #

Uniform CSigAtomic Source # 
Instance details

Defined in System.Random.Internal

Methods

uniformM :: StatefulGen g m => g -> m CSigAtomic Source #

Uniform CSize Source # 
Instance details

Defined in System.Random.Internal

Methods

uniformM :: StatefulGen g m => g -> m CSize Source #

Uniform CUChar Source # 
Instance details

Defined in System.Random.Internal

Methods

uniformM :: StatefulGen g m => g -> m CUChar Source #

Uniform CUInt Source # 
Instance details

Defined in System.Random.Internal

Methods

uniformM :: StatefulGen g m => g -> m CUInt Source #

Uniform CUIntMax Source # 
Instance details

Defined in System.Random.Internal

Methods

uniformM :: StatefulGen g m => g -> m CUIntMax Source #

Uniform CUIntPtr Source # 
Instance details

Defined in System.Random.Internal

Methods

uniformM :: StatefulGen g m => g -> m CUIntPtr Source #

Uniform CULLong Source # 
Instance details

Defined in System.Random.Internal

Methods

uniformM :: StatefulGen g m => g -> m CULLong Source #

Uniform CULong Source # 
Instance details

Defined in System.Random.Internal

Methods

uniformM :: StatefulGen g m => g -> m CULong Source #

Uniform CUShort Source # 
Instance details

Defined in System.Random.Internal

Methods

uniformM :: StatefulGen g m => g -> m CUShort Source #

Uniform CWchar Source # 
Instance details

Defined in System.Random.Internal

Methods

uniformM :: StatefulGen g m => g -> m CWchar Source #

Uniform Int16 Source # 
Instance details

Defined in System.Random.Internal

Methods

uniformM :: StatefulGen g m => g -> m Int16 Source #

Uniform Int32 Source # 
Instance details

Defined in System.Random.Internal

Methods

uniformM :: StatefulGen g m => g -> m Int32 Source #

Uniform Int64 Source # 
Instance details

Defined in System.Random.Internal

Methods

uniformM :: StatefulGen g m => g -> m Int64 Source #

Uniform Int8 Source # 
Instance details

Defined in System.Random.Internal

Methods

uniformM :: StatefulGen g m => g -> m Int8 Source #

Uniform Word16 Source # 
Instance details

Defined in System.Random.Internal

Methods

uniformM :: StatefulGen g m => g -> m Word16 Source #

Uniform Word32 Source # 
Instance details

Defined in System.Random.Internal

Methods

uniformM :: StatefulGen g m => g -> m Word32 Source #

Uniform Word64 Source # 
Instance details

Defined in System.Random.Internal

Methods

uniformM :: StatefulGen g m => g -> m Word64 Source #

Uniform Word8 Source # 
Instance details

Defined in System.Random.Internal

Methods

uniformM :: StatefulGen g m => g -> m Word8 Source #

Uniform () Source # 
Instance details

Defined in System.Random.Internal

Methods

uniformM :: StatefulGen g m => g -> m () Source #

Uniform Bool Source # 
Instance details

Defined in System.Random.Internal

Methods

uniformM :: StatefulGen g m => g -> m Bool Source #

Uniform Char Source # 
Instance details

Defined in System.Random.Internal

Methods

uniformM :: StatefulGen g m => g -> m Char Source #

Uniform Int Source # 
Instance details

Defined in System.Random.Internal

Methods

uniformM :: StatefulGen g m => g -> m Int Source #

Uniform Word Source # 
Instance details

Defined in System.Random.Internal

Methods

uniformM :: StatefulGen g m => g -> m Word Source #

SeedGen g => Uniform (Seed g) Source # 
Instance details

Defined in System.Random.Seed

Methods

uniformM :: StatefulGen g0 m => g0 -> m (Seed g) Source #

(Finite a, Uniform a) => Uniform (Maybe a) Source # 
Instance details

Defined in System.Random.Internal

Methods

uniformM :: StatefulGen g m => g -> m (Maybe a) Source #

(Finite a, Uniform a, Finite b, Uniform b) => Uniform (Either a b) Source # 
Instance details

Defined in System.Random.Internal

Methods

uniformM :: StatefulGen g m => g -> m (Either a b) Source #

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

Defined in System.Random.Internal

Methods

uniformM :: StatefulGen g m => g -> m (a, b) Source #

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

Defined in System.Random.Internal

Methods

uniformM :: StatefulGen g m => g -> m (a, b, c) Source #

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

Defined in System.Random.Internal

Methods

uniformM :: StatefulGen g m => g -> m (a, b, c, d) Source #

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

Defined in System.Random.Internal

Methods

uniformM :: StatefulGen g m => g -> m (a, b, c, d, e) Source #

(Uniform a, Uniform b, Uniform c, Uniform d, Uniform e, Uniform f) => Uniform (a, b, c, d, e, f) Source # 
Instance details

Defined in System.Random.Internal

Methods

uniformM :: StatefulGen g m => g -> m (a, b, c, d, e, f) Source #

(Uniform a, Uniform b, Uniform c, Uniform d, Uniform e, Uniform f, Uniform g) => Uniform (a, b, c, d, e, f, g) Source # 
Instance details

Defined in System.Random.Internal

Methods

uniformM :: StatefulGen g0 m => g0 -> m (a, b, c, d, e, f, g) Source #

class UniformRange a Source #

The class of types for which a uniformly distributed value can be drawn from a range.

Since: 1.2.0

Instances

Instances details
UniformRange CBool Source # 
Instance details

Defined in System.Random.Internal

Methods

uniformRM :: StatefulGen g m => (CBool, CBool) -> g -> m CBool Source #

isInRange :: (CBool, CBool) -> CBool -> Bool Source #

UniformRange CChar Source # 
Instance details

Defined in System.Random.Internal

Methods

uniformRM :: StatefulGen g m => (CChar, CChar) -> g -> m CChar Source #

isInRange :: (CChar, CChar) -> CChar -> Bool Source #

UniformRange CDouble Source #

See Floating point number caveats.

Instance details

Defined in System.Random.Internal

UniformRange CFloat Source #

See Floating point number caveats.

Instance details

Defined in System.Random.Internal

UniformRange CInt Source # 
Instance details

Defined in System.Random.Internal

Methods

uniformRM :: StatefulGen g m => (CInt, CInt) -> g -> m CInt Source #

isInRange :: (CInt, CInt) -> CInt -> Bool Source #

UniformRange CIntMax Source # 
Instance details

Defined in System.Random.Internal

UniformRange CIntPtr Source # 
Instance details

Defined in System.Random.Internal

UniformRange CLLong Source # 
Instance details

Defined in System.Random.Internal

UniformRange CLong Source # 
Instance details

Defined in System.Random.Internal

Methods

uniformRM :: StatefulGen g m => (CLong, CLong) -> g -> m CLong Source #

isInRange :: (CLong, CLong) -> CLong -> Bool Source #

UniformRange CPtrdiff Source # 
Instance details

Defined in System.Random.Internal

UniformRange CSChar Source # 
Instance details

Defined in System.Random.Internal

UniformRange CShort Source # 
Instance details

Defined in System.Random.Internal

UniformRange CSigAtomic Source # 
Instance details

Defined in System.Random.Internal

UniformRange CSize Source # 
Instance details

Defined in System.Random.Internal

Methods

uniformRM :: StatefulGen g m => (CSize, CSize) -> g -> m CSize Source #

isInRange :: (CSize, CSize) -> CSize -> Bool Source #

UniformRange CUChar Source # 
Instance details

Defined in System.Random.Internal

UniformRange CUInt Source # 
Instance details

Defined in System.Random.Internal

Methods

uniformRM :: StatefulGen g m => (CUInt, CUInt) -> g -> m CUInt Source #

isInRange :: (CUInt, CUInt) -> CUInt -> Bool Source #

UniformRange CUIntMax Source # 
Instance details

Defined in System.Random.Internal

UniformRange CUIntPtr Source # 
Instance details

Defined in System.Random.Internal

UniformRange CULLong Source # 
Instance details

Defined in System.Random.Internal

UniformRange CULong Source # 
Instance details

Defined in System.Random.Internal

UniformRange CUShort Source # 
Instance details

Defined in System.Random.Internal

UniformRange CWchar Source # 
Instance details

Defined in System.Random.Internal

UniformRange Int16 Source # 
Instance details

Defined in System.Random.Internal

Methods

uniformRM :: StatefulGen g m => (Int16, Int16) -> g -> m Int16 Source #

isInRange :: (Int16, Int16) -> Int16 -> Bool Source #

UniformRange Int32 Source # 
Instance details

Defined in System.Random.Internal

Methods

uniformRM :: StatefulGen g m => (Int32, Int32) -> g -> m Int32 Source #

isInRange :: (Int32, Int32) -> Int32 -> Bool Source #

UniformRange Int64 Source # 
Instance details

Defined in System.Random.Internal

Methods

uniformRM :: StatefulGen g m => (Int64, Int64) -> g -> m Int64 Source #

isInRange :: (Int64, Int64) -> Int64 -> Bool Source #

UniformRange Int8 Source # 
Instance details

Defined in System.Random.Internal

Methods

uniformRM :: StatefulGen g m => (Int8, Int8) -> g -> m Int8 Source #

isInRange :: (Int8, Int8) -> Int8 -> Bool Source #

UniformRange Word16 Source # 
Instance details

Defined in System.Random.Internal

UniformRange Word32 Source # 
Instance details

Defined in System.Random.Internal

UniformRange Word64 Source # 
Instance details

Defined in System.Random.Internal

UniformRange Word8 Source # 
Instance details

Defined in System.Random.Internal

Methods

uniformRM :: StatefulGen g m => (Word8, Word8) -> g -> m Word8 Source #

isInRange :: (Word8, Word8) -> Word8 -> Bool Source #

UniformRange Integer Source # 
Instance details

Defined in System.Random.Internal

UniformRange Natural Source # 
Instance details

Defined in System.Random.Internal

UniformRange () Source # 
Instance details

Defined in System.Random.Internal

Methods

uniformRM :: StatefulGen g m => ((), ()) -> g -> m () Source #

isInRange :: ((), ()) -> () -> Bool Source #

UniformRange Bool Source # 
Instance details

Defined in System.Random.Internal

Methods

uniformRM :: StatefulGen g m => (Bool, Bool) -> g -> m Bool Source #

isInRange :: (Bool, Bool) -> Bool -> Bool Source #

UniformRange Char Source # 
Instance details

Defined in System.Random.Internal

Methods

uniformRM :: StatefulGen g m => (Char, Char) -> g -> m Char Source #

isInRange :: (Char, Char) -> Char -> Bool Source #

UniformRange Double Source #

See Floating point number caveats.

Instance details

Defined in System.Random.Internal

UniformRange Float Source #

See Floating point number caveats.

Instance details

Defined in System.Random.Internal

Methods

uniformRM :: StatefulGen g m => (Float, Float) -> g -> m Float Source #

isInRange :: (Float, Float) -> Float -> Bool Source #

UniformRange Int Source # 
Instance details

Defined in System.Random.Internal

Methods

uniformRM :: StatefulGen g m => (Int, Int) -> g -> m Int Source #

isInRange :: (Int, Int) -> Int -> Bool Source #

UniformRange Word Source # 
Instance details

Defined in System.Random.Internal

Methods

uniformRM :: StatefulGen g m => (Word, Word) -> g -> m Word Source #

isInRange :: (Word, Word) -> Word -> Bool Source #

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

Defined in System.Random.Internal

Methods

uniformRM :: StatefulGen g m => ((a, b), (a, b)) -> g -> m (a, b) Source #

isInRange :: ((a, b), (a, b)) -> (a, b) -> Bool Source #

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

Defined in System.Random.Internal

Methods

uniformRM :: StatefulGen g m => ((a, b, c), (a, b, c)) -> g -> m (a, b, c) Source #

isInRange :: ((a, b, c), (a, b, c)) -> (a, b, c) -> Bool Source #

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

Defined in System.Random.Internal

Methods

uniformRM :: StatefulGen g m => ((a, b, c, d), (a, b, c, d)) -> g -> m (a, b, c, d) Source #

isInRange :: ((a, b, c, d), (a, b, c, d)) -> (a, b, c, d) -> Bool Source #

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

Defined in System.Random.Internal

Methods

uniformRM :: StatefulGen g m => ((a, b, c, d, e), (a, b, c, d, e)) -> g -> m (a, b, c, d, e) Source #

isInRange :: ((a, b, c, d, e), (a, b, c, d, e)) -> (a, b, c, d, e) -> Bool Source #

(UniformRange a, UniformRange b, UniformRange c, UniformRange d, UniformRange e, UniformRange f) => UniformRange (a, b, c, d, e, f) Source # 
Instance details

Defined in System.Random.Internal

Methods

uniformRM :: StatefulGen g m => ((a, b, c, d, e, f), (a, b, c, d, e, f)) -> g -> m (a, b, c, d, e, f) Source #

isInRange :: ((a, b, c, d, e, f), (a, b, c, d, e, f)) -> (a, b, c, d, e, f) -> Bool Source #

(UniformRange a, UniformRange b, UniformRange c, UniformRange d, UniformRange e, UniformRange f, UniformRange g) => UniformRange (a, b, c, d, e, f, g) Source # 
Instance details

Defined in System.Random.Internal

Methods

uniformRM :: StatefulGen g0 m => ((a, b, c, d, e, f, g), (a, b, c, d, e, f, g)) -> g0 -> m (a, b, c, d, e, f, g) Source #

isInRange :: ((a, b, c, d, e, f, g), (a, b, c, d, e, f, g)) -> (a, b, c, d, e, f, g) -> Bool Source #

class Finite a Source #

A type class for data with a finite number of inhabitants. This type class is used in the default implementation of Uniform.

Users are not supposed to write instances of Finite manually. There is a default implementation in terms of Generic instead.

>>> :seti -XDeriveGeneric -XDeriveAnyClass
>>> import GHC.Generics (Generic)
>>> data MyBool = MyTrue | MyFalse deriving (Generic, Finite)
>>> data Action = Code MyBool | Eat (Maybe Bool) | Sleep deriving (Generic, Finite)

Instances

Instances details
Finite Void Source # 
Instance details

Defined in System.Random.GFinite

Methods

cardinality :: Proxy# Void -> Cardinality

toFinite :: Integer -> Void

fromFinite :: Void -> Integer

Finite Int16 Source # 
Instance details

Defined in System.Random.GFinite

Methods

cardinality :: Proxy# Int16 -> Cardinality

toFinite :: Integer -> Int16

fromFinite :: Int16 -> Integer

Finite Int32 Source # 
Instance details

Defined in System.Random.GFinite

Methods

cardinality :: Proxy# Int32 -> Cardinality

toFinite :: Integer -> Int32

fromFinite :: Int32 -> Integer

Finite Int64 Source # 
Instance details

Defined in System.Random.GFinite

Methods

cardinality :: Proxy# Int64 -> Cardinality

toFinite :: Integer -> Int64

fromFinite :: Int64 -> Integer

Finite Int8 Source # 
Instance details

Defined in System.Random.GFinite

Methods

cardinality :: Proxy# Int8 -> Cardinality

toFinite :: Integer -> Int8

fromFinite :: Int8 -> Integer

Finite Word16 Source # 
Instance details

Defined in System.Random.GFinite

Finite Word32 Source # 
Instance details

Defined in System.Random.GFinite

Finite Word64 Source # 
Instance details

Defined in System.Random.GFinite

Finite Word8 Source # 
Instance details

Defined in System.Random.GFinite

Methods

cardinality :: Proxy# Word8 -> Cardinality

toFinite :: Integer -> Word8

fromFinite :: Word8 -> Integer

Finite Ordering Source # 
Instance details

Defined in System.Random.GFinite

Finite () Source # 
Instance details

Defined in System.Random.GFinite

Methods

cardinality :: Proxy# () -> Cardinality

toFinite :: Integer -> ()

fromFinite :: () -> Integer

Finite Bool Source # 
Instance details

Defined in System.Random.GFinite

Methods

cardinality :: Proxy# Bool -> Cardinality

toFinite :: Integer -> Bool

fromFinite :: Bool -> Integer

Finite Char Source # 
Instance details

Defined in System.Random.GFinite

Methods

cardinality :: Proxy# Char -> Cardinality

toFinite :: Integer -> Char

fromFinite :: Char -> Integer

Finite Int Source # 
Instance details

Defined in System.Random.GFinite

Methods

cardinality :: Proxy# Int -> Cardinality

toFinite :: Integer -> Int

fromFinite :: Int -> Integer

Finite Word Source # 
Instance details

Defined in System.Random.GFinite

Methods

cardinality :: Proxy# Word -> Cardinality

toFinite :: Integer -> Word

fromFinite :: Word -> Integer

Finite a => Finite (Maybe a) Source # 
Instance details

Defined in System.Random.GFinite

Methods

cardinality :: Proxy# (Maybe a) -> Cardinality

toFinite :: Integer -> Maybe a

fromFinite :: Maybe a -> Integer

(Finite a, Finite b) => Finite (Either a b) Source # 
Instance details

Defined in System.Random.GFinite

Methods

cardinality :: Proxy# (Either a b) -> Cardinality

toFinite :: Integer -> Either a b

fromFinite :: Either a b -> Integer

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

Defined in System.Random.GFinite

Methods

cardinality :: Proxy# (a, b) -> Cardinality

toFinite :: Integer -> (a, b)

fromFinite :: (a, b) -> Integer

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

Defined in System.Random.GFinite

Methods

cardinality :: Proxy# (a, b, c) -> Cardinality

toFinite :: Integer -> (a, b, c)

fromFinite :: (a, b, c) -> Integer

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

Defined in System.Random.GFinite

Methods

cardinality :: Proxy# (a, b, c, d) -> Cardinality

toFinite :: Integer -> (a, b, c, d)

fromFinite :: (a, b, c, d) -> Integer

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

Defined in System.Random.GFinite

Methods

cardinality :: Proxy# (a, b, c, d, e) -> Cardinality

toFinite :: Integer -> (a, b, c, d, e)

fromFinite :: (a, b, c, d, e) -> Integer

(Finite a, Finite b, Finite c, Finite d, Finite e, Finite f) => Finite (a, b, c, d, e, f) Source # 
Instance details

Defined in System.Random.GFinite

Methods

cardinality :: Proxy# (a, b, c, d, e, f) -> Cardinality

toFinite :: Integer -> (a, b, c, d, e, f)

fromFinite :: (a, b, c, d, e, f) -> Integer

(Finite a, Finite b, Finite c, Finite d, Finite e, Finite f, Finite g) => Finite (a, b, c, d, e, f, g) Source # 
Instance details

Defined in System.Random.GFinite

Methods

cardinality :: Proxy# (a, b, c, d, e, f, g) -> Cardinality

toFinite :: Integer -> (a, b, c, d, e, f, g)

fromFinite :: (a, b, c, d, e, f, g) -> Integer

Seed

class (KnownNat (SeedSize g), 1 <= SeedSize g, Typeable g) => SeedGen g where Source #

Interface for converting a pure pseudo-random number generator to and from non-empty sequence of bytes. Seeds are stored in Little-Endian order regardless of the platform it is being used on, which provides cross-platform compatibility, while providing optimal performance for the most common platform type.

Conversion to and from a Seed serves as a building block for implementing serialization for any pure or frozen pseudo-random number generator.

It is not trivial to implement platform independence. For this reason this type class has two alternative ways of creating an instance for this class. The easiest way for constructing a platform indepent seed is by converting the inner state of a generator to and from a list of 64 bit words using toSeed64 and fromSeed64 respectively. In that case cross-platform support will be handled automaticaly.

>>> :set -XDataKinds -XTypeFamilies
>>> import Data.Word (Word8, Word32)
>>> import Data.Bits ((.|.), shiftR, shiftL)
>>> import Data.List.NonEmpty (NonEmpty ((:|)))
>>> data FiveByteGen = FiveByteGen Word8 Word32 deriving Show
>>> :{
instance SeedGen FiveByteGen where
  type SeedSize FiveByteGen = 5
  fromSeed64 (w64 :| _) =
    FiveByteGen (fromIntegral (w64 `shiftR` 32)) (fromIntegral w64)
  toSeed64 (FiveByteGen x1 x4) =
    let w64 = (fromIntegral x1 `shiftL` 32) .|. fromIntegral x4
     in (w64 :| [])
:}
>>> FiveByteGen 0x80 0x01020304
FiveByteGen 128 16909060
>>> fromSeed (toSeed (FiveByteGen 0x80 0x01020304))
FiveByteGen 128 16909060
>>> toSeed (FiveByteGen 0x80 0x01020304)
Seed [0x04, 0x03, 0x02, 0x01, 0x80]
>>> toSeed64 (FiveByteGen 0x80 0x01020304)
549772722948 :| []

However, when performance is of utmost importance or default handling of cross platform independence is not sufficient, then an adventurous developer can try implementing conversion into bytes directly with toSeed and fromSeed.

Properties that must hold:

> fromSeed (toSeed gen) == gen
> fromSeed64 (toSeed64 gen) == gen

Note, that there is no requirement for every Seed to roundtrip, eg. this proprty does not even hold for StdGen:

>>> let seed = nonEmptyToSeed (0xab :| [0xff00]) :: Seed StdGen
>>> seed == toSeed (fromSeed seed)
False

Since: 1.3.0

Minimal complete definition

fromSeed, toSeed | fromSeed64, toSeed64

Associated Types

type SeedSize g :: Nat Source #

Number of bytes that is required for storing the full state of a pseudo-random number generator. It should be big enough to satisfy the roundtrip property:

> fromSeed (toSeed gen) == gen

Methods

fromSeed :: Seed g -> g Source #

Convert from a binary representation to a pseudo-random number generator

Since: 1.3.0

toSeed :: g -> Seed g Source #

Convert to a binary representation of a pseudo-random number generator

Since: 1.3.0

fromSeed64 :: NonEmpty Word64 -> g Source #

Construct pseudo-random number generator from a list of words. Whenever list does not have enough bytes to satisfy the SeedSize requirement, it will be padded with zeros. On the other hand when it has more than necessary, extra bytes will be dropped.

For example if SeedSize is set to 2, then only the lower 16 bits of the first element in the list will be used.

Since: 1.3.0

toSeed64 :: g -> NonEmpty Word64 Source #

Convert pseudo-random number generator to a list of words

In case when SeedSize is not a multiple of 8, then the upper bits of the last word in the list will be set to zero.

Since: 1.3.0

Instances

Instances details
SeedGen StdGen Source # 
Instance details

Defined in System.Random.Seed

Associated Types

type SeedSize StdGen :: Nat Source #

SeedGen SMGen Source # 
Instance details

Defined in System.Random.Seed

Associated Types

type SeedSize SMGen :: Nat Source #

SeedGen SMGen Source # 
Instance details

Defined in System.Random.Seed

Associated Types

type SeedSize SMGen :: Nat Source #

SeedGen g => SeedGen (StateGen g) Source # 
Instance details

Defined in System.Random.Seed

Associated Types

type SeedSize (StateGen g) :: Nat Source #

SeedGen g => SeedGen (AtomicGen g) Source # 
Instance details

Defined in System.Random.Stateful

Associated Types

type SeedSize (AtomicGen g) :: Nat Source #

SeedGen g => SeedGen (IOGen g) Source # 
Instance details

Defined in System.Random.Stateful

Associated Types

type SeedSize (IOGen g) :: Nat Source #

SeedGen g => SeedGen (STGen g) Source # 
Instance details

Defined in System.Random.Stateful

Associated Types

type SeedSize (STGen g) :: Nat Source #

SeedGen g => SeedGen (TGen g) Source # 
Instance details

Defined in System.Random.Stateful

Associated Types

type SeedSize (TGen g) :: Nat Source #

Seed

data Seed g Source #

This is a binary form of pseudo-random number generator's state. It is designed to be safe and easy to use for input/output operations like restoring from file, transmitting over the network, etc.

Constructor is not exported, becasue it is important for implementation to enforce the invariant of the underlying byte array being of the exact same length as the generator has specified in SeedSize. Use mkSize and unSize to get access to the raw bytes in a safe manner.

Since: 1.3.0

Instances

Instances details
Show (Seed g) Source # 
Instance details

Defined in System.Random.Internal

Methods

showsPrec :: Int -> Seed g -> ShowS #

show :: Seed g -> String #

showList :: [Seed g] -> ShowS #

Eq (Seed g) Source # 
Instance details

Defined in System.Random.Internal

Methods

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

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

Ord (Seed g) Source # 
Instance details

Defined in System.Random.Internal

Methods

compare :: Seed g -> Seed g -> Ordering #

(<) :: Seed g -> Seed g -> Bool #

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

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

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

max :: Seed g -> Seed g -> Seed g #

min :: Seed g -> Seed g -> Seed g #

SeedGen g => Uniform (Seed g) Source # 
Instance details

Defined in System.Random.Seed

Methods

uniformM :: StatefulGen g0 m => g0 -> m (Seed g) Source #

seedSize :: forall g. SeedGen g => Int Source #

Get the expected size of the Seed in number bytes

Since: 1.3.0

seedSizeProxy :: forall proxy g. SeedGen g => proxy g -> Int Source #

Just like seedSize, except it accepts a proxy as an argument.

Since: 1.3.0

mkSeed :: forall g m. (SeedGen g, MonadFail m) => ByteArray -> m (Seed g) Source #

Construct a Seed from a ByteArray of expected length. Whenever ByteArray does not match the SeedSize specified by the pseudo-random generator, this function will fail.

Since: 1.3.0

unSeed :: Seed g -> ByteArray Source #

Unwrap the Seed and get the underlying ByteArray

Since: 1.3.0

mkSeedFromByteString :: (SeedGen g, MonadFail m) => ByteString -> m (Seed g) Source #

Just like mkSeed, but uses ByteString as argument. Results in a memcopy of the seed.

Since: 1.3.0

unSeedToByteString :: Seed g -> ByteString Source #

Just like unSeed, but produced a ByteString. Results in a memcopy of the seed.

Since: 1.3.0

withSeed :: SeedGen g => Seed g -> (g -> (a, g)) -> (a, Seed g) Source #

Helper function that allows for operating directly on the Seed, while supplying a function that uses the pseudo-random number generator that is constructed from that Seed.

Example

Expand
>>> :set -XTypeApplications
>>> import System.Random
>>> withSeed (nonEmptyToSeed (pure 2024) :: Seed StdGen) (uniform @Int)
(1039666877624726199,Seed [0xe9, 0x07, 0x00, 0x00, 0x00, 0x00, 0x00, 0x00, 0x01, 0x00, 0x00, 0x00, 0x00, 0x00, 0x00, 0x00])

Since: 1.3.0

withSeedM :: (SeedGen g, Functor f) => Seed g -> (g -> f (a, g)) -> f (a, Seed g) Source #

Same as withSeed, except it is useful with monadic computation and frozen generators.

See withSeedMutableGen for a helper that also handles seeds for mutable pseduo-random number generators.

Since: 1.3.0

withSeedFile :: (SeedGen g, MonadIO m) => FilePath -> (Seed g -> m (a, Seed g)) -> m a Source #

Read the seed from a file and use it for constructing a pseudo-random number generator. After supplied action has been applied to the constructed generator, the resulting generator will be converted back to a seed and written to the same file.

Since: 1.3.0

seedGenTypeName :: forall g. SeedGen g => String Source #

This is a function that shows the name of the generator type, which is useful for error reporting.

Since: 1.3.0

nonEmptyToSeed :: forall g. SeedGen g => NonEmpty Word64 -> Seed g Source #

Construct a seed from a list of 64-bit words. At most SeedSize many bytes will be used.

Since: 1.3.0

nonEmptyFromSeed :: forall g. SeedGen g => Seed g -> NonEmpty Word64 Source #

Convert a Seed to a list of 64bit words.

Since: 1.3.0

Generators for sequences of pseudo-random bytes

Lists

uniforms :: (Uniform a, RandomGen g) => g -> [a] Source #

Produce an infinite list of pseudo-random values. Integrates nicely with list fusion. Naturally, there is no way to recover the final generator, therefore either use split before calling uniforms or use uniformList instead.

Similar to randoms, except it relies on Uniform type class instead of Random

Examples

Expand
>>> let gen = mkStdGen 2023
>>> import Data.Word (Word16)
>>> take 5 $ uniforms gen :: [Word16]
[56342,15850,25292,14347,13919]

Since: 1.3.0

uniformRs :: (UniformRange a, RandomGen g) => (a, a) -> g -> [a] Source #

Produce an infinite list of pseudo-random values in a specified range. Same as uniforms, integrates nicely with list fusion. There is no way to recover the final generator, therefore either use split before calling uniformRs or use uniformListR instead.

Similar to randomRs, except it relies on UniformRange type class instead of Random.

Examples

Expand
>>> let gen = mkStdGen 2023
>>> take 5 $ uniformRs (10, 100) gen :: [Int]
[32,86,21,57,39]

Since: 1.3.0

uniformList :: (Uniform a, RandomGen g) => Int -> g -> ([a], g) Source #

Produce a list of the supplied length with elements generated uniformly.

See uniformListM for a stateful counterpart.

Examples

Expand
>>> let gen = mkStdGen 2023
>>> import Data.Word (Word16)
>>> uniformList 5 gen :: ([Word16], StdGen)
([56342,15850,25292,14347,13919],StdGen {unStdGen = SMGen 6446154349414395371 1920468677557965761})

Since: 1.3.0

uniformListR :: (UniformRange a, RandomGen g) => Int -> (a, a) -> g -> ([a], g) Source #

Produce a list of the supplied length with elements generated uniformly.

See uniformListM for a stateful counterpart.

Examples

Expand
>>> let gen = mkStdGen 2023
>>> uniformListR 10 (20, 30) gen :: ([Int], StdGen)
([26,30,27,24,30,25,27,21,27,27],StdGen {unStdGen = SMGen 12965503083958398648 1920468677557965761})

Since: 1.3.0

uniformShuffleList :: RandomGen g => [a] -> g -> ([a], g) Source #

Shuffle elements of a list in a uniformly random order.

Examples

Expand
>>> uniformShuffleList "ELVIS" $ mkStdGen 252
("LIVES",StdGen {unStdGen = SMGen 17676540583805057877 5302934877338729551})

Since: 1.3.0

Bytes

uniformByteArray Source #

Arguments

:: RandomGen g 
=> Bool

Should byte array be allocted in pinned or unpinned memory.

-> Int

Number of bytes to generate

-> g

Pure pseudo-random numer generator

-> (ByteArray, g) 

Efficiently generates a sequence of pseudo-random bytes in a platform independent manner.

Since: 1.3.0

uniformByteString :: RandomGen g => Int -> g -> (ByteString, g) Source #

Generates a ByteString of the specified size using a pure pseudo-random number generator. See uniformByteStringM for the monadic version.

Examples

Expand
>>> import System.Random
>>> import Data.ByteString (unpack)
>>> let pureGen = mkStdGen 137
>>> unpack . fst $ uniformByteString 10 pureGen
[51,123,251,37,49,167,90,109,1,4]

Since: 1.3.0

uniformShortByteString :: RandomGen g => Int -> g -> (ShortByteString, g) Source #

Same as uniformByteArray False, but for ShortByteString.

Returns a ShortByteString of length n filled with pseudo-random bytes.

Examples

Expand
>>> import System.Random
>>> import Data.ByteString.Short (unpack)
>>> let pureGen = mkStdGen 137
>>> unpack . fst $ uniformShortByteString 10 pureGen
[51,123,251,37,49,167,90,109,1,4]

Since: 1.3.0

uniformFillMutableByteArray Source #

Arguments

:: RandomGen g 
=> MutableByteArray s

Mutable array to fill with random bytes

-> Int

Offset into a mutable array from the beginning in number of bytes. Offset will be clamped into the range between 0 and the total size of the mutable array

-> Int

Number of randomly generated bytes to write into the array. This number will be clamped between 0 and the total size of the array without the offset.

-> g 
-> ST s g 

Fill in a slice of a mutable byte array with randomly generated bytes. This function does not fail, instead it clamps the offset and number of bytes to generate into a valid range.

Since: 1.3.0

Deprecated

genByteString :: RandomGen g => Int -> g -> (ByteString, g) Source #

Deprecated: In favor of uniformByteString

Generates a ByteString of the specified size using a pure pseudo-random number generator. See uniformByteStringM for the monadic version.

Examples

Expand
>>> import System.Random
>>> import Data.ByteString
>>> let pureGen = mkStdGen 137
>>> :seti -Wno-deprecations
>>> unpack . fst . genByteString 10 $ pureGen
[51,123,251,37,49,167,90,109,1,4]

Since: 1.2.0

genShortByteString :: RandomGen g => Int -> g -> (ShortByteString, g) Source #

Deprecated: In favor of uniformShortByteString

Same as uniformByteArray False, but for ShortByteString.

genShortByteString n g returns a ShortByteString of length n filled with pseudo-random bytes.

Note - This function will be removed from the type class in the next major release as it is no longer needed because of unsafeUniformFillMutableByteArray.

Since: 1.2.0

Standard pseudo-random number generator

data StdGen Source #

The standard pseudo-random number generator.

Instances

Instances details
Show StdGen Source # 
Instance details

Defined in System.Random.Internal

NFData StdGen Source # 
Instance details

Defined in System.Random.Internal

Methods

rnf :: StdGen -> () #

Eq StdGen Source # 
Instance details

Defined in System.Random.Internal

Methods

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

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

RandomGen StdGen Source # 
Instance details

Defined in System.Random.Internal

SplitGen StdGen Source # 
Instance details

Defined in System.Random.Internal

SeedGen StdGen Source # 
Instance details

Defined in System.Random.Seed

Associated Types

type SeedSize StdGen :: Nat Source #

type SeedSize StdGen Source # 
Instance details

Defined in System.Random.Seed

mkStdGen :: Int -> StdGen Source #

Constructs a StdGen deterministically from an Int seed. See mkStdGen64 for a Word64 variant that is architecture agnostic.

mkStdGen64 :: Word64 -> StdGen Source #

Constructs a StdGen deterministically from a Word64 seed.

The difference between mkStdGen is that mkStdGen64 will work the same on 64-bit and 32-bit architectures, while the former can only use 32-bit of information for initializing the psuedo-random number generator on 32-bit operating systems

Since: 1.3.0

initStdGen :: MonadIO m => m StdGen Source #

Initialize StdGen using system entropy (i.e. /dev/urandom) when it is available, while falling back on using system time as the seed.

Since: 1.2.1

Global standard pseudo-random number generator

There is a single, implicit, global pseudo-random number generator of type StdGen, held in a global mutable variable that can be manipulated from within the IO monad. It is also available as globalStdGen, therefore it is recommended to use the new System.Random.Stateful interface to explicitly operate on the global pseudo-random number generator.

It is initialised with initStdGen, although it is possible to override its value with setStdGen. All operations on the global pseudo-random number generator are thread safe, however in presence of concurrency they are naturally become non-deterministic. Moreover, relying on the global mutable state makes it hard to know which of the dependent libraries are using it as well, making it unpredictable in the local context. Precisely of this reason, the global pseudo-random number generator is only suitable for uses in applications, test suites, etc. and is advised against in development of reusable libraries.

It is also important to note that either using StdGen with pure functions from other sections of this module or by relying on runStateGen from stateful interface does not only give us deterministic behaviour without requiring IO, but it is also more efficient.

getStdRandom :: MonadIO m => (StdGen -> (a, StdGen)) -> m a Source #

Uses the supplied function to get a value from the current global random generator, and updates the global generator with the new generator returned by the function. For example, rollDice produces a pseudo-random integer between 1 and 6:

>>> rollDice = getStdRandom (randomR (1, 6))
>>> replicateM 10 (rollDice :: IO Int)
[1,1,1,4,5,6,1,2,2,5]

This is an outdated function and it is recommended to switch to its equivalent applyAtomicGen instead, possibly with the globalStdGen if relying on the global state is acceptable.

>>> import System.Random.Stateful
>>> rollDice = applyAtomicGen (uniformR (1, 6)) globalStdGen
>>> replicateM 10 (rollDice :: IO Int)
[2,1,1,5,4,3,6,6,3,2]

Since: 1.0.0

getStdGen :: MonadIO m => m StdGen Source #

Gets the global pseudo-random number generator. Extracts the contents of globalStdGen

Since: 1.0.0

setStdGen :: MonadIO m => StdGen -> m () Source #

Sets the global pseudo-random number generator. Overwrites the contents of globalStdGen

Since: 1.0.0

newStdGen :: MonadIO m => m StdGen Source #

Applies split to the current global pseudo-random generator globalStdGen, updates it with one of the results, and returns the other.

Since: 1.0.0

randomIO :: (Random a, MonadIO m) => m a Source #

A variant of randomM that uses the global pseudo-random number generator globalStdGen.

>>> import Data.Int
>>> randomIO :: IO Int32
114794456

This function is equivalent to getStdRandom random and is included in this interface for historical reasons and backwards compatibility. It is recommended to use uniformM instead, possibly with the globalStdGen if relying on the global state is acceptable.

>>> import System.Random.Stateful
>>> uniformM globalStdGen :: IO Int32
-1768545016

Since: 1.0.0

randomRIO :: (Random a, MonadIO m) => (a, a) -> m a Source #

A variant of randomRM that uses the global pseudo-random number generator globalStdGen

>>> randomRIO (2020, 2100) :: IO Int
2028

Similar to randomIO, this function is equivalent to getStdRandom randomR and is included in this interface for historical reasons and backwards compatibility. It is recommended to use uniformRM instead, possibly with the globalStdGen if relying on the global state is acceptable.

>>> import System.Random.Stateful
>>> uniformRM (2020, 2100) globalStdGen :: IO Int
2044

Since: 1.0.0

Compatibility and reproducibility

Backwards compatibility and deprecations

genRange :: RandomGen g => g -> (Int, Int) Source #

Deprecated: No longer used

Yields the range of values returned by next.

It is required that:

  • If (a, b) = genRange g, then a < b.
  • genRange must not examine its argument so the value it returns is determined only by the instance of RandomGen.

The default definition spans the full range of Int.

Since: 1.0.0

next :: RandomGen g => g -> (Int, g) Source #

Deprecated: No longer used

Returns an Int that is uniformly distributed over the range returned by genRange (including both end points), and a new generator. Using next is inefficient as all operations go via Integer. See here for more details. It is thus deprecated.

Since: 1.0.0

Version 1.2 mostly maintains backwards compatibility with version 1.1. This has a few consequences users should be aware of:

  • The type class Random is only provided for backwards compatibility. New code should use Uniform and UniformRange instead.
  • The methods next and genRange in RandomGen are deprecated and only provided for backwards compatibility. New instances of RandomGen should implement word-based methods instead. See below for more information about how to write a RandomGen instance.
  • This library provides instances for Random for some unbounded types for backwards compatibility. For an unbounded type, there is no way to generate a value with uniform probability out of its entire domain, so the random implementation for unbounded types actually generates a value based on some fixed range.

    For Integer, random generates a value in the Int range. For Float and Double, random generates a floating point value in the range [0, 1).

    This library does not provide Uniform instances for any unbounded types.

Reproducibility

If you have two builds of a particular piece of code against this library, any deterministic function call should give the same result in the two builds if the builds are

  • compiled against the same major version of this library
  • on the same architecture (32-bit or 64-bit)

Notes for pseudo-random number generator implementors

How to implement RandomGen

Consider these points when writing a RandomGen instance for a given pure pseudo-random number generator:

  • If the pseudo-random number generator has a power-of-2 modulus, that is, it natively outputs 2^n bits of randomness for some n, implement genWord8, genWord16, genWord32 and genWord64. See below for more details.
  • If the pseudo-random number generator does not have a power-of-2 modulus, implement next and genRange. See below for more details.
  • If the pseudo-random number generator is splittable, implement split. If there is no suitable implementation, split should fail with a helpful error message.

How to implement RandomGen for a pseudo-random number generator with power-of-2 modulus

Suppose you want to implement a permuted congruential generator.

>>> data PCGen = PCGen !Word64 !Word64

It produces a full Word32 of randomness per iteration.

>>> import Data.Bits
>>> :{
let stepGen :: PCGen -> (Word32, PCGen)
    stepGen (PCGen state inc) = let
      newState = state * 6364136223846793005 + (inc .|. 1)
      xorShifted = fromIntegral (((state `shiftR` 18) `xor` state) `shiftR` 27) :: Word32
      rot = fromIntegral (state `shiftR` 59) :: Word32
      out = (xorShifted `shiftR` (fromIntegral rot)) .|. (xorShifted `shiftL` fromIntegral ((-rot) .&. 31))
      in (out, PCGen newState inc)
:}
>>> fst $ stepGen $ snd $ stepGen (PCGen 17 29)
3288430965

You can make it an instance of RandomGen as follows:

>>> :{
instance RandomGen PCGen where
  genWord32 = stepGen
  split _ = error "PCG is not splittable"
:}

How to implement RandomGen for a pseudo-random number generator without a power-of-2 modulus

We do not recommend you implement any new pseudo-random number generators without a power-of-2 modulus.

Pseudo-random number generators without a power-of-2 modulus perform significantly worse than pseudo-random number generators with a power-of-2 modulus with this library. This is because most functionality in this library is based on generating and transforming uniformly pseudo-random machine words, and generating uniformly pseudo-random machine words using a pseudo-random number generator without a power-of-2 modulus is expensive.

The pseudo-random number generator from L’Ecuyer (1988) natively generates an integer value in the range [1, 2147483562]. This is the generator used by this library before it was replaced by SplitMix in version 1.2.

>>> data LegacyGen = LegacyGen !Int32 !Int32
>>> :{
let legacyNext :: LegacyGen -> (Int, LegacyGen)
    legacyNext (LegacyGen s1 s2) = (fromIntegral z', LegacyGen s1'' s2'') where
      z' = if z < 1 then z + 2147483562 else z
      z = s1'' - s2''
      k = s1 `quot` 53668
      s1'  = 40014 * (s1 - k * 53668) - k * 12211
      s1'' = if s1' < 0 then s1' + 2147483563 else s1'
      k' = s2 `quot` 52774
      s2' = 40692 * (s2 - k' * 52774) - k' * 3791
      s2'' = if s2' < 0 then s2' + 2147483399 else s2'
:}

You can make it an instance of RandomGen as follows:

>>> :{
instance RandomGen LegacyGen where
  next = legacyNext
  genRange _ = (1, 2147483562)
  split _ = error "Not implemented"
:}

References

  1. Guy L. Steele, Jr., Doug Lea, and Christine H. Flood. 2014. Fast splittable pseudorandom number generators. In Proceedings of the 2014 ACM International Conference on Object Oriented Programming Systems Languages & Applications (OOPSLA '14). ACM, New York, NY, USA, 453-472. DOI: https://doi.org/10.1145/2660193.2660195