random-source-0.3.0.8: Generic basis for random number generators
Safe HaskellNone
LanguageHaskell98

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.

Synopsis

Documentation

data PureMT Source #

PureMT, a pure mersenne twister pseudo-random number generator

Instances

Instances details
Show PureMT 
Instance details

Defined in System.Random.Mersenne.Pure64.Internal

Methods

showsPrec :: Int -> PureMT -> ShowS

show :: PureMT -> String

showList :: [PureMT] -> ShowS

MonadIO m => RandomSource m (IORef PureMT) Source # 
Instance details

Defined in Data.Random.Source.PureMT

(Monad m1, ModifyRef (Ref m2 PureMT) m1 PureMT) => RandomSource m1 (Ref m2 PureMT) Source # 
Instance details

Defined in Data.Random.Source.PureMT

Methods

getRandomPrimFrom :: Ref m2 PureMT -> Prim t -> m1 t Source #

getRandomWord8From :: Ref m2 PureMT -> m1 Word8 Source #

getRandomWord16From :: Ref m2 PureMT -> m1 Word16 Source #

getRandomWord32From :: Ref m2 PureMT -> m1 Word32 Source #

getRandomWord64From :: Ref m2 PureMT -> m1 Word64 Source #

getRandomDoubleFrom :: Ref m2 PureMT -> m1 Double Source #

getRandomNByteIntegerFrom :: Ref m2 PureMT -> Int -> m1 Integer Source #

(Monad m, ModifyRef (STRef s PureMT) m PureMT) => RandomSource m (STRef s PureMT) Source # 
Instance details

Defined in Data.Random.Source.PureMT

Monad m => MonadRandom (StateT PureMT m) Source # 
Instance details

Defined in Data.Random.Source.PureMT

Methods

getRandomPrim :: Prim t -> StateT PureMT m t Source #

getRandomWord8 :: StateT PureMT m Word8 Source #

getRandomWord16 :: StateT PureMT m Word16 Source #

getRandomWord32 :: StateT PureMT m Word32 Source #

getRandomWord64 :: StateT PureMT m Word64 Source #

getRandomDouble :: StateT PureMT m Double Source #

getRandomNByteInteger :: Int -> StateT PureMT m Integer Source #

Monad m => MonadRandom (StateT PureMT m) Source # 
Instance details

Defined in Data.Random.Source.PureMT

Methods

getRandomPrim :: Prim t -> StateT PureMT m t Source #

getRandomWord8 :: StateT PureMT m Word8 Source #

getRandomWord16 :: StateT PureMT m Word16 Source #

getRandomWord32 :: StateT PureMT m Word32 Source #

getRandomWord64 :: StateT PureMT m Word64 Source #

getRandomDouble :: StateT PureMT m Double Source #

getRandomNByteInteger :: Int -> StateT PureMT m Integer Source #

(Monad m, Monoid w) => MonadRandom (RWST r w PureMT m) Source # 
Instance details

Defined in Data.Random.Source.PureMT

Methods

getRandomPrim :: Prim t -> RWST r w PureMT m t Source #

getRandomWord8 :: RWST r w PureMT m Word8 Source #

getRandomWord16 :: RWST r w PureMT m Word16 Source #

getRandomWord32 :: RWST r w PureMT m Word32 Source #

getRandomWord64 :: RWST r w PureMT m Word64 Source #

getRandomDouble :: RWST r w PureMT m Double Source #

getRandomNByteInteger :: Int -> RWST r w PureMT m Integer Source #

(Monad m, Monoid w) => MonadRandom (RWST r w PureMT m) Source # 
Instance details

Defined in Data.Random.Source.PureMT

Methods

getRandomPrim :: Prim t -> RWST r w PureMT m t Source #

getRandomWord8 :: RWST r w PureMT m Word8 Source #

getRandomWord16 :: RWST r w PureMT m Word16 Source #

getRandomWord32 :: RWST r w PureMT m Word32 Source #

getRandomWord64 :: RWST r w PureMT m Word64 Source #

getRandomDouble :: RWST r w PureMT m Double Source #

getRandomNByteInteger :: Int -> RWST r w PureMT m Integer Source #

newPureMT :: IO PureMT Source #

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

pureMT :: Word64 -> PureMT Source #

Create a PureMT generator from a Word64 seed.

getRandomPrimFromMTRef :: ModifyRef sr m PureMT => sr -> Prim a -> m a Source #

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

Orphan instances

MonadIO m => RandomSource m (IORef PureMT) Source # 
Instance details

(Monad m1, ModifyRef (Ref m2 PureMT) m1 PureMT) => RandomSource m1 (Ref m2 PureMT) Source # 
Instance details

Methods

getRandomPrimFrom :: Ref m2 PureMT -> Prim t -> m1 t Source #

getRandomWord8From :: Ref m2 PureMT -> m1 Word8 Source #

getRandomWord16From :: Ref m2 PureMT -> m1 Word16 Source #

getRandomWord32From :: Ref m2 PureMT -> m1 Word32 Source #

getRandomWord64From :: Ref m2 PureMT -> m1 Word64 Source #

getRandomDoubleFrom :: Ref m2 PureMT -> m1 Double Source #

getRandomNByteIntegerFrom :: Ref m2 PureMT -> Int -> m1 Integer Source #

(Monad m, ModifyRef (STRef s PureMT) m PureMT) => RandomSource m (STRef s PureMT) Source # 
Instance details

Monad m => MonadRandom (StateT PureMT m) Source # 
Instance details

Methods

getRandomPrim :: Prim t -> StateT PureMT m t Source #

getRandomWord8 :: StateT PureMT m Word8 Source #

getRandomWord16 :: StateT PureMT m Word16 Source #

getRandomWord32 :: StateT PureMT m Word32 Source #

getRandomWord64 :: StateT PureMT m Word64 Source #

getRandomDouble :: StateT PureMT m Double Source #

getRandomNByteInteger :: Int -> StateT PureMT m Integer Source #

Monad m => MonadRandom (StateT PureMT m) Source # 
Instance details

Methods

getRandomPrim :: Prim t -> StateT PureMT m t Source #

getRandomWord8 :: StateT PureMT m Word8 Source #

getRandomWord16 :: StateT PureMT m Word16 Source #

getRandomWord32 :: StateT PureMT m Word32 Source #

getRandomWord64 :: StateT PureMT m Word64 Source #

getRandomDouble :: StateT PureMT m Double Source #

getRandomNByteInteger :: Int -> StateT PureMT m Integer Source #

(Monad m, Monoid w) => MonadRandom (RWST r w PureMT m) Source # 
Instance details

Methods

getRandomPrim :: Prim t -> RWST r w PureMT m t Source #

getRandomWord8 :: RWST r w PureMT m Word8 Source #

getRandomWord16 :: RWST r w PureMT m Word16 Source #

getRandomWord32 :: RWST r w PureMT m Word32 Source #

getRandomWord64 :: RWST r w PureMT m Word64 Source #

getRandomDouble :: RWST r w PureMT m Double Source #

getRandomNByteInteger :: Int -> RWST r w PureMT m Integer Source #

(Monad m, Monoid w) => MonadRandom (RWST r w PureMT m) Source # 
Instance details

Methods

getRandomPrim :: Prim t -> RWST r w PureMT m t Source #

getRandomWord8 :: RWST r w PureMT m Word8 Source #

getRandomWord16 :: RWST r w PureMT m Word16 Source #

getRandomWord32 :: RWST r w PureMT m Word32 Source #

getRandomWord64 :: RWST r w PureMT m Word64 Source #

getRandomDouble :: RWST r w PureMT m Double Source #

getRandomNByteInteger :: Int -> RWST r w PureMT m Integer Source #