csound-expression-5.1.0: library to make electronic music

Safe HaskellNone
LanguageHaskell98

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 :: * #

Tables (or arrays)

Instances

IfB Tab 

Methods

ifB :: (* ~ bool) (BooleanOf Tab) => bool -> Tab -> Tab -> Tab #

Tuple Tab 
Arg Tab 
Val Tab 

Methods

fromGE :: GE E -> Tab #

toGE :: Tab -> GE E #

fromE :: E -> Tab #

Default Tab 

Methods

def :: Tab #

type BooleanOf Tab 
type Snap Tab 
type Snap Tab = Tab

noTab :: Tab Source #

The default table. It's rendered to (-1) in the Csound.

Table querries

nsamp :: Tab -> D #

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

ftlen :: Tab -> D #

Returns a length of the table.

ftsr :: Tab -> D #

Returns the sample rate for a table that stores wav files

ftchnls :: Tab -> D #

Returns the number of channels for a table that stores wav files

ftcps :: Tab -> D #

Returns the base frequency for a table that stores wav files

Table granularity

data TabFi :: * #

Table size fidelity (how many points in the table by default).

Instances

Default TabFi 

Methods

def :: TabFi #

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

Sets different table size for different GEN-routines.

fineFi n ps 

where

  • n is the default value for table size (size is a n power of 2) for all gen routines that are not listed in the next argument ps.
  • 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.

coarseFi :: Int -> TabFi #

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

newTab :: D -> SE Tab #

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 :: Int -> SE Tab #

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

data WavChn Source #

Constructors

WavLeft 
WavRight 
WavAll 

Instances

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.

wavLeft :: String -> Tab Source #

Reads left channel of audio-file

wavRight :: String -> Tab Source #

Reads right channel of audio-file

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

mp3Left :: String -> Tab Source #

Reads left channel of mp3-file

mp3Right :: String -> Tab Source #

Reads right channel of mp3-file

mp3m :: String -> Tab Source #

Reads mono of mp3-file

(In)Harmonic series

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.

bwSines :: [Double] -> Double -> Tab Source #

Sines with bandwidth (simplified padsynth generator)

bwSines harmonics bandwidth

bwOddSines :: [Double] -> Double -> Tab Source #

Sines with bandwidth (simplified padsynth generator). Only odd harmonics are present

bwOddSines harmonics bandwidth

Special cases

sine :: Tab Source #

Table for pure sine wave.

cosine :: Tab Source #

Table for pure cosine wave.

sigmoid :: Tab Source #

Table for sigmoid wave.

sigmoidRise :: Tab Source #

Table for sigmoid rise wave.

sigmoidFall :: Tab Source #

Table for sigmoid fall wave.

tanhSigmoid :: Double -> Tab Source #

Creates tanh sigmoid. The argument is the radius of teh sigmoid.

triTab :: Tab Source #

Linear segments that form a singl cycle of triangle wave.

sawTab :: Tab Source #

Linear segments that form a single cycle of sawtooth wave.

sqrTab :: Tab Source #

Linear segments that form a single cycle of square wave.

pwTab :: Double -> Tab Source #

Pulse-width wave formed with linear segments. Duty cycle rages from 0 to 1. 0.5 is a square 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] -> 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 values
  • n1, 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

Padsynth

padsynth :: PadsynthSpec -> Tab Source #

Creates tables for the padsynth algorithm (described at http://www.paulnasca.com/algorithms-created-by-me). The table size should be very big the default is 18 power of 2.

csound docs: http://csound.github.io/docs/manual/GENpadsynth.html

defPadsynthSpec :: Double -> [Double] -> PadsynthSpec Source #

Specs for padsynth algorithm:

defPadsynthSpec partialBandwidth harmonics
  • partialBandwidth -- bandwidth of the first partial.
  • harmonics -- the list of amplitudes for harmonics.

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

skipNorm :: Tab -> Tab #

Skips normalization (sets table size to negative value)

forceNorm :: Tab -> Tab #

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

gp :: Tab -> Tab Source #

Shortcut for guardPoint.

Handy shortcuts

handy shortcuts for the function setDegree.

lllofi :: Tab -> Tab Source #

Sets degrees from -3 to 3.

llofi :: Tab -> Tab Source #

Sets degrees from -3 to 3.

lofi :: Tab -> Tab Source #

Sets degrees from -3 to 3.

midfi :: Tab -> Tab Source #

Sets degrees from -3 to 3.

hifi :: Tab -> Tab Source #

Sets degrees from -3 to 3.

hhifi :: Tab -> Tab Source #

Sets degrees from -3 to 3.

hhhifi :: Tab -> Tab Source #

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

Tabular opcodes

sec2rel :: Tab -> Sig -> Sig Source #

Transforms phasor that is defined in seconds to relative phasor that ranges in 0 to 1.

Tables of tables

data TabList :: * #

Container list of tables

Mic table functions

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

tablew :: Sig -> Sig -> Tab -> SE () Source #

tablew — Change the contents of existing function tables.

This opcode operates on existing function tables, changing their contents. tablew is for writing at k- or at a-rates, with the table number being specified at init time. Using tablew with i-rate signal and index values is allowed, but the specified data will always be written to the function table at k-rate, not during the initialization pass. The valid combinations of variable types are shown by the first letter of the variable names.

tablew asig, andx, ifn [, ixmode] [, ixoff] [, iwgmode]
tablew isig, indx, ifn [, ixmode] [, ixoff] [, iwgmode]
tablew ksig, kndx, ifn [, ixmode] [, ixoff] [, iwgmode]

csound doc: http://www.csounds.com/manual/html/tablew.html

readTab :: Sig -> Tab -> SE Sig Source #

Notice that this function is the same as tab, but it wraps the output in the SE-monad. So you can use the tab if your table is read-only and you can use readTab if you want to update the table and the order of read/write operation is important.

Fast table opcodes.

Fast table opcodes. Faster than table and tablew because don't allow wrap-around and limit and don't check index validity. Have been implemented in order to provide fast access to arrays. Support non-power of two tables (can be generated by any GEN function by giving a negative length value).

kr  tab  kndx, ifn[, ixmode]
ar  tab  xndx, ifn[, ixmode]

csound doc: http://www.csounds.com/manual/html/tab.html

readTable :: SigOrD a => a -> Tab -> SE a Source #

Notice that this function is the same as table, but it wraps the output in the SE-monad. So you can use the table if your table is read-only and you can use readTable if you want to update the table and the order of read/write operation is important.

Accesses table values by direct indexing.

ares  table  andx, ifn [, ixmode] [, ixoff] [, iwrap]
ires  table  indx, ifn [, ixmode] [, ixoff] [, iwrap]
kres  table  kndx, ifn [, ixmode] [, ixoff] [, iwrap]

csound doc: http://www.csounds.com/manual/html/table.html

readTable3 :: SigOrD a => a -> Tab -> SE a Source #

Notice that this function is the same as tablei, but it wraps the output in the SE-monad. So you can use the tablei if your table is read-only and you can use readTablei if you want to update the table and the order of read/write operation is important.

Accesses table values by direct indexing with cubic interpolation.

ares  table3  andx, ifn [, ixmode] [, ixoff] [, iwrap]
ires  table3  indx, ifn [, ixmode] [, ixoff] [, iwrap]
kres  table3  kndx, ifn [, ixmode] [, ixoff] [, iwrap]

csound doc: http://www.csounds.com/manual/html/table3.html

readTablei :: SigOrD a => a -> Tab -> SE a Source #

Notice that this function is the same as table3, but it wraps the output in the SE-monad. So you can use the table3 if your table is read-only and you can use readTable3 if you want to update the table and the order of read/write operation is important.

Accesses table values by direct indexing with linear interpolation.

ares  tablei  andx, ifn [, ixmode] [, ixoff] [, iwrap]
ires  tablei  indx, ifn [, ixmode] [, ixoff] [, iwrap]
kres  tablei  kndx, ifn [, ixmode] [, ixoff] [, iwrap]

csound doc: http://www.csounds.com/manual/html/tablei.html

Table Reading with Dynamic Selection

tableikt :: Sig -> Tab -> Sig Source #

tableikt — Provides k-rate control over table numbers.

k-rate control over table numbers. Function tables are read with linear interpolation. The standard Csound opcode tablei, when producing a k- or a-rate result, can only use an init-time variable to select the table number. tableikt accepts k-rate control as well as i-time. In all other respects they are similar to the original opcodes.

ares tableikt xndx, kfn [, ixmode] [, ixoff] [, iwrap]
kres tableikt kndx, kfn [, ixmode] [, ixoff] [, iwrap]

csound doc: http://www.csounds.com/manual/html/tableikt.html

tablekt :: Sig -> Tab -> Sig Source #

tablekt — Provides k-rate control over table numbers.

k-rate control over table numbers. Function tables are read with linear interpolation. The standard Csound opcode table when producing a k- or a-rate result, can only use an init-time variable to select the table number. tablekt accepts k-rate control as well as i-time. In all other respects they are similar to the original opcodes.

ares tablekt xndx, kfn [, ixmode] [, ixoff] [, iwrap]
kres tablekt kndx, kfn [, ixmode] [, ixoff] [, iwrap]

csound doc: http://www.csounds.com/manual/html/tablekt.html

tablexkt :: Sig -> Tab -> Sig -> D -> Sig Source #

tablexkt — Reads function tables with linear, cubic, or sinc interpolation.

ares tablexkt xndx, kfn, kwarp, iwsize [, ixmode] [, ixoff] [, iwrap]

csound doc: http://www.csounds.com/manual/html/tablexkt.html