random-fu-0.1.4: Random number generation

Data.Random.Source.PureMT

Description

This module provides functions useful for implementing new MonadRandom and RandomSource instances for state-abstractions containing PureMT values (the pure pseudorandom generator provided by the mersenne-random-pure64 package), as well as instances for some common cases.

A PureMT generator is immutable, so PureMT by itself cannot be a RandomSource (if it were, it would always give the same "random" values). Some form of mutable state must be used, such as an IORef, State monad, etc.. A few default instances are provided by this module along with more-general functions (getRandomPrimFromMTRef and getRandomPrimFromMTState) usable as implementations for new cases users might need.

Synopsis

Documentation

data PureMT

PureMT, a pure mersenne twister pseudo-random number generator

newPureMT :: IO PureMT

Create a new PureMT generator, using the clocktime as the base for the seed.

pureMT :: Word64 -> PureMT

Create a PureMT generator from a Word64 seed.

getRandomPrimBy :: Monad m => (forall t. (PureMT -> (t, PureMT)) -> m t) -> Prim a -> m aSource

Given a function for applying a PureMT transformation to some hidden state, this function derives a function able to generate all Prims in the given monad. This is then suitable for either a MonadRandom or RandomSource instance, where the supportedPrims or supportedPrimsFrom function (respectively) is const True.

getRandomPrimFromMTRef :: forall sr m t. (Monad m, ModifyRef sr m PureMT) => sr -> Prim t -> m tSource

Given a mutable reference to a PureMT generator, we can implement RandomSource for in any monad in which the reference can be modified.

Typically this would be used to define a new RandomSource instance for some new reference type or new monad in which an existing reference type can be modified atomically. As an example, the following instance could be used to describe how IORef PureMT can be a RandomSource in the IO monad:

 instance RandomSource IO (IORef PureMT) where
     supportedPrimsFrom _ _ = True
     getSupportedRandomPrimFrom = getRandomPrimFromMTRef

(note that there is actually a more general instance declared already covering this as a a special case, so there's no need to repeat this declaration anywhere)

Example usage:

 main = do
     src <- newIORef (pureMT 1234)          -- OR: newPureMT >>= newIORef
     x <- sampleFrom src (uniform 0 100)    -- OR: runRVar (uniform 0 100) src
     print x

getRandomPrimFromMTState :: forall m t. MonadState PureMT m => Prim t -> m tSource

Similarly, getRandomPrimFromMTState x can be used in any "state" monad in the mtl sense whose state is a PureMT generator. Additionally, the standard mtl state monads have MonadRandom instances which do precisely that, allowing an easy conversion of RVars and other Distribution instances to "pure" random variables (e.g., by runState . sample :: Distribution d t => d t -> PureMT -> (t, PureMT). PureMT in the type there can be replaced by StdGen or anything else satisfying MonadRandom (State s) => s).

For example, this module includes the following declaration:

 instance MonadRandom (State PureMT) where
     supportedPrims _ _ = True
     getSupportedRandomPrim = getRandomPrimFromMTState

This describes a "standard" way of getting random values in State PureMT, which can then be used in various ways, for example (assuming some RVar foo and some Word64 seed):

 runState (runRVar foo StdRandom) (pureMT seed)
 runState (sampleFrom StdRandom foo) (pureMT seed)
 runState (sample foo) (pureMT seed)

Of course, the initial PureMT state could also be obtained by any other convenient means, such as newPureMT if you don't care what seed is used.