random-eff-0.1.0.1: A simple random generator library for extensible-effects

Safe HaskellNone

Control.Eff.Random

Contents

Synopsis

Documentation

data Rand a Source

Random number generator

Since 0.1.0.0

data Generator Source

Wrapper Type for RandomGen types

Since 0.1.0.0

Constructors

forall g . RandomGen g => Generator g 

Instances

Typeable Generator 
RandomGen Generator

This behaves exactly as same as the original, un-quantified instance.

Since 0.1.0.0

Execution

runRandSource

Arguments

:: RandomGen g 
=> g

initial internal random generator

-> Eff (Rand :> r) w

Effect using random numbers

-> Eff r (w, Generator)

Effect containing return value and final random number generator. The generator is returned as existential type due to the limitation of the current implementation, but it's guaranteed to work exactly as same as the original given generator type.

Run a computation with random numbers

Since 0.1.0.0

evalRand :: RandomGen g => g -> Eff (Rand :> r) w -> Eff r wSource

Run a computation with random numbers, discarding the final generator.

Since 0.1.0.0

evalRandIO :: SetMember Lift (Lift IO) r => Eff (Rand :> r) w -> Eff r wSource

Run a computation with random numbers, using newStdGen as its initial generator.

Since 0.1.0.0

Generator functions

getRandom :: forall a r. (Typeable a, Random a, Member Rand r) => Eff r aSource

Return a randomly-selected value of type a. See random for details.

Since 0.1.0.0

getRandomR :: (Typeable a, Random a, Member Rand r) => (a, a) -> Eff r aSource

Return a randomly-selected value of type a in the range (lo,hi). See randomR for details.

Since 0.1.0.0

getRandoms :: (Random a, Typeable a, Member Rand r) => Eff r [a]Source

Return an infinite stream of random values of type a. See randoms for details.

Since 0.1.0.0

getRandomRs :: (Typeable a, Random a, Member Rand r) => (a, a) -> Eff r [a]Source

Return an infinite stream of randomly-selected value of type a in the range (lo,hi). See randomRs for details.

Since 0.1.0.0

fromList :: Member Rand r => [(a, Rational)] -> Eff r aSource

Sample a random value from a weighted list. The total weight of all elements must not be 0.

Since 0.1.0.0

uniform :: Member Rand r => [a] -> Eff r aSource

Sample a value from a uniform distribution of a list of elements.

Since 0.1.0.0

Misc

getSplit :: Member Rand r => Eff r GeneratorSource

Split the internal generator. This returns the second result of split and set the new internal generator to the first one.

Since 0.1.0.0