Copyright | (c) Colin Woodbury 2016 |
---|---|
License | BSD3 |
Maintainer | Colin Woodbury <cwoodbury@azavea.com> |
Safe Haskell | None |
Language | Haskell2010 |
Producers for handling randomness.
Random Numbers
Use functions like uniform
and normal
to generate endless streams
of random numbers of the standard Num
types. For instance, you could
perform some IO action based on a threshold:
{-# LANGUAGE TypeApplications #-} -- GHC8 only. Provides the @ syntax. import qualified Pipes.Prelude as P perhaps :: Effect IO () perhaps = uniform @Float >-> P.filter (> 0.1) >-> lift releaseTheHounds
Random Elements from Containers
We expose the functions finite
and endless
for randomly Producing
elements from a collection.
finite
will only Produce until each of its elements have been yielded once.
Making a shuffle function then is easy:
import Data.Vector (Vector) import qualified Pipes.Prelude as P shuffle :: Vector a -> IO [a] shuffle = P.toListM . finite
endless
on the other hand will endlessly Produce elements in any order.
Repeats will likely appear long before each element has been yielded once.
You can limit the number of results with take
:
import Data.Vector (Vector) import qualified Pipes.Prelude as P twenty :: Vector a -> Producer a IO () twenty v = endless v >-> P.take 20
For the time being, only Vector
s (all kinds) are supported.
Pseudo-random Number Generators
Numbers
uniform :: Variate v => Producer v IO () Source #
Endlessly produce anything that's Variate
from a uniform distribution.
- For integral types, the entire bit range is used.
- For floating types, the range is (0,1], where 0 is specifically excluded.
uniformR :: Variate v => (v, v) -> Producer v IO () Source #
Endlessly produce anything that's Variate
from a uniform distribution,
within some given range of values.
- For integral types, inclusive range is used.
- For floating types, (a,b] is used.
normal :: Double -> Double -> Producer Double IO () Source #
Given a mean and a standard deviation, endlessly produce values from a normal (Gaussian) distribution.