| Safe Haskell | None | 
|---|
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 a more-general function (getRandomPrimFromMTRef) usable as
 an implementation for new cases users might need.
Documentation
data PureMT
PureMT, a pure mersenne twister pseudo-random number generator
Instances
| Show PureMT | |
| RandomGen PureMT | |
| MonadIO m0 => RandomSource m0 (IORef PureMT) | |
| (Monad m10, ModifyRef (Ref m20 PureMT) m10 PureMT) => RandomSource m10 (Ref m20 PureMT) | |
| (Monad m0, ModifyRef (STRef s0 PureMT) m0 PureMT) => RandomSource m0 (STRef s0 PureMT) | |
| Monad m0 => MonadRandom (StateT PureMT m0) | |
| Monad m0 => MonadRandom (StateT PureMT m0) | 
getRandomPrimFromMTRef :: ModifyRef sr m PureMT => sr -> Prim a -> m aSource
Given a mutable reference to a PureMT generator, we can implement
 RandomSource for it 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 (using some functions from Data.Random in the random-fu package):
 main = do
     src <- newIORef (pureMT 1234)          -- OR: newPureMT >>= newIORef
     x <- runRVar (uniform 0 100) src :: IO Double
     print x