hsc3-lang-0.12: Haskell SuperCollider Language

Safe HaskellNone

Sound.SC3.Lang.Random.IO

Description

getStdRandom based sclang random number functions.

Synopsis

Documentation

randomM :: (Random a, MonadIO m) => (a, a) -> m aSource

rand :: (MonadIO m, Random n, Num n) => n -> m nSource

SimpleNumber.rand is randomRIO in (0,n).

rand2 :: (MonadIO m, Random n, Num n) => n -> m nSource

SimpleNumber.rand2 is randomRIO in (-n,n).

randomG :: MonadIO m => (StdGen -> (a, StdGen)) -> m aSource

nrand2 :: (Random a, Num a) => Int -> a -> IO [a]Source

Variant of rand2 generating k values.

rrand :: (MonadIO m, Random n) => n -> n -> m nSource

SimpleNumber.rrand is curry randomRIO.

nrrand :: (MonadIO m, Random a, Num a) => Int -> a -> a -> m [a]Source

Variant of rrand generating k values.

choose :: MonadIO m => [a] -> m aSource

SequenceableCollection.choose selects an element at random.

exprand :: (MonadIO m, Floating n, Random n) => n -> n -> m nSource

SimpleNumber.exprand generates exponentially distributed random number in the given interval.

coin :: (MonadIO m, Random n, Fractional n, Ord n) => n -> m BoolSource

SimpleNumber.coin is True at given probability, which is in range (0,1).

scramble :: MonadIO m => [t] -> m [t]Source

List.scramble shuffles the elements.

wchoose :: (MonadIO m, Random a, Ord a, Fractional a) => [b] -> [a] -> m bSource

SequenceableCollection.wchoose selects an element from a list given a list of weights which sum to 1.