hsc3-lang-0.15: Haskell SuperCollider Language

Safe HaskellNone
LanguageHaskell98

Sound.SC3.Lang.Pattern.Stream

Description

Infinte list SC3 pattern functions.

Synopsis

Documentation

rsd :: Eq a => [a] -> [a] Source

Remove successive duplicates.

rsd [1,2,3,1,2,3] == [1,2,3,1,2,3]

iEq :: Eq a => [a] -> [a] -> Bool Source

True if a is initially equal to b.

take_until_forms_set :: Eq a => [a] -> [a] -> [a] Source

Take elements from l until all elements in s have been seen. If s contains duplicate elements these must be seen multiple times.

take_until_forms_set "abc" "a random sentence beginning" == "a random sentence b"

brown_ :: (RandomGen g, Random n, Num n, Ord n) => (n, n, n) -> (n, g) -> (n, g) Source

Underlying brown.

brown :: (Enum e, Random n, Num n, Ord n) => e -> [n] -> [n] -> [n] -> [n] Source

Brown noise with list inputs.

let l = brown 'α' (repeat 1) (repeat 700) (cycle [1,20])
in l `iEq` [415,419,420,428]

exprand :: (Enum e, Random a, Floating a) => e -> a -> a -> [a] Source

geom :: Num a => a -> a -> [a] Source

Geometric series.

geom 3 6 `iEq` [3,18,108,648,3888,23328,139968]

lace :: [[a]] -> [a] Source

rand :: Enum e => e -> [a] -> [a] Source

Random elements from list.

take_until_forms_set "string" (rand 'α' "string") == "grtrsiirn"

segment :: [a] -> Int -> (Int, Int) -> [a] Source

List section with wrapped indices.

segment [0..4] 5 (3,5) == [3,4,0]

slide :: [a] -> Int -> Int -> Int -> Bool -> [[a]] Source

slidec :: [a] -> Int -> Int -> Int -> Bool -> [a] Source

white :: (Random n, Enum e) => e -> n -> n -> [n] Source

White noise.

take_until_forms_set [1..5] (white 'α' 1 5) == [4,1,2,2,2,1,2,1,2,5,1,4,3]

wrand_generic :: (Enum e, Fractional n, Ord n, Random n) => e -> [a] -> [n] -> [a] Source

Weighted selection of elements from a list.

wrand :: Enum e => e -> [a] -> [Double] -> [a] Source

Type restricted variant.

import qualified Sound.SC3.Lang.Collection as C
let {w = C.normalizeSum [1..5]
    ;r = wrand 'ζ' "wrand" w}
in take_until_forms_set "wrand" r == "dnanrdnaddrnrrndrrdw"

xrand :: Enum e => e -> [a] -> [a] Source

Select elements from l in random sequence, but do not immediately repeat an element.

take_until_forms_set "string" (xrand 'α' "string") == "grtrsirn"