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 ()
- 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
- 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 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.
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
>>>
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 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.
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. 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:
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
Random Bool | |
Random Char | |
Random Double | |
Random Float | |
Random Int | |
Random Int8 | |
Random Int16 | |
Random Int32 | |
Random Int64 | |
Random Integer | |
Random Word | |
Random Word8 | |
Random Word16 | |
Random Word32 | |
Random Word64 | |
Random CChar | |
Random CSChar | |
Random CUChar | |
Random CShort | |
Random CUShort | |
Random CInt | |
Random CUInt | |
Random CLong | |
Random CULong | |
Random CLLong | |
Random CULLong | |
Random CFloat | |
Random CDouble | |
Random CPtrdiff | |
Random CSize | |
Random CWchar | |
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 CIntPtr | |
Random CUIntPtr | |
Random CIntMax | |
Random CUIntMax | |
RandomGen
is an interface to pure pseudo-random number generators.
StdGen
is the standard RandomGen
instance provided by this library.
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.
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
Instances
The standard pseudo-random number generator.
Instances
Eq StdGen | |
Show StdGen | |
NFData StdGen | |
Defined in System.Random.Internal | |
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
module Control.Monad.Random.Class
module Control.Monad
module Control.Monad.Fix
module Control.Monad.Trans