Copyright | (c) The University of Glasgow 2001 |
---|---|
License | BSD-style (see the file LICENSE in the 'random' repository) |
Maintainer | libraries@haskell.org |
Stability | stable |
Safe Haskell | Trustworthy |
Language | Haskell2010 |
This library deals with the common task of pseudo-random number generation.
Synopsis
- class RandomGen g where
- next :: g -> (Int, g)
- genWord8 :: g -> (Word8, g)
- genWord16 :: g -> (Word16, g)
- genWord32 :: g -> (Word32, g)
- genWord64 :: g -> (Word64, g)
- genWord32R :: Word32 -> g -> (Word32, g)
- genWord64R :: Word64 -> g -> (Word64, g)
- genShortByteString :: Int -> g -> (ShortByteString, g)
- genRange :: g -> (Int, Int)
- split :: g -> (g, g)
- uniform :: (RandomGen g, Uniform a) => g -> (a, g)
- uniformR :: (RandomGen g, UniformRange a) => (a, a) -> g -> (a, g)
- genByteString :: RandomGen g => Int -> g -> (ByteString, g)
- class Random a where
- class Uniform a
- class UniformRange a
- data StdGen
- mkStdGen :: Int -> StdGen
- getStdRandom :: MonadIO m => (StdGen -> (a, StdGen)) -> m a
- getStdGen :: MonadIO m => m StdGen
- setStdGen :: MonadIO m => StdGen -> m ()
- newStdGen :: MonadIO m => m StdGen
- randomIO :: (Random a, MonadIO m) => m a
- randomRIO :: (Random a, MonadIO m) => (a, a) -> m a
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 ofRandomGen
. It uses the SplitMix implementation provided by the splitmix package. Programmers may, of course, supply their own instances ofRandomGen
.
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 = take n . unfoldr (Just . uniformR (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 runGenState
and its variants.
>>>
:{
let rollsM :: StatefulGen g m => Int -> g -> m [Word] rollsM n = replicateM n . uniformRM (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.
next :: 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.
genWord8 :: g -> (Word8, g) Source #
genWord16 :: g -> (Word16, g) Source #
genWord32 :: g -> (Word32, g) Source #
genWord64 :: g -> (Word64, g) Source #
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
genShortByteString :: Int -> g -> (ShortByteString, g) Source #
genShortByteString n g
returns a ShortByteString
of length n
filled with pseudo-random bytes.
Since: 1.2.0
Instances
uniform :: (RandomGen g, Uniform a) => g -> (a, g) Source #
Generates a value uniformly distributed over all possible values of that type.
This is a pure version of uniformM
.
Examples
>>>
import System.Random
>>>
let pureGen = mkStdGen 137
>>>
uniform pureGen :: (Bool, StdGen)
(True,StdGen {unStdGen = SMGen 11285859549637045894 7641485672361121627})
Since: 1.2.0
uniformR :: (RandomGen g, UniformRange a) => (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
>>>
import System.Random
>>>
let pureGen = mkStdGen 137
>>>
uniformR (1 :: Int, 4 :: Int) pureGen
(4,StdGen {unStdGen = SMGen 11285859549637045894 7641485672361121627})
Since: 1.2.0
genByteString :: RandomGen g => Int -> g -> (ByteString, g) Source #
Generates a ByteString
of the specified size using a pure pseudo-random
number generator. See uniformByteString
for the monadic version.
Examples
>>>
import System.Random
>>>
import Data.ByteString
>>>
let pureGen = mkStdGen 137
>>>
unpack . fst . genByteString 10 $ pureGen
[51,123,251,37,49,167,90,109,1,4]
Since: 1.2.0
The class of types for which uniformly distributed values can be generated.
Random
exists primarily for backwards compatibility with version 1.1 of
this library. In new code, use the better specified Uniform
and
UniformRange
instead.
Nothing
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. 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.
randomR :: (RandomGen g, UniformRange a) => (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. 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.
random :: RandomGen g => g -> (a, g) Source #
The same as randomR
, but using a default range determined by the type:
random :: (RandomGen g, Uniform a) => g -> (a, g) Source #
The same as randomR
, but using a default range determined by the type:
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.
randoms :: RandomGen g => g -> [a] Source #
Plural variant of random
, producing an infinite list of
pseudo-random values instead of returning a new generator.
Instances
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
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
Standard pseudo-random number generator
The standard pseudo-random number generator.
Instances
Eq StdGen Source # | |
Show StdGen Source # | |
NFData StdGen Source # | |
Defined in System.Random.Internal | |
RandomGen StdGen Source # | |
Defined in System.Random.Internal next :: StdGen -> (Int, StdGen) Source # genWord8 :: StdGen -> (Word8, StdGen) Source # genWord16 :: StdGen -> (Word16, StdGen) Source # genWord32 :: StdGen -> (Word32, StdGen) Source # genWord64 :: StdGen -> (Word64, StdGen) Source # genWord32R :: Word32 -> StdGen -> (Word32, StdGen) Source # genWord64R :: Word64 -> StdGen -> (Word64, StdGen) Source # genShortByteString :: Int -> StdGen -> (ShortByteString, StdGen) Source # |
Global standard pseudo-random number generator
There is a single, implicit, global pseudo-random number generator of type
StdGen
, held in a global variable maintained by the IO
monad. It is
initialised automatically in some system-dependent fashion. To get
deterministic behaviour, use setStdGen
.
Note that mkStdGen
also gives deterministic behaviour without requiring an
IO
context.
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
gets a pseudo-random integer
between 1 and 6:
rollDice :: IO Int rollDice = getStdRandom (randomR (1,6))
newStdGen :: MonadIO m => m StdGen Source #
Applies split
to the current global pseudo-random generator,
updates it with one of the results, and returns the other.
randomIO :: (Random a, MonadIO m) => m a Source #
A variant of random
that uses the global pseudo-random number
generator.
randomRIO :: (Random a, MonadIO m) => (a, a) -> m a Source #
A variant of randomR
that uses the global pseudo-random number
generator.
Compatibility and reproducibility
Backwards compatibility and deprecations
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 useUniform
andUniformRange
instead. - The methods
next
andgenRange
inRandomGen
are deprecated and only provided for backwards compatibility. New instances ofRandomGen
should implement word-based methods instead. See below for more information about how to write aRandomGen
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 therandom
implementation for unbounded types actually generates a value based on some fixed range.For
Integer
,random
generates a value in theInt
range. ForFloat
andDouble
,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 somen
, implementgenWord8
,genWord16
,genWord32
andgenWord64
. See below for more details. - If the pseudo-random number generator does not have a power-of-2
modulus, implement
next
andgenRange
. 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
- 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