csound-expression-4.1.0: library to make electronic music

Safe HaskellNone

Csound.Tab

Contents

Description

Creating Function Tables (Buffers)

Synopsis

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

Instances

Tuple Tab 
Arg Tab 
Val Tab 
IfB Tab 
Default Tab 

Table querries

nsamp :: Tab -> D

ftlen :: Tab -> D

ftsr :: Tab -> D

ftchnls :: Tab -> D

ftcps :: Tab -> D

Table granularity

data TabFi

Instances

Default TabFi 

fineFi :: Int -> [(Int, Int)] -> TabFi

Fill table with numbers

doubles :: [Double] -> TabSource

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).

Read from files

(In)Harmonic series

sines :: [PartialStrength] -> TabSource

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)] -> TabSource

Specifies series of possibly inharmonic partials.

sines2 :: [(PartialNumber, PartialStrength)] -> TabSource

Just like sines3 but phases are set to zero.

sines1 :: [PartialNumber] -> TabSource

Just like sines2 but partial strength is set to one.

sines4 :: [(PartialNumber, PartialStrength, PartialPhase, PartialDC)] -> TabSource

Specifies series of possibly inharmonic partials with direct current.

buzzes :: Double -> [Double] -> TabSource

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

sine :: TabSource

Table for pure sine wave.

cosine :: TabSource

Table for pure cosine wave.

sigmoid :: TabSource

Table for sigmoid wave.

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] -> TabSource

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] -> TabSource

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] -> TabSource

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] -> TabSource

Segments of the exponential curves.

 exps [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

splines :: [Double] -> TabSource

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] -> TabSource

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(
  • beg, end - end points of the segment
  • dur - duration of the segment

Equally spaced interpolants

econsts :: [Double] -> TabSource

Equally spaced constant segments.

 econsts [a, b, c, ...] 

is the same as

 consts [a, 1, b, 1, c, ...]

elins :: [Double] -> TabSource

Equally spaced segments of straight lines.

 elins [a, b, c, ...] 

is the same as

 lins [a, 1, b, 1, c, ...]

ecubes :: [Double] -> TabSource

Equally spaced segments of cubic polynomials.

 ecubes [a, b, c, ...] 

is the same as

 cubes [a, 1, b, 1, c, ...]

eexps :: [Double] -> TabSource

Equally spaced segments of exponential curves.

 eexps [a, b, c, ...] 

is the same as

 exps [a, 1, b, 1, c, ...]

esplines :: [Double] -> TabSource

Equally spaced spline curve.

 esplines [a, b, c, ...] 

is the same as

 splines [a, 1, b, 1, c, ...]

estartEnds :: [Double] -> TabSource

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] -> TabSource

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] -> TabSource

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] -> TabSource

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 -> TabSource

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

Low level Csound definition.

gen :: Int -> [Double] -> TabSource

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

setSize :: Int -> Tab -> TabSource

Sets an absolute size value. As you can do it in the Csound files.

setDegree :: Int -> Tab -> TabSource

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 -> TabSource

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).

gp :: Tab -> TabSource

Shortcut for guardPoint.

Handy shortcuts

handy shortcuts for the function setDegree.

lllofi :: Tab -> TabSource

Sets degrees from -3 to 3.

llofi :: Tab -> TabSource

Sets degrees from -3 to 3.

lofi :: Tab -> TabSource

Sets degrees from -3 to 3.

midfi :: Tab -> TabSource

Sets degrees from -3 to 3.

hifi :: Tab -> TabSource

Sets degrees from -3 to 3.

hhifi :: Tab -> TabSource

Sets degrees from -3 to 3.

hhhifi :: Tab -> TabSource

Sets degrees from -3 to 3.

Identifiers for GEN-routines

Low level Csound integer identifiers for tables. These names can be used in the function fineFi