| 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 |
System.Random.Stateful
Contents
Description
This library deals with the common task of pseudo-random number generation.
Synopsis
- module System.Random
- class Monad m => StatefulGen g m where
- uniformWord32R :: Word32 -> g -> m Word32
- uniformWord64R :: Word64 -> g -> m Word64
- uniformWord8 :: g -> m Word8
- uniformWord16 :: g -> m Word16
- uniformWord32 :: g -> m Word32
- uniformWord64 :: g -> m Word64
- uniformShortByteString :: Int -> g -> m ShortByteString
- class StatefulGen (MutableGen f m) m => FrozenGen f m where
- type MutableGen f m = (g :: Type) | g -> f
- freezeGen :: MutableGen f m -> m f
- thawGen :: f -> m (MutableGen f m)
- class (RandomGen r, StatefulGen g m) => RandomGenM g r m | g -> r where
- applyRandomGenM :: (r -> (a, r)) -> g -> m a
- withMutableGen :: FrozenGen f m => f -> (MutableGen f m -> m a) -> m (a, f)
- withMutableGen_ :: FrozenGen f m => f -> (MutableGen f m -> m a) -> m a
- randomM :: (RandomGenM g r m, Random a) => g -> m a
- randomRM :: (RandomGenM g r m, Random a) => (a, a) -> g -> m a
- splitGenM :: RandomGenM g r m => g -> m r
- newtype StateGen g = StateGen {
- unStateGen :: g
- data StateGenM g = StateGenM
- runStateGen :: RandomGen g => g -> (StateGenM g -> State g a) -> (a, g)
- runStateGen_ :: RandomGen g => g -> (StateGenM g -> State g a) -> a
- runStateGenT :: RandomGen g => g -> (StateGenM g -> StateT g m a) -> m (a, g)
- runStateGenT_ :: (RandomGen g, Functor f) => g -> (StateGenM g -> StateT g f a) -> f a
- runStateGenST :: RandomGen g => g -> (forall s. StateGenM g -> StateT g (ST s) a) -> (a, g)
- newtype AtomicGen g = AtomicGen {
- unAtomicGen :: g
- newtype AtomicGenM g = AtomicGenM {
- unAtomicGenM :: IORef g
- newAtomicGenM :: AtomicGenM g)
- applyAtomicGen :: MonadIO m => (g -> (a, g)) -> AtomicGenM g -> m a
- newtype IOGen g = IOGen {
- unIOGen :: g
- newtype IOGenM g = IOGenM {}
- newIOGenM :: MonadIO m => g -> m (IOGenM g)
- applyIOGen :: MonadIO m => (g -> (a, g)) -> IOGenM g -> m a
- newtype STGen g = STGen {
- unSTGen :: g
- newtype STGenM g s = STGenM {}
- newSTGenM :: g -> ST s (STGenM g s)
- applySTGen :: (g -> (a, g)) -> STGenM g s -> ST s a
- runSTGen :: RandomGen g => g -> (forall s. STGenM g s -> ST s a) -> (a, g)
- runSTGen_ :: RandomGen g => g -> (forall s. STGenM g s -> ST s a) -> a
- class Uniform a where
- uniformM :: StatefulGen g m => g -> m a
- uniformListM :: (StatefulGen g m, Uniform a) => Int -> g -> m [a]
- class UniformRange a where
- uniformRM :: StatefulGen g m => (a, a) -> g -> m a
- genShortByteStringIO :: MonadIO m => Int -> m Word64 -> m ShortByteString
- genShortByteStringST :: Int -> ST s Word64 -> ST s ShortByteString
- uniformByteStringM :: StatefulGen g m => Int -> g -> m ByteString
- uniformDouble01M :: StatefulGen g m => g -> m Double
- uniformDoublePositive01M :: StatefulGen g m => g -> m Double
- uniformFloat01M :: StatefulGen g m => g -> m Float
- uniformFloatPositive01M :: StatefulGen g m => g -> m Float
Pure Random Generator
module System.Random
Monadic Random Generator
This module provides type classes and instances for the following concepts:
- Monadic pseudo-random number generators
StatefulGenis an interface to monadic pseudo-random number generators.- Monadic adapters
StateGenM,AtomicGenM,IOGenMandSTGenMturn aRandomGeninstance into aStatefulGeninstance.- Drawing from a range
UniformRangeis used to generate a value of a type uniformly within a range.This library provides instances of
UniformRangefor many common numeric types.- Drawing from the entire domain of a type
Uniformis used to generate a value of a type uniformly over all possible values of that type.This library provides instances of
Uniformfor 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
STorIOor some transformer that implementsPrimMonad.
class Monad m => StatefulGen g m where Source #
StatefulGen is an interface to monadic pseudo-random number generators.
Minimal complete definition
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
Instance details
Defined in System.Random.Internal
Methods
uniformWord32R :: Word32 -> StateGenM g -> m Word32 Source #
uniformWord64R :: Word64 -> StateGenM g -> m Word64 Source #
uniformWord8 :: StateGenM g -> m Word8 Source #
uniformWord16 :: StateGenM g -> m Word16 Source #
uniformWord32 :: StateGenM g -> m Word32 Source #
uniformWord64 :: StateGenM g -> m Word64 Source #
uniformShortByteString :: Int -> StateGenM g -> m ShortByteString Source #
Instance details
Defined in System.Random.Stateful
Methods
uniformWord32R :: Word32 -> IOGenM g -> m Word32 Source #
uniformWord64R :: Word64 -> IOGenM g -> m Word64 Source #
uniformWord8 :: IOGenM g -> m Word8 Source #
uniformWord16 :: IOGenM g -> m Word16 Source #
uniformWord32 :: IOGenM g -> m Word32 Source #
uniformWord64 :: IOGenM g -> m Word64 Source #
uniformShortByteString :: Int -> IOGenM g -> m ShortByteString Source #
Instance details
Defined in System.Random.Stateful
Methods
uniformWord32R :: Word32 -> AtomicGenM g -> m Word32 Source #
uniformWord64R :: Word64 -> AtomicGenM g -> m Word64 Source #
uniformWord8 :: AtomicGenM g -> m Word8 Source #
uniformWord16 :: AtomicGenM g -> m Word16 Source #
uniformWord32 :: AtomicGenM g -> m Word32 Source #
uniformWord64 :: AtomicGenM g -> m Word64 Source #
uniformShortByteString :: Int -> AtomicGenM g -> m ShortByteString Source #
Instance details
Defined in System.Random.Stateful
Methods
uniformWord32R :: Word32 -> STGenM g s -> ST s Word32 Source #
uniformWord64R :: Word64 -> STGenM g s -> ST s Word64 Source #
uniformWord8 :: STGenM g s -> ST s Word8 Source #
uniformWord16 :: STGenM g s -> ST s Word16 Source #
uniformWord32 :: STGenM g s -> ST s Word32 Source #
uniformWord64 :: STGenM g s -> ST s Word64 Source #
uniformShortByteString :: Int -> STGenM g s -> ST s ShortByteString Source #
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 #
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
Instance details
Defined in System.Random.Internal
Associated Types
type MutableGen (StateGen g) m = (g :: Type) Source #
Instance details
Defined in System.Random.Stateful
Associated Types
type MutableGen (IOGen g) m = (g :: Type) Source #
Instance details
Defined in System.Random.Stateful
Associated Types
type MutableGen (AtomicGen g) m = (g :: Type) Source #
class (RandomGen r, StatefulGen g m) => RandomGenM g r m | g -> r where Source #
Methods
applyRandomGenM :: (r -> (a, r)) -> g -> m a Source #
Instances
Instance details
Defined in System.Random.Stateful
Methods
applyRandomGenM :: (r -> (a, r)) -> StateGenM r -> m a Source #
Instance details
Defined in System.Random.Stateful
Methods
applyRandomGenM :: (r -> (a, r)) -> IOGenM r -> m a Source #
Instance details
Defined in System.Random.Stateful
Methods
applyRandomGenM :: (r -> (a, r)) -> AtomicGenM r -> m a 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 Double0.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 Int52
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 .
StateGenMcan be used in any state monad. With strictStateTthere is no performance overhead compared to using theRandomGeninstance directly.StateGenMis not safe to use in the presence of exceptions and concurrency.AtomicGenMis safe in the presence of exceptions and concurrency since it performs all actions atomically.IOGenMis a wrapper around anIORefthat holds a pure generator.IOGenMis safe in the presence of exceptions, but not concurrency.STGenMis a wrapper around anSTRefthat holds a pure generator.STGenMis safe in the presence of exceptions, but not concurrency.
Pure adapter
Wrapper for pure state gen, which acts as an immutable seed for the corresponding
stateful generator StateGenM
Since: 1.2.0
Instances
Instance details
Defined in System.Random.Internal
Instance details
Defined in System.Random.Internal
Methods
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 () #
Instance details
Defined in System.Random.Internal
Methods
next :: StateGen g -> (Int, StateGen g) Source #
genWord8 :: StateGen g -> (Word8, StateGen g) Source #
genWord16 :: StateGen g -> (Word16, StateGen g) Source #
genWord32 :: StateGen g -> (Word32, StateGen g) Source #
genWord64 :: StateGen g -> (Word64, StateGen g) Source #
genWord32R :: Word32 -> StateGen g -> (Word32, StateGen g) Source #
genWord64R :: Word64 -> StateGen g -> (Word64, StateGen g) Source #
genShortByteString :: Int -> StateGen g -> (ShortByteString, StateGen g) Source #
Instance details
Defined in System.Random.Internal
Associated Types
type MutableGen (StateGen g) m = (g :: Type) Source #
Opaque data type that carries the type of a pure pseudo-random number generator.
Since: 1.2.0
Constructors
Instances
Instance details
Defined in System.Random.Internal
Methods
uniformWord32R :: Word32 -> StateGenM g -> m Word32 Source #
uniformWord64R :: Word64 -> StateGenM g -> m Word64 Source #
uniformWord8 :: StateGenM g -> m Word8 Source #
uniformWord16 :: StateGenM g -> m Word16 Source #
uniformWord32 :: StateGenM g -> m Word32 Source #
uniformWord64 :: StateGenM g -> m Word64 Source #
uniformShortByteString :: Int -> StateGenM g -> m ShortByteString Source #
Instance details
Defined in System.Random.Stateful
Methods
applyRandomGenM :: (r -> (a, r)) -> StateGenM r -> m a Source #
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 :: Int7879794327570578227
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 Int7879794327570578227
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
Frozen version of mutable AtomicGenM generator
Since: 1.2.0
Instances
Instance details
Defined in System.Random.Stateful
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 () #
Instance details
Defined in System.Random.Stateful
Methods
next :: AtomicGen g -> (Int, AtomicGen g) Source #
genWord8 :: AtomicGen g -> (Word8, AtomicGen g) Source #
genWord16 :: AtomicGen g -> (Word16, AtomicGen g) Source #
genWord32 :: AtomicGen g -> (Word32, AtomicGen g) Source #
genWord64 :: AtomicGen g -> (Word64, AtomicGen g) Source #
genWord32R :: Word32 -> AtomicGen g -> (Word32, AtomicGen g) Source #
genWord64R :: Word64 -> AtomicGen g -> (Word64, AtomicGen g) Source #
genShortByteString :: Int -> AtomicGen g -> (ShortByteString, AtomicGen g) Source #
Instance details
Defined in System.Random.Stateful
Associated Types
type MutableGen (AtomicGen g) m = (g :: Type) Source #
newtype AtomicGenM g Source #
Wraps an IORef that holds a pure pseudo-random number generator. All
operations are performed atomically.
AtomicGenMis safe in the presence of exceptions and concurrency.AtomicGenMis the slowest of the monadic adapters due to the overhead of its atomic operations.
Since: 1.2.0
Instances
Instance details
Defined in System.Random.Stateful
Methods
uniformWord32R :: Word32 -> AtomicGenM g -> m Word32 Source #
uniformWord64R :: Word64 -> AtomicGenM g -> m Word64 Source #
uniformWord8 :: AtomicGenM g -> m Word8 Source #
uniformWord16 :: AtomicGenM g -> m Word16 Source #
uniformWord32 :: AtomicGenM g -> m Word32 Source #
uniformWord64 :: AtomicGenM g -> m Word64 Source #
uniformShortByteString :: Int -> AtomicGenM g -> m ShortByteString Source #
Instance details
Defined in System.Random.Stateful
Methods
applyRandomGenM :: (r -> (a, r)) -> AtomicGenM r -> m a Source #
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 Int7879794327570578227
Since: 1.2.0
Mutable adapter in IO
Frozen version of mutable IOGenM generator
Since: 1.2.0
Instances
Instance details
Defined in System.Random.Stateful
Instance details
Defined in System.Random.Stateful
Instance details
Defined in System.Random.Stateful
Methods
next :: IOGen g -> (Int, IOGen g) Source #
genWord8 :: IOGen g -> (Word8, IOGen g) Source #
genWord16 :: IOGen g -> (Word16, IOGen g) Source #
genWord32 :: IOGen g -> (Word32, IOGen g) Source #
genWord64 :: IOGen g -> (Word64, IOGen g) Source #
genWord32R :: Word32 -> IOGen g -> (Word32, IOGen g) Source #
genWord64R :: Word64 -> IOGen g -> (Word64, IOGen g) Source #
genShortByteString :: Int -> IOGen g -> (ShortByteString, IOGen g) Source #
Instance details
Defined in System.Random.Stateful
Associated Types
type MutableGen (IOGen g) m = (g :: Type) Source #
Wraps an IORef that holds a pure pseudo-random number generator.
IOGenMis safe in the presence of exceptions, but not concurrency.IOGenMis slower thanStateGenMdue to the extra pointer indirection.IOGenMis faster thanAtomicGenMsince theIORefoperations used byIOGenMare not atomic.
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
Instances
Instance details
Defined in System.Random.Stateful
Methods
uniformWord32R :: Word32 -> IOGenM g -> m Word32 Source #
uniformWord64R :: Word64 -> IOGenM g -> m Word64 Source #
uniformWord8 :: IOGenM g -> m Word8 Source #
uniformWord16 :: IOGenM g -> m Word16 Source #
uniformWord32 :: IOGenM g -> m Word32 Source #
uniformWord64 :: IOGenM g -> m Word64 Source #
uniformShortByteString :: Int -> IOGenM g -> m ShortByteString Source #
Instance details
Defined in System.Random.Stateful
Methods
applyRandomGenM :: (r -> (a, r)) -> IOGenM r -> m a Source #
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 Int7879794327570578227
Since: 1.2.0
Mutable adapter in ST
Frozen version of mutable STGenM generator
Since: 1.2.0
Instances
Instance details
Defined in System.Random.Stateful
Instance details
Defined in System.Random.Stateful
Instance details
Defined in System.Random.Stateful
Methods
next :: STGen g -> (Int, STGen g) Source #
genWord8 :: STGen g -> (Word8, STGen g) Source #
genWord16 :: STGen g -> (Word16, STGen g) Source #
genWord32 :: STGen g -> (Word32, STGen g) Source #
genWord64 :: STGen g -> (Word64, STGen g) Source #
genWord32R :: Word32 -> STGen g -> (Word32, STGen g) Source #
genWord64R :: Word64 -> STGen g -> (Word64, STGen g) Source #
genShortByteString :: Int -> STGen g -> (ShortByteString, STGen g) Source #
Wraps an STRef that holds a pure pseudo-random number generator.
STGenMis safe in the presence of exceptions, but not concurrency.STGenMis slower thanStateGenMdue to the extra pointer indirection.
Since: 1.2.0
Instances
Instance details
Defined in System.Random.Stateful
Methods
applyRandomGenM :: (r -> (a, r)) -> STGenM r s -> ST s a Source #
Instance details
Defined in System.Random.Stateful
Methods
uniformWord32R :: Word32 -> STGenM g s -> ST s Word32 Source #
uniformWord64R :: Word64 -> STGenM g s -> ST s Word64 Source #
uniformWord8 :: STGenM g s -> ST s Word8 Source #
uniformWord16 :: STGenM g s -> ST s Word16 Source #
uniformWord32 :: STGenM g s -> ST s Word32 Source #
uniformWord64 :: STGenM g s -> ST s Word64 Source #
uniformShortByteString :: Int -> STGenM g s -> ST s ShortByteString Source #
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)) :: Int7879794327570578227
Since: 1.2.0
Pseudo-random values of various types
This library provides two type classes to generate pseudo-random values:
UniformRangeis used to generate a value of a type uniformly within a range.Uniformis 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,Word16andBoolare instances of bothUniformRangeandUniform.Integer,FloatandDoubleeach have an instance forUniformRangebut noUniforminstance.- A hypothetical type
Radianrepresenting angles by taking values in the range[0, 2π)has a trivialUniforminstance, but noUniformRangeinstance: the problem is that two givenRadianvalues always span two ranges, one clockwise and one anti-clockwise. - It is trivial to construct a
Uniform (a, b)instance givenUniform aandUniform 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 justUniformRange aandUniformRange 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
Instance details
Defined in System.Random.Internal
Methods
uniformM :: StatefulGen g m => g -> m Bool Source #
Instance details
Defined in System.Random.Internal
Methods
uniformM :: StatefulGen g m => g -> m Char Source #
Instance details
Defined in System.Random.Internal
Methods
uniformM :: StatefulGen g m => g -> m Int Source #
Instance details
Defined in System.Random.Internal
Methods
uniformM :: StatefulGen g m => g -> m Int8 Source #
Instance details
Defined in System.Random.Internal
Methods
uniformM :: StatefulGen g m => g -> m Int16 Source #
Instance details
Defined in System.Random.Internal
Methods
uniformM :: StatefulGen g m => g -> m Int32 Source #
Instance details
Defined in System.Random.Internal
Methods
uniformM :: StatefulGen g m => g -> m Int64 Source #
Instance details
Defined in System.Random.Internal
Methods
uniformM :: StatefulGen g m => g -> m Word Source #
Instance details
Defined in System.Random.Internal
Methods
uniformM :: StatefulGen g m => g -> m Word8 Source #
Instance details
Defined in System.Random.Internal
Methods
uniformM :: StatefulGen g m => g -> m Word16 Source #
Instance details
Defined in System.Random.Internal
Methods
uniformM :: StatefulGen g m => g -> m Word32 Source #
Instance details
Defined in System.Random.Internal
Methods
uniformM :: StatefulGen g m => g -> m Word64 Source #
Instance details
Defined in System.Random.Internal
Methods
uniformM :: StatefulGen g m => g -> m CChar Source #
Instance details
Defined in System.Random.Internal
Methods
uniformM :: StatefulGen g m => g -> m CSChar Source #
Instance details
Defined in System.Random.Internal
Methods
uniformM :: StatefulGen g m => g -> m CUChar Source #
Instance details
Defined in System.Random.Internal
Methods
uniformM :: StatefulGen g m => g -> m CShort Source #
Instance details
Defined in System.Random.Internal
Methods
uniformM :: StatefulGen g m => g -> m CUShort Source #
Instance details
Defined in System.Random.Internal
Methods
uniformM :: StatefulGen g m => g -> m CInt Source #
Instance details
Defined in System.Random.Internal
Methods
uniformM :: StatefulGen g m => g -> m CUInt Source #
Instance details
Defined in System.Random.Internal
Methods
uniformM :: StatefulGen g m => g -> m CLong Source #
Instance details
Defined in System.Random.Internal
Methods
uniformM :: StatefulGen g m => g -> m CULong Source #
Instance details
Defined in System.Random.Internal
Methods
uniformM :: StatefulGen g m => g -> m CLLong Source #
Instance details
Defined in System.Random.Internal
Methods
uniformM :: StatefulGen g m => g -> m CULLong Source #
Instance details
Defined in System.Random.Internal
Methods
uniformM :: StatefulGen g m => g -> m CBool Source #
Instance details
Defined in System.Random.Internal
Methods
uniformM :: StatefulGen g m => g -> m CPtrdiff Source #
Instance details
Defined in System.Random.Internal
Methods
uniformM :: StatefulGen g m => g -> m CSize Source #
Instance details
Defined in System.Random.Internal
Methods
uniformM :: StatefulGen g m => g -> m CWchar Source #
Instance details
Defined in System.Random.Internal
Methods
uniformM :: StatefulGen g m => g -> m CSigAtomic Source #
Instance details
Defined in System.Random.Internal
Methods
uniformM :: StatefulGen g m => g -> m CIntPtr Source #
Instance details
Defined in System.Random.Internal
Methods
uniformM :: StatefulGen g m => g -> m CUIntPtr Source #
Instance details
Defined in System.Random.Internal
Methods
uniformM :: StatefulGen g m => g -> m CIntMax Source #
Instance details
Defined in System.Random.Internal
Methods
uniformM :: StatefulGen g m => g -> m CUIntMax Source #
Instance details
Defined in System.Random.Internal
Methods
uniformM :: StatefulGen g m => g -> m (a, b) Source #
Instance details
Defined in System.Random.Internal
Methods
uniformM :: StatefulGen g m => g -> m (a, b, c) Source #
Instance details
Defined in System.Random.Internal
Methods
uniformM :: StatefulGen g m => g -> m (a, b, c, d) Source #
Instance details
Defined in System.Random.Internal
Methods
uniformM :: StatefulGen g m => g -> m (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, f) 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
Instance details
Defined in System.Random.Internal
Instance details
Defined in System.Random.Internal
Instance details
Defined in System.Random.Internal
Instance details
Defined in System.Random.Internal
Instance details
Defined in System.Random.Internal
Instance details
Defined in System.Random.Internal
Instance details
Defined in System.Random.Internal
Instance details
Defined in System.Random.Internal
Instance details
Defined in System.Random.Internal
Instance details
Defined in System.Random.Internal
Instance details
Defined in System.Random.Internal
Instance details
Defined in System.Random.Internal
Instance details
Defined in System.Random.Internal
Instance details
Defined in System.Random.Internal
Instance details
Defined in System.Random.Internal
Instance details
Defined in System.Random.Internal
Instance details
Defined in System.Random.Internal
Instance details
Defined in System.Random.Internal
Instance details
Defined in System.Random.Internal
Instance details
Defined in System.Random.Internal
Instance details
Defined in System.Random.Internal
Instance details
Defined in System.Random.Internal
Instance details
Defined in System.Random.Internal
Instance details
Defined in System.Random.Internal
Instance details
Defined in System.Random.Internal
Instance details
Defined in System.Random.Internal
Instance details
Defined in System.Random.Internal
Instance details
Defined in System.Random.Internal
Instance details
Defined in System.Random.Internal
Instance details
Defined in System.Random.Internal
Instance details
Defined in System.Random.Internal
Instance details
Defined in System.Random.Internal
Instance details
Defined in System.Random.Internal
Instance details
Defined in System.Random.Internal
Methods
uniformRM :: StatefulGen g m => (CSigAtomic, CSigAtomic) -> g -> m CSigAtomic Source #
Instance details
Defined in System.Random.Internal
Instance details
Defined in System.Random.Internal
Instance details
Defined in System.Random.Internal
Instance details
Defined in System.Random.Internal
Generators for sequences of pseudo-random bytes
Arguments
Number of bytes to generate
IO action that can generate 8 random bytes at a time
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 #
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 #
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:
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.
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
NaNas 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 isNaN.>>>let (a, b, x) = (nan, 1, 0.5) in x * a + (1 - x) * bNaN>>>let (a, b, x) = (-1, nan, 0.5) in x * a + (1 - x) * bNaN- If \(a\) is
-Infinityand \(b\) isInfinity, the result isNaN. >>> let (a, b, x) = (-inf, inf, 0.5) in x * a + (1 - x) * b NaN Otherwise, if \(a\) is
Infinityor-Infinity, the result is \(a\).>>>let (a, b, x) = (inf, 1, 0.5) in x * a + (1 - x) * bInfinity>>>let (a, b, x) = (-inf, 1, 0.5) in x * a + (1 - x) * b-InfinityOtherwise, if \(b\) is
Infinityor-Infinity, the result is \(b\).>>>let (a, b, x) = (1, inf, 0.5) in x * a + (1 - x) * bInfinity>>>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
- 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