Safe Haskell | None |
---|---|
Language | Haskell98 |
Creating Function Tables (Buffers)
- data Tab :: *
- noTab :: Tab
- nsamp :: Tab -> D
- ftlen :: Tab -> D
- ftsr :: Tab -> D
- ftchnls :: Tab -> D
- ftcps :: Tab -> D
- data TabFi :: *
- fineFi :: Int -> [(Int, Int)] -> TabFi
- coarseFi :: Int -> TabFi
- doubles :: [Double] -> Tab
- newTab :: D -> SE Tab
- newGlobalTab :: D -> SE Tab
- tabSizeSeconds :: D -> D
- tabSizePower2 :: D -> D
- tabSizeSecondsPower2 :: D -> D
- data WavChn
- data Mp3Chn
- wavs :: String -> Double -> WavChn -> Tab
- mp3s :: String -> Double -> Mp3Chn -> Tab
- type PartialStrength = Double
- type PartialNumber = Double
- type PartialPhase = Double
- type PartialDC = Double
- sines :: [PartialStrength] -> Tab
- sines3 :: [(PartialNumber, PartialStrength, PartialPhase)] -> Tab
- sines2 :: [(PartialNumber, PartialStrength)] -> Tab
- sines1 :: [PartialNumber] -> Tab
- sines4 :: [(PartialNumber, PartialStrength, PartialPhase, PartialDC)] -> Tab
- buzzes :: Double -> [Double] -> Tab
- sine :: Tab
- cosine :: Tab
- sigmoid :: Tab
- consts :: [Double] -> Tab
- lins :: [Double] -> Tab
- cubes :: [Double] -> Tab
- exps :: [Double] -> Tab
- splines :: [Double] -> Tab
- startEnds :: [Double] -> Tab
- econsts :: [Double] -> Tab
- elins :: [Double] -> Tab
- ecubes :: [Double] -> Tab
- eexps :: [Double] -> Tab
- esplines :: [Double] -> Tab
- estartEnds :: [Double] -> Tab
- polys :: Double -> Double -> [Double] -> Tab
- chebs1 :: Double -> Double -> [Double] -> Tab
- chebs2 :: Double -> Double -> [Double] -> Tab
- bessels :: Double -> Tab
- winHamming :: [Double] -> Tab
- winHanning :: [Double] -> Tab
- winBartlett :: [Double] -> Tab
- winBlackman :: [Double] -> Tab
- winHarris :: [Double] -> Tab
- winGaussian :: [Double] -> Tab
- winKaiser :: [Double] -> Tab
- winRectangle :: [Double] -> Tab
- winSync :: [Double] -> Tab
- gen :: Int -> [Double] -> Tab
- skipNorm :: Tab -> Tab
- forceNorm :: Tab -> Tab
- setSize :: Int -> Tab -> Tab
- setDegree :: Int -> Tab -> Tab
- guardPoint :: Tab -> Tab
- gp :: Tab -> Tab
- lllofi :: Tab -> Tab
- llofi :: Tab -> Tab
- lofi :: Tab -> Tab
- midfi :: Tab -> Tab
- hifi :: Tab -> Tab
- hhifi :: Tab -> Tab
- hhhifi :: Tab -> Tab
- idWavs :: Int
- idMp3s :: Int
- idDoubles :: Int
- idSines :: Int
- idSines3 :: Int
- idSines2 :: Int
- idPartials :: Int
- idSines4 :: Int
- idBuzzes :: Int
- idConsts :: Int
- idLins :: Int
- idCubes :: Int
- idExps :: Int
- idSplines :: Int
- idStartEnds :: Int
- idPolys :: Int
- idChebs1 :: Int
- idChebs2 :: Int
- idBessels :: Int
- idWins :: Int
- tablewa :: Tab -> Sig -> Sig -> SE Sig
- sec2rel :: Tab -> Sig -> Sig
Documentation
If you are not familliar with Csound's conventions you are pobably not aware of the fact that for efficiency reasons Csound requires that table size is equal to power of 2 or power of two plus one which stands for guard point (you do need guard point if your intention is to read the table once but you don't need the guard point if you read the table in many cycles, then the guard point is the the first point of your table).
data Tab :: *
Tables (or arrays)
Table querries
nsamp — Returns the number of samples loaded into a stored function table number.
nsamp(x) (init-rate args only)
csound doc: http://www.csounds.com/manual/html/nsamp.html
Table granularity
fineFi :: Int -> [(Int, Int)] -> TabFi
Sets different table size for different GEN-routines.
fineFi n ps
where
n
is the default value for table size (size is an
power of 2) for all gen routines that are not listed in the next argumentps
.ps
is a list of pairs(genRoutineId, tableSizeDegreeOf2)
that sets the given table size for a given GEN-routine.
with this function we can set lower table sizes for tables that are usually used in the envelopes.
Sets the same table size for all tables.
coarseFi n
where n
is a degree of 2. For example, n = 10
sets size to 1024 points for all tables by default.
Fill table with numbers
doubles :: [Double] -> Tab Source
Table contains all provided values (table is extended to contain all values and to be of the power of 2 or the power of two plus one). (by default it skips normalization).
Create new tables to write/update data
Creates a new table. The Tab could be used while the instrument is playing. When the instrument is retriggered the new tab is allocated.
newTab size
newGlobalTab :: D -> SE Tab Source
Creates a new global table. It's generated only once. It's persisted between instrument calls.
newGlobalTab identifier size
tabSizeSeconds :: D -> D Source
Calculates the number of samples needed to store the given amount of seconds. It multiplies the value by the current sample rate.
tabSizePower2 :: D -> D Source
Calculates the closest power of two value for a given size.
tabSizeSecondsPower2 :: D -> D Source
Calculates the closest power of two value in samples for a given size in seconds.
Read from files
wavs :: String -> Double -> WavChn -> Tab Source
Loads wav or aiff file to table
wavs fileName skipTime channel
skipTime specifies from what second it should read the file.
with channel argument we can read left, right or both channels.
mp3s :: String -> Double -> Mp3Chn -> Tab Source
Loads mp3 file to table:
mp3s fileName skipTime format
skipTime specifies from what second it should read the file.
format is: 1 - for mono files, 2 - for stereo files, 3 - for left channel of stereo file, 4 for right channel of stereo file
(In)Harmonic series
type PartialStrength = Double Source
type PartialNumber = Double Source
type PartialPhase = Double Source
sines :: [PartialStrength] -> Tab Source
Series of harmonic partials:
sine = sines [1]
saw = sines $ fmap (1 / ) [1 .. 10]
square = sines $ fmap (1 / ) [1, 3 .. 11]
triangle = sines $ zipWith (\a b -> a / (b ** 2)) (cycle [1, -1]) [1, 3 .. 11]
sines3 :: [(PartialNumber, PartialStrength, PartialPhase)] -> Tab Source
Specifies series of possibly inharmonic partials.
sines2 :: [(PartialNumber, PartialStrength)] -> Tab Source
Just like sines3
but phases are set to zero.
sines1 :: [PartialNumber] -> Tab Source
Just like sines2
but partial strength is set to one.
sines4 :: [(PartialNumber, PartialStrength, PartialPhase, PartialDC)] -> Tab Source
Specifies series of possibly inharmonic partials with direct current.
buzzes :: Double -> [Double] -> Tab Source
Generates values similar to the opcode buzz
.
buzzes numberOfHarmonics [lowestHarmonic, coefficientOfAttenuation]
With buzzes n [l, r]
you get n
harmonics from l
that are attenuated by the factor of r
on each step.
Special cases
Interpolants
All funtions have the same shape of arguments:
fun [a, n1, b, n2, c, ...]
where
- a, b, c .. - are ordinate values
- n1, n2 .. - are lengths of the segments relative to the total number of the points in the table
Csounders, Heads up! all segment lengths are relative to the total sum of the segments. You don't need to make the sum equal to the number of points in the table. Segment's lengths will be resized automatically. For example if we want to define a curve that rises to 1 over 25% of the table and then falls down to zero we can define it like this:
lins [0, 0.25, 1, 0.75, 0]
or
lins [0, 25, 1, 75, 0]
or
lins [0, 1, 1, 3, 0]
all these expressions are equivalent.
consts :: [Double] -> Tab Source
Constant segments (sample and hold).
consts [a, n1, b, n2, c, ...]
where
- a, b, c .. - are ordinate values
n1, n2, ...
are lengths of the segments relative to the total number of the points in the table
lins :: [Double] -> Tab Source
Segments of straight lines.
lins [a, n1, b, n2, c, ...]
where
- a, b, c .. - are ordinate values
n1, n2, ...
are lengths of the segments relative to the total number of the points in the table
cubes :: [Double] -> Tab Source
Segments of cubic polynomials.
cubes [a, n1, b, n2, c, ...]
where
- a, b, c .. - are ordinate values
n1, n2, ...
are lengths of the segments relative to the total number of the points in the table
exps :: [Double] -> Tab Source
Segments of the exponential curves.
exps [a, n1, b, n2, c, ...]
where
a, b, c, ...
are ordinate valuesn1, n2, ...
are lengths of the segments relative to the total number of the points in the table
splines :: [Double] -> Tab Source
Cubic spline curve.
splines [a, n1, b, n2, c, ...]
where
- a, b, c .. - are ordinate values
n1, n2, ...
are lengths of the segments relative to the total number of the points in the table
startEnds :: [Double] -> Tab Source
Creates a table from a starting value to an ending value.
startEnds [val1, dur1, type1, val2, dur2, type2, val3, ... typeX, valN]
- val1, val2 ... -- end points of the segments
- dur1, dur2 ... -- durations of the segments
- type1, type2 ... -- if 0, a straight line is produced. If non-zero, then it creates the following curve, for dur steps:
beg + (end - beg) * (1 - exp( i*type)) / (1 - exp(type * dur))
- beg, end - end points of the segment
- dur - duration of the segment
Equally spaced interpolants
econsts :: [Double] -> Tab Source
Equally spaced constant segments.
econsts [a, b, c, ...]
is the same as
consts [a, 1, b, 1, c, ...]
elins :: [Double] -> Tab Source
Equally spaced segments of straight lines.
elins [a, b, c, ...]
is the same as
lins [a, 1, b, 1, c, ...]
ecubes :: [Double] -> Tab Source
Equally spaced segments of cubic polynomials.
ecubes [a, b, c, ...]
is the same as
cubes [a, 1, b, 1, c, ...]
eexps :: [Double] -> Tab Source
Equally spaced segments of exponential curves.
eexps [a, b, c, ...]
is the same as
exps [a, 1, b, 1, c, ...]
esplines :: [Double] -> Tab Source
Equally spaced spline curve.
esplines [a, b, c, ...]
is the same as
splines [a, 1, b, 1, c, ...]
estartEnds :: [Double] -> Tab Source
Equally spaced interpolation for the function startEnds
estartEnds [val1, type1, val2, typ2, ...]
is the same as
estartEnds [val1, 1, type1, val2, 1, type2, ...]
Polynomials
polys :: Double -> Double -> [Double] -> Tab Source
Polynomials.
polys xl xr [c0, c1, c2, ..]
where
- xl, xr - left and right values of the interval over wich polynomial is defined
- [c0, c1, c2, ...] -- coefficients of the polynomial
c0 + c1 * x + c2 * x * x + ...
chebs1 :: Double -> Double -> [Double] -> Tab Source
Chebyshev polynomials of the first kind.
polys xl xr [h0, h1, h2, ..]
where
- xl, xr - left and right values of the interval over wich polynomial is defined
- [h0, h1, h2, ...] -- relative strength of the partials
chebs2 :: Double -> Double -> [Double] -> Tab Source
Chebyshev polynomials of the second kind.
polys xl xr [h0, h1, h2, ..]
where
- xl, xr - left and right values of the interval over wich polynomial is defined
- [h0, h1, h2, ...] -- relative strength of the partials
bessels :: Double -> Tab Source
Modified Bessel function of the second kind, order 0 (for amplitude modulated FM).
bessels xint
the function is defined within the interval [0, xint]
.
Windows
winHamming :: [Double] -> Tab Source
winHanning :: [Double] -> Tab Source
winBartlett :: [Double] -> Tab Source
winBlackman :: [Double] -> Tab Source
winGaussian :: [Double] -> Tab Source
winRectangle :: [Double] -> Tab Source
Low level Csound definition.
gen :: Int -> [Double] -> Tab Source
Creates a table of doubles (It's f-table in Csound). Arguments are:
- identificator of the GEN routine
- GEN routine arguments
All tables are created at 0 and memory is never released.
Modify tables
Force normalization (sets table size to positive value).
Might be useful to restore normalization for table doubles
.
setSize :: Int -> Tab -> Tab Source
Sets an absolute size value. As you can do it in the Csound files.
setDegree :: Int -> Tab -> Tab Source
Sets the relative size value. You can set the base value in the options
(see tabResolution
at CsdOptions
, with tabResolution you can easily change table sizes for all your tables).
Here zero means the base value. 1 is the base value multiplied by 2, 2 is the base value multiplied by 4
and so on. Negative values mean division by the specified degree.
guardPoint :: Tab -> Tab Source
Adds guard point to the table size (details of the interpolation schemes: you do need guard point if your intention is to read the table once but you don't need the guard point if you read table in many cycles, the guard point is the the first point of your table).
Shortcut for guardPoint
.
Handy shortcuts
handy shortcuts for the function setDegree
.
Identifiers for GEN-routines
Low level Csound integer identifiers for tables. These names can be used in the function fineFi
idPartials :: Int
idStartEnds :: Int
Tabular opcodes
tablewa :: Tab -> Sig -> Sig -> SE Sig Source
Writes tables in sequential locations.
This opcode writes to a table in sequential locations to and from an a-rate variable. Some thought is required before using it. It has at least two major, and quite different, applications which are discussed below.
kstart tablewa kfn, asig, koff
csound docs: http://www.csounds.com/manual/html/tablewa.html