hsc3-lang-0.15: Haskell SuperCollider Language

Safe HaskellNone
LanguageHaskell98

Sound.SC3.Lang.Pattern.List

Contents

Description

List variants of SC3 pattern functions.

Synopsis

Data.Bool variants

bool :: (Ord n, Num n) => n -> Bool Source

> 0. Values greater than zero are True and zero and negative values are False.

Data.Functor variants

fbool :: (Ord a, Num a, Functor f) => f a -> f Bool Source

fmap of bool.

fbool [2,1,0,-1] == [True,True,False,False]

ffold :: (Functor f, Num a, Ord a) => f a -> a -> a -> f a Source

SC3 pattern to fold values to lie within range (as opposed to wrap and clip). This is not related to Data.Foldable.

ffold [10,11,12,-6,-7,-8] (-7) 11 == [10,11,10,-6,-7,-6]

The underlying primitive is the fold_ function.

let f n = S.fold_ n (-7) 11
in map f [10,11,12,-6,-7,-8] == [10,11,10,-6,-7,-6]

fwrap :: (Functor f, Ord a, Num a) => f a -> a -> a -> f a Source

SC3 pattern to constrain the range of output values by wrapping, the primitive is genericWrap.

let p = fmap round (fwrap (geom 200 1.2 10) 200 1000)
in p == [200,240,288,346,415,498,597,717,860,231]

Non-SC3 Patterns

countpost :: [Bool] -> [Int] Source

Count the number of False values following each True value.

countpost (map bool [1,0,1,0,0,0,1,1]) == [1,3,0,0]

countpre :: [Bool] -> [Int] Source

Count the number of False values preceding each True value.

countpre (fbool [0,0,1,0,0,0,1,1]) == [2,3,0]

hold :: [a] -> [a] Source

Sample and hold initial value.

hold [] == []
hold [1..5] == [1,1,1,1,1]
hold [1,undefined] == [1,1]

interleave2 :: [a] -> [a] -> [a] Source

Interleave elements from two lists. If one list ends the other continues until it also ends.

interleave2 [1,2,3,1,2,3] [4,5,6,7] == [1,4,2,5,3,6,1,7,2,3]
[1..9] `isPrefixOf` interleave2 [1,3..] [2,4..]

interleave :: [[a]] -> [a] Source

N-ary variant of interleave2, ie. concat of transpose.

interleave [whitei 'α' 0 4 3,whitei 'β' 5 9 3] == [3,7,0,8,1,6]
[1..9] `isPrefixOf` interleave [[1,4..],[2,5..],[3,6..]]

trigger :: [Bool] -> [a] -> [Maybe a] Source

Pattern where the tr pattern determines the rate at which values are read from the x pattern. For each sucessive true value at tr the output is a (Just e) of each succesive element at x. False values at tr generate Nothing values.

let l = trigger (map toEnum [0,1,0,0,1,1]) [1,2,3]
in l == [Nothing,Just 1,Nothing,Nothing,Just 2,Just 3]

SC3 Patterns

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

Pbrown. SC3 pattern to generate psuedo-brownian motion.

[4,4,1,8,5] `isPrefixOf` brown 'α' 0 9 15

durStutter :: Fractional a => [Int] -> [a] -> [a] Source

PdurStutter. SC3 pattern to partition a value into n equal subdivisions. Subdivides each duration by each stutter and yields that value stutter times. A stutter of 0 will skip the duration value, a stutter of 1 yields the duration value unaffected.

let {s = [1,1,1,1,1,2,2,2,2,2,0,1,3,4,0]
    ;d = [0.5,1,2,0.25,0.25]}
in durStutter s d == [0.5,1.0,2.0,0.25,0.25]

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

Pexprand. SC3 pattern of random values that follow a exponential distribution.

exprand 'α' 0.0001 1 10

funcn :: Enum e => e -> (StdGen -> (n, StdGen)) -> Int -> [n] Source

Pfuncn. Variant of the SC3 pattern that evaluates a closure at each step that has a StdGen form.

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

Pgeom. geom with arguments re-ordered.

geom 3 6 5 == [3,18,108,648,3888]

if_demand :: [Bool] -> [a] -> [a] -> [a] Source

Pif. Consume values from q or r according to p.

if_demand [True,False,True] [1,3] [2] == [1,2,3]

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

Prand. Random elements of p.

rand' 'α' [1..9] 9 == [3,9,2,9,4,7,4,3,8]

seq' :: [[a]] -> Int -> [a] Source

Pseq. concat of replicate of concat.

seq' [return 1,[2,3],return 4] 2 == [1,2,3,4,1,2,3,4]

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

Pslide. SC3 pattern to slide over a list of values.

slide [1,2,3,4] 4 3 1 0 True == [1,2,3,2,3,4,3,4,1,4,1,2]
slide [1,2,3,4,5] 3 3 (-1) 0 True == [1,2,3,5,1,2,4,5,1]

stutter :: [Int] -> [a] -> [a] Source

Pstutter. Repeat each element of a pattern n times.

stutter [1,2,3] [4,5,6] == [4,5,5,6,6,6]
stutter (repeat 2) [4,5,6] == [4,4,5,5,6,6]

switch :: [[a]] -> [Int] -> [a] Source

Pswitch. SC3 pattern to select elements from a list of patterns by a pattern of indices.

let r = switch [[1,2,3,1,2,3],[65,76],[800]] [2,2,0,1]
in r == [800,800,1,2,3,1,2,3,65,76]

switch1 :: [[a]] -> [Int] -> [a] Source

Pswitch1. SC3 pattern that uses a pattern of indices to select which pattern to retrieve the next value from. Only one value is selected from each pattern. This is in comparison to switch, which embeds the pattern in its entirety.

let p = switch1 [(cycle [1,2,3])
                ,(cycle [65,76])
                ,repeat 8] (concat (replicate 6 [2,2,0,1]))
in p == [8,8,1,65,8,8,2,76,8,8,3,65,8,8,1,76,8,8,2,65,8,8,3,76]

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

Pwhite. SC3 pattern to generate a uniform linear distribution in given range.

white 'α' 0 9 5 == [3,0,1,6,6]

It is important to note that this structure is not actually indeterminate, so that the below is zero.

white 'α' 1 9 5  == [3,9,2,9,4]
let p = white 'α' 0.0 1.0 3 in zipWith (-) p p == [0,0,0]

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

Pwrand. SC3 pattern to embed values randomly chosen from a list. Returns one item from the list at random for each repeat, the probability for each item is determined by a list of weights which should sum to 1.0 and must be equal in length to the selection list.

let w = C.normalizeSum [1,3,5]
in wrand 'ζ' [[1],[2],[3,4]] w 6 == [3,4,2,2,3,4,1,3,4]

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

Pxrand. SC3 pattern that is like rand but filters successive duplicates.

xrand 'α' [return 1,[2,3],[4,5,6]] 9 == [4,5,6,2,3,4,5,6,1]

SC3 Variant Patterns

if_rec :: ([Bool], [a], [a]) -> Maybe (a, ([Bool], [a], [a])) Source

Underlying if_demand.

if_zip :: [Bool] -> [a] -> [a] -> [a] Source

zip3 variant.

if_zip [True,False,True] [1,3] [2] == [1]

funcn' :: RandomGen g => g -> (g -> (n, g)) -> Int -> [n] Source

Underlying funcn.

rorate_n' :: Num a => a -> a -> [a] Source

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

rorate_l' :: Num a => [a] -> a -> [a] Source

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

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

white with pattern inputs.

white' 'α' (repeat 0) [9,19,9,19,9,19] == [3,0,1,6,6,15]

whitei' :: (Random n, Integral n, Enum e) => e -> n -> n -> Int -> [n] Source

Type-specialised (Integral) white.

whitei' 'α' 1 9 5 == [3,9,2,9,4]

whitei :: (Random n, RealFracE n, Enum e) => e -> n -> n -> Int -> [n] Source

A variant of pwhite that generates integral (rounded) values.

whitei 'α' 1 9 5 == [5,1,7,7,8]

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

Underlying xrand.