Safe Haskell | Safe-Inferred |
---|---|
Language | Haskell2010 |
- Table querries
- Table granularity
- Fill table with numbers
- Create new tables to write/update data
- Read from files
- (In)Harmonic series
- Wavelets
- Interpolants
- Polynomials
- Random values
- Windows
- Padsynth
- Harmonics
- Normalize table
- Low level Csound definition.
- Modify tables
- Identifiers for GEN-routines
- Tabular opcodes
- Tables of tables
- Mic table functions
- Appendix (original GEN identifiers lookup)
Creating Function Tables (Buffers)
Synopsis
- data Tab
- noTab :: Tab
- isNoTab :: Tab -> BoolD
- nsamp :: Tab -> D
- ftlen :: Tab -> D
- ftsr :: Tab -> D
- ftchnls :: Tab -> D
- ftcps :: Tab -> D
- tabDur :: Tab -> D
- data TabFi
- fineFi :: Int -> [(Int, Int)] -> [(Text, Int)] -> TabFi
- coarseFi :: Int -> TabFi
- doubles :: [Double] -> Tab
- newTab :: D -> SE Tab
- newGlobalTab :: Int -> SE Tab
- tabSizeSeconds :: D -> D
- tabSizePower2 :: D -> D
- tabSizeSecondsPower2 :: D -> D
- data WavChn
- data Mp3Chn
- wavs :: String -> Double -> WavChn -> Tab
- wavAll :: String -> Tab
- wavLeft :: String -> Tab
- wavRight :: String -> Tab
- mp3s :: String -> Double -> Mp3Chn -> Tab
- mp3Left :: String -> Tab
- mp3Right :: String -> Tab
- mp3m :: String -> Tab
- readNumFile :: String -> Tab
- readTrajectoryFile :: String -> Tab
- readPvocex :: String -> Int -> Tab
- readMultichannel :: Int -> [(Tab, Int, Int)] -> 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
- bwSines :: [Double] -> Double -> Tab
- bwOddSines :: [Double] -> Double -> Tab
- mixOnTab :: Tab -> [(PartialNumber, PartialStrength, PartialPhase)] -> Tab
- mixTabs :: [(Tab, PartialNumber, PartialStrength, PartialPhase)] -> Tab
- tabSines1 :: Tab -> Double -> Double -> Maybe Double -> Tab
- tabSines2 :: Tab -> Double -> Double -> Maybe Double -> Tab
- waveletTab :: Tab -> Int -> Tab
- rescaleWaveletTab :: Tab -> Int -> Tab
- sine :: Tab
- cosine :: Tab
- sigmoid :: Tab
- sigmoidRise :: Tab
- sigmoidFall :: Tab
- tanhSigmoid :: Double -> Tab
- triTab :: Tab
- sawTab :: Tab
- sqrTab :: Tab
- pwTab :: Double -> Tab
- tanhTab :: (Double, Double) -> Tab
- rescaleTanhTab :: (Double, Double) -> Tab
- expTab :: (Double, Double) -> Tab
- rescaleExpTab :: (Double, Double) -> Tab
- soneTab :: (Double, Double) -> Double -> Tab
- rescaleSoneTab :: (Double, Double) -> Double -> Tab
- fareyTab :: Int -> Int -> Tab
- consts :: [Double] -> Tab
- lins :: [Double] -> Tab
- cubes :: [Double] -> Tab
- exps :: [Double] -> Tab
- splines :: [Double] -> Tab
- startEnds :: [Double] -> Tab
- tabseg :: [(Tab, PartialStrength, Double)] -> Tab
- bpLins :: [Double] -> Tab
- bpExps :: [Double] -> Tab
- econsts :: [Double] -> Tab
- elins :: [Double] -> Tab
- ecubes :: [Double] -> Tab
- eexps :: [Double] -> Tab
- esplines :: [Double] -> Tab
- estartEnds :: [Double] -> Tab
- etabseg :: [(Tab, PartialStrength)] -> Tab
- polys :: Double -> Double -> [Double] -> Tab
- chebs1 :: Double -> Double -> [Double] -> Tab
- chebs2 :: Double -> Double -> [Double] -> Tab
- bessels :: Double -> Tab
- uniDist :: Tab
- linDist :: Tab
- triDist :: Tab
- expDist :: Tab
- biexpDist :: Tab
- gaussDist :: Tab
- cauchyDist :: Tab
- pcauchyDist :: Tab
- betaDist :: Double -> Double -> Tab
- weibullDist :: Double -> Tab
- poissonDist :: Tab
- tabDist :: Tab -> Tab
- uniDist' :: Double -> Tab
- linDist' :: Double -> Tab
- triDist' :: Double -> Tab
- expDist' :: Double -> Tab
- biexpDist' :: Double -> Tab
- gaussDist' :: Double -> Tab
- cauchyDist' :: Double -> Tab
- pcauchyDist' :: Double -> Tab
- betaDist' :: Double -> Double -> Double -> Tab
- weibullDist' :: Double -> Double -> Tab
- poissonDist' :: Double -> Tab
- randDist :: [Double] -> Tab
- rangeDist :: [Double] -> Tab
- winHamming :: Tab
- winHanning :: Tab
- winBartlett :: Tab
- winBlackman :: Tab
- winHarris :: Tab
- winGauss :: Double -> Tab
- winKaiser :: Double -> Tab
- winRectangle :: Tab
- winSync :: Tab
- padsynth :: PadsynthSpec -> Tab
- data PadsynthSpec = PadsynthSpec {}
- data PadsynthShape
- defPadsynthSpec :: Double -> [Double] -> PadsynthSpec
- tabHarmonics :: Tab -> Double -> Double -> Maybe Double -> Maybe Double -> Tab
- normTab :: NormTabSpec -> Tab -> Tab
- data NormTabSpec
- scaleTab :: (Double, Double) -> Tab -> 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
- idPadsynth :: Text
- idTanh :: Text
- idExp :: Text
- idSone :: Text
- idFarey :: Text
- idWave :: Text
- sec2rel :: Tab -> Sig -> Sig
- data TabList
- tabList :: [Tab] -> TabList
- fromTabList :: TabList -> Sig -> Tab
- fromTabListD :: TabList -> D -> Tab
- tablewa :: Tab -> Sig -> Sig -> SE Sig
- tablew :: Sig -> Sig -> Tab -> SE ()
- readTab :: Sig -> Tab -> SE Sig
- readTable :: SigOrD a => a -> Tab -> SE a
- readTable3 :: SigOrD a => a -> Tab -> SE a
- readTablei :: SigOrD a => a -> Tab -> SE a
- tableikt :: Sig -> Tab -> Sig
- tablekt :: Sig -> Tab -> Sig
- tablexkt :: Sig -> Tab -> Sig -> D -> Sig
- cuserrnd :: SigOrD a => a -> a -> Tab -> SE a
- duserrnd :: SigOrD a => Tab -> SE a
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).
Tables (or arrays)
Instances
IfB Tab | |
PureSingle Tab | |
Defined in Csound.Typed.Types.Lift pureSingleGE :: GE ([E] -> E) -> Tab | |
Val Tab | |
Arg Tab | |
Defined in Csound.Typed.Types.Tuple | |
Tuple Tab | |
Defined in Csound.Typed.Types.Tuple | |
Default Tab | |
Defined in Csound.Typed.Types.Prim | |
DirtySingle (SE Tab) | |
Defined in Csound.Typed.Types.Lift | |
DirtyMulti b => DirtyMulti (Tab -> b) | |
Defined in Csound.Typed.Types.Lift | |
DirtySingle b => DirtySingle (Tab -> b) | |
Defined in Csound.Typed.Types.Lift | |
Procedure b => Procedure (Tab -> b) | |
Defined in Csound.Typed.Types.Lift procedureGE :: GE ([E] -> Dep ()) -> Tab -> b | |
PureMulti b => PureMulti (Tab -> b) | |
Defined in Csound.Typed.Types.Lift | |
PureSingle b => PureSingle (Tab -> b) | |
Defined in Csound.Typed.Types.Lift pureSingleGE :: GE ([E] -> E) -> Tab -> b | |
type BooleanOf Tab | |
Defined in Csound.Typed.Types.Prim | |
type Snap Tab | |
Defined in Csound.Typed.Types.Evt |
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 length in seconds for files that are read with GEN01 (which a re read with functions like wavs, wavTab, wavLeft, wavRight).
Table granularity
Table size fidelity (how many points in the table by default).
fineFi :: Int -> [(Int, Int)] -> [(Text, 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 :: 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
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
readNumFile :: String -> Tab Source #
Reads numbers from file (GEN23)
csound doc: http://www.csounds.com/manual/html/GEN23.html
readTrajectoryFile :: String -> Tab Source #
Reads trajectory from file (GEN28)
csound doc: http://www.csounds.com/manual/html/GEN28.html
readPvocex :: String -> Int -> Tab Source #
Reads PVOCEX files (GEN43)
csound doc: http://www.csounds.com/manual/html/GEN43.html
readMultichannel :: Int -> [(Tab, Int, Int)] -> Tab Source #
readMultichannel — Creates an interleaved multichannel table from the specified source tables, in the format expected by the ftconv opcode (GEN52).
f # time size 52 nchannels fsrc1 offset1 srcchnls1 [fsrc2 offset2 srcchnls2 ... fsrcN offsetN srcchnlsN]
csound doc: http://www.csounds.com/manual/html/GEN52.html
(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.
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
mixOnTab :: Tab -> [(PartialNumber, PartialStrength, PartialPhase)] -> Tab Source #
It's just like sines3 but inplace of pure sinewave it uses supplied in the first argument shape.
mixOnTab srcTable [(partialNumber, partialStrength, partialPahse)]
phahse is in range [0, 1]
mixTabs :: [(Tab, PartialNumber, PartialStrength, PartialPhase)] -> Tab Source #
It's like mixOnTab
but it's more generic since we can mix not only one shape.
But we can specify shape for each harmonic.
tabSines1 :: Tab -> Double -> Double -> Maybe Double -> Tab Source #
Csound's GEN33 — Generate composite waveforms by mixing simple sinusoids.
tabSines1 srcTab nh scl [fmode]
Csound docs: http://www.csounds.com/manual/html/GEN33.html
tabSines2 :: Tab -> Double -> Double -> Maybe Double -> Tab Source #
Csound's GEN34 — Generate composite waveforms by mixing simple sinusoids.
tabSines2 srcTab nh scl [fmode]
Csound docs: http://www.csounds.com/manual/html/GEN3.html
Wavelets
waveletTab :: Tab -> Int -> Tab Source #
"wave" — Generates a compactly supported wavelet function.
waveletTab srcTab seq
Csound docs: http://www.csounds.com/manual/html/GENwave.html
rescaleWaveletTab :: Tab -> Int -> Tab Source #
"wave" — Generates a compactly supported wavelet function. The result table is rescaled.
waveletTab srcTab seq
Csound docs: http://www.csounds.com/manual/html/GENwave.html
Special cases
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.
pwTab :: Double -> Tab Source #
Pulse-width wave formed with linear segments. Duty cycle rages from 0 to 1. 0.5 is a square wave.
tanhTab :: (Double, Double) -> Tab Source #
Tab with tanh from the given interval.
tanhTab (start, end)
rescaleTanhTab :: (Double, Double) -> Tab Source #
Tab with tanh from the given interval. The table is rescaled.
rescaleTanhTab (start, end)
expTab :: (Double, Double) -> Tab Source #
Tab with exponential from the given interval.
expTab (start, end)
rescaleExpTab :: (Double, Double) -> Tab Source #
Tab with exponential from the given interval. The table is rescaled.
rescaleExpTab (start, end)
soneTab :: (Double, Double) -> Double -> Tab Source #
Tab with sone from the given interval.
soneTab (start, end) equalpoint
- start, end -- first and last value to be stored. The points stored are uniformly spaced between these to the table size.
- equalpoint -- the point on the curve when the input and output values are equal.
rescaleSoneTab :: (Double, Double) -> Double -> Tab Source #
Tab with sone from the given interval.
soneTab (start, end) equalpoint
- start, end -- first and last value to be stored. The points stored are uniformly spaced between these to the table size.
- equalpoint -- the point on the curve when the input and output values are equal.
fareyTab :: Int -> Int -> Tab Source #
"farey" — Fills a table with the Farey Sequence Fn of the integer n.
see details in Csound doc: http://www.csounds.com/manual/html/GENfarey.html
Notice that the arguments are reversed (in the haskell mindset)
fareyTab mode num
num -- the integer n for generating Farey Sequence Fn
mode -- integer to trigger a specific output to be written into the table:
- 0 -- outputs floating point numbers representing the elements of Fn.
- 1 -- outputs delta values of successive elements of Fn, useful for generating note durations for example.
- 2 -- outputs only the denominators of the integer ratios, useful for indexing other tables or instruments for example.
- 3 -- same as mode 2 but with normalised output.
- 4 -- same as mode 0 but with 1 added to each number, useful for generating tables for tuning opcodes, for example cps2pch.
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
tabseg :: [(Tab, PartialStrength, Double)] -> Tab Source #
tabseg -- Writes composite waveforms made up of pre-existing waveforms.
tabseg [(tab, amplitude, duration)]
Csound GEN18: http://www.csounds.com/manual/html/GEN18.html
Butnotice the difference with Csound we specify start and finish of writing but here we only specify the relative length of segments. Segments are arranged so that the start f next segment comes right after the end of the prev segment.
bpLins :: [Double] -> Tab Source #
Linear segments in breakpoint fashion:
bpLins [x1, y1, x2, y2, ..., xN, yN]
csound docs: http://www.csounds.com/manual/html/GEN27.html
All x1, x2, .. should belong to the interval [0, 1]. The actual values are rescaled to fit the table size.
bpExps :: [Double] -> Tab Source #
Exponential segments in breakpoint fashion:
bpExps [x1, y1, x2, y2, ..., xN, yN]
csound docs: http://www.csounds.com/manual/html/GEN25.html
All x1, x2, .. should belong to the interval [0, 1]. The actual values are rescaled to fit the table size.
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]
.
Random values
Distributions
cauchyDist :: Tab Source #
Cauchy (positive and negative numbers)
pcauchyDist :: Tab Source #
Positive Cauchy (positive numbers only)
betaDist :: Double -> Double -> Tab Source #
Beta (positive numbers only)
betaDist alpha beta
alpha
-- alpha value. If kalpha is smaller than one, smaller values favor values near 0.beta
-- beta value. If kbeta is smaller than one, smaller values favor values near krange.
weibullDist :: Double -> Tab Source #
Weibull (positive numbers only)
- tau -- if greater than one, numbers near ksigma are favored. If smaller than one, small values are favored. If t equals 1, the distribution is exponential. Outputs only positive numbers.
poissonDist :: Tab Source #
Poisson (positive numbers only)
tabDist :: Tab -> Tab Source #
Generates a random distribution using a distribution histogram (GEN40).
Csound docs: http://www.csounds.com/manual/html/GEN40.html
Distributions with levels
biexpDist' :: Double -> Tab Source #
gaussDist' :: Double -> Tab Source #
cauchyDist' :: Double -> Tab Source #
pcauchyDist' :: Double -> Tab Source #
poissonDist' :: Double -> Tab Source #
Rand values and ranges
randDist :: [Double] -> Tab Source #
randDist — Generates a random list of numerical pairs (GEN41).
randDist [value1, prob1, value2, prob2, value3, prob3 ... valueN, probN]
The first number of each pair is a value, and the second is the probability of that value to be chosen by a random algorithm. Even if any number can be assigned to the probability element of each pair, it is suggested to give it a percent value, in order to make it clearer for the user.
This subroutine is designed to be used together with duserrnd and urd opcodes (see duserrnd for more information).
rangeDist :: [Double] -> Tab Source #
rangeDist — Generates a random distribution of discrete ranges of values (GEN42).
The first number of each group is a the minimum value of the range, the second is the maximum value and the third is the probability of that an element belonging to that range of values can be chosen by a random algorithm. Probabilities for a range should be a fraction of 1, and the sum of the probabilities for all the ranges should total 1.0.
This subroutine is designed to be used together with duserrnd and urd opcodes (see duserrnd for more information). Since both duserrnd and urd do not use any interpolation, it is suggested to give a size reasonably big.
Windows
winHamming :: Tab Source #
The Hamming window. The peak equals to 1.
winHanning :: Tab Source #
The Hanning window. The peak equals to 1.
winBartlett :: Tab Source #
The Bartlett window. The peak equals to 1.
winBlackman :: Tab Source #
The Blackman window. The peak equals to 1.
winGauss :: Double -> Tab Source #
This creates a function that contains a Gaussian window with a maximum value of 1. The extra argument specifies how broad the window is, as the standard deviation of the curve; in this example the s.d. is 2. The default value is 1.
winGauss 2
winKaiser :: Double -> Tab Source #
This creates a function that contains a Kaiser window with a maximum value of 1. The extra argument specifies how "open" the window is, for example a value of 0 results in a rectangular window and a value of 10 in a Hamming like window.
winKaiser openness
winRectangle :: Tab Source #
The Rectangle window. The peak equals to 1.
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
data PadsynthSpec Source #
Padsynth parameters.
see for details: http://csound.github.io/docs/manual/GENpadsynth.html
Instances
Show PadsynthSpec Source # | |
Defined in Csound.Tab showsPrec :: Int -> PadsynthSpec -> ShowS # show :: PadsynthSpec -> String # showList :: [PadsynthSpec] -> ShowS # | |
Eq PadsynthSpec Source # | |
Defined in Csound.Tab (==) :: PadsynthSpec -> PadsynthSpec -> Bool # (/=) :: PadsynthSpec -> PadsynthSpec -> Bool # |
data PadsynthShape Source #
Instances
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.
Harmonics
tabHarmonics :: Tab -> Double -> Double -> Maybe Double -> Maybe Double -> Tab Source #
Generates harmonic partials by analyzing an existing table.
tabHarmonics src minh maxh [ref_sr] [interp]
- src -- source ftable. It should be primitive ie constructed not with "ftgen" family of opcodes.
- minh -- lowest harmonic number
- maxh -- maxh -- highest harmonic number
- ref_sr (optional) -- maxh is scaled by (sr / ref_sr). The default value of ref_sr is sr. If ref_sr is zero or negative, it is now ignored.
- interp (optional) -- if non-zero, allows changing the amplitude of the lowest and highest harmonic partial depending on the fractional part of minh and maxh. For example, if maxh is 11.3 then the 12th harmonic partial is added with 0.3 amplitude. This parameter is zero by default.
GEN30 for Csound: http://www.csounds.com/manual/html/GEN30.html
Normalize table
normTab :: NormTabSpec -> Tab -> Tab Source #
Normalizing table
Csound GEN04: http://www.csounds.com/manual/html/GEN04.html
scaleTab :: (Double, Double) -> Tab -> Tab Source #
Creates a new table wich contains all values from the source table rescaled to the given interval.
scaleTab (minValue, maxValue) sourceTab
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).
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 #
idPadsynth :: Text #
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
Container list of tables
Instances
Val TabList | |
Arg TabList | |
Defined in Csound.Typed.Types.Tuple | |
Tuple TabList | |
Defined in Csound.Typed.Types.Tuple | |
Default TabList | |
Defined in Csound.Typed.Types.Prim |
fromTabList :: TabList -> Sig -> Tab #
fromTabListD :: TabList -> D -> Tab #
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
random generators from tables
cuserrnd :: SigOrD a => a -> a -> Tab -> SE a Source #
cuserrnd — Continuous USER-defined-distribution RaNDom generator.
Continuous USER-defined-distribution RaNDom generator.
aout cuserrnd kmin, kmax, ktableNum iout cuserrnd imin, imax, itableNum kout cuserrnd kmin, kmax, ktableNum
csound doc: http://www.csounds.com/manual/html/cuserrnd.html
the tab should be done with tabDist, randDist or rangeDist
duserrnd :: SigOrD a => Tab -> SE a Source #
duserrnd — Discrete USER-defined-distribution RaNDom generator.
Discrete USER-defined-distribution RaNDom generator.
aout duserrnd ktableNum iout duserrnd itableNum kout duserrnd ktableNum
csound doc: http://www.csounds.com/manual/html/duserrnd.html
the tab should be done with tabDist, randDist or rangeDist
Appendix (original GEN identifiers lookup)
We can find the CE name of the GEN routine by it's integer id.
- GEN01 — wavs, wavLeft, wavRight -- Transfers data from a soundfile into a function table.
- GEN02 — doubles -- Transfers data from immediate pfields into a function table.
- GEN03 — polys -- Generates a stored function table by evaluating a polynomial.
- GEN04 — normTab -- Generates a normalizing function.
- GEN05 — exps -- Constructs functions from segments of exponential curves.
- GEN06 — cubes -- Generates a function comprised of segments of cubic polynomials.
- GEN07 — lins -- Constructs functions from segments of straight lines.
- GEN08 — splines -- Generate a piecewise cubic spline curve.
- GEN09 — sines2, sines3 -- Generate composite waveforms made up of weighted sums of simple sinusoids.
- GEN10 — sines -- Generate composite waveforms made up of weighted sums of simple sinusoids.
- GEN11 — buzzes -- Generates an additive set of cosine partials.
- GEN12 — bessels -- Generates the log of a modified Bessel function of the second kind.
- GEN13 — chebs1 -- Stores a polynomial whose coefficients derive from the Chebyshev polynomials of the first kind.
- GEN14 — chebs2 -- Stores a polynomial whose coefficients derive from Chebyshevs of the second kind.
- GEN15 — (not implemented yet) -- Creates two tables of stored polynomial functions.
- GEN16 — startEnds -- Creates a table from a starting value to an ending value.
- GEN17 — consts -- Creates a step function from given x-y pairs.
- GEN18 — tabseg -- Writes composite waveforms made up of pre-existing waveforms.
- GEN19 — sines4 -- Generate composite waveforms made up of weighted sums of simple sinusoids.
- GEN20 — wins -- Generates functions of different windows.
- GEN21 — dist, uniDist, linDist, triDist, expDist, biexpDist, gaussDist, cauchyDist, pcauchyDist, betaDist, weibullDist, poissonDist -- Generates tables of different random distributions.
- GEN23 — readNumFile -- Reads numeric values from a text file.
- GEN24 — readNumTab -- Reads numeric values from another allocated function-table and rescales them.
- GEN25 — bpExps -- Construct functions from segments of exponential curves in breakpoint fashion.
- GEN27 — bpLins -- Construct functions from segments of straight lines in breakpoint fashion.
- GEN28 — readTrajectoryFile -- Reads a text file which contains a time-tagged trajectory.
- GEN30 — tabHarmonics -- Generates harmonic partials by analyzing an existing table.
- GEN31 — mixOnTab -- Mixes any waveform specified in an existing table.
- GEN32 — mixTabs -- Mixes any waveform, resampled with either FFT or linear interpolation.
- GEN33 — mixSines1 -- Generate composite waveforms by mixing simple sinusoids.
- GEN34 — mixSines2 -- Generate composite waveforms by mixing simple sinusoids.
- GEN40 — tabDist -- Generates a random distribution using a distribution histogram.
- GEN41 — randDist -- Generates a random list of numerical pairs.
- GEN42 — rangeDist Generates a random distribution of discrete ranges of values.
- GEN43 — readPvocex -- Loads a PVOCEX file containing a PV analysis.
- GEN49 — mp3s -- Transfers data from an MP3 soundfile into a function table.
- GEN51 — (see module Csound.Tuning) This subroutine fills a table with a fully customized micro-tuning scale, in the manner of Csound opcodes cpstun, cpstuni and cpstmid.
- GEN52 — readMultichannel -- Creates an interleaved multichannel table from the specified source tables, in the format expected by the ftconv opcode.
- GENtanh — tanhTab, rescaleTanhTab Generate a table with values on the tanh function.
- GENexp — expTab, rescaleExpTab Generate a table with values on the exp function.
- GENsone — soneTab Generate a table with values of the sone function.
- GENquadbezier — (not implemented yet) Generate a table with values from a quadratic Bézier function.
- GENfarey — fareyTab -- Fills a table with the Farey Sequence Fn of the integer n.
- GENwave — waveletTab -- Generates a compactly supported wavelet function.
- GENpadsynth — pdsynth, bwSines Generate a sample table using the padsynth algorithm.