hsc3-0.21: Haskell SuperCollider
Safe HaskellSafe-Inferred
LanguageHaskell2010

Sound.Sc3.Ugen.Hs

Description

Haskell implementations of Sc3 Ugens.

Synopsis

Documentation

type F_St0 st o = st -> (o, st) Source #

F = function, St = state

type F_St1 st i o = (i, st) -> (o, st) Source #

type F_U2 n = n -> n -> n Source #

U = uniform

type F_U3 n = n -> n -> n -> n Source #

type F_U4 n = n -> n -> n -> n -> n Source #

type F_U5 n = n -> n -> n -> n -> n -> n Source #

type F_U6 n = n -> n -> n -> n -> n -> n -> n Source #

type F_U7 n = n -> n -> n -> n -> n -> n -> n -> n Source #

type F_U8 n = n -> n -> n -> n -> n -> n -> n -> n -> n Source #

type F_U9 n = n -> n -> n -> n -> n -> n -> n -> n -> n -> n Source #

type T5 n = (n, n, n, n, n) Source #

T = tuple (see Base for T2-T4)

type T6 n = (n, n, n, n, n, n) Source #

type T7 n = (n, n, n, n, n, n, n) Source #

type T8 n = (n, n, n, n, n, n, n, n) Source #

type T9 n = (n, n, n, n, n, n, n, n, n) Source #

avg2 :: Fractional n => F_U2 n Source #

avg = average

fir1 :: F_U2 n -> F_St1 n n n Source #

fir = finite impulse response

>>> l_apply_f_st1 (fir1 (\x z1 -> (x + z1) / 2)) 0 [0 .. 5]
[0.0,0.5,1.5,2.5,3.5,4.5]

fir2 :: F_U3 n -> F_St1 (T2 n) n n Source #

fir = finite impulse response

>>> l_apply_f_st1 (fir2 (\x x1 x2 -> (x + x1 + x2) / 2)) (0,0) [0 .. 5]
[0.0,0.5,1.5,3.0,4.5,6.0]

fir3 :: F_U4 n -> F_St1 (T3 n) n n Source #

fir4 :: F_U5 n -> F_St1 (T4 n) n n Source #

fir8 :: F_U9 n -> F_St1 (T8 n) n n Source #

iir1 :: F_U2 n -> F_St1 n n n Source #

iir = infinite impulse response

> l_apply_f_st1 (iir1 (\x y1 -> x + y1)) 0 (replicate 10 1)
1,2,3,4,5,6,7,8,9,10

iir2 :: F_U3 n -> F_St1 (T2 n) n n Source #

Two place iir

>>> l_apply_f_st1 (iir2 (\x y1 y2 -> x + y1 + y2)) (0,0) (replicate 10 1)
[1,2,4,7,12,20,33,54,88,143]
>>> map (+1) [0+0,1+0,2+1,4+2,7+4,12+7,20+12,33+20,54+33,88+54] -- https://oeis.org/A000071
[1,2,4,7,12,20,33,54,88,143]

iir2_ff_fb :: (n -> n -> n -> T2 n) -> F_St1 (T2 n) n n Source #

ff = feed-forward, fb = feed-back

biquad :: F_U5 n -> F_St1 (T4 n) n n Source #

sos_f :: Num n => T5 n -> F_U5 n Source #

sos = second order section

sos :: Num n => T5 n -> F_St1 (T4 n) n n Source #

hpz1 :: Fractional n => F_St1 n n n Source #

hp = high pass

hpz2 :: Fractional n => F_St1 (T2 n) n n Source #

lpz1 :: Fractional n => F_St1 n n n Source #

lp = low pass

lpz2 :: Fractional n => F_St1 (T2 n) n n Source #

bpz2 :: Fractional n => F_St1 (T2 n) n n Source #

bp = band pass

brz2 :: Fractional n => F_St1 (T2 n) n n Source #

br = band reject

mavg5 :: Fractional n => F_St1 (T4 n) n n Source #

mavg = moving average

mavg9 :: Fractional n => F_St1 (T8 n) n n Source #

sr_to_rps :: Floating n => n -> n Source #

Sample rate (SR) to radians per sample (RPS).

>>> sr_to_rps 44100 == 0.00014247585730565955
True

resonz_f :: Floating n => T3 n -> n -> n -> n -> T2 n Source #

resonz iir2_ff_fb function. param are for resonz_coef.

resonz_ir :: Floating n => T3 n -> F_St1 (T2 n) n n Source #

ir = initialization rate

rlpf_f :: Floating n => (n -> n -> n) -> T3 n -> F_U3 n Source #

rlpf = resonant low pass filter

rlpf_ir :: (Floating n, Ord n) => T3 n -> F_St1 (T2 n) n n Source #

bw_hpf_ir :: Floating n => T2 n -> F_St1 (T4 n) n n Source #

bw_lpf_ir :: Floating n => T2 n -> F_St1 (T4 n) n n Source #

brown_noise_f :: (Fractional n, Ord n) => n -> n -> n Source #

brown_noise :: (RandomGen g, Fractional n, Random n, Ord n) => F_St0 (g, n) n Source #

pk_pinking_filter_f :: Fractional a => (a, a, a, a, a, a, a) -> a -> (a, (a, a, a, a, a, a, a)) Source #

decay_f :: Floating a => a -> a -> a -> a -> a Source #

dt must not be zero.

lag_f_frames :: Floating a => a -> a -> a -> a Source #

Given time dt in frames construct iir1 lag function. dt must not be zero.

lag_f :: Floating a => a -> a -> a -> a -> a Source #

lag_f_frames with dt in seconds.

lag :: Floating t => t -> F_St1 t (t, t) t Source #

slope :: Num t => t -> F_St1 t t t Source #

latch :: F_St1 t (t, Bool) t Source #

phasor :: RealFrac t => F_St1 t (Bool, t, t, t, t) t Source #

mod_dif :: RealFrac a => a -> a -> a -> a Source #

l_apply_f_st0 :: F_St0 st o -> st -> [o] Source #

  • List Processing

l_white_noise :: (Enum e, Fractional n, Random n) => e -> [n] Source #

White noise

>>> take 4 (l_white_noise 'α')
[0.9687553280469108,0.808159221997721,-0.8993330152164296,0.23197278942699834]

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

Brown noise

>>> take 4 (l_brown_noise 'α')
[0.12109441600586385,0.22211431875557897,0.10969769185352526,0.13869429053190005]

l_apply_f_st1 :: F_St1 st i o -> st -> [i] -> [o] Source #

l_lag :: Floating t => t -> [t] -> [t] -> [t] Source #

l_slope :: Floating t => t -> [t] -> [t] Source #

l_phasor :: RealFrac n => [Bool] -> [n] -> [n] -> [n] -> [n] -> [n] Source #

Phasor

>>> let rp = repeat
>>> take 10 (l_phasor (rp False) (rp 1) (rp 0) (rp 4) (rp 0))
[0.0,1.0,2.0,3.0,0.0,1.0,2.0,3.0,0.0,1.0]

l_phasor_osc :: RealFrac n => n -> n -> [n] -> [n] Source #

l_sin_osc :: (Floating n, RealFrac n) => n -> [n] -> [n] Source #

l_cos_osc :: (Floating n, RealFrac n) => n -> [n] -> [n] Source #

l_hpz1 :: Fractional n => [n] -> [n] Source #

l_hpz2 :: Fractional n => [n] -> [n] Source #

l_lpz1 :: Fractional n => [n] -> [n] Source #

l_lpz2 :: Fractional n => [n] -> [n] Source #

l_bpz2 :: Fractional n => [n] -> [n] Source #

l_brz2 :: Fractional n => [n] -> [n] Source #

l_bw_hpf :: Floating n => T2 n -> [n] -> [n] Source #

l_bw_lpf :: Floating n => T2 n -> [n] -> [n] Source #

l_resonz_ir :: Floating n => T3 n -> [n] -> [n] Source #

l_rlpf_ir :: (Floating n, Ord n) => T3 n -> [n] -> [n] Source #

l_mavg5 :: Fractional n => [n] -> [n] Source #

l_mavg9 :: Fractional n => [n] -> [n] Source #