Yampa-0.14.2: Elegant Functional Reactive Programming Language for Hybrid Systems
Copyright(c) Ivan Perez 2014-2022
(c) George Giorgidze 2007-2012
(c) Henrik Nilsson 2005-2006
(c) Antony Courtney and Henrik Nilsson Yale University 2003-2004
LicenseBSD-style (see the LICENSE file in the distribution)
Maintainerivan.perez@keera.co.uk
Stabilityprovisional
Portabilitynon-portable (GHC extensions)
Safe HaskellSafe-Inferred
LanguageHaskell2010

FRP.Yampa.Random

Description

Signals and signal functions with noise and randomness.

The Random number generators are re-exported from System.Random.

Synopsis

Random number generators

class RandomGen g where #

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

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

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.

Since: random-1.0.0

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.

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 (StateGen g) 
Instance details

Defined in System.Random.Internal

class Random a where #

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

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

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

Instances details
Random CBool 
Instance details

Defined in System.Random

Methods

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

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

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

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

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 CDouble

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

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 CFloat

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

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

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 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 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 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 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 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 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 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 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 Integer

Note - random generates values in the Int range

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

Noise, random signals, and stochastic event sources

noise :: (RandomGen g, Random b) => g -> SF a b Source #

Noise (random signal) with default range for type in question; based on "randoms".

noiseR :: (RandomGen g, Random b) => (b, b) -> g -> SF a b Source #

Noise (random signal) with specified range; based on "randomRs".

occasionally :: RandomGen g => g -> Time -> b -> SF a (Event b) Source #

Stochastic event source with events occurring on average once every t_avg seconds. However, no more than one event results from any one sampling interval in the case of relatively sparse sampling, thus avoiding an "event backlog" should sampling become more frequent at some later point in time.