CsoundExpr.Tutorial.Orchestra
Contents
Description
Guide to instrument-making
- Prev : CsoundExpr.Tutorial.Composition
- Next : CsoundExpr.Tutorial.Limits
Instruments
Instruments are functions from some signal representation to signal.
Score is a Functor, so to play on instrument means to apply instrument
to Score of its notes. Instrument can be made with opcodes.
Translator derives p-fields from instrument structure. There are only
two explicit p-fields itime and idur (p2 and p3 in csound).
Signals / Types
Signals are represented with trees. Tree contains information about how signal was build.
There are four types for signals (CsoundExpr.Base.Types).
Arate is audio rate signal
Krate is control rate signal
Irate is init value
SignalOut is no output at all (it's produced by opcodes like out, outs, xtratim)
There are two classes to allow csound's polymorphism : X and K
Csound's S - signal is represented with String.
Ftable is represented with Irate.
There are two special types MultiOut
(for opcodes that may produce several outputs, see CsoundExpr.Base.MultiOut)
and SideEffect
(for opcodes that rely on number of appearances in csound code,
like unirand, see CsoundExpr.Base.SideEffect)
Opcodes
Naming conventions : Opcodes are named after csound's counterparts usually. Some opcodes in csound can produce signals of different rates by request (oscil, linseg). Those opcodes are labelled with suffix. Suffix defines output rate of signal (oscilA, oscilK). Some opcodes in csound have unfixed number of inputs due to setup parameters, almost all of them. Those opcodes have first argument that is list of setup parameters.
example
oscilA :: (X a, X b) => [Irate] -> a -> b -> Irate -> Arate oscilK :: (K a, K b) => [Irate] -> a -> b -> Irate -> Krate
Imperative style csound code
Most of csound opcodes can be used in functional way. You can plug them in one another, and make expressions, but some of them behave like procedures and rely on order of execution in instrument. Module CsoundExpr.Base.Imperative provides functions to write imperative csound code.
outList - to sequence procedures
'(<=>)' - Assignment
ar, kr, ir, gar, gkr, gir - named values, to produce signal with specified name and rate.
Functional style :
exmpInstr :: Irate -> SignalOut exmpInstr pch = out $ oscilA [] (num 1000) (cpspch pch) $ gen10 4096 [1]
Imperative style :
exmpImper :: Irate -> SignalOut
exmpImper pch = outList [
ir "amp" <=> num 1000,
ir "cps" <=> cpspch pch,
ir "ft" <=> gen10 4096 [1],
ar "sig" <=> oscilA [] (ir "amp") (ir "cps") (ir "ft"),
out (ar "sig")]
Arithmetic
You can use polymorphic operations to do some arihmetic on signals
from CsoundExpr.Base.Arithmetic. And Signal is Num. Eq is undefined though.
Preview
To see what will come out of an expression you can print it. Signal is Show.
exmpPreview :: IO ()Source
User Defined opcodes
You can add your own opcodes to library, see CsoundExpr.Base.UserDefined
MIDI
There are two ways to tell csd to include instrument in csound file.
Instrument can be a part of Score or it can be midi instrument, then it should
be mentioned in massign or pgmassign function. If you want to play midi-instr
for some time t, you can tell it to csd function by invoking csd with
in place of rest tEventList value.
flags = "-odac -iadc -+rtmidi=virtual -M0" header = [massign [] 1 instrMidi] instrMidi :: SignalOut instrMidi = out $ oscilA [] (num 1000) cpsmidi $ gen10 4096 [1] -- play instrMidi for 2 minutes exmpMidi = print $ csd flags header (rest 120)
Example
Song, see src