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 |
Random monads that are strict in the generator state. For a lazy version, see Control.Monad.Random.Lazy, which has the same interface.
Synopsis
- type Rand g = RandT g Identity
- liftRand :: (g -> (a, g)) -> Rand g a
- runRand :: Rand g a -> g -> (a, g)
- evalRand :: Rand g a -> g -> a
- execRand :: Rand g a -> g -> g
- mapRand :: ((a, g) -> (b, g)) -> Rand g a -> Rand g b
- withRand :: (g -> g) -> Rand g a -> Rand g a
- evalRandIO :: Rand StdGen a -> IO a
- data RandT g m a
- liftRandT :: (g -> m (a, g)) -> RandT g m a
- runRandT :: RandT g m a -> g -> m (a, g)
- evalRandT :: Monad m => RandT g m a -> g -> m a
- execRandT :: Monad m => RandT g m a -> g -> m g
- mapRandT :: (m (a, g) -> n (b, g)) -> RandT g m a -> RandT g n b
- withRandT :: (g -> g) -> RandT g m a -> RandT g m a
- evalRandTIO :: MonadIO m => RandT StdGen m a -> m a
- randomIO :: (Random a, MonadIO m) => m a
- randomRIO :: (Random a, MonadIO m) => (a, a) -> m a
- getStdRandom :: MonadIO m => (StdGen -> (a, StdGen)) -> m a
- newStdGen :: MonadIO m => m StdGen
- getStdGen :: MonadIO m => m StdGen
- setStdGen :: MonadIO m => StdGen -> m ()
- initStdGen :: MonadIO m => m StdGen
- genByteString :: RandomGen g => Int -> g -> (ByteString, g)
- class Random a where
- mkStdGen :: Int -> StdGen
- class RandomGen g where
- next :: g -> (Int, g)
- genWord8 :: g -> (Word8, g)
- genWord16 :: g -> (Word16, g)
- genWord32 :: g -> (Word32, g)
- genWord64 :: g -> (Word64, g)
- genWord32R :: Word32 -> g -> (Word32, g)
- genWord64R :: Word64 -> g -> (Word64, g)
- genShortByteString :: Int -> g -> (ShortByteString, g)
- genRange :: g -> (Int, Int)
- split :: g -> (g, g)
- data StdGen
- class Uniform a
- class UniformRange a
- class Finite a
- module Control.Monad.Random.Class
- module Control.Monad
- module Control.Monad.Fix
- module Control.Monad.Trans
The Rand monad transformer
:: (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
.)
:: 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
.)
:: Rand g a | generator-passing computation to execute |
-> g | initial generator |
-> a | return value of the random computation |
:: Rand g a | generator-passing computation to execute |
-> g | initial generator |
-> g | final generator |
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
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
:: (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
.)
:: 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
.)
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 randomM
that uses the global
pseudo-random number generator globalStdGen
.
>>>
import Data.Int
>>>
randomIO :: IO Int32
-1580093805
This function is equivalent to
and is included in
this interface for historical reasons and backwards compatibility. It is
recommended to use getStdRandom
random
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 #
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
and is included in this interface for historical reasons and
backwards compatibility. It is recommended to use
getStdRandom
randomR
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 #
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 #
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 #
Gets the global pseudo-random number generator. Extracts the contents of
globalStdGen
Since: random-1.0.0
setStdGen :: MonadIO m => StdGen -> m () #
Sets the global pseudo-random number generator. Overwrites the contents of
globalStdGen
Since: random-1.0.0
initStdGen :: MonadIO m => m StdGen #
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) #
Generates a ByteString
of the specified size using a pure pseudo-random
number generator. See uniformByteStringM
for the monadic version.
Examples
>>>
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
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
Nothing
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, 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) #
The same as randomR
, but using a default range determined by the type:
- For bounded types (instances of
Bounded
, such asChar
), 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 ofInt
.
Since: random-1.0.0
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.
Since: random-1.0.0
randoms :: RandomGen g => g -> [a] #
Plural variant of random
, producing an infinite list of
pseudo-random values instead of returning a new generator.
Since: random-1.0.0
Instances
Random CBool | |
Random CChar | |
Random CDouble | Note - |
Random CFloat | Note - |
Random CInt | |
Random CIntMax | |
Random CIntPtr | |
Random CLLong | |
Random CLong | |
Random CPtrdiff | |
Random CSChar | |
Random CShort | |
Random CSigAtomic | |
Defined in System.Random 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 CSize | |
Random CUChar | |
Random CUInt | |
Random CUIntMax | |
Random CUIntPtr | |
Random CULLong | |
Random CULong | |
Random CUShort | |
Random CWchar | |
Random Int16 | |
Random Int32 | |
Random Int64 | |
Random Int8 | |
Random Word16 | |
Random Word32 | |
Random Word64 | |
Random Word8 | |
Random Integer | |
Random Bool | |
Random Char | |
Random Double | Note - |
Random Float | Note - |
Random Int | |
Random Word | |
(Random a, Random b) => Random (a, b) | Note - |
(Random a, Random b, Random c) => Random (a, b, c) | Note - |
(Random a, Random b, Random c, Random d) => Random (a, b, c, d) | Note - |
(Random a, Random b, Random c, Random d, Random e) => Random (a, b, c, d, e) | Note - |
Defined in System.Random | |
(Random a, Random b, Random c, Random d, Random e, Random f) => Random (a, b, c, d, e, f) | Note - |
(Random a, Random b, Random c, Random d, Random e, Random f, Random g) => Random (a, b, c, d, e, f, g) | Note - |
Defined in System.Random |
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
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
genWord16 :: g -> (Word16, g) #
genWord32 :: g -> (Word32, g) #
genWord64 :: g -> (Word64, g) #
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
Yields the range of values returned by next
.
It is required that:
- If
(a, b) =
, thengenRange
ga < b
. genRange
must not examine its argument so the value it returns is determined only by the instance ofRandomGen
.
The default definition spans the full range of Int
.
Since: random-1.0.0
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
The standard pseudo-random number generator.
Instances
Show StdGen | |
NFData StdGen | |
Defined in System.Random.Internal | |
Eq StdGen | |
RandomGen StdGen | |
Defined in System.Random.Internal next :: StdGen -> (Int, StdGen) # genWord8 :: StdGen -> (Word8, StdGen) # genWord16 :: StdGen -> (Word16, StdGen) # genWord32 :: StdGen -> (Word32, StdGen) # genWord64 :: StdGen -> (Word64, StdGen) # genWord32R :: Word32 -> StdGen -> (Word32, StdGen) # genWord64R :: Word64 -> StdGen -> (Word64, StdGen) # genShortByteString :: Int -> StdGen -> (ShortByteString, StdGen) # | |
MonadSplit StdGen IO 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
class UniformRange a #
The class of types for which a uniformly distributed value can be drawn from a range.
Since: random-1.2.0
Instances
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
module Control.Monad.Random.Class
module Control.Monad
module Control.Monad.Fix
module Control.Monad.Trans