| Copyright | (c) Justin Le 2015 |
|---|---|
| License | MIT |
| Maintainer | justin@jle.im |
| Stability | unstable |
| Portability | portable |
| Safe Haskell | None |
| Language | Haskell2010 |
Control.Auto.Process.Random
Contents
Description
This module provides Autos (purely) generating entropy in the form of
random or noisy processes. Note that every Auto here is completely
deterministic --- given the same initial seed, one would expect the same
stream of outputs on every run. Furthermore, if a serializable Auto
is serialized and resumed, it will continue along the deterministic path
dictated by the original seed given.
All of these Autos come in three flavors: one serializing one that
works with any serializable RandomGen instance, one serializing one
that works specifically with StdGen from System.Random, and one that
takes any RandomGen (including StdGen) and runs it without the
ability to serialize and resume deterministically.
The reason why there's a specialized StdGen version for all of these
is that StdGen actually doesn't have a Serialize instance, so a
rudimentary serialization process is provded with the StdGen versions.
The first class of generators take arbitrary g -> (b, g) functions:
"Generate a random b, using the given function, and replace the seed
with the resulting seed". Most "random" functions follow this pattern,
including random and randomR, and if you are using something from
MonadRandom,
then you can use the runRand function to turn a into a Rand g bg
-> (b, g), as well:
runRand::RandomGeng =>Randg b -> (g -> (b, g))
These are useful for generating noise...a new random value at every stoep. They are entropy sources.
Alternatively, if you want to give up parallelizability and determinism
and have your entire Auto be sequential, you can make your entire
Auto run under Rand or RandT as its internal monad, from
MonadRandom.
Auto(Randg) a bAuto(RandTg m) a b
In this case, if you wanted to pull a random number, you could do:
effectrandom:: (Randomr,RandomGeng) =>Auto(Randg) a reffectrandom:: (Randomr,RandomGeng) =>Auto(RandTg m) a r
Which pulls a random r from "thin air" (from the internal Rand
monad).
However, you lose a great deal of determinism from this method, as your
Autos are no longer deterministic with a given seed...and resumability
becomes dependent on starting everything with the same seed every time
you re-load your Auto. Also, Auto's are parallelizable, while
s are not.Auto (Rand g)
As a compromise, you can then "seal" away the stateful part with
sealState and hoistA:
sealRandom ::Monadm =>Auto(RandTg m) a b -> g ->Autom a b sealRandom a0 =sealState.hoistA(StateT.runRandT) sealRandom' ::Auto(Randg) a b -> g ->Auto'a b sealRandom' = sealRandom
Where hoistA turns an into an Auto (RandT g m).Auto m
In this way, you can run any Auto under Rand or RandT as if it was
a normal Auto "without" underlying randomness. (These functions
aren't given here so that this library doesn't incurr a dependency on
MonadRandom). This lets you compose your sequential/non-parallel parts
in Rand and use it as a part of an Auto'.
The other generators given are for useful random processes you might run
into. The first is a Blip stream that emits at random times with the
given frequencyprobability. The second works Interval/ semantics from
Control.Auto.Interval, and is a stream that is "on" or "off", chunks
at a time, for random lengths. The average length of each on or off
period is controlled by the parameter you pass in.
- rands :: (Serialize g, RandomGen g) => (g -> (b, g)) -> g -> Auto m a b
- stdRands :: (StdGen -> (b, StdGen)) -> StdGen -> Auto m a b
- rands_ :: RandomGen g => (g -> (b, g)) -> g -> Auto m a b
- randsM :: (Serialize g, RandomGen g, Monad m) => (g -> m (b, g)) -> g -> Auto m a b
- stdRandsM :: Monad m => (StdGen -> m (b, StdGen)) -> StdGen -> Auto m a b
- randsM_ :: (RandomGen g, Monad m) => (g -> m (b, g)) -> g -> Auto m a b
- arrRand :: (Serialize g, RandomGen g) => (a -> g -> (b, g)) -> g -> Auto m a b
- arrRandM :: (Monad m, Serialize g, RandomGen g) => (a -> g -> m (b, g)) -> g -> Auto m a b
- arrRandStd :: (a -> StdGen -> (b, StdGen)) -> StdGen -> Auto m a b
- arrRandStdM :: (a -> StdGen -> m (b, StdGen)) -> StdGen -> Auto m a b
- arrRand_ :: RandomGen g => (a -> g -> (b, g)) -> g -> Auto m a b
- arrRandM_ :: RandomGen g => (a -> g -> m (b, g)) -> g -> Auto m a b
- bernoulli :: (Serialize g, RandomGen g) => Double -> g -> Auto m a (Blip a)
- stdBernoulli :: Double -> StdGen -> Auto m a (Blip a)
- bernoulli_ :: RandomGen g => Double -> g -> Auto m a (Blip a)
- randIntervals :: (Serialize g, RandomGen g) => Double -> g -> Interval m a a
- stdRandIntervals :: Double -> StdGen -> Interval m a a
- randIntervals_ :: RandomGen g => Double -> g -> Interval m a a
Streams of random values from random generators
Arguments
| :: (Serialize g, RandomGen g) | |
| => (g -> (b, g)) | random generating function |
| -> g | initial generator |
| -> Auto m a b |
Given a seed-consuming generating function of form g -> (b, g)
(where g is the seed, and b is the result) and an initial seed,
return an Auto that continually generates random values using the
given generating funcion.
You'll notice that most of the useful functions from System.Random fit this form:
random::RandomGeng => g -> (b, g)randomR::RandomGeng => (b, b) -> (g -> (b, g))
If you are using something from MonadRandom,
then you can use the runRand function to turn a into a Rand g bg
-> (b, g):
runRand::RandomGeng =>Randg b -> (g -> (b, g))
Here is an example using stdRands (for StdGen), but rands works
exactly the same way, I promise!
>>>let g = mkStdGen 8675309>>>let a = stdRands (randomR (1,100)) g :: Auto' a Int>>>let (res, _) = stepAutoN' 10 a ()>>>res[67, 15, 97, 13, 55, 12, 34, 86, 57, 42]
Yeah, if you are using StdGen from System.Random, you'll notice that
StdGen has no Serialize instance, so you can't use it with this; you
have to either use stdRands or rands_ (if you don't want
serialization/resumability).
In the context of these generators, resumability basically means deterministic behavior over re-loads...if "reloading", it'll ignore the seed you pass in, and use the original seed given when originally saved.
Arguments
| :: RandomGen g | |
| => (g -> (b, g)) | random generating function |
| -> g | initial generator |
| -> Auto m a b |
The non-serializing/non-resuming version of rands.
randsM :: (Serialize g, RandomGen g, Monad m) => (g -> m (b, g)) -> g -> Auto m a b Source
Like rands, except taking a "monadic" random seed function g ->
m (b, g), instead of g -> (b, g). Your random generating function
has access to the underlying monad.
If you are using something from
MonadRandom, then you
can use the runRandT function to turn a into a RandT g m bg ->
m (b, g):
runRandT:: (Monadm,RandomGeng) =>RandTg m b -> (g -> m (b, g))
randsM_ :: (RandomGen g, Monad m) => (g -> m (b, g)) -> g -> Auto m a b Source
The non-serializing/non-resuming version of randsM.
Lifting/wrapping random functions
arrRand :: (Serialize g, RandomGen g) => (a -> g -> (b, g)) -> g -> Auto m a b Source
Takes a "random function", or "random arrow" --- a function taking an
input value and a starting seed/entropy generator and returning a result
and an ending seed/entropy generator --- and turns it into an Auto
that feeds its input into such a function and outputs the result, with
a new seed every time.
>>>let f x = randomR (0 :: Int, x)>>>streamAuto' (arrRandStd f (mkStdGen 782065)) [1..10]-- [1,2,3,4,5,6,7,8,9,10] <- upper bounds [1,2,0,1,5,3,7,6,8,10] -- random number from 0 to upper bound
If you are using something from
MonadRandom, then you
can use the ( function to turn a runRand .)a -> into
a Rand g ba -> g -> (b, g):
(runRand.) ::RandomGeng => (a ->Randg b) -> (a -> g -> (b, g))
(This is basically mkState, specialized.)
arrRandM :: (Monad m, Serialize g, RandomGen g) => (a -> g -> m (b, g)) -> g -> Auto m a b Source
Like arrRand, except the result is the result of a monadic action.
Your random arrow function has access to the underlying monad.
If you are using something from
MonadRandom, then you
can use the ( function to turn a runRandT .)a ->
into a RandT m g ba -> g -> m (b, g):
(runRandT.) ::RandomGeng => (a ->RandTg b) -> (a -> g -> m (b, g))
arrRand_ :: RandomGen g => (a -> g -> (b, g)) -> g -> Auto m a b Source
The non-serializing/non-resuming version of arrRand.
arrRandM_ :: RandomGen g => (a -> g -> m (b, g)) -> g -> Auto m a b Source
The non-serializing/non-resuming version of arrRandM.
Random processes
Bernoulli (on/off) processes
Arguments
| :: (Serialize g, RandomGen g) | |
| => Double | probability of success per step |
| -> g | initial seed |
| -> Auto m a (Blip a) |
Simulates a Bernoulli Process:
a process of sequential independent trials each with a success of
probability p.
Implemented here is an Auto producing a blip stream that emits
whenever the bernoulli process succeeds with the value of the received
input of the Auto, with its probability of succuss per each trial as
the Double parameter.
It is expected that, for probability p, the stream will emit a value
on average once every 1/p ticks.
Arguments
| :: RandomGen g | |
| => Double | probability of any step emitting |
| -> g | initial seed |
| -> Auto m a (Blip a) |
The non-serializing/non-resuming version of bernoulli.
Random-length intervals
randIntervals :: (Serialize g, RandomGen g) => Double -> g -> Interval m a a Source
An Interval that is "on" and "off" for contiguous but random
intervals of time...when "on", allows values to pass as "on" (Just),
but when "off", suppresses all incoming values (outputing Nothing).
You provide a Double, an l parameter, representing the
averageexpected length of each onoff interval.
The distribution of interval lengths follows
a Geometric Distribution.
This distribution is, as we call it in maths, "memoryless", which means
that the "time left" that the Auto will be "on" or "off" at any given
time is going to be, on average, the given l parameter.
Internally, the "toggling" events follow a bernoulli process with a p
parameter of 1 / l.
stdRandIntervals :: Double -> StdGen -> Interval m a a Source
Like randIntervals, but specialized for StdGen from
System.Random, so that you can serialize and resume. This is needed
because StdGen doesn't have a Serialize instance.
See the documentation of randIntervals for more information.
randIntervals_ :: RandomGen g => Double -> g -> Interval m a a Source
The non-serializing/non-resuming version of randIntervals.