hsc3-0.20: Haskell SuperCollider
Safe HaskellSafe-Inferred
LanguageHaskell2010

Sound.Sc3.Common.Buffer.Gen

Description

Implementaion of server b_gen routines.

The naming scheme is: _p generates one partial, _l generates a list of partials, _nrm is the unit normalised form.

Synopsis

Documentation

sum_l :: Num n => [[n]] -> [n] Source #

Sum (mix) multiple tables into one.

nrm_u :: (Fractional n, Ord n) => [n] -> [n] Source #

Unit normalisation.

sine1

sine1_p :: (Enum n, Floating n) => Int -> (n, n) -> [n] Source #

sine3_p with zero phase.

import Sound.Sc3.Plot {- hsc3-plot -}
plot_p1_ln [sine1_p 512 (1, 1)]

sine1_l :: (Enum n, Floating n) => Int -> [n] -> [[n]] Source #

Series of sine wave harmonics using specified amplitudes.

sine1 :: (Enum n, Floating n) => Int -> [n] -> [n] Source #

sum_l of sine1_l.

plot_p1_ln [sine1 256 [1, 0.95 .. 0.5]]

sine1_nrm :: (Enum n, Floating n, Ord n) => Int -> [n] -> [n] Source #

nrm_u of sine1_l.

Sound.Sc3.Plot.plot_p1_ln [sine1_nrm 256 [1, 0.95 .. 0.5]]
Sound.Sc3.Plot.plot_p1_ln [sine1_nrm 256 [1, 1/2, 1/3, 1/4, 1/5]]

sine1Tbl :: (Enum n, Floating n, Ord n) => Int -> [n] -> [n] Source #

Variant that generates a wavetable (without guard point) suitable for the Shaper Ugen.

sine2

sine2_l :: (Enum n, Floating n) => Int -> [(n, n)] -> [[n]] Source #

Series of n sine wave partials using specified frequencies and amplitudes.

sine2 :: (Enum n, Floating n) => Int -> [(n, n)] -> [n] Source #

sum_l of sine2_l.

Sound.Sc3.Plot.plot_p1_ln [sine2 256 (zip [1, 2..] [1, 0.95 .. 0.5])]
Sound.Sc3.Plot.plot_p1_ln [sine2 256 (zip [1, 1.5 ..] [1, 0.95 .. 0.5])]

sine2_nrm :: (Enum n, Floating n, Ord n) => Int -> [n] -> [n] Source #

sine3

sine3_p :: (Enum n, Floating n) => Int -> (n, n, n) -> [n] Source #

Sine wave table at specified frequency, amplitude and phase.

sine3_l :: (Enum n, Floating n) => Int -> [(n, n, n)] -> [[n]] Source #

sine3 :: (Enum n, Floating n) => Int -> [(n, n, n)] -> [n] Source #

sum_l of sine3_l.

plot_p1_ln [sine3 256 (zip3 [1,1.5 ..] [1,0.95 .. 0.5] [0,pi/7..])]

cheby

gen_cheby :: (Enum n, Floating n, Ord n, Integral i) => i -> [n] -> [n] Source #

Generate Chebyshev waveshaping table, see b_gen_cheby.

Sound.Sc3.Plot.plot_p1_ln [gen_cheby 256 [1, 0, 1, 1, 0, 1]]

cheby :: (Enum n, Floating n, Ord n) => Int -> [n] -> [n] Source #

Type specialised gen_cheby.

chebyShaperTbl :: (Enum n, Floating n, Ord n) => Int -> [n] -> [n] Source #

Variant that generates a wavetable (without guard point) suitable for the Shaper Ugen.