MonadRandom-0.6: Random-number generation monad.
Copyright (c) Brent Yorgey 2016
License BSD3 (see LICENSE)
Maintainer byorgey@gmail.com
Stability experimental
Portability non-portable (multi-param classes, functional dependencies, undecidable instances)
Safe Haskell Safe
Language Haskell2010

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 Source #

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

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

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

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

Defined in Control.Monad.Trans.Random.Lazy

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

Defined in Control.Monad.Trans.Random.Lazy

Methods

ask :: RandT g m r Source #

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

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

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

Defined in Control.Monad.Trans.Random.Lazy

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

Defined in Control.Monad.Trans.Random.Lazy

MonadTrans ( RandT g) Source #
Instance details

Defined in Control.Monad.Trans.Random.Lazy

Methods

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

( 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 Source #

( 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

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 Source #

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

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 Source #

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

Defined in Control.Monad.Trans.Random.Lazy

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

Defined in Control.Monad.Trans.Random.Lazy

Methods

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

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

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

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

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

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

Defined in Control.Monad.Trans.Random.Lazy

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

Defined in Control.Monad.Trans.Random.Lazy

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

Defined in Control.Monad.Trans.Random.Lazy

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 Source #

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

Defined in Control.Monad.Trans.Random.Lazy

Associated Types

type PrimState ( RandT s m) Source #

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

Defined in Control.Monad.Trans.Random.Lazy

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

Defined in Control.Monad.Trans.Random.Lazy

type PrimState ( RandT s m) Source #
Instance details

Defined in Control.Monad.Trans.Random.Lazy

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 Source #

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

>>> import Data.Int
>>> randomIO :: IO Int32
-1580093805

This function is equivalent to getStdRandom random and is included in this interface for historical reasons and backwards compatibility. It is recommended to use uniformM instead, possibly with the globalStdGen if relying on the global state is acceptable.

>>> import System.Random.Stateful
>>> uniformM globalStdGen :: IO Int32
-1649127057

Since: random-1.0.0

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

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

>>> randomRIO (2020, 2100) :: IO Int
2040

Similar to randomIO , this function is equivalent to getStdRandom randomR and is included in this interface for historical reasons and backwards compatibility. It is recommended to use uniformRM instead, possibly with the globalStdGen if relying on the global state is acceptable.

>>> import System.Random.Stateful
>>> uniformRM (2020, 2100) globalStdGen :: IO Int
2079

Since: random-1.0.0

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

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 produces a pseudo-random integer between 1 and 6:

>>> rollDice = getStdRandom (randomR (1, 6))
>>> replicateM 10 (rollDice :: IO Int)
[5,6,6,1,1,6,4,2,4,1]

This is an outdated function and it is recommended to switch to its equivalent applyAtomicGen instead, possibly with the globalStdGen if relying on the global state is acceptable.

>>> import System.Random.Stateful
>>> rollDice = applyAtomicGen (uniformR (1, 6)) globalStdGen
>>> replicateM 10 (rollDice :: IO Int)
[4,6,1,1,4,4,3,2,1,2]

Since: random-1.0.0

newStdGen :: MonadIO m => m StdGen Source #

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

Since: random-1.0.0

getStdGen :: MonadIO m => m StdGen Source #

Gets the global pseudo-random number generator. Extracts the contents of globalStdGen

Since: random-1.0.0

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

Sets the global pseudo-random number generator. Overwrites the contents of globalStdGen

Since: random-1.0.0

initStdGen :: MonadIO m => m StdGen Source #

Initialize StdGen using system entropy (i.e. /dev/urandom ) when it is available, while falling back on using system time as the seed.

Since: random-1.2.1

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

Generates a ByteString of the specified size using a pure pseudo-random number generator. See uniformByteStringM 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 Source #

The class of types for which random values can be generated. Most instances of Random will produce values that are uniformly distributed on the full range, but for those types without a well-defined "full range" some sensible default subrange will be selected.

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

Since: random-1.0.0

Minimal complete definition

Nothing

Methods

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

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 , but usually the values will simply get swapped.

>>> let gen = mkStdGen 2021
>>> fst $ randomR ('a', 'z') gen
't'
>>> fst $ randomR ('z', 'a') gen
't'

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.

There is no requirement to follow the Ord instance and the concept of range can be defined on per type basis. For example product types will treat their values independently:

>>> fst $ randomR (('a', 5.0), ('z', 10.0)) $ mkStdGen 2021
('t',6.240232662366563)

In case when a lawful range is desired uniformR should be used instead.

Since: random-1.0.0

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

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 floating point types, the range is normally the closed interval [0,1] .
  • For Integer , the range is (arbitrarily) the range of Int .

Since: random-1.0.0

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

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

Since: random-1.0.0

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

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

Since: random-1.0.0

Instances

Instances details
Random Bool
Instance details

Defined in System.Random

Random Char
Instance details

Defined in System.Random

Random Double

Note - random produces values in the closed range [0,1] .

Instance details

Defined in System.Random

Random Float

Note - random produces values in the closed range [0,1] .

Instance details

Defined in System.Random

Random Int
Instance details

Defined in System.Random

Random Int8
Instance details

Defined in System.Random

Random Int16
Instance details

Defined in System.Random

Random Int32
Instance details

Defined in System.Random

Random Int64
Instance details

Defined in System.Random

Random Integer

Note - random generates values in the Int range

Instance details

Defined in System.Random

Random Word
Instance details

Defined in System.Random

Random Word8
Instance details

Defined in System.Random

Random Word16
Instance details

Defined in System.Random

Random Word32
Instance details

Defined in System.Random

Random Word64
Instance details

Defined in System.Random

Random CChar
Instance details

Defined in System.Random

Random CSChar
Instance details

Defined in System.Random

Random CUChar
Instance details

Defined in System.Random

Random CShort
Instance details

Defined in System.Random

Random CUShort
Instance details

Defined in System.Random

Random CInt
Instance details

Defined in System.Random

Random CUInt
Instance details

Defined in System.Random

Random CLong
Instance details

Defined in System.Random

Random CULong
Instance details

Defined in System.Random

Random CLLong
Instance details

Defined in System.Random

Random CULLong
Instance details

Defined in System.Random

Random CBool
Instance details

Defined in System.Random

Random CFloat

Note - random produces values in the closed range [0,1] .

Instance details

Defined in System.Random

Random CDouble

Note - random produces values in the closed range [0,1] .

Instance details

Defined in System.Random

Random CPtrdiff
Instance details

Defined in System.Random

Random CSize
Instance details

Defined in System.Random

Random CWchar
Instance details

Defined in System.Random

Random CSigAtomic
Instance details

Defined in System.Random

Random CIntPtr
Instance details

Defined in System.Random

Random CUIntPtr
Instance details

Defined in System.Random

Random CIntMax
Instance details

Defined in System.Random

Random CUIntMax
Instance details

Defined in System.Random

( Random a, Random b) => Random (a, b)

Note - randomR treats a and b types independently

Instance details

Defined in System.Random

Methods

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

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

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

randoms :: RandomGen g => g -> [(a, b)] Source #

( Random a, Random b, Random c) => Random (a, b, c)

Note - randomR treats a , b and c types independently

Instance details

Defined in System.Random

Methods

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

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

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

randoms :: RandomGen g => g -> [(a, b, c)] Source #

( Random a, Random b, Random c, Random d) => Random (a, b, c, d)

Note - randomR treats a , b , c and d types independently

Instance details

Defined in System.Random

Methods

randomR :: RandomGen g => ((a, b, c, d), (a, b, c, d)) -> g -> ((a, b, c, d), g) Source #

random :: RandomGen g => g -> ((a, b, c, d), g) Source #

randomRs :: RandomGen g => ((a, b, c, d), (a, b, c, d)) -> g -> [(a, b, c, d)] Source #

randoms :: RandomGen g => g -> [(a, b, c, d)] Source #

( Random a, Random b, Random c, Random d, Random e) => Random (a, b, c, d, e)

Note - randomR treats a , b , c , d and e types independently

Instance details

Defined in System.Random

Methods

randomR :: RandomGen g => ((a, b, c, d, e), (a, b, c, d, e)) -> g -> ((a, b, c, d, e), g) Source #

random :: RandomGen g => g -> ((a, b, c, d, e), g) Source #

randomRs :: RandomGen g => ((a, b, c, d, e), (a, b, c, d, e)) -> g -> [(a, b, c, d, e)] Source #

randoms :: RandomGen g => g -> [(a, b, c, d, e)] Source #

( Random a, Random b, Random c, Random d, Random e, Random f) => Random (a, b, c, d, e, f)

Note - randomR treats a , b , c , d , e and f types independently

Instance details

Defined in System.Random

Methods

randomR :: RandomGen g => ((a, b, c, d, e, f), (a, b, c, d, e, f)) -> g -> ((a, b, c, d, e, f), g) Source #

random :: RandomGen g => g -> ((a, b, c, d, e, f), g) Source #

randomRs :: RandomGen g => ((a, b, c, d, e, f), (a, b, c, d, e, f)) -> g -> [(a, b, c, d, e, f)] Source #

randoms :: RandomGen g => g -> [(a, b, c, d, e, f)] Source #

( Random a, Random b, Random c, Random d, Random e, Random f, Random g) => Random (a, b, c, d, e, f, g)

Note - randomR treats a , b , c , d , e , f and g types independently

Instance details

Defined in System.Random

Methods

randomR :: RandomGen g0 => ((a, b, c, d, e, f, g), (a, b, c, d, e, f, g)) -> g0 -> ((a, b, c, d, e, f, g), g0) Source #

random :: RandomGen g0 => g0 -> ((a, b, c, d, e, f, g), g0) Source #

randomRs :: RandomGen g0 => ((a, b, c, d, e, f, g), (a, b, c, d, e, f, g)) -> g0 -> [(a, b, c, d, e, f, g)] Source #

randoms :: RandomGen g0 => g0 -> [(a, b, c, d, e, f, g)] Source #

mkStdGen :: Int -> StdGen Source #

Constructs a StdGen deterministically.

class RandomGen g where Source #

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

StdGen is the standard RandomGen instance provided by this library.

Since: random-1.0.0

Minimal complete definition

split , ( genWord32 | genWord64 | next , genRange )

Methods

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

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.

Since: random-1.0.0

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

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

Since: random-1.2.0

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

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

Since: random-1.2.0

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

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

Since: random-1.2.0

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

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

Since: random-1.2.0

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

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) Source #

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) Source #

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

Since: random-1.2.0

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

Yields the range of values returned by next .

It is required that:

The default definition spans the full range of Int .

Since: random-1.0.0

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

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.

Since: random-1.0.0

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

RandomGen g => RandomGen ( STGen g)
Instance details

Defined in System.Random.Stateful

RandomGen g => RandomGen ( TGen g)
Instance details

Defined in System.Random.Stateful

RandomGen g => RandomGen ( StateGen g)
Instance details

Defined in System.Random.Internal

class Uniform a Source #

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

Instances

Instances details
Uniform Bool
Instance details

Defined in System.Random.Internal

Uniform Char
Instance details

Defined in System.Random.Internal

Uniform Int
Instance details

Defined in System.Random.Internal

Uniform Int8
Instance details

Defined in System.Random.Internal

Uniform Int16
Instance details

Defined in System.Random.Internal

Uniform Int32
Instance details

Defined in System.Random.Internal

Uniform Int64
Instance details

Defined in System.Random.Internal

Uniform Word
Instance details

Defined in System.Random.Internal

Uniform Word8
Instance details

Defined in System.Random.Internal

Uniform Word16
Instance details

Defined in System.Random.Internal

Uniform Word32
Instance details

Defined in System.Random.Internal

Uniform Word64
Instance details

Defined in System.Random.Internal

Uniform ()
Instance details

Defined in System.Random.Internal

Methods

uniformM :: StatefulGen g m => g -> m () Source #

Uniform CChar
Instance details

Defined in System.Random.Internal

Uniform CSChar
Instance details

Defined in System.Random.Internal

Uniform CUChar
Instance details

Defined in System.Random.Internal

Uniform CShort
Instance details

Defined in System.Random.Internal

Uniform CUShort
Instance details

Defined in System.Random.Internal

Uniform CInt
Instance details

Defined in System.Random.Internal

Uniform CUInt
Instance details

Defined in System.Random.Internal

Uniform CLong
Instance details

Defined in System.Random.Internal

Uniform CULong
Instance details

Defined in System.Random.Internal

Uniform CLLong
Instance details

Defined in System.Random.Internal

Uniform CULLong
Instance details

Defined in System.Random.Internal

Uniform CBool
Instance details

Defined in System.Random.Internal

Uniform CPtrdiff
Instance details

Defined in System.Random.Internal

Uniform CSize
Instance details

Defined in System.Random.Internal

Uniform CWchar
Instance details

Defined in System.Random.Internal

Uniform CSigAtomic
Instance details

Defined in System.Random.Internal

Uniform CIntPtr
Instance details

Defined in System.Random.Internal

Uniform CUIntPtr
Instance details

Defined in System.Random.Internal

Uniform CIntMax
Instance details

Defined in System.Random.Internal

Uniform CUIntMax
Instance details

Defined in System.Random.Internal

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

Defined in System.Random.Internal

Methods

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

( 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) Source #

( 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) Source #

( 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) Source #

( 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) Source #

( 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) Source #

class UniformRange a Source #

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

UniformRange Char
Instance details

Defined in System.Random.Internal

UniformRange Double

See Floating point number caveats .

Instance details

Defined in System.Random.Internal

UniformRange Float

See Floating point number caveats .

Instance details

Defined in System.Random.Internal

UniformRange Int
Instance details

Defined in System.Random.Internal

UniformRange Int8
Instance details

Defined in System.Random.Internal

UniformRange Int16
Instance details

Defined in System.Random.Internal

UniformRange Int32
Instance details

Defined in System.Random.Internal

UniformRange Int64
Instance details

Defined in System.Random.Internal

UniformRange Integer
Instance details

Defined in System.Random.Internal

UniformRange Natural
Instance details

Defined in System.Random.Internal

UniformRange Word
Instance details

Defined in System.Random.Internal

UniformRange Word8
Instance details

Defined in System.Random.Internal

UniformRange Word16
Instance details

Defined in System.Random.Internal

UniformRange Word32
Instance details

Defined in System.Random.Internal

UniformRange Word64
Instance details

Defined in System.Random.Internal

UniformRange ()
Instance details

Defined in System.Random.Internal

Methods

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

UniformRange CChar
Instance details

Defined in System.Random.Internal

UniformRange CSChar
Instance details

Defined in System.Random.Internal

UniformRange CUChar
Instance details

Defined in System.Random.Internal

UniformRange CShort
Instance details

Defined in System.Random.Internal

UniformRange CUShort
Instance details

Defined in System.Random.Internal

UniformRange CInt
Instance details

Defined in System.Random.Internal

UniformRange CUInt
Instance details

Defined in System.Random.Internal

UniformRange CLong
Instance details

Defined in System.Random.Internal

UniformRange CULong
Instance details

Defined in System.Random.Internal

UniformRange CLLong
Instance details

Defined in System.Random.Internal

UniformRange CULLong
Instance details

Defined in System.Random.Internal

UniformRange CBool
Instance details

Defined in System.Random.Internal

UniformRange CFloat

See Floating point number caveats .

Instance details

Defined in System.Random.Internal

UniformRange CDouble

See Floating point number caveats .

Instance details

Defined in System.Random.Internal

UniformRange CPtrdiff
Instance details

Defined in System.Random.Internal

UniformRange CSize
Instance details

Defined in System.Random.Internal

UniformRange CWchar
Instance details

Defined in System.Random.Internal

UniformRange CSigAtomic
Instance details

Defined in System.Random.Internal

UniformRange CIntPtr
Instance details

Defined in System.Random.Internal

UniformRange CUIntPtr
Instance details

Defined in System.Random.Internal

UniformRange CIntMax
Instance details

Defined in System.Random.Internal

UniformRange CUIntMax
Instance details

Defined in System.Random.Internal

class Finite a Source #

A type class for data with a finite number of inhabitants. This type class is used in default implementations of Uniform .

Users are not supposed to write instances of Finite manually. There is a default implementation in terms of Generic instead.

>>> :set -XDeriveGeneric -XDeriveAnyClass
>>> import GHC.Generics (Generic)
>>> data MyBool = MyTrue | MyFalse deriving (Generic, Finite)
>>> data Action = Code MyBool | Eat (Maybe Bool) | Sleep deriving (Generic, Finite)

Instances

Instances details
Finite Bool
Instance details

Defined in System.Random.GFinite

Finite Char
Instance details

Defined in System.Random.GFinite

Finite Int
Instance details

Defined in System.Random.GFinite

Finite Int8
Instance details

Defined in System.Random.GFinite

Finite Int16
Instance details

Defined in System.Random.GFinite

Finite Int32
Instance details

Defined in System.Random.GFinite

Finite Int64
Instance details

Defined in System.Random.GFinite

Finite Ordering
Instance details

Defined in System.Random.GFinite

Finite Word
Instance details

Defined in System.Random.GFinite

Finite Word8
Instance details

Defined in System.Random.GFinite

Finite Word16
Instance details

Defined in System.Random.GFinite

Finite Word32
Instance details

Defined in System.Random.GFinite

Finite Word64
Instance details

Defined in System.Random.GFinite

Finite ()
Instance details

Defined in System.Random.GFinite

Methods

cardinality :: Proxy# () -> Cardinality

toFinite :: Integer -> ()

fromFinite :: () -> Integer

Finite Void
Instance details

Defined in System.Random.GFinite

Finite a => Finite ( Maybe a)
Instance details

Defined in System.Random.GFinite

( Finite a, Finite b) => Finite ( Either a b)
Instance details

Defined in System.Random.GFinite

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

Defined in System.Random.GFinite

Methods

cardinality :: Proxy# (a, b) -> Cardinality

toFinite :: Integer -> (a, b)

fromFinite :: (a, b) -> Integer

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

Defined in System.Random.GFinite

Methods

cardinality :: Proxy# (a, b, c) -> Cardinality

toFinite :: Integer -> (a, b, c)

fromFinite :: (a, b, c) -> Integer

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

Defined in System.Random.GFinite

Methods

cardinality :: Proxy# (a, b, c, d) -> Cardinality

toFinite :: Integer -> (a, b, c, d)

fromFinite :: (a, b, c, d) -> Integer

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

Defined in System.Random.GFinite

Methods

cardinality :: Proxy# (a, b, c, d, e) -> Cardinality

toFinite :: Integer -> (a, b, c, d, e)

fromFinite :: (a, b, c, d, e) -> Integer

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

Defined in System.Random.GFinite

Methods

cardinality :: Proxy# (a, b, c, d, e, f) -> Cardinality

toFinite :: Integer -> (a, b, c, d, e, f)

fromFinite :: (a, b, c, d, e, f) -> Integer