Safe Haskell | None |
---|
This module provides functions useful for implementing new MonadRandom
and RandomSource
instances for state-abstractions containing StdGen
values (the pure pseudorandom generator provided by the System.Random
module in the "random" package), as well as instances for some common
cases.
- data StdGen
- mkStdGen :: Int -> StdGen
- newStdGen :: IO StdGen
- getRandomPrimFromStdGenIO :: Prim a -> IO a
- getRandomPrimFromRandomGenRef :: (Monad m, ModifyRef sr m g, RandomGen g) => sr -> Prim a -> m a
- getRandomPrimFromRandomGenState :: forall g m a. (RandomGen g, MonadState g m) => Prim a -> m a
Documentation
data StdGen
The StdGen
instance of RandomGen
has a genRange
of at least 30 bits.
The result of repeatedly using next
should be at least as statistically
robust as the Minimal Standard Random Number Generator described by
[System.Random, System.Random].
Until more is known about implementations of split
, all we require is
that split
deliver generators that are (a) not identical and
(b) independently robust in the sense just given.
The Show
and Read
instances of StdGen
provide a primitive way to save the
state of a random number generator.
It is required that
.
read
(show
g) == g
In addition, reads
may be used to map an arbitrary string (not necessarily one
produced by show
) onto a value of type StdGen
. In general, the Read
instance of StdGen
has the following properties:
- It guarantees to succeed on any string.
- It guarantees to consume only a finite portion of the string.
- Different argument strings are likely to result in different results.
Read StdGen | |
Show StdGen | |
RandomGen StdGen | |
(Monad m, ModifyRef (IORef StdGen) m StdGen) => RandomSource m (IORef StdGen) | |
(Monad m, ModifyRef (STRef s StdGen) m StdGen) => RandomSource m (STRef s StdGen) | |
(Monad m1, ModifyRef (Ref m2 StdGen) m1 StdGen) => RandomSource m1 (Ref m2 StdGen) | |
Monad m => MonadRandom (StateT StdGen m) | |
Monad m => MonadRandom (StateT StdGen m) |
Applies split
to the current global random generator,
updates it with one of the results, and returns the other.
getRandomPrimFromStdGenIO :: Prim a -> IO aSource
getRandomPrimFromRandomGenRef :: (Monad m, ModifyRef sr m g, RandomGen g) => sr -> Prim a -> m aSource
Given a mutable reference to a RandomGen
generator, we can make a
RandomSource
usable in any monad in which the reference can be modified.
See Data.Random.Source.PureMT.getRandomPrimFromMTRef
for more detailed
usage hints - this function serves exactly the same purpose except for a
StdGen
generator instead of a PureMT
generator.
getRandomPrimFromRandomGenState :: forall g m a. (RandomGen g, MonadState g m) => Prim a -> m aSource
Similarly, getRandomWordFromRandomGenState x
can be used in any "state"
monad in the mtl sense whose state is a RandomGen
generator.
Additionally, the standard mtl state monads have MonadRandom
instances
which do precisely that, allowing an easy conversion of RVar
s and
other Distribution
instances to "pure" random variables.
Again, see Data.Random.Source.PureMT.getRandomPrimFromMTState
for more
detailed usage hints - this function serves exactly the same purpose except
for a StdGen
generator instead of a PureMT
generator.