pipes-random-1.0.0.4: Producers for handling randomness.

Copyright(c) Colin Woodbury 2016
LicenseBSD3
MaintainerColin Woodbury <cwoodbury@azavea.com>
Safe HaskellNone
LanguageHaskell2010

Pipes.Random

Contents

Description

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 Vectors (all kinds) are supported.

Synopsis

Pseudo-random Number Generators

pool :: IO GenIO Source #

A pseudo-random number generator, produced using system randomness.

lift this to transform it into a Producer.

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.

Collections

finite :: Vector v a => v a -> Producer a IO () Source #

Given some Vector, produce its elements in a random order, once each.

>>> P.toListM $ finite (V.fromList @Data.Vector.Vector ['a'..'z'])
"rkzpnwjfeqotvdlsaxiuhcbymg"

endless :: Vector v a => v a -> Producer a IO () Source #

Given some Vector, endlessly produce elements from it.

>>> P.toListM $ endless (V.fromList @Data.Vector.Vector ['a'..'z']) >-> P.take 20
"nvecotyjhestgrrlganj"