auto-0.2.0.6: Denotative, locally stateful programming DSL & platform

Copyright(c) Justin Le 2015
LicenseMIT
Maintainerjustin@jle.im
Stabilityunstable
Portabilityportable
Safe HaskellNone
LanguageHaskell2010

Control.Auto.Process.Random

Contents

Description

This module provides Autos (purely) generating entropy in the form of random or noisy processes, as well as Autos to purify/seal Autos with underlying entropy.

Note that every Auto and combinator 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 and combinators 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 Rand g b into a g -> (b, g), as well:

runRand :: RandomGen g => Rand g b -> (g -> (b, g))

These are useful for generating noise...a new random value at every step. 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 (Rand g) a b
Auto (RandT g m) a b

In this case, if you wanted to pull a random number, you could do:

effect random :: (Random r, RandomGen g) => Auto (Rand g) a r
effect random :: (Random r, RandomGen g) => Auto (RandT g 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 Auto (Rand g)s are not.

As a compromise, you can then "seal" away the underlying monad with sealRandom, which takes an Auto (RandT g m) a b, a starting g, and turns it into a normal Auto m a b, with no underlying randomness monad.

In this way, you can run any Auto under Rand or RandT as if it was a normal Auto "without" underlying randomness. This lets you compose your sequential/non-parallel parts in Rand...and the later, use it as a part of a parallelizable/potentially non-sequential Auto'. It's also convenient because you don't have to manually split and pass around seeds to every Auto that requires entropy.

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.

Synopsis

Streams of random values from random generators

rands Source

Arguments

:: (Serialize g, RandomGen g) 
=> (g -> (b, g))

random generating function

-> g

random generator seed

-> 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  :: RandomGen g =>            g -> (b, g)
randomR :: RandomGen g => (b, b) -> (g -> (b, g))

If you are using something from MonadRandom, then you can use the runRand function to turn a Rand g b into a g -> (b, g):

runRand :: RandomGen g => Rand g 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.

stdRands Source

Arguments

:: (StdGen -> (b, StdGen))

random generating function

-> StdGen

random generator seed

-> Auto m a b 

Like rands, 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 rands for more information on this Auto.

rands_ Source

Arguments

:: RandomGen g 
=> (g -> (b, g))

random generating function

-> g

random generator seed

-> Auto m a b 

The non-serializing/non-resuming version of rands.

randsM Source

Arguments

:: (Serialize g, RandomGen g, Monad m) 
=> (g -> m (b, g))

(monadic) random generating function

-> g

random generator seed

-> Auto m a b 

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 RandT g m b into a g -> m (b, g):

runRandT :: (Monad m, RandomGen g)
           => RandT g m b -> (g -> m (b, g))

stdRandsM Source

Arguments

:: Monad m 
=> (StdGen -> m (b, StdGen))

(monadic) random generating function

-> StdGen

random generator seed

-> Auto m a b 

Like randsM, 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 randsM for more information on this Auto.

randsM_ Source

Arguments

:: (RandomGen g, Monad m) 
=> (g -> m (b, g))

(monadic) random generating function

-> g

random generator seed

-> Auto m a b 

The non-serializing/non-resuming version of randsM.

Lifting/wrapping random functions

arrRand Source

Arguments

:: (Serialize g, RandomGen g) 
=> (a -> g -> (b, g))

random arrow

-> g

random generator seed

-> Auto m a b 

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 (runRand .) function to turn a a -> Rand g b into a a -> g -> (b, g):

(runRand .) :: RandomGen g => (a -> Rand g b) -> (a -> g -> (b, g))

(This is basically mkState, specialized.)

arrRandM Source

Arguments

:: (Monad m, Serialize g, RandomGen g) 
=> (a -> g -> m (b, g))

(monadic) random arrow

-> g

random generator seed

-> Auto m a b 

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 (runRandT .) function to turn a a -> RandT m g b into a a -> g -> m (b, g):

(runRandT .) :: RandomGen g => (a -> RandT g b) -> (a -> g -> m (b, g))

arrRandStd Source

Arguments

:: (a -> StdGen -> (b, StdGen))

random arrow

-> StdGen

random generator seed

-> Auto m a b 

Like arrRand, 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 arrRand for more information on this Auto.

arrRandStdM Source

Arguments

:: (a -> StdGen -> m (b, StdGen))

(mondic) random arrow

-> StdGen

random generator seed

-> Auto m a b 

Like arrRandM, 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 arrRandM for more information on this Auto.

arrRand_ Source

Arguments

:: RandomGen g 
=> (a -> g -> (b, g))

random arrow

-> g

random generator seed

-> Auto m a b 

The non-serializing/non-resuming version of arrRand.

arrRandM_ Source

Arguments

:: RandomGen g 
=> (a -> g -> m (b, g))

(monadic) random arrow

-> g

random generator seed

-> Auto m a b 

The non-serializing/non-resuming version of arrRandM.

Random processes

Bernoulli (on/off) processes

bernoulli Source

Arguments

:: (Serialize g, RandomGen g) 
=> Double

probability of any step emitting

-> g

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

stdBernoulli Source

Arguments

:: Double

probability of any step emitting

-> StdGen

random generator seed (between 0 and 1)

-> Auto m a (Blip a) 

Like bernoulli, 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 bernoulli for more information on this Auto.

bernoulli_ Source

Arguments

:: RandomGen g 
=> Double

probability of any step emitting

-> g

random generator seed (between 0 and 1)

-> Auto m a (Blip a) 

The non-serializing/non-resuming version of bernoulli.

Random-length intervals

randIntervals Source

Arguments

:: (Serialize g, RandomGen g) 
=> Double

expected length of on/off intervals

-> g

random generator seed

-> Interval m a a 

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 Source

Arguments

:: Double

expected length of on/off intervals

-> StdGen

random generator seed

-> Interval m a a 

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 on this Auto.

randIntervals_ Source

Arguments

:: RandomGen g 
=> Double

expected length of on/off intervals

-> g

random generator seed

-> Interval m a a 

The non-serializing/non-resuming version of randIntervals.

Underlying entropy monads

Sealers

sealRandom Source

Arguments

:: (RandomGen g, Serialize g, Monad m) 
=> Auto (RandT g m) a b

Auto to seal

-> g

initial seed

-> Auto m a b 

Takes an Auto over an Rand or RandT underlying monad as an entropy source, and "seals it away" to just be a normal Auto or Auto':

sealRandom :: Auto (Rand g) a b -> g -> Auto' a b

You can now compose your entropic Auto with other Autos (using ., and other combinators) as if it were a normal Auto.

Useful because you can create entire programs that have access to an underlying entropy souce by composing with Rand...and then, at the end of it all, use/compose it with normal Autos as if it were a "pure" Auto.

sealRandomStd Source

Arguments

:: Monad m 
=> Auto (RandT StdGen m) a b

Auto to seal

-> StdGen

initial seed

-> Auto m a b 

Like sealRandom, 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 sealRandom for more information on this combinator.

sealRandom_ Source

Arguments

:: (RandomGen g, Serialize g, Monad m) 
=> Auto (RandT g m) a b

Auto to seal

-> g

initial seed

-> Auto m a b 

The non-serializing/non-resuming version of sealRandom_. The random seed is not re-loaded/resumed, so every time you resume, the stream of available randomness begins afresh.

Processes

bernoulliMR Source

Arguments

:: MonadRandom m 
=> Double

probability of any step emiting (between 0 and 1)

-> Auto m a (Blip a) 

bernoulli, but uses an underlying entropy source (MonadRandom) to get its randomness from, instead of an initially passed seed.

You can recover exactly bernoulli p by using sealRandom (bernoulliMR p).

See sealRandom for more information.

randIntervalsMR Source

Arguments

:: MonadRandom m 
=> Double

expected length of on/off intervals

-> Interval m a a 

randIntervals, but uses an underlying entropy source (MonadRandom) to get its randomness from, instead of an initially passed seed.

You can recover exactly randIntervals l by using sealRandom (randIntervalsMR l).

See sealRandom for more information.