MonadRandom-0.5.3: Random-number generation monad.
Copyright(c) Brent Yorgey 2016
LicenseBSD3 (see LICENSE)
Maintainerbyorgey@gmail.com
Stabilityexperimental
Portabilitynon-portable (multi-param classes, functional dependencies, undecidable instances)
Safe HaskellSafe
LanguageHaskell2010

Control.Monad.Random.Lazy

Description

Random monads that are lazy in the generator state. For a strict version, see Control.Monad.Random.Strict, which has the same interface.

Synopsis

The Rand monad

type Rand g = RandT g Identity Source #

A random monad parameterized by the type g of the generator to carry.

The return function leaves the generator unchanged, while >>= uses the final generator of the first computation as the initial generator of the second.

liftRand Source #

Arguments

:: (g -> (a, g))

pure random transformer

-> Rand g a

equivalent generator-passing computation

Construct a random monad computation from a function. (The inverse of runRand.)

runRand Source #

Arguments

:: Rand g a

generator-passing computation to execute

-> g

initial generator

-> (a, g)

return value and final generator

Unwrap a random monad computation as a function. (The inverse of liftRand.)

evalRand Source #

Arguments

:: Rand g a

generator-passing computation to execute

-> g

initial generator

-> a

return value of the random computation

Evaluate a random computation with the given initial generator and return the final value, discarding the final generator.

execRand Source #

Arguments

:: Rand g a

generator-passing computation to execute

-> g

initial generator

-> g

final generator

Evaluate a random computation with the given initial generator and return the final generator, discarding the final value.

mapRand :: ((a, g) -> (b, g)) -> Rand g a -> Rand g b Source #

Map both the return value and final generator of a computation using the given function.

withRand :: (g -> g) -> Rand g a -> Rand g a Source #

withRand f m executes action m on a generator modified by applying f.

evalRandIO :: Rand StdGen a -> IO a Source #

Evaluate a random computation in the IO monad, splitting the global standard generator to get a new one for the computation.

The RandT monad transformer

data RandT g m a Source #

A random transformer monad parameterized by:

  • g - The generator.
  • m - The inner monad.

The return function leaves the generator unchanged, while >>= uses the final generator of the first computation as the initial generator of the second.

Instances

Instances details
(MonadReader r m, MonadWriter w m, MonadState s m) => MonadRWS r w s (RandT g m) Source # 
Instance details

Defined in Control.Monad.Trans.Random.Lazy

MonadWriter w m => MonadWriter w (RandT g m) Source # 
Instance details

Defined in Control.Monad.Trans.Random.Lazy

Methods

writer :: (a, w) -> RandT g m a #

tell :: w -> RandT g m () #

listen :: RandT g m a -> RandT g m (a, w) #

pass :: RandT g m (a, w -> w) -> RandT g m a #

MonadState s m => MonadState s (RandT g m) Source # 
Instance details

Defined in Control.Monad.Trans.Random.Lazy

Methods

get :: RandT g m s #

put :: s -> RandT g m () #

state :: (s -> (a, s)) -> RandT g m a #

MonadReader r m => MonadReader r (RandT g m) Source # 
Instance details

Defined in Control.Monad.Trans.Random.Lazy

Methods

ask :: RandT g m r #

local :: (r -> r) -> RandT g m a -> RandT g m a #

reader :: (r -> a) -> RandT g m a #

MonadError e m => MonadError e (RandT g m) Source # 
Instance details

Defined in Control.Monad.Trans.Random.Lazy

Methods

throwError :: e -> RandT g m a #

catchError :: RandT g m a -> (e -> RandT g m a) -> RandT g m a #

(RandomGen g, Monad m) => MonadSplit g (RandT g m) Source # 
Instance details

Defined in Control.Monad.Trans.Random.Lazy

Methods

getSplit :: RandT g m g Source #

MonadTrans (RandT g) Source # 
Instance details

Defined in Control.Monad.Trans.Random.Lazy

Methods

lift :: Monad m => m a -> RandT g m a #

(Monad m, RandomGen g) => RandomGenM (RandGen g) g (RandT g m) Source #

Since: 0.5.3

Instance details

Defined in Control.Monad.Trans.Random.Lazy

Methods

applyRandomGenM :: (g -> (a, g)) -> RandGen g -> RandT g m a #

(Monad m, RandomGen g) => StatefulGen (RandGen g) (RandT g m) Source #

Since: 0.5.3

Instance details

Defined in Control.Monad.Trans.Random.Lazy

Monad m => Monad (RandT g m) Source # 
Instance details

Defined in Control.Monad.Trans.Random.Lazy

Methods

(>>=) :: RandT g m a -> (a -> RandT g m b) -> RandT g m b #

(>>) :: RandT g m a -> RandT g m b -> RandT g m b #

return :: a -> RandT g m a #

Functor m => Functor (RandT g m) Source # 
Instance details

Defined in Control.Monad.Trans.Random.Lazy

Methods

fmap :: (a -> b) -> RandT g m a -> RandT g m b #

(<$) :: a -> RandT g m b -> RandT g m a #

MonadFix m => MonadFix (RandT g m) Source # 
Instance details

Defined in Control.Monad.Trans.Random.Lazy

Methods

mfix :: (a -> RandT g m a) -> RandT g m a #

MonadFail m => MonadFail (RandT g m) Source # 
Instance details

Defined in Control.Monad.Trans.Random.Lazy

Methods

fail :: String -> RandT g m a #

Monad m => Applicative (RandT g m) Source # 
Instance details

Defined in Control.Monad.Trans.Random.Lazy

Methods

pure :: a -> RandT g m a #

(<*>) :: RandT g m (a -> b) -> RandT g m a -> RandT g m b #

liftA2 :: (a -> b -> c) -> RandT g m a -> RandT g m b -> RandT g m c #

(*>) :: RandT g m a -> RandT g m b -> RandT g m b #

(<*) :: RandT g m a -> RandT g m b -> RandT g m a #

MonadIO m => MonadIO (RandT g m) Source # 
Instance details

Defined in Control.Monad.Trans.Random.Lazy

Methods

liftIO :: IO a -> RandT g m a #

MonadPlus m => Alternative (RandT g m) Source # 
Instance details

Defined in Control.Monad.Trans.Random.Lazy

Methods

empty :: RandT g m a #

(<|>) :: RandT g m a -> RandT g m a -> RandT g m a #

some :: RandT g m a -> RandT g m [a] #

many :: RandT g m a -> RandT g m [a] #

MonadPlus m => MonadPlus (RandT g m) Source # 
Instance details

Defined in Control.Monad.Trans.Random.Lazy

Methods

mzero :: RandT g m a #

mplus :: RandT g m a -> RandT g m a -> RandT g m a #

MonadCont m => MonadCont (RandT g m) Source # 
Instance details

Defined in Control.Monad.Trans.Random.Lazy

Methods

callCC :: ((a -> RandT g m b) -> RandT g m a) -> RandT g m a #

PrimMonad m => PrimMonad (RandT s m) Source # 
Instance details

Defined in Control.Monad.Trans.Random.Lazy

Associated Types

type PrimState (RandT s m) #

Methods

primitive :: (State# (PrimState (RandT s m)) -> (# State# (PrimState (RandT s m)), a #)) -> RandT s m a #

(Monad m, RandomGen g) => MonadInterleave (RandT g m) Source # 
Instance details

Defined in Control.Monad.Trans.Random.Lazy

Methods

interleave :: RandT g m a -> RandT g m a Source #

(RandomGen g, Monad m) => MonadRandom (RandT g m) Source # 
Instance details

Defined in Control.Monad.Trans.Random.Lazy

Methods

getRandomR :: Random a => (a, a) -> RandT g m a Source #

getRandom :: Random a => RandT g m a Source #

getRandomRs :: Random a => (a, a) -> RandT g m [a] Source #

getRandoms :: Random a => RandT g m [a] Source #

type PrimState (RandT s m) Source # 
Instance details

Defined in Control.Monad.Trans.Random.Lazy

type PrimState (RandT s m) = PrimState m

liftRandT Source #

Arguments

:: (g -> m (a, g))

impure random transformer

-> RandT g m a

equivalent generator-passing computation

Construct a random monad computation from an impure function. (The inverse of runRandT.)

runRandT Source #

Arguments

:: RandT g m a

generator-passing computation to execute

-> g

initial generator

-> m (a, g)

return value and final generator

Unwrap a random monad computation as an impure function. (The inverse of liftRandT.)

evalRandT :: Monad m => RandT g m a -> g -> m a Source #

Evaluate a random computation with the given initial generator and return the final value, discarding the final generator.

execRandT :: Monad m => RandT g m a -> g -> m g Source #

Evaluate a random computation with the given initial generator and return the final generator, discarding the final value.

mapRandT :: (m (a, g) -> n (b, g)) -> RandT g m a -> RandT g n b Source #

Map both the return value and final generator of a computation using the given function.

withRandT :: (g -> g) -> RandT g m a -> RandT g m a Source #

withRandT f m executes action m on a generator modified by applying f.

evalRandTIO :: MonadIO m => RandT StdGen m a -> m a Source #

Evaluate a random computation that is embedded in the IO monad, splitting the global standard generator to get a new one for the computation.

Some convenience re-exports

randomIO :: (Random a, MonadIO m) => m a #

A variant of random that uses the global pseudo-random number generator.

randomRIO :: (Random a, MonadIO m) => (a, a) -> m a #

A variant of randomR that uses the global pseudo-random number generator.

getStdRandom :: MonadIO m => (StdGen -> (a, StdGen)) -> m a #

Uses the supplied function to get a value from the current global random generator, and updates the global generator with the new generator returned by the function. For example, rollDice gets a pseudo-random integer between 1 and 6:

 rollDice :: IO Int
 rollDice = getStdRandom (randomR (1,6))

newStdGen :: MonadIO m => m StdGen #

Applies split to the current global pseudo-random generator, updates it with one of the results, and returns the other.

getStdGen :: MonadIO m => m StdGen #

Gets the global pseudo-random number generator.

setStdGen :: MonadIO m => StdGen -> m () #

Sets the global pseudo-random number generator.

genByteString :: RandomGen g => Int -> g -> (ByteString, g) #

Generates a ByteString of the specified size using a pure pseudo-random number generator. See uniformByteString for the monadic version.

Examples

Expand
>>> import System.Random
>>> import Data.ByteString
>>> let pureGen = mkStdGen 137
>>> unpack . fst . genByteString 10 $ pureGen
[51,123,251,37,49,167,90,109,1,4]

Since: random-1.2.0

class Random a where #

The class of types for which uniformly distributed values can be generated.

Random exists primarily for backwards compatibility with version 1.1 of this library. In new code, use the better specified Uniform and UniformRange instead.

Minimal complete definition

Nothing

Methods

randomR :: RandomGen g => (a, a) -> g -> (a, g) #

Takes a range (lo,hi) and a pseudo-random number generator g, and returns a pseudo-random value uniformly distributed over the closed interval [lo,hi], together with a new generator. It is unspecified what happens if lo>hi. For continuous types there is no requirement that the values lo and hi are ever produced, but they may be, depending on the implementation and the interval.

random :: RandomGen g => g -> (a, g) #

The same as randomR, but using a default range determined by the type:

  • For bounded types (instances of Bounded, such as Char), the range is normally the whole type.
  • For fractional types, the range is normally the semi-closed interval [0,1).
  • For Integer, the range is (arbitrarily) the range of Int.

randomRs :: RandomGen g => (a, a) -> g -> [a] #

Plural variant of randomR, producing an infinite list of pseudo-random values instead of returning a new generator.

randoms :: RandomGen g => g -> [a] #

Plural variant of random, producing an infinite list of pseudo-random values instead of returning a new generator.

Instances

Instances details
Random Bool 
Instance details

Defined in System.Random

Methods

randomR :: RandomGen g => (Bool, Bool) -> g -> (Bool, g) #

random :: RandomGen g => g -> (Bool, g) #

randomRs :: RandomGen g => (Bool, Bool) -> g -> [Bool] #

randoms :: RandomGen g => g -> [Bool] #

Random Char 
Instance details

Defined in System.Random

Methods

randomR :: RandomGen g => (Char, Char) -> g -> (Char, g) #

random :: RandomGen g => g -> (Char, g) #

randomRs :: RandomGen g => (Char, Char) -> g -> [Char] #

randoms :: RandomGen g => g -> [Char] #

Random Double 
Instance details

Defined in System.Random

Methods

randomR :: RandomGen g => (Double, Double) -> g -> (Double, g) #

random :: RandomGen g => g -> (Double, g) #

randomRs :: RandomGen g => (Double, Double) -> g -> [Double] #

randoms :: RandomGen g => g -> [Double] #

Random Float 
Instance details

Defined in System.Random

Methods

randomR :: RandomGen g => (Float, Float) -> g -> (Float, g) #

random :: RandomGen g => g -> (Float, g) #

randomRs :: RandomGen g => (Float, Float) -> g -> [Float] #

randoms :: RandomGen g => g -> [Float] #

Random Int 
Instance details

Defined in System.Random

Methods

randomR :: RandomGen g => (Int, Int) -> g -> (Int, g) #

random :: RandomGen g => g -> (Int, g) #

randomRs :: RandomGen g => (Int, Int) -> g -> [Int] #

randoms :: RandomGen g => g -> [Int] #

Random Int8 
Instance details

Defined in System.Random

Methods

randomR :: RandomGen g => (Int8, Int8) -> g -> (Int8, g) #

random :: RandomGen g => g -> (Int8, g) #

randomRs :: RandomGen g => (Int8, Int8) -> g -> [Int8] #

randoms :: RandomGen g => g -> [Int8] #

Random Int16 
Instance details

Defined in System.Random

Methods

randomR :: RandomGen g => (Int16, Int16) -> g -> (Int16, g) #

random :: RandomGen g => g -> (Int16, g) #

randomRs :: RandomGen g => (Int16, Int16) -> g -> [Int16] #

randoms :: RandomGen g => g -> [Int16] #

Random Int32 
Instance details

Defined in System.Random

Methods

randomR :: RandomGen g => (Int32, Int32) -> g -> (Int32, g) #

random :: RandomGen g => g -> (Int32, g) #

randomRs :: RandomGen g => (Int32, Int32) -> g -> [Int32] #

randoms :: RandomGen g => g -> [Int32] #

Random Int64 
Instance details

Defined in System.Random

Methods

randomR :: RandomGen g => (Int64, Int64) -> g -> (Int64, g) #

random :: RandomGen g => g -> (Int64, g) #

randomRs :: RandomGen g => (Int64, Int64) -> g -> [Int64] #

randoms :: RandomGen g => g -> [Int64] #

Random Integer 
Instance details

Defined in System.Random

Methods

randomR :: RandomGen g => (Integer, Integer) -> g -> (Integer, g) #

random :: RandomGen g => g -> (Integer, g) #

randomRs :: RandomGen g => (Integer, Integer) -> g -> [Integer] #

randoms :: RandomGen g => g -> [Integer] #

Random Word 
Instance details

Defined in System.Random

Methods

randomR :: RandomGen g => (Word, Word) -> g -> (Word, g) #

random :: RandomGen g => g -> (Word, g) #

randomRs :: RandomGen g => (Word, Word) -> g -> [Word] #

randoms :: RandomGen g => g -> [Word] #

Random Word8 
Instance details

Defined in System.Random

Methods

randomR :: RandomGen g => (Word8, Word8) -> g -> (Word8, g) #

random :: RandomGen g => g -> (Word8, g) #

randomRs :: RandomGen g => (Word8, Word8) -> g -> [Word8] #

randoms :: RandomGen g => g -> [Word8] #

Random Word16 
Instance details

Defined in System.Random

Methods

randomR :: RandomGen g => (Word16, Word16) -> g -> (Word16, g) #

random :: RandomGen g => g -> (Word16, g) #

randomRs :: RandomGen g => (Word16, Word16) -> g -> [Word16] #

randoms :: RandomGen g => g -> [Word16] #

Random Word32 
Instance details

Defined in System.Random

Methods

randomR :: RandomGen g => (Word32, Word32) -> g -> (Word32, g) #

random :: RandomGen g => g -> (Word32, g) #

randomRs :: RandomGen g => (Word32, Word32) -> g -> [Word32] #

randoms :: RandomGen g => g -> [Word32] #

Random Word64 
Instance details

Defined in System.Random

Methods

randomR :: RandomGen g => (Word64, Word64) -> g -> (Word64, g) #

random :: RandomGen g => g -> (Word64, g) #

randomRs :: RandomGen g => (Word64, Word64) -> g -> [Word64] #

randoms :: RandomGen g => g -> [Word64] #

Random CChar 
Instance details

Defined in System.Random

Methods

randomR :: RandomGen g => (CChar, CChar) -> g -> (CChar, g) #

random :: RandomGen g => g -> (CChar, g) #

randomRs :: RandomGen g => (CChar, CChar) -> g -> [CChar] #

randoms :: RandomGen g => g -> [CChar] #

Random CSChar 
Instance details

Defined in System.Random

Methods

randomR :: RandomGen g => (CSChar, CSChar) -> g -> (CSChar, g) #

random :: RandomGen g => g -> (CSChar, g) #

randomRs :: RandomGen g => (CSChar, CSChar) -> g -> [CSChar] #

randoms :: RandomGen g => g -> [CSChar] #

Random CUChar 
Instance details

Defined in System.Random

Methods

randomR :: RandomGen g => (CUChar, CUChar) -> g -> (CUChar, g) #

random :: RandomGen g => g -> (CUChar, g) #

randomRs :: RandomGen g => (CUChar, CUChar) -> g -> [CUChar] #

randoms :: RandomGen g => g -> [CUChar] #

Random CShort 
Instance details

Defined in System.Random

Methods

randomR :: RandomGen g => (CShort, CShort) -> g -> (CShort, g) #

random :: RandomGen g => g -> (CShort, g) #

randomRs :: RandomGen g => (CShort, CShort) -> g -> [CShort] #

randoms :: RandomGen g => g -> [CShort] #

Random CUShort 
Instance details

Defined in System.Random

Methods

randomR :: RandomGen g => (CUShort, CUShort) -> g -> (CUShort, g) #

random :: RandomGen g => g -> (CUShort, g) #

randomRs :: RandomGen g => (CUShort, CUShort) -> g -> [CUShort] #

randoms :: RandomGen g => g -> [CUShort] #

Random CInt 
Instance details

Defined in System.Random

Methods

randomR :: RandomGen g => (CInt, CInt) -> g -> (CInt, g) #

random :: RandomGen g => g -> (CInt, g) #

randomRs :: RandomGen g => (CInt, CInt) -> g -> [CInt] #

randoms :: RandomGen g => g -> [CInt] #

Random CUInt 
Instance details

Defined in System.Random

Methods

randomR :: RandomGen g => (CUInt, CUInt) -> g -> (CUInt, g) #

random :: RandomGen g => g -> (CUInt, g) #

randomRs :: RandomGen g => (CUInt, CUInt) -> g -> [CUInt] #

randoms :: RandomGen g => g -> [CUInt] #

Random CLong 
Instance details

Defined in System.Random

Methods

randomR :: RandomGen g => (CLong, CLong) -> g -> (CLong, g) #

random :: RandomGen g => g -> (CLong, g) #

randomRs :: RandomGen g => (CLong, CLong) -> g -> [CLong] #

randoms :: RandomGen g => g -> [CLong] #

Random CULong 
Instance details

Defined in System.Random

Methods

randomR :: RandomGen g => (CULong, CULong) -> g -> (CULong, g) #

random :: RandomGen g => g -> (CULong, g) #

randomRs :: RandomGen g => (CULong, CULong) -> g -> [CULong] #

randoms :: RandomGen g => g -> [CULong] #

Random CLLong 
Instance details

Defined in System.Random

Methods

randomR :: RandomGen g => (CLLong, CLLong) -> g -> (CLLong, g) #

random :: RandomGen g => g -> (CLLong, g) #

randomRs :: RandomGen g => (CLLong, CLLong) -> g -> [CLLong] #

randoms :: RandomGen g => g -> [CLLong] #

Random CULLong 
Instance details

Defined in System.Random

Methods

randomR :: RandomGen g => (CULLong, CULLong) -> g -> (CULLong, g) #

random :: RandomGen g => g -> (CULLong, g) #

randomRs :: RandomGen g => (CULLong, CULLong) -> g -> [CULLong] #

randoms :: RandomGen g => g -> [CULLong] #

Random CFloat 
Instance details

Defined in System.Random

Methods

randomR :: RandomGen g => (CFloat, CFloat) -> g -> (CFloat, g) #

random :: RandomGen g => g -> (CFloat, g) #

randomRs :: RandomGen g => (CFloat, CFloat) -> g -> [CFloat] #

randoms :: RandomGen g => g -> [CFloat] #

Random CDouble 
Instance details

Defined in System.Random

Methods

randomR :: RandomGen g => (CDouble, CDouble) -> g -> (CDouble, g) #

random :: RandomGen g => g -> (CDouble, g) #

randomRs :: RandomGen g => (CDouble, CDouble) -> g -> [CDouble] #

randoms :: RandomGen g => g -> [CDouble] #

Random CPtrdiff 
Instance details

Defined in System.Random

Methods

randomR :: RandomGen g => (CPtrdiff, CPtrdiff) -> g -> (CPtrdiff, g) #

random :: RandomGen g => g -> (CPtrdiff, g) #

randomRs :: RandomGen g => (CPtrdiff, CPtrdiff) -> g -> [CPtrdiff] #

randoms :: RandomGen g => g -> [CPtrdiff] #

Random CSize 
Instance details

Defined in System.Random

Methods

randomR :: RandomGen g => (CSize, CSize) -> g -> (CSize, g) #

random :: RandomGen g => g -> (CSize, g) #

randomRs :: RandomGen g => (CSize, CSize) -> g -> [CSize] #

randoms :: RandomGen g => g -> [CSize] #

Random CWchar 
Instance details

Defined in System.Random

Methods

randomR :: RandomGen g => (CWchar, CWchar) -> g -> (CWchar, g) #

random :: RandomGen g => g -> (CWchar, g) #

randomRs :: RandomGen g => (CWchar, CWchar) -> g -> [CWchar] #

randoms :: RandomGen g => g -> [CWchar] #

Random CSigAtomic 
Instance details

Defined in System.Random

Methods

randomR :: RandomGen g => (CSigAtomic, CSigAtomic) -> g -> (CSigAtomic, g) #

random :: RandomGen g => g -> (CSigAtomic, g) #

randomRs :: RandomGen g => (CSigAtomic, CSigAtomic) -> g -> [CSigAtomic] #

randoms :: RandomGen g => g -> [CSigAtomic] #

Random CIntPtr 
Instance details

Defined in System.Random

Methods

randomR :: RandomGen g => (CIntPtr, CIntPtr) -> g -> (CIntPtr, g) #

random :: RandomGen g => g -> (CIntPtr, g) #

randomRs :: RandomGen g => (CIntPtr, CIntPtr) -> g -> [CIntPtr] #

randoms :: RandomGen g => g -> [CIntPtr] #

Random CUIntPtr 
Instance details

Defined in System.Random

Methods

randomR :: RandomGen g => (CUIntPtr, CUIntPtr) -> g -> (CUIntPtr, g) #

random :: RandomGen g => g -> (CUIntPtr, g) #

randomRs :: RandomGen g => (CUIntPtr, CUIntPtr) -> g -> [CUIntPtr] #

randoms :: RandomGen g => g -> [CUIntPtr] #

Random CIntMax 
Instance details

Defined in System.Random

Methods

randomR :: RandomGen g => (CIntMax, CIntMax) -> g -> (CIntMax, g) #

random :: RandomGen g => g -> (CIntMax, g) #

randomRs :: RandomGen g => (CIntMax, CIntMax) -> g -> [CIntMax] #

randoms :: RandomGen g => g -> [CIntMax] #

Random CUIntMax 
Instance details

Defined in System.Random

Methods

randomR :: RandomGen g => (CUIntMax, CUIntMax) -> g -> (CUIntMax, g) #

random :: RandomGen g => g -> (CUIntMax, g) #

randomRs :: RandomGen g => (CUIntMax, CUIntMax) -> g -> [CUIntMax] #

randoms :: RandomGen g => g -> [CUIntMax] #

mkStdGen :: Int -> StdGen #

Constructs a StdGen deterministically.

class RandomGen g where #

RandomGen is an interface to pure pseudo-random number generators.

StdGen is the standard RandomGen instance provided by this library.

Minimal complete definition

split, (genWord32 | genWord64 | next, genRange)

Methods

next :: g -> (Int, g) #

Returns an Int that is uniformly distributed over the range returned by genRange (including both end points), and a new generator. Using next is inefficient as all operations go via Integer. See here for more details. It is thus deprecated.

genWord8 :: g -> (Word8, g) #

Returns a Word8 that is uniformly distributed over the entire Word8 range.

Since: random-1.2.0

genWord16 :: g -> (Word16, g) #

Returns a Word16 that is uniformly distributed over the entire Word16 range.

Since: random-1.2.0

genWord32 :: g -> (Word32, g) #

Returns a Word32 that is uniformly distributed over the entire Word32 range.

Since: random-1.2.0

genWord64 :: g -> (Word64, g) #

Returns a Word64 that is uniformly distributed over the entire Word64 range.

Since: random-1.2.0

genWord32R :: Word32 -> g -> (Word32, g) #

genWord32R upperBound g returns a Word32 that is uniformly distributed over the range [0, upperBound].

Since: random-1.2.0

genWord64R :: Word64 -> g -> (Word64, g) #

genWord64R upperBound g returns a Word64 that is uniformly distributed over the range [0, upperBound].

Since: random-1.2.0

genShortByteString :: Int -> g -> (ShortByteString, g) #

genShortByteString n g returns a ShortByteString of length n filled with pseudo-random bytes.

Since: random-1.2.0

genRange :: g -> (Int, Int) #

Yields the range of values returned by next.

It is required that:

  • If (a, b) = genRange g, then a < b.
  • genRange must not examine its argument so the value it returns is determined only by the instance of RandomGen.

The default definition spans the full range of Int.

split :: g -> (g, g) #

Returns two distinct pseudo-random number generators.

Implementations should take care to ensure that the resulting generators are not correlated. Some pseudo-random number generators are not splittable. In that case, the split implementation should fail with a descriptive error message.

Instances

Instances details
RandomGen StdGen 
Instance details

Defined in System.Random.Internal

RandomGen SMGen 
Instance details

Defined in System.Random.Internal

RandomGen SMGen 
Instance details

Defined in System.Random.Internal

RandomGen g => RandomGen (AtomicGen g) 
Instance details

Defined in System.Random.Stateful

RandomGen g => RandomGen (IOGen g) 
Instance details

Defined in System.Random.Stateful

Methods

next :: IOGen g -> (Int, IOGen g) #

genWord8 :: IOGen g -> (Word8, IOGen g) #

genWord16 :: IOGen g -> (Word16, IOGen g) #

genWord32 :: IOGen g -> (Word32, IOGen g) #

genWord64 :: IOGen g -> (Word64, IOGen g) #

genWord32R :: Word32 -> IOGen g -> (Word32, IOGen g) #

genWord64R :: Word64 -> IOGen g -> (Word64, IOGen g) #

genShortByteString :: Int -> IOGen g -> (ShortByteString, IOGen g) #

genRange :: IOGen g -> (Int, Int) #

split :: IOGen g -> (IOGen g, IOGen g) #

RandomGen g => RandomGen (STGen g) 
Instance details

Defined in System.Random.Stateful

Methods

next :: STGen g -> (Int, STGen g) #

genWord8 :: STGen g -> (Word8, STGen g) #

genWord16 :: STGen g -> (Word16, STGen g) #

genWord32 :: STGen g -> (Word32, STGen g) #

genWord64 :: STGen g -> (Word64, STGen g) #

genWord32R :: Word32 -> STGen g -> (Word32, STGen g) #

genWord64R :: Word64 -> STGen g -> (Word64, STGen g) #

genShortByteString :: Int -> STGen g -> (ShortByteString, STGen g) #

genRange :: STGen g -> (Int, Int) #

split :: STGen g -> (STGen g, STGen g) #

RandomGen g => RandomGen (StateGen g) 
Instance details

Defined in System.Random.Internal

data StdGen #

The standard pseudo-random number generator.

Instances

Instances details
Eq StdGen 
Instance details

Defined in System.Random.Internal

Methods

(==) :: StdGen -> StdGen -> Bool #

(/=) :: StdGen -> StdGen -> Bool #

Show StdGen 
Instance details

Defined in System.Random.Internal

NFData StdGen 
Instance details

Defined in System.Random.Internal

Methods

rnf :: StdGen -> () #

RandomGen StdGen 
Instance details

Defined in System.Random.Internal

MonadSplit StdGen IO Source # 
Instance details

Defined in Control.Monad.Random.Class

class Uniform a #

The class of types for which a uniformly distributed value can be drawn from all possible values of the type.

Since: random-1.2.0

Minimal complete definition

uniformM

Instances

Instances details
Uniform Bool 
Instance details

Defined in System.Random.Internal

Methods

uniformM :: StatefulGen g m => g -> m Bool #

Uniform Char 
Instance details

Defined in System.Random.Internal

Methods

uniformM :: StatefulGen g m => g -> m Char #

Uniform Int 
Instance details

Defined in System.Random.Internal

Methods

uniformM :: StatefulGen g m => g -> m Int #

Uniform Int8 
Instance details

Defined in System.Random.Internal

Methods

uniformM :: StatefulGen g m => g -> m Int8 #

Uniform Int16 
Instance details

Defined in System.Random.Internal

Methods

uniformM :: StatefulGen g m => g -> m Int16 #

Uniform Int32 
Instance details

Defined in System.Random.Internal

Methods

uniformM :: StatefulGen g m => g -> m Int32 #

Uniform Int64 
Instance details

Defined in System.Random.Internal

Methods

uniformM :: StatefulGen g m => g -> m Int64 #

Uniform Word 
Instance details

Defined in System.Random.Internal

Methods

uniformM :: StatefulGen g m => g -> m Word #

Uniform Word8 
Instance details

Defined in System.Random.Internal

Methods

uniformM :: StatefulGen g m => g -> m Word8 #

Uniform Word16 
Instance details

Defined in System.Random.Internal

Methods

uniformM :: StatefulGen g m => g -> m Word16 #

Uniform Word32 
Instance details

Defined in System.Random.Internal

Methods

uniformM :: StatefulGen g m => g -> m Word32 #

Uniform Word64 
Instance details

Defined in System.Random.Internal

Methods

uniformM :: StatefulGen g m => g -> m Word64 #

Uniform CChar 
Instance details

Defined in System.Random.Internal

Methods

uniformM :: StatefulGen g m => g -> m CChar #

Uniform CSChar 
Instance details

Defined in System.Random.Internal

Methods

uniformM :: StatefulGen g m => g -> m CSChar #

Uniform CUChar 
Instance details

Defined in System.Random.Internal

Methods

uniformM :: StatefulGen g m => g -> m CUChar #

Uniform CShort 
Instance details

Defined in System.Random.Internal

Methods

uniformM :: StatefulGen g m => g -> m CShort #

Uniform CUShort 
Instance details

Defined in System.Random.Internal

Methods

uniformM :: StatefulGen g m => g -> m CUShort #

Uniform CInt 
Instance details

Defined in System.Random.Internal

Methods

uniformM :: StatefulGen g m => g -> m CInt #

Uniform CUInt 
Instance details

Defined in System.Random.Internal

Methods

uniformM :: StatefulGen g m => g -> m CUInt #

Uniform CLong 
Instance details

Defined in System.Random.Internal

Methods

uniformM :: StatefulGen g m => g -> m CLong #

Uniform CULong 
Instance details

Defined in System.Random.Internal

Methods

uniformM :: StatefulGen g m => g -> m CULong #

Uniform CLLong 
Instance details

Defined in System.Random.Internal

Methods

uniformM :: StatefulGen g m => g -> m CLLong #

Uniform CULLong 
Instance details

Defined in System.Random.Internal

Methods

uniformM :: StatefulGen g m => g -> m CULLong #

Uniform CBool 
Instance details

Defined in System.Random.Internal

Methods

uniformM :: StatefulGen g m => g -> m CBool #

Uniform CPtrdiff 
Instance details

Defined in System.Random.Internal

Methods

uniformM :: StatefulGen g m => g -> m CPtrdiff #

Uniform CSize 
Instance details

Defined in System.Random.Internal

Methods

uniformM :: StatefulGen g m => g -> m CSize #

Uniform CWchar 
Instance details

Defined in System.Random.Internal

Methods

uniformM :: StatefulGen g m => g -> m CWchar #

Uniform CSigAtomic 
Instance details

Defined in System.Random.Internal

Methods

uniformM :: StatefulGen g m => g -> m CSigAtomic #

Uniform CIntPtr 
Instance details

Defined in System.Random.Internal

Methods

uniformM :: StatefulGen g m => g -> m CIntPtr #

Uniform CUIntPtr 
Instance details

Defined in System.Random.Internal

Methods

uniformM :: StatefulGen g m => g -> m CUIntPtr #

Uniform CIntMax 
Instance details

Defined in System.Random.Internal

Methods

uniformM :: StatefulGen g m => g -> m CIntMax #

Uniform CUIntMax 
Instance details

Defined in System.Random.Internal

Methods

uniformM :: StatefulGen g m => g -> m CUIntMax #

(Uniform a, Uniform b) => Uniform (a, b) 
Instance details

Defined in System.Random.Internal

Methods

uniformM :: StatefulGen g m => g -> m (a, b) #

(Uniform a, Uniform b, Uniform c) => Uniform (a, b, c) 
Instance details

Defined in System.Random.Internal

Methods

uniformM :: StatefulGen g m => g -> m (a, b, c) #

(Uniform a, Uniform b, Uniform c, Uniform d) => Uniform (a, b, c, d) 
Instance details

Defined in System.Random.Internal

Methods

uniformM :: StatefulGen g m => g -> m (a, b, c, d) #

(Uniform a, Uniform b, Uniform c, Uniform d, Uniform e) => Uniform (a, b, c, d, e) 
Instance details

Defined in System.Random.Internal

Methods

uniformM :: StatefulGen g m => g -> m (a, b, c, d, e) #

(Uniform a, Uniform b, Uniform c, Uniform d, Uniform e, Uniform f) => Uniform (a, b, c, d, e, f) 
Instance details

Defined in System.Random.Internal

Methods

uniformM :: StatefulGen g m => g -> m (a, b, c, d, e, f) #

(Uniform a, Uniform b, Uniform c, Uniform d, Uniform e, Uniform f, Uniform g) => Uniform (a, b, c, d, e, f, g) 
Instance details

Defined in System.Random.Internal

Methods

uniformM :: StatefulGen g0 m => g0 -> m (a, b, c, d, e, f, g) #

class UniformRange a #

The class of types for which a uniformly distributed value can be drawn from a range.

Since: random-1.2.0

Minimal complete definition

uniformRM

Instances

Instances details
UniformRange Bool 
Instance details

Defined in System.Random.Internal

Methods

uniformRM :: StatefulGen g m => (Bool, Bool) -> g -> m Bool #

UniformRange Char 
Instance details

Defined in System.Random.Internal

Methods

uniformRM :: StatefulGen g m => (Char, Char) -> g -> m Char #

UniformRange Double

See Floating point number caveats.

Instance details

Defined in System.Random.Internal

Methods

uniformRM :: StatefulGen g m => (Double, Double) -> g -> m Double #

UniformRange Float

See Floating point number caveats.

Instance details

Defined in System.Random.Internal

Methods

uniformRM :: StatefulGen g m => (Float, Float) -> g -> m Float #

UniformRange Int 
Instance details

Defined in System.Random.Internal

Methods

uniformRM :: StatefulGen g m => (Int, Int) -> g -> m Int #

UniformRange Int8 
Instance details

Defined in System.Random.Internal

Methods

uniformRM :: StatefulGen g m => (Int8, Int8) -> g -> m Int8 #

UniformRange Int16 
Instance details

Defined in System.Random.Internal

Methods

uniformRM :: StatefulGen g m => (Int16, Int16) -> g -> m Int16 #

UniformRange Int32 
Instance details

Defined in System.Random.Internal

Methods

uniformRM :: StatefulGen g m => (Int32, Int32) -> g -> m Int32 #

UniformRange Int64 
Instance details

Defined in System.Random.Internal

Methods

uniformRM :: StatefulGen g m => (Int64, Int64) -> g -> m Int64 #

UniformRange Integer 
Instance details

Defined in System.Random.Internal

Methods

uniformRM :: StatefulGen g m => (Integer, Integer) -> g -> m Integer #

UniformRange Natural 
Instance details

Defined in System.Random.Internal

Methods

uniformRM :: StatefulGen g m => (Natural, Natural) -> g -> m Natural #

UniformRange Word 
Instance details

Defined in System.Random.Internal

Methods

uniformRM :: StatefulGen g m => (Word, Word) -> g -> m Word #

UniformRange Word8 
Instance details

Defined in System.Random.Internal

Methods

uniformRM :: StatefulGen g m => (Word8, Word8) -> g -> m Word8 #

UniformRange Word16 
Instance details

Defined in System.Random.Internal

Methods

uniformRM :: StatefulGen g m => (Word16, Word16) -> g -> m Word16 #

UniformRange Word32 
Instance details

Defined in System.Random.Internal

Methods

uniformRM :: StatefulGen g m => (Word32, Word32) -> g -> m Word32 #

UniformRange Word64 
Instance details

Defined in System.Random.Internal

Methods

uniformRM :: StatefulGen g m => (Word64, Word64) -> g -> m Word64 #

UniformRange CChar 
Instance details

Defined in System.Random.Internal

Methods

uniformRM :: StatefulGen g m => (CChar, CChar) -> g -> m CChar #

UniformRange CSChar 
Instance details

Defined in System.Random.Internal

Methods

uniformRM :: StatefulGen g m => (CSChar, CSChar) -> g -> m CSChar #

UniformRange CUChar 
Instance details

Defined in System.Random.Internal

Methods

uniformRM :: StatefulGen g m => (CUChar, CUChar) -> g -> m CUChar #

UniformRange CShort 
Instance details

Defined in System.Random.Internal

Methods

uniformRM :: StatefulGen g m => (CShort, CShort) -> g -> m CShort #

UniformRange CUShort 
Instance details

Defined in System.Random.Internal

Methods

uniformRM :: StatefulGen g m => (CUShort, CUShort) -> g -> m CUShort #

UniformRange CInt 
Instance details

Defined in System.Random.Internal

Methods

uniformRM :: StatefulGen g m => (CInt, CInt) -> g -> m CInt #

UniformRange CUInt 
Instance details

Defined in System.Random.Internal

Methods

uniformRM :: StatefulGen g m => (CUInt, CUInt) -> g -> m CUInt #

UniformRange CLong 
Instance details

Defined in System.Random.Internal

Methods

uniformRM :: StatefulGen g m => (CLong, CLong) -> g -> m CLong #

UniformRange CULong 
Instance details

Defined in System.Random.Internal

Methods

uniformRM :: StatefulGen g m => (CULong, CULong) -> g -> m CULong #

UniformRange CLLong 
Instance details

Defined in System.Random.Internal

Methods

uniformRM :: StatefulGen g m => (CLLong, CLLong) -> g -> m CLLong #

UniformRange CULLong 
Instance details

Defined in System.Random.Internal

Methods

uniformRM :: StatefulGen g m => (CULLong, CULLong) -> g -> m CULLong #

UniformRange CBool 
Instance details

Defined in System.Random.Internal

Methods

uniformRM :: StatefulGen g m => (CBool, CBool) -> g -> m CBool #

UniformRange CFloat

See Floating point number caveats.

Instance details

Defined in System.Random.Internal

Methods

uniformRM :: StatefulGen g m => (CFloat, CFloat) -> g -> m CFloat #

UniformRange CDouble

See Floating point number caveats.

Instance details

Defined in System.Random.Internal

Methods

uniformRM :: StatefulGen g m => (CDouble, CDouble) -> g -> m CDouble #

UniformRange CPtrdiff 
Instance details

Defined in System.Random.Internal

Methods

uniformRM :: StatefulGen g m => (CPtrdiff, CPtrdiff) -> g -> m CPtrdiff #

UniformRange CSize 
Instance details

Defined in System.Random.Internal

Methods

uniformRM :: StatefulGen g m => (CSize, CSize) -> g -> m CSize #

UniformRange CWchar 
Instance details

Defined in System.Random.Internal

Methods

uniformRM :: StatefulGen g m => (CWchar, CWchar) -> g -> m CWchar #

UniformRange CSigAtomic 
Instance details

Defined in System.Random.Internal

Methods

uniformRM :: StatefulGen g m => (CSigAtomic, CSigAtomic) -> g -> m CSigAtomic #

UniformRange CIntPtr 
Instance details

Defined in System.Random.Internal

Methods

uniformRM :: StatefulGen g m => (CIntPtr, CIntPtr) -> g -> m CIntPtr #

UniformRange CUIntPtr 
Instance details

Defined in System.Random.Internal

Methods

uniformRM :: StatefulGen g m => (CUIntPtr, CUIntPtr) -> g -> m CUIntPtr #

UniformRange CIntMax 
Instance details

Defined in System.Random.Internal

Methods

uniformRM :: StatefulGen g m => (CIntMax, CIntMax) -> g -> m CIntMax #

UniformRange CUIntMax 
Instance details

Defined in System.Random.Internal

Methods

uniformRM :: StatefulGen g m => (CUIntMax, CUIntMax) -> g -> m CUIntMax #