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

Contents

Description

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

Synopsis

Pure Random Generator

Monadic Random Generator

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

Monadic pseudo-random number generators
StatefulGen is an interface to monadic pseudo-random number generators.
Monadic adapters
StateGenM, AtomicGenM, IOGenM and STGenM turn a RandomGen instance into a StatefulGen instance.
Drawing from a range
UniformRange is used to generate a value of a type uniformly within a range.

This library provides instances of UniformRange for many common numeric types.

Drawing from the entire domain of a type
Uniform is used to generate a value of a type uniformly over all possible values of that type.

This library provides instances of Uniform for many common bounded numeric types.

Usage

In monadic code, use the relevant Uniform and UniformRange instances to generate pseudo-random values via uniformM and uniformRM, respectively.

As an example, rollsM generates n pseudo-random values of Word in the range [1, 6] in a StatefulGen context; given a monadic pseudo-random number generator, you can run this probabilistic computation as follows:

>>> :{
let rollsM :: StatefulGen g m => Int -> g -> m [Word]
    rollsM n = replicateM n . uniformRM (1, 6)
in do
    monadicGen <- MWC.create
    rollsM 10 monadicGen :: IO [Word]
:}
[3,4,3,1,4,6,1,6,1,4]

Given a pure pseudo-random number generator, you can run the monadic pseudo-random number computation rollsM in an IO or ST context by applying a monadic adapter like AtomicGenM, IOGenM or STGenM (see monadic-adapters) to the pure pseudo-random number generator.

>>> :{
let rollsM :: StatefulGen g m => Int -> g -> m [Word]
    rollsM n = replicateM n . uniformRM (1, 6)
    pureGen = mkStdGen 42
in
    newIOGenM pureGen >>= rollsM 10 :: IO [Word]
:}
[1,1,3,2,4,5,3,4,6,2]

Mutable pseudo-random number generator interfaces

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

RandomGen: pure pseudo-random number generators
See System.Random module.
StatefulGen: monadic pseudo-random number generators
These generators mutate their own state as they produce pseudo-random values. They generally live in ST or IO or some transformer that implements PrimMonad.

class Monad m => StatefulGen g m where Source #

StatefulGen is an interface to monadic pseudo-random number generators.

Minimal complete definition

(uniformWord32 | uniformWord64)

Methods

uniformWord32R :: Word32 -> g -> m Word32 Source #

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

Since: 1.2.0

uniformWord64R :: Word64 -> g -> m Word64 Source #

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

Since: 1.2.0

uniformWord8 :: g -> m Word8 Source #

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

The default implementation extracts a Word8 from uniformWord32.

Since: 1.2.0

uniformWord16 :: g -> m Word16 Source #

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

The default implementation extracts a Word16 from uniformWord32.

Since: 1.2.0

uniformWord32 :: g -> m Word32 Source #

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

The default implementation extracts a Word32 from uniformWord64.

Since: 1.2.0

uniformWord64 :: g -> m Word64 Source #

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

The default implementation combines two Word32 from uniformWord32 into one Word64.

Since: 1.2.0

uniformShortByteString :: Int -> g -> m ShortByteString Source #

uniformShortByteString n g generates a ShortByteString of length n filled with pseudo-random bytes.

Since: 1.2.0

uniformShortByteString :: MonadIO m => Int -> g -> m ShortByteString Source #

uniformShortByteString n g generates a ShortByteString of length n filled with pseudo-random bytes.

Since: 1.2.0

Instances
(RandomGen g, MonadState g m) => StatefulGen (StateGenM g) m Source # 
Instance details

Defined in System.Random.Internal

(RandomGen g, MonadIO m) => StatefulGen (IOGenM g) m Source # 
Instance details

Defined in System.Random.Stateful

(RandomGen g, MonadIO m) => StatefulGen (AtomicGenM g) m Source # 
Instance details

Defined in System.Random.Stateful

RandomGen g => StatefulGen (STGenM g s) (ST s) Source # 
Instance details

Defined in System.Random.Stateful

class StatefulGen (MutableGen f m) m => FrozenGen f m where Source #

This class is designed for stateful pseudo-random number generators that can be saved as and restored from an immutable data type.

Since: 1.2.0

Associated Types

type MutableGen f m = (g :: Type) | g -> f Source #

Represents the state of the pseudo-random number generator for use with thawGen and freezeGen.

Since: 1.2.0

Methods

freezeGen :: MutableGen f m -> m f Source #

Saves the state of the pseudo-random number generator as a frozen seed.

Since: 1.2.0

thawGen :: f -> m (MutableGen f m) Source #

Restores the pseudo-random number generator from its frozen seed.

Since: 1.2.0

Instances
(RandomGen g, MonadState g m) => FrozenGen (StateGen g) m Source # 
Instance details

Defined in System.Random.Internal

Associated Types

type MutableGen (StateGen g) m = (g :: Type) Source #

(RandomGen g, MonadIO m) => FrozenGen (IOGen g) m Source # 
Instance details

Defined in System.Random.Stateful

Associated Types

type MutableGen (IOGen g) m = (g :: Type) Source #

Methods

freezeGen :: MutableGen (IOGen g) m -> m (IOGen g) Source #

thawGen :: IOGen g -> m (MutableGen (IOGen g) m) Source #

(RandomGen g, MonadIO m) => FrozenGen (AtomicGen g) m Source # 
Instance details

Defined in System.Random.Stateful

Associated Types

type MutableGen (AtomicGen g) m = (g :: Type) Source #

RandomGen g => FrozenGen (STGen g) (ST s) Source # 
Instance details

Defined in System.Random.Stateful

Associated Types

type MutableGen (STGen g) (ST s) = (g :: Type) Source #

Methods

freezeGen :: MutableGen (STGen g) (ST s) -> ST s (STGen g) Source #

thawGen :: STGen g -> ST s (MutableGen (STGen g) (ST s)) Source #

class (RandomGen r, StatefulGen g m) => RandomGenM g r m | g -> r where Source #

Interface to operations on RandomGen wrappers like IOGenM and StateGenM.

Since: 1.2.0

Methods

applyRandomGenM :: (r -> (a, r)) -> g -> m a Source #

Instances
(RandomGen r, MonadState r m) => RandomGenM (StateGenM r) r m Source # 
Instance details

Defined in System.Random.Stateful

Methods

applyRandomGenM :: (r -> (a, r)) -> StateGenM r -> m a Source #

(RandomGen r, MonadIO m) => RandomGenM (IOGenM r) r m Source # 
Instance details

Defined in System.Random.Stateful

Methods

applyRandomGenM :: (r -> (a, r)) -> IOGenM r -> m a Source #

(RandomGen r, MonadIO m) => RandomGenM (AtomicGenM r) r m Source # 
Instance details

Defined in System.Random.Stateful

Methods

applyRandomGenM :: (r -> (a, r)) -> AtomicGenM r -> m a Source #

RandomGen r => RandomGenM (STGenM r s) r (ST s) Source # 
Instance details

Defined in System.Random.Stateful

Methods

applyRandomGenM :: (r -> (a, r)) -> STGenM r s -> ST s a Source #

withMutableGen :: FrozenGen f m => f -> (MutableGen f m -> m a) -> m (a, f) Source #

Runs a mutable pseudo-random number generator from its Frozen state.

Examples

Expand
>>> import Data.Int (Int8)
>>> withMutableGen (IOGen (mkStdGen 217)) (uniformListM 5) :: IO ([Int8], IOGen StdGen)
([-74,37,-50,-2,3],IOGen {unIOGen = StdGen {unStdGen = SMGen 4273268533320920145 15251669095119325999}})

Since: 1.2.0

withMutableGen_ :: FrozenGen f m => f -> (MutableGen f m -> m a) -> m a Source #

Same as withMutableGen, but only returns the generated value.

Examples

Expand
>>> import System.Random.Stateful
>>> let pureGen = mkStdGen 137
>>> withMutableGen_ (IOGen pureGen) (uniformRM (1 :: Int, 6 :: Int))
4

Since: 1.2.0

randomM :: (RandomGenM g r m, Random a) => g -> m a Source #

Generates a pseudo-random value using monadic interface and Random instance.

Examples

Expand
>>> import System.Random.Stateful
>>> let pureGen = mkStdGen 137
>>> g <- newIOGenM pureGen
>>> randomM g :: IO Double
0.5728354935654512

Since: 1.2.0

randomRM :: (RandomGenM g r m, Random a) => (a, a) -> g -> m a Source #

Generates a pseudo-random value using monadic interface and Random instance.

Examples

Expand
>>> import System.Random.Stateful
>>> let pureGen = mkStdGen 137
>>> g <- newIOGenM pureGen
>>> randomRM (1, 100) g :: IO Int
52

Since: 1.2.0

splitGenM :: RandomGenM g r m => g -> m r Source #

Splits a pseudo-random number generator into two. Overwrites the mutable wrapper with one of the resulting generators and returns the other.

Since: 1.2.0

Monadic adapters for pure pseudo-random number generators

Pure pseudo-random number generators can be used in monadic code via the adapters StateGenM, AtomicGenM, IOGenM and STGenM.

  • StateGenM can be used in any state monad. With strict StateT there is no performance overhead compared to using the RandomGen instance directly. StateGenM is not safe to use in the presence of exceptions and concurrency.
  • AtomicGenM is safe in the presence of exceptions and concurrency since it performs all actions atomically.
  • IOGenM is a wrapper around an IORef that holds a pure generator. IOGenM is safe in the presence of exceptions, but not concurrency.
  • STGenM is a wrapper around an STRef that holds a pure generator. STGenM is safe in the presence of exceptions, but not concurrency.

Pure adapter

newtype StateGen g Source #

Wrapper for pure state gen, which acts as an immutable seed for the corresponding stateful generator StateGenM

Since: 1.2.0

Constructors

StateGen 

Fields

Instances
Eq g => Eq (StateGen g) Source # 
Instance details

Defined in System.Random.Internal

Methods

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

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

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

Defined in System.Random.Internal

Methods

compare :: StateGen g -> StateGen g -> Ordering #

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

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

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

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

max :: StateGen g -> StateGen g -> StateGen g #

min :: StateGen g -> StateGen g -> StateGen g #

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

Defined in System.Random.Internal

Methods

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

show :: StateGen g -> String #

showList :: [StateGen g] -> ShowS #

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

Defined in System.Random.Internal

Methods

sizeOf :: StateGen g -> Int #

alignment :: StateGen g -> Int #

peekElemOff :: Ptr (StateGen g) -> Int -> IO (StateGen g) #

pokeElemOff :: Ptr (StateGen g) -> Int -> StateGen g -> IO () #

peekByteOff :: Ptr b -> Int -> IO (StateGen g) #

pokeByteOff :: Ptr b -> Int -> StateGen g -> IO () #

peek :: Ptr (StateGen g) -> IO (StateGen g) #

poke :: Ptr (StateGen g) -> StateGen g -> IO () #

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

Defined in System.Random.Internal

Methods

rnf :: StateGen g -> () #

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

Defined in System.Random.Internal

(RandomGen g, MonadState g m) => FrozenGen (StateGen g) m Source # 
Instance details

Defined in System.Random.Internal

Associated Types

type MutableGen (StateGen g) m = (g :: Type) Source #

type MutableGen (StateGen g) m Source # 
Instance details

Defined in System.Random.Internal

data StateGenM g Source #

Opaque data type that carries the type of a pure pseudo-random number generator.

Since: 1.2.0

Constructors

StateGenM 

runStateGen :: RandomGen g => g -> (StateGenM g -> State g a) -> (a, g) Source #

Runs a monadic generating action in the State monad using a pure pseudo-random number generator.

Examples

Expand
>>> import System.Random.Stateful
>>> let pureGen = mkStdGen 137
>>> runStateGen pureGen randomM :: (Int, StdGen)
(7879794327570578227,StdGen {unStdGen = SMGen 11285859549637045894 7641485672361121627})

Since: 1.2.0

runStateGen_ :: RandomGen g => g -> (StateGenM g -> State g a) -> a Source #

Runs a monadic generating action in the State monad using a pure pseudo-random number generator. Returns only the resulting pseudo-random value.

Examples

Expand
>>> import System.Random.Stateful
>>> let pureGen = mkStdGen 137
>>> runStateGen_ pureGen  randomM :: Int
7879794327570578227

Since: 1.2.0

runStateGenT :: RandomGen g => g -> (StateGenM g -> StateT g m a) -> m (a, g) Source #

Runs a monadic generating action in the StateT monad using a pure pseudo-random number generator.

Examples

Expand
>>> import System.Random.Stateful
>>> let pureGen = mkStdGen 137
>>> runStateGenT pureGen randomM :: IO (Int, StdGen)
(7879794327570578227,StdGen {unStdGen = SMGen 11285859549637045894 7641485672361121627})

Since: 1.2.0

runStateGenT_ :: (RandomGen g, Functor f) => g -> (StateGenM g -> StateT g f a) -> f a Source #

Runs a monadic generating action in the StateT monad using a pure pseudo-random number generator. Returns only the resulting pseudo-random value.

Examples

Expand
>>> import System.Random.Stateful
>>> let pureGen = mkStdGen 137
>>> runStateGenT_ pureGen randomM :: IO Int
7879794327570578227

Since: 1.2.0

runStateGenST :: RandomGen g => g -> (forall s. StateGenM g -> StateT g (ST s) a) -> (a, g) Source #

Runs a monadic generating action in the ST monad using a pure pseudo-random number generator.

Since: 1.2.0

Mutable adapter with atomic operations

newtype AtomicGen g Source #

Frozen version of mutable AtomicGenM generator

Since: 1.2.0

Constructors

AtomicGen 

Fields

Instances
Eq g => Eq (AtomicGen g) Source # 
Instance details

Defined in System.Random.Stateful

Methods

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

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

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

Defined in System.Random.Stateful

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

Defined in System.Random.Stateful

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

Defined in System.Random.Stateful

Methods

sizeOf :: AtomicGen g -> Int #

alignment :: AtomicGen g -> Int #

peekElemOff :: Ptr (AtomicGen g) -> Int -> IO (AtomicGen g) #

pokeElemOff :: Ptr (AtomicGen g) -> Int -> AtomicGen g -> IO () #

peekByteOff :: Ptr b -> Int -> IO (AtomicGen g) #

pokeByteOff :: Ptr b -> Int -> AtomicGen g -> IO () #

peek :: Ptr (AtomicGen g) -> IO (AtomicGen g) #

poke :: Ptr (AtomicGen g) -> AtomicGen g -> IO () #

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

Defined in System.Random.Stateful

Methods

rnf :: AtomicGen g -> () #

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

Defined in System.Random.Stateful

(RandomGen g, MonadIO m) => FrozenGen (AtomicGen g) m Source # 
Instance details

Defined in System.Random.Stateful

Associated Types

type MutableGen (AtomicGen g) m = (g :: Type) Source #

type MutableGen (AtomicGen g) m Source # 
Instance details

Defined in System.Random.Stateful

newtype AtomicGenM g Source #

Wraps an IORef that holds a pure pseudo-random number generator. All operations are performed atomically.

  • AtomicGenM is safe in the presence of exceptions and concurrency.
  • AtomicGenM is the slowest of the monadic adapters due to the overhead of its atomic operations.

Since: 1.2.0

Constructors

AtomicGenM 

Fields

newAtomicGenM :: MonadIO m => g -> m (AtomicGenM g) Source #

Creates a new AtomicGenM.

Since: 1.2.0

applyAtomicGen :: MonadIO m => (g -> (a, g)) -> AtomicGenM g -> m a Source #

Atomically applies a pure operation to the wrapped pseudo-random number generator.

Examples

Expand
>>> import System.Random.Stateful
>>> let pureGen = mkStdGen 137
>>> g <- newAtomicGenM pureGen
>>> applyAtomicGen random g :: IO Int
7879794327570578227

Since: 1.2.0

Mutable adapter in IO

newtype IOGen g Source #

Frozen version of mutable IOGenM generator

Since: 1.2.0

Constructors

IOGen 

Fields

Instances
Eq g => Eq (IOGen g) Source # 
Instance details

Defined in System.Random.Stateful

Methods

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

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

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

Defined in System.Random.Stateful

Methods

compare :: IOGen g -> IOGen g -> Ordering #

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

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

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

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

max :: IOGen g -> IOGen g -> IOGen g #

min :: IOGen g -> IOGen g -> IOGen g #

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

Defined in System.Random.Stateful

Methods

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

show :: IOGen g -> String #

showList :: [IOGen g] -> ShowS #

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

Defined in System.Random.Stateful

Methods

sizeOf :: IOGen g -> Int #

alignment :: IOGen g -> Int #

peekElemOff :: Ptr (IOGen g) -> Int -> IO (IOGen g) #

pokeElemOff :: Ptr (IOGen g) -> Int -> IOGen g -> IO () #

peekByteOff :: Ptr b -> Int -> IO (IOGen g) #

pokeByteOff :: Ptr b -> Int -> IOGen g -> IO () #

peek :: Ptr (IOGen g) -> IO (IOGen g) #

poke :: Ptr (IOGen g) -> IOGen g -> IO () #

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

Defined in System.Random.Stateful

Methods

rnf :: IOGen g -> () #

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

Defined in System.Random.Stateful

(RandomGen g, MonadIO m) => FrozenGen (IOGen g) m Source # 
Instance details

Defined in System.Random.Stateful

Associated Types

type MutableGen (IOGen g) m = (g :: Type) Source #

Methods

freezeGen :: MutableGen (IOGen g) m -> m (IOGen g) Source #

thawGen :: IOGen g -> m (MutableGen (IOGen g) m) Source #

type MutableGen (IOGen g) m Source # 
Instance details

Defined in System.Random.Stateful

type MutableGen (IOGen g) m = IOGenM g

newtype IOGenM g Source #

Wraps an IORef that holds a pure pseudo-random number generator.

An example use case is writing pseudo-random bytes into a file:

>>> import UnliftIO.Temporary (withSystemTempFile)
>>> import Data.ByteString (hPutStr)
>>> let ioGen g = withSystemTempFile "foo.bin" $ \_ h -> uniformRM (0, 100) g >>= flip uniformByteStringM g >>= hPutStr h

and then run it:

>>> newIOGenM (mkStdGen 1729) >>= ioGen

Since: 1.2.0

Constructors

IOGenM 

Fields

newIOGenM :: MonadIO m => g -> m (IOGenM g) Source #

Creates a new IOGenM.

Since: 1.2.0

applyIOGen :: MonadIO m => (g -> (a, g)) -> IOGenM g -> m a Source #

Applies a pure operation to the wrapped pseudo-random number generator.

Examples

Expand
>>> import System.Random.Stateful
>>> let pureGen = mkStdGen 137
>>> g <- newIOGenM pureGen
>>> applyIOGen random g :: IO Int
7879794327570578227

Since: 1.2.0

Mutable adapter in ST

newtype STGen g Source #

Frozen version of mutable STGenM generator

Since: 1.2.0

Constructors

STGen 

Fields

Instances
Eq g => Eq (STGen g) Source # 
Instance details

Defined in System.Random.Stateful

Methods

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

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

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

Defined in System.Random.Stateful

Methods

compare :: STGen g -> STGen g -> Ordering #

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

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

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

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

max :: STGen g -> STGen g -> STGen g #

min :: STGen g -> STGen g -> STGen g #

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

Defined in System.Random.Stateful

Methods

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

show :: STGen g -> String #

showList :: [STGen g] -> ShowS #

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

Defined in System.Random.Stateful

Methods

sizeOf :: STGen g -> Int #

alignment :: STGen g -> Int #

peekElemOff :: Ptr (STGen g) -> Int -> IO (STGen g) #

pokeElemOff :: Ptr (STGen g) -> Int -> STGen g -> IO () #

peekByteOff :: Ptr b -> Int -> IO (STGen g) #

pokeByteOff :: Ptr b -> Int -> STGen g -> IO () #

peek :: Ptr (STGen g) -> IO (STGen g) #

poke :: Ptr (STGen g) -> STGen g -> IO () #

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

Defined in System.Random.Stateful

Methods

rnf :: STGen g -> () #

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

Defined in System.Random.Stateful

RandomGen g => FrozenGen (STGen g) (ST s) Source # 
Instance details

Defined in System.Random.Stateful

Associated Types

type MutableGen (STGen g) (ST s) = (g :: Type) Source #

Methods

freezeGen :: MutableGen (STGen g) (ST s) -> ST s (STGen g) Source #

thawGen :: STGen g -> ST s (MutableGen (STGen g) (ST s)) Source #

type MutableGen (STGen g) (ST s) Source # 
Instance details

Defined in System.Random.Stateful

type MutableGen (STGen g) (ST s) = STGenM g s

newtype STGenM g s Source #

Wraps an STRef that holds a pure pseudo-random number generator.

  • STGenM is safe in the presence of exceptions, but not concurrency.
  • STGenM is slower than StateGenM due to the extra pointer indirection.

Since: 1.2.0

Constructors

STGenM 

Fields

Instances
RandomGen r => RandomGenM (STGenM r s) r (ST s) Source # 
Instance details

Defined in System.Random.Stateful

Methods

applyRandomGenM :: (r -> (a, r)) -> STGenM r s -> ST s a Source #

RandomGen g => StatefulGen (STGenM g s) (ST s) Source # 
Instance details

Defined in System.Random.Stateful

newSTGenM :: g -> ST s (STGenM g s) Source #

Creates a new STGenM.

Since: 1.2.0

applySTGen :: (g -> (a, g)) -> STGenM g s -> ST s a Source #

Applies a pure operation to the wrapped pseudo-random number generator.

Examples

Expand
>>> import System.Random.Stateful
>>> let pureGen = mkStdGen 137
>>> (runSTGen pureGen (\g -> applySTGen random g)) :: (Int, StdGen)
(7879794327570578227,StdGen {unStdGen = SMGen 11285859549637045894 7641485672361121627})

Since: 1.2.0

runSTGen :: RandomGen g => g -> (forall s. STGenM g s -> ST s a) -> (a, g) Source #

Runs a monadic generating action in the ST monad using a pure pseudo-random number generator.

Examples

Expand
>>> import System.Random.Stateful
>>> let pureGen = mkStdGen 137
>>> (runSTGen pureGen (\g -> applySTGen random g)) :: (Int, StdGen)
(7879794327570578227,StdGen {unStdGen = SMGen 11285859549637045894 7641485672361121627})

Since: 1.2.0

runSTGen_ :: RandomGen g => g -> (forall s. STGenM g s -> ST s a) -> a Source #

Runs a monadic generating action in the ST monad using a pure pseudo-random number generator. Returns only the resulting pseudo-random value.

Examples

Expand
>>> import System.Random.Stateful
>>> let pureGen = mkStdGen 137
>>> (runSTGen_ pureGen (\g -> applySTGen random g)) :: Int
7879794327570578227

Since: 1.2.0

Pseudo-random values of various types

This library provides two type classes to generate pseudo-random values:

  • UniformRange is used to generate a value of a type uniformly within a range.
  • Uniform is used to generate a value of a type uniformly over all possible values of that type.

Types may have instances for both or just one of UniformRange and Uniform. A few examples illustrate this:

  • Int, Word16 and Bool are instances of both UniformRange and Uniform.
  • Integer, Float and Double each have an instance for UniformRange but no Uniform instance.
  • A hypothetical type Radian representing angles by taking values in the range [0, 2π) has a trivial Uniform instance, but no UniformRange instance: the problem is that two given Radian values always span two ranges, one clockwise and one anti-clockwise.
  • It is trivial to construct a Uniform (a, b) instance given Uniform a and Uniform b (and this library provides this tuple instance).
  • On the other hand, there is no correct way to construct a UniformRange (a, b) instance based on just UniformRange a and UniformRange b.

class Uniform a where 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

Methods

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

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

Since: 1.2.0

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 #

uniformListM :: (StatefulGen g m, Uniform a) => Int -> g -> m [a] Source #

Generates a list of pseudo-random values.

Examples

Expand
>>> import System.Random.Stateful
>>> let pureGen = mkStdGen 137
>>> g <- newIOGenM pureGen
>>> uniformListM 10 g :: IO [Bool]
[True,True,True,True,False,True,True,False,False,False]

Since: 1.2.0

class UniformRange a where Source #

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

Since: 1.2.0

Methods

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

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

  • uniformRM (1 :: Int, 4 :: Int) generates values uniformly from the set \(\{1,2,3,4\}\)
  • uniformRM (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:

uniformRM (a, b) = uniformRM (b, a)

Since: 1.2.0

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 #

Generators for sequences of pseudo-random bytes

genShortByteStringIO Source #

Arguments

:: MonadIO m 
=> Int

Number of bytes to generate

-> m Word64

IO action that can generate 8 random bytes at a time

-> m ShortByteString 

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

Since: 1.2.0

genShortByteStringST :: Int -> ST s Word64 -> ST s ShortByteString Source #

Same as genShortByteStringIO, but runs in ST.

Since: 1.2.0

uniformByteStringM :: StatefulGen g m => Int -> g -> m ByteString Source #

Generates a pseudo-random ByteString of the specified size.

Since: 1.2.0

uniformDouble01M :: StatefulGen g m => g -> m Double Source #

Generates uniformly distributed Double in the range \([0, 1]\). Numbers are generated by generating uniform Word64 and dividing it by \(2^{64}\). It's used to implement UniformR instance for Double.

Since: 1.2.0

uniformDoublePositive01M :: StatefulGen g m => g -> m Double Source #

Generates uniformly distributed Double in the range \((0, 1]\). Number is generated as \(2^{-64}/2+\operatorname{uniformDouble01M}\). Constant is 1/2 of smallest nonzero value which could be generated by uniformDouble01M.

Since: 1.2.0

uniformFloat01M :: StatefulGen g m => g -> m Float Source #

Generates uniformly distributed Float in the range \([0, 1]\). Numbers are generated by generating uniform Word32 and dividing it by \(2^{32}\). It's used to implement UniformR instance for Float

Since: 1.2.0

uniformFloatPositive01M :: StatefulGen g m => g -> m Float Source #

Generates uniformly distributed Float in the range \((0, 1]\). Number is generated as \(2^{-32}/2+\operatorname{uniformFloat01M}\). Constant is 1/2 of smallest nonzero value which could be generated by uniformFloat01M.

Since: 1.2.0

Appendix

How to implement StatefulGen

Typically, a monadic pseudo-random number generator has facilities to save and restore its internal state in addition to generating pseudo-random numbers.

Here is an example instance for the monadic pseudo-random number generator from the mwc-random package:

instance (s ~ PrimState m, PrimMonad m) => StatefulGen (MWC.Gen s) m where
  uniformWord8 = MWC.uniform
  uniformWord16 = MWC.uniform
  uniformWord32 = MWC.uniform
  uniformWord64 = MWC.uniform
  uniformShortByteString n g = unsafeSTToPrim (genShortByteStringST n (MWC.uniform g))
instance PrimMonad m => FrozenGen MWC.Seed m where
  type MutableGen MWC.Seed m = MWC.Gen (PrimState m)
  thawGen = MWC.restore
  freezeGen = MWC.save

FrozenGen

FrozenGen gives us ability to use any stateful pseudo-random number generator in its immutable form, if one exists that is. This concept is commonly known as a seed, which allows us to save and restore the actual mutable state of a pseudo-random number generator. The biggest benefit that can be drawn from a polymorphic access to a stateful pseudo-random number generator in a frozen form is the ability to serialize, deserialize and possibly even use the stateful generator in a pure setting without knowing the actual type of a generator ahead of time. For example we can write a function that accepts a frozen state of some pseudo-random number generator and produces a short list with random even integers.

>>> import Data.Int (Int8)
>>> :{
myCustomRandomList :: FrozenGen f m => f -> m [Int8]
myCustomRandomList f =
  withMutableGen_ f $ \gen -> do
    len <- uniformRM (5, 10) gen
    replicateM len $ do
      x <- uniformM gen
      pure $ if even x then x else x + 1
:}

and later we can apply it to a frozen version of a stateful generator, such as STGen:

>>> print $ runST $ myCustomRandomList (STGen (mkStdGen 217))
[-50,-2,4,-8,-58,-40,24,-32,-110,24]

or a Seed from mwc-random:

>>> import Data.Vector.Primitive as P
>>> print $ runST $ myCustomRandomList (MWC.toSeed (P.fromList [1,2,3]))
[24,40,10,40,-8,48,-78,70,-12]

Alternatively, instead of discarding the final state of the generator, as it happens above, we could have used withMutableGen, which together with the result would give us back its frozen form. This would allow us to store the end state of our generator somewhere for the later reuse.

Floating point number caveats

The UniformRange instances for Float and Double use the following procedure to generate a random value in a range for uniformRM (a, b) g:

If \(a = b\), return \(a\). Otherwise:

  1. Generate \(x\) uniformly such that \(0 \leq x \leq 1\).

    The method by which \(x\) is sampled does not cover all representable floating point numbers in the unit interval. The method never generates denormal floating point numbers, for example.

  2. Return \(x \cdot a + (1 - x) \cdot b\).

    Due to rounding errors, floating point operations are neither associative nor distributive the way the corresponding operations on real numbers are. Additionally, floating point numbers admit special values NaN as well as negative and positive infinity.

For pathological values, step 2 can yield surprising results.

  • The result may be greater than max a b.

    >>> :{
    let (a, b, x) = (-2.13238e-29, -2.1323799e-29, 0.27736077)
        result = x * a + (1 - x) * b :: Float
    in (result, result > max a b)
    :}
    (-2.1323797e-29,True)
    
  • The result may be smaller than min a b.

    >>> :{
    let (a, b, x) = (-1.9087862, -1.908786, 0.4228573)
        result = x * a + (1 - x) * b :: Float
    in (result, result < min a b)
    :}
    (-1.9087863,True)
    

What happens when NaN or Infinity are given to uniformRM? We first define them as constants:

>>> nan = read "NaN" :: Float
>>> inf = read "Infinity" :: Float
  • If at least one of \(a\) or \(b\) is NaN, the result is NaN.

    >>> let (a, b, x) = (nan, 1, 0.5) in x * a + (1 - x) * b
    NaN
    >>> let (a, b, x) = (-1, nan, 0.5) in x * a + (1 - x) * b
    NaN
    
  • If \(a\) is -Infinity and \(b\) is Infinity, the result is NaN. >>> let (a, b, x) = (-inf, inf, 0.5) in x * a + (1 - x) * b NaN
  • Otherwise, if \(a\) is Infinity or -Infinity, the result is \(a\).

    >>> let (a, b, x) = (inf, 1, 0.5) in x * a + (1 - x) * b
    Infinity
    >>> let (a, b, x) = (-inf, 1, 0.5) in x * a + (1 - x) * b
    -Infinity
    
  • Otherwise, if \(b\) is Infinity or -Infinity, the result is \(b\).

    >>> let (a, b, x) = (1, inf, 0.5) in x * a + (1 - x) * b
    Infinity
    >>> let (a, b, x) = (1, -inf, 0.5) in x * a + (1 - x) * b
    -Infinity
    

Note that the GCC 10.1.0 C++ standard library, the Java 10 standard library and CPython 3.8 use the same procedure to generate floating point values in a range.

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