random-1.2.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

Contents

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 = 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.

Minimal complete definition

split, (genWord32 | genWord64 | next, genRange)

Methods

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 #

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

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

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

Since: 1.2.0

genRange :: 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.

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

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.

Instances
RandomGen SMGen Source # 
Instance details

Defined in System.Random.Internal

RandomGen SMGen Source # 
Instance details

Defined in System.Random.Internal

RandomGen StdGen Source # 
Instance details

Defined in System.Random.Internal

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

Defined in System.Random.Internal

RandomGen g => RandomGen (STGen 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 (AtomicGen g) Source # 
Instance details

Defined in System.Random.Stateful

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

Expand
>>> 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

Expand
>>> 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

Expand
>>> 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

class Random a where Source #

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.

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. 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:

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

random :: (RandomGen g, Uniform a) => 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 fractional types, the range is normally the semi-closed interval [0,1).
  • For Integer, the range is (arbitrarily) the range of Int.

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
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 # 
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 # 
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 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 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 Integer Source # 
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 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 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 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 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 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 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 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 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 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 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 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 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 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 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 CFloat Source # 
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 CDouble Source # 
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 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 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 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 CSigAtomic Source # 
Instance details

Defined in System.Random

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 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 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 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 #

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

Minimal complete definition

uniformM

Instances
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 Int8 Source # 
Instance details

Defined in System.Random.Internal

Methods

uniformM :: StatefulGen g m => g -> m Int8 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 Word Source # 
Instance details

Defined in System.Random.Internal

Methods

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

Uniform Word8 Source # 
Instance details

Defined in System.Random.Internal

Methods

uniformM :: StatefulGen g m => g -> m Word8 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 CChar Source # 
Instance details

Defined in System.Random.Internal

Methods

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

Uniform CSChar Source # 
Instance details

Defined in System.Random.Internal

Methods

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

Uniform CUChar Source # 
Instance details

Defined in System.Random.Internal

Methods

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

Uniform CShort Source # 
Instance details

Defined in System.Random.Internal

Methods

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

Uniform CUShort Source # 
Instance details

Defined in System.Random.Internal

Methods

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

Uniform CInt Source # 
Instance details

Defined in System.Random.Internal

Methods

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

Uniform CUInt Source # 
Instance details

Defined in System.Random.Internal

Methods

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

Uniform CLong Source # 
Instance details

Defined in System.Random.Internal

Methods

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

Uniform CULong Source # 
Instance details

Defined in System.Random.Internal

Methods

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

Uniform CLLong Source # 
Instance details

Defined in System.Random.Internal

Methods

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

Uniform CULLong Source # 
Instance details

Defined in System.Random.Internal

Methods

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

Uniform CBool Source # 
Instance details

Defined in System.Random.Internal

Methods

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

Uniform CPtrdiff Source # 
Instance details

Defined in System.Random.Internal

Methods

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

Uniform CSize Source # 
Instance details

Defined in System.Random.Internal

Methods

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

Uniform CWchar Source # 
Instance details

Defined in System.Random.Internal

Methods

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

Uniform CSigAtomic Source # 
Instance details

Defined in System.Random.Internal

Methods

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

Uniform CIntPtr Source # 
Instance details

Defined in System.Random.Internal

Methods

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

Uniform CUIntPtr Source # 
Instance details

Defined in System.Random.Internal

Methods

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

Uniform CIntMax Source # 
Instance details

Defined in System.Random.Internal

Methods

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

Uniform CUIntMax Source # 
Instance details

Defined in System.Random.Internal

Methods

uniformM :: StatefulGen g m => g -> m CUIntMax 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

Minimal complete definition

uniformRM

Instances
UniformRange Bool Source # 
Instance details

Defined in System.Random.Internal

Methods

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

UniformRange Char Source # 
Instance details

Defined in System.Random.Internal

Methods

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

UniformRange Double Source #

See Floating point number caveats.

Instance details

Defined in System.Random.Internal

Methods

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

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 #

UniformRange Int Source # 
Instance details

Defined in System.Random.Internal

Methods

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

UniformRange Int8 Source # 
Instance details

Defined in System.Random.Internal

Methods

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

UniformRange Int16 Source # 
Instance details

Defined in System.Random.Internal

Methods

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

UniformRange Int32 Source # 
Instance details

Defined in System.Random.Internal

Methods

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

UniformRange Int64 Source # 
Instance details

Defined in System.Random.Internal

Methods

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

UniformRange Integer Source # 
Instance details

Defined in System.Random.Internal

Methods

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

UniformRange Natural Source # 
Instance details

Defined in System.Random.Internal

Methods

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

UniformRange Word Source # 
Instance details

Defined in System.Random.Internal

Methods

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

UniformRange Word8 Source # 
Instance details

Defined in System.Random.Internal

Methods

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

UniformRange Word16 Source # 
Instance details

Defined in System.Random.Internal

Methods

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

UniformRange Word32 Source # 
Instance details

Defined in System.Random.Internal

Methods

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

UniformRange Word64 Source # 
Instance details

Defined in System.Random.Internal

Methods

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

UniformRange CChar Source # 
Instance details

Defined in System.Random.Internal

Methods

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

UniformRange CSChar Source # 
Instance details

Defined in System.Random.Internal

Methods

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

UniformRange CUChar Source # 
Instance details

Defined in System.Random.Internal

Methods

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

UniformRange CShort Source # 
Instance details

Defined in System.Random.Internal

Methods

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

UniformRange CUShort Source # 
Instance details

Defined in System.Random.Internal

Methods

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

UniformRange CInt Source # 
Instance details

Defined in System.Random.Internal

Methods

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

UniformRange CUInt Source # 
Instance details

Defined in System.Random.Internal

Methods

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

UniformRange CLong Source # 
Instance details

Defined in System.Random.Internal

Methods

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

UniformRange CULong Source # 
Instance details

Defined in System.Random.Internal

Methods

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

UniformRange CLLong Source # 
Instance details

Defined in System.Random.Internal

Methods

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

UniformRange CULLong Source # 
Instance details

Defined in System.Random.Internal

Methods

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

UniformRange CBool Source # 
Instance details

Defined in System.Random.Internal

Methods

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

UniformRange CFloat Source #

See Floating point number caveats.

Instance details

Defined in System.Random.Internal

Methods

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

UniformRange CDouble Source #

See Floating point number caveats.

Instance details

Defined in System.Random.Internal

Methods

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

UniformRange CPtrdiff Source # 
Instance details

Defined in System.Random.Internal

Methods

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

UniformRange CSize Source # 
Instance details

Defined in System.Random.Internal

Methods

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

UniformRange CWchar Source # 
Instance details

Defined in System.Random.Internal

Methods

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

UniformRange CSigAtomic Source # 
Instance details

Defined in System.Random.Internal

UniformRange CIntPtr Source # 
Instance details

Defined in System.Random.Internal

Methods

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

UniformRange CUIntPtr Source # 
Instance details

Defined in System.Random.Internal

Methods

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

UniformRange CIntMax Source # 
Instance details

Defined in System.Random.Internal

Methods

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

UniformRange CUIntMax Source # 
Instance details

Defined in System.Random.Internal

Methods

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

Standard pseudo-random number generator

data StdGen Source #

The standard pseudo-random number generator.

mkStdGen :: Int -> StdGen Source #

Constructs a StdGen deterministically.

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))

getStdGen :: MonadIO m => m StdGen Source #

Gets the global pseudo-random number generator.

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

Sets the global pseudo-random number generator.

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 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