HasSound - The Haskell CSound InterfaceCSound is a software synthesizer that allows its user to create a virtually unlimited number of sounds and instruments. It is extremely portable because it is written entirely in C. Its strength lies mainly in the fact that all computations are performed in software, so it is not reliant on sophisticated musical hardware. The output of a CSound computation is a file representing the signal which can be played by an independent application, so there is no hard upper limit on computation time. This is important because many sophisticated signals take much longer to compute than to play. The purpose is to create an interface between Haskore and CSound in order to give the Haskore user access to all the powerful features of a software sound synthesizer. CSound takes as input two plain text files: a score (.sco) file and an orchestra (.orc) file. The score file is similar to a Midi file, and the orchestra file defines one or more instruments that are referenced from the score file (the orchestra file can thus be thought of as the software equivalent of Midi hardware). The CSound program takes these two files as input, and produces a sound file as output, usually in .wav format. Sound files are generally much larger than Midi files, since they describe the actual sound to be generated, represented as a sequence of values (typically 44,100 of them for each second of music), which are converted directly into voltages that drive the audio speakers. Sound files can be played by any standard media player found on conventional PC's. HasSound is a set of Haskell modules to interface between Haskore and CSound. It consists of the module Haskore.Interface.CSound.Score, Haskore.Interface.CSound.Orchestra, and a few others.
Function TableA function table is used by instruments to produce audio signals. For example, sequencing through a table containing a perfect sine wave will produce a very pure tone, while a table containing an elaborate polynomial will produce a complex sound with many overtones. The tables can also be used to produce control signals that modify other signals. Perhaps the simplest example of this is a tremolo or vibrato effect, but more complex sound effects, and FM (frequency modulation) synthesis in general, is possible. Built-in functions
For convenience, here are some common function tables, which take as
argument the identifier integer ( simpleSine, square, sawtooth, triangle, whiteNoise :: Table -> Statement
compSine :: Table -> [PStrength] -> Statement Reference function table in Orchestra
The table number is used in the Ochestra file to refer to the same table
created in the Score file. (in module tableNumber :: Table -> SigExp Table constructor
To manually create a function table, one has to use generator functions. The
constructor for Table :: Table -> CreatTime -> TableSize -> Normalize -> Generator.T -> Statement type Table = Int type CreatTime = Time type TableSize = Int type Normalize = Bool type Time = Float
By default, the above helper functions generates function table of size 1024 except for
Each function table must have a unique integer ID ( Generator
Tables are simply arrays of floating point values. The values stored
in the table are calculated by one of CSound's predefined generating
routines, represented by the following type (in module data T = Routine Number [Parameter] | SoundFile SFName SkipTime ChanNum deriving Show type SFName = String type SkipTime = Time type ChanNum = Float type Number = Int type Parameter = Float
Knowing which of CSound's generating routines to use and with what arguments can be a daunting task. The newest version of CSound provides 23 different generating routines, and each one of them assigns special meanings to its arguments. To avoid having to reference routines using integer ids, the following functions are defined for the most often-used generating routines. A brief discussion of each routine is also included. For a full description of these and other routines, refer to the CSound manual or consult the following : CSound GENS page. The user familiar with CSound is free to write helper functions like the ones below to capture other generating routines. GEN01 (soundFile)
Transfers data from a soundfile into a function
table. Recall that the size of the function table in CSound must be a
power of two. If the soundfile is larger than the table size, reading
stops when the table is full; if it is smaller, then the table is
padded with zeros. One exception is allowed: if the file is of type
AIFF and the table size is set to zero, the size of the function table
is allocated dynamically as the number of points in the soundfile.
The table is then unusable by normal oscillators, but can be used by a
special soundFile :: SFName -> SkipTime -> ChanNum -> Generator.T soundFile = SoundFile GEN02 (tableValues)Transfers data from its argument fields directly into the function table. We represent its functionality as follows: tableValues :: [Parameter] -> Generator.T tableValues gas = Routine 2 gas GEN03 (polynomial)Fills the table by evaluating a polynomial over a specified interval and with given coefficients. For example, calling GEN03 with an interval of (-1,1) and coefficients 5, 4, 3, 2, 0, 1 will generate values of the function 5+4x+3x^2+2x^3+x^5 over the interval -1 to 1. The number of values generated is equal to the size of the table. Let's express this by the following function: polynomial :: Interval -> Coefficients -> Generator.T polynomial (x1,x2) cfs = Routine 3 (x1:x2:cfs) type Interval = (Float, Float) type Coefficients = [Float] GEN05 (exponential1)
Constructs a table from segments of exponential
curves. The first argument is the starting point. The meaning of the
subsequent arguments alternates between the length of a segment in
samples, and the endpoint of the segment. The endpoint of one segment
is the starting point of the next. The sum of all the segment lengths
normally equals the size of the table: if it is less the table is
padded with zeros, if it is more, only the first exponential1 :: StartPt -> [(SegLength, EndPt)] -> Generator.T exponential1 sp xs = Routine 5 (sp : flattenTuples2 xs) type StartPt = Float type SegLength = Float type EndPt = Float GEN25 (exponential2)Similar to GEN05 in that it produces segments of exponential curves, but instead of representing the lengths of segments and their endpoints, its arguments represent (x,y) coordinates in the table, and the subroutine produces curves between successive locations. The x-coordinates must be in increasing order. exponential2 :: [Point] -> Generator.T exponential2 pts = Routine 25 (flattenTuples2 pts) type Point = (Float,Float) GEN06 (cubic)Generates a table from segments of cubic polynomial functions, spanning three points at a time. We define a function cubic with two arguments: a starting position and a list of segment length (in number of samples) and segment endpoint pairs. The endpoint of one segment is the starting point of the next. The meaning of the segment endpoint alternates between a local minimum/maximum and point of inflexion. Whether a point is a maximum or a minimum is determined by its relation to the next point of inflexion. Also note that for two successive minima or maxima, the inflexion points will be jagged, whereas for alternating maxima and minima, they will be smooth. The slope of the two segments is independent at the point of inflection and will likely vary. The starting point is a local minimum or maximum (if the following point is greater than the starting point, then the starting point is a minimum, otherwise it is a maximum). The first pair of numbers will in essence indicate the position of the first inflexion point in (x,y) coordinates. The folowing pair will determine the next local minimum/maximum, followed by the second point of inflexion, etc. cubic :: StartPt -> [(SegLength, EndPt)] -> Generator.T cubic sp pts = Routine 6 (sp : flattenTuples2 pts) GEN07 (lineSeg1)Similar to GEN05, except that it generates straight lines instead of exponential curve segments. All other issues discussed about GEN05 also apply to GEN07. We represent it as: lineSeg1 :: StartPt -> [(SegLength, EndPt)] -> Generator.T lineSeg1 sp pts = Routine 7 (sp : flattenTuples2 pts) GEN27 (lineSeg2)As with GEN05 and GEN25, produces straight line segments between points whose locations are given as (x,y) coordinates, rather than a list of segment length, endpoint pairs. lineSeg2 :: [Point] -> Generator.T lineSeg2 pts = Routine 27 (flattenTuples2 pts) GEN08 (cubicSpline)Produces a smooth piecewise cubic spline curve through the specified points. Neighboring segments have the same slope at the common points, and it is that of a parabola through that point and its two neighbors. The slope is zero at the ends. cubicSpline :: StartPt -> [(SegLength, EndPt)] -> Generator.T cubicSpline sp pts = Routine 8 (sp : flattenTuples2 pts) GEN10 (compSine1)Produces a composite sinusoid. It takes a list of relative strengths of harmonic partials 1, 2, 3, etc. Partials not required should be given strength of zero. compSine1 :: [PStrength] -> Generator.T compSine1 pss = Routine 10 pss type PStrength = Float GEN09 (compSine2)Also produces a composite sinusoid, but requires three arguments to specify each contributing partial. The arguments specify the partial number, which doesn't have to be an integer (i.e. inharmonic partials are allowed), the relative partial strength, and the initial phase offset of each partial, expressed in degrees. compSine2 :: [(PNum, PStrength, PhaseOffset)] -> Generator.T compSine2 args = Routine 9 (flattenTuples3 args) type PNum = Float type PhaseOffset = Float GEN19 (compSine3)Provides all of the functionality of GEN09, but in addition a DC offset must be specified for each partial. The DC offset is a vertical displacement, so that a value of 2 will lift a 2-strength partial from range [-2,2] to range [0,4] before further scaling. compSine3 :: [(PNum, PStrength, PhaseOffset, DCOffset)] -> Generator.T compSine3 args = Routine 19 (flattenTuples4 args) type DCOffset = Float GEN11 (cosineHarms)Produces an additive set of harmonic cosine partials, similar to GEN10. We will represent it by a function that takes three arguments: the number of harmonics present, the lowest harmonic present, and a multiplier in an exponential series of harmonics amplitudes (if the x-th harmonic has strength coefficient of A, then the (x+n) th harmonic will have a strength of A*(r^n), where r is the multiplier). cosineHarms :: NHarms -> LowestHarm -> Mult -> Generator.T cosineHarms n l m = Routine 11 [fromIntegral n, fromIntegral l, m] type NHarms = Int type LowestHarm = Int type Mult = Float GEN21 (randomTable)Produces tables having selected random distributions. randomTable :: RandDist -> Generator.T randomTable rd = Routine 21 [fromIntegral (fromEnum rd + 1)] data RandDist = Uniform | Linear | Triangular | Expon | BiExpon | Gaussian | Cauchy | PosCauchy deriving (Eq, Ord, Enum, Show) Orchestra and InstrumentThe orchestra file consists of two parts: a header, and one or more instrument blocks. The header sets global parameters controlling sampling rate and control rate. The instrument blocks define instruments, each identified by a unique integer ID, and containing statements modifying or generating various audio signals. Each note statement in a score file passes all its arguments---including the p-fields---to its corresponding instrument in the orchestra file. While some properties vary from note to note, and should therefore be designed as p-fields, many can be defined within the instrument; the choice is up to the user. Orchestra Type
The orchestra file is represented as (in module data Output a => T a = Cons Header [InstrBlock a] deriving (Show, Eq) The orchestra header sets the audio rate, control rate, and number of output channels: type Header = (AudRate, CtrlRate) type AudRate = Int -- samples per second type CtrlRate = Int -- samples per second
Each instrument block contains four things: a unique identifying
integer; an expression giving the amount of extra time the instrument
should be granted, usually used for reverb; an type Reverb = SigExp type Instr = Int data InstrBlock a = InstrBlock {instrBlockInstr :: Instr, instrBlockReverb :: Reverb, instrBlockOutput :: a, instrBlockGlobals :: [(GlobalSig, SigExp)]} deriving (Show, Eq) Orchestra can be saved to a file save :: Output a => FilePath -> Orchestra.T a -> IO () type FilePath = String Output types (Mono, Stereo, Quad)
There are 3 kinds of data Mono = Mono SigExp deriving (Show, Eq) data Stereo = Stereo SigExp SigExp deriving (Show, Eq) data Quad = Quad SigExp SigExp SigExp SigExp deriving (Show, Eq) instance Output Mono where ... instance Output Stereo where ... instance Output Quad where ... Here is an example to construct Orchestra of Mono type o1 :: Orchestra.T Mono o1 = Cons hdr [ InstrBlock instr1 0 oe1 [] ] hdr :: Orchestra.Header hdr = (44100, 4410) instr1 :: Int instr1 = 1 oe1 :: Mono oe1 = let signal = osc AR pureToneTable (dbToAmp noteVel) (pchToHz notePit) in Mono signal pureToneTable :: SigExp pureToneTable = tableNumber 1 Signal Expressions
The data type
Table ReferenceThis refers to the function table created in the score file tableNumber :: Table -> SigExp Constants
The representation of numbers in constFloat :: Float -> SigExp constInt :: Int -> SigExp constEnum :: Enum a => a -> SigExp P-field Arguments
noteDur, notePit, noteVel :: SigExp noteDur = pField 3 notePit = pField 4 noteVel = pField 5 pField :: Int -> SigExp It is also useful to define the following standard names, which are identical to those used in CSound: p1,p2,p3,p4,p5,p6,p7,p8,p9 :: SigExp Logical and Conditional Statements
Comparison and boolean operators are lifted to the (<*), (<=*), (>*), (>=*), (==*), (/=*) :: SigExp -> SigExp -> Boolean (&&*), (||*) :: Boolean -> Boolean -> Boolean ifthen :: Boolean -> SigExp -> SigExp -> SigExp Arithmetic functions
(+), (-), (*), (/) :: SigExp -> SigExp -> SigExp negate, abs, signum :: SigExp -> SigExp fromInteger :: Integral a => a -> SigExp fromRational :: Rational -> SigExp exp, log, sqrt, sin, cos, tan, asin, acos, atan, sinh, cosh, tanh, asinh, acosh, atanh :: SigExp -> SigExp (**) :: SigExp -> SigExp -> SigExp pi :: SigExp And we can now write simple code like noteDur + sin p6 ** 2 :: SigExp Other Prefix'ssin, log, and sqrt aren't the only functions use Prefix as a constructor --- Prefix is used for all functions in CSound that take a single argument and are represented like normal mathematical functions. Most of these functions are, indeed, mathematical, such as the function converting a CSound pitch value to the number of cycles per second, or the function converting decibels to the corresponding amplitude. For convenience, we will define a few common operators here: prefixTerm :: String -> SigExp -> SigExp pchToHz, dbToAmp :: SigExp -> SigExp pchToHz = prefixTerm "cpspch" dbToAmp = prefixTerm "ampdb" Now, when we want to convert a pitch to its hertz value or a decibel level to the desired amplitude, we can simply say \code{pchToHz notePit} or \code{dbToAmp noteVel}. Signal Generation and Modification
The most sophisticated Most of these we have seen before. But what is the rate of output? Well, signals in CSound can be generated at three rates: the note rate (i.e., with, every note event), the control rate, and the audio rate (we discussed the latter two earlier). Many of the signal generating routines can produce signals at more than one rate, so the rate must be specified as an argument. The following simple data structure serves this purpose: data EvalRate = NR -- note rate | CR -- control rate | AR -- audio rate deriving (Show, Eq, Ord)
line, exponThe CSound statement line evalrate start duration finish, produces values along a straight line from start to finish. The values can be generated either at control or audio rate, and the line covers a period of time equal to duration seconds. We can translate this into CSound like so: line, expon :: EvalRate -> SigExp -> SigExp -> SigExp -> SigExp line rate start duration finish = ... expon rate start duration finish = ...
lineseg, expsegIf a more elaborate signal is required, one can use the CSound functions linseg or expseg. They both take 5 arguments, audio rate, the starting value (y0), the next point (duration or length x1, and value y1), and then a list of subsequent segment lengths and endpoints. lineSeg, exponSeg :: EvalRate -> SigExp -> SigExp -> SigExp -> [(SigExp, SigExp)] -> SigExp lineSeg rate start x1 y1 lst = ... exponSeg rate start x1 y1 lst = ... env - envelope
The Haskore code
env :: EvalRate -> SigExp -> SigExp -> SigExp -> SigExp -> SigExp -> SigExp -> SigExp -> SigExp -> SigExp env rate rshape sattn dattn steep dtime rtime durn sig = ... phasor - phase offset setting
phasor :: EvalRate -> SigExp -> SigExp -> SigExp phasor rate phase freq = ... tblLookup, tblLookupI - table lookup
data IndexMode = RawIndex | NormalIndex deriving (Show, Eq, Enum)
Both functions return values stored in the specified table at the given index.
The difference is that tblLookup, tblLookupI :: EvalRate -> IndexMode -> SigExp -> SigExp -> SigExp tblLookup rate mode table ix = ... tblLookupI rate mode table ix = ...
As mentioned, the output of oscil = let index = phasor AR (pchToHz notePit) 0.0 in tblLookupI AR NormalIndex table index
where osc, oscI - oscillators
Instead of the above design we could use one of the built-in CSound
oscillators. osc, oscI :: EvalRate -> SigExp -> SigExp -> SigExp -> SigExp osc rate table amp freq = ... oscI rate table amp freq = ... Now, the following statement is equivalent to \function{osc}, defined above: oscil' = oscI AR 1 (pchToHz notePit) table fmOsc, fmOscI - frequency modulation
It is often desirable to use the output of one oscillator to modulate
the frequency of another, a process known as frequency modulation.
Interestingly enough, these two functions are the first listed here that
work at audio rate only; thus, we do not have to pass the rate as an
argument to the helper function, because the rate is always
fmOsc, fmOscI :: SigExp -> SigExp -> SigExp -> SigExp -> SigExp -> SigExp -> SigExp fmOsc table modindex carfreq modfreq amp freq = ... fmOscI table modindex carfreq modfreq amp freq = ... sampOsc - Sample Oscillator
sampOsc :: SigExp -> SigExp -> SigExp -> SigExp sampOsc table amp freq = ... random, randomH, randomI - Random Number Generator
random :: EvalRate -> SigExp -> SigExp random rate amp = ... randomH, randomI :: EvalRate -> SigExp -> SigExp -> SigExp randomH rate quantRate amp = ... randomI rate quantRate amp = ... genBuzz - Buzz sound
The amplitude
coefficients of the harmonics are given by the exponential series genBuzz :: SigExp -> SigExp -> SigExp -> SigExp -> SigExp -> SigExp -> SigExp genBuzz table multiplier loharm numharms amp freq = ...
buzz :: SigExp -> SigExp -> SigExp -> SigExp -> SigExp buzz table numharms amp freq = ... pluck - Plucked String
There are six possible decay modes:
data PluckDecayMethod = PluckSimpleSmooth | PluckStretchSmooth SigExp | PluckSimpleDrum SigExp | PluckStretchDrum SigExp SigExp | PluckWeightedSmooth SigExp SigExp | PluckFilterSmooth And here is the Haskore code for the CSound pluck function: pluck :: SigExp -> SigExp -> PluckDecayMethod -> SigExp -> SigExp -> SigExp pluck table freq2 decayMethod amp freq = ... delay - Delay a Signal
In contrast to delay :: SigExp -> SigExp -> SigExp delay delayTime sig = ... vdelay :: SigExp -> SigExp -> SigExp -> SigExp vdelay maxDelay delayTime sig = ... reverb, Reverberation
Reverberation can be added to a signal using functions
comb, alpass :: SigExp -> SigExp -> SigExp -> SigExp comb looptime revtime sig = ... alpass looptime revtime sig = ... reverb :: SigExp -> SigExp -> SigExp reverb revtime sig = ... Recursive StatementsIn some cases, the user may want their instrument to have certain special effects --- such as an infinite echo, going back and forth but getting fainter and fainter. It would seem logical that the user would, in that case, write something like this: x = sig + delay (0.5 * x) 1.0
We offer a very simple solution: the rec :: (SigExp -> SigExp) -> SigExp In order to perform the infinite echo listed above, we would write this code: x = rec (\y -> sig + delay (0.5 * y) 1.0) Score File
The translation between
Velocity is instrument dependent and different velocities might result in different flavors of a sound. As a quick work-around we turn the velocity information into volume.
We can convert from a rhythmic Performance to a score type by the following two functions (in module fromRhyPerformance :: (RealFrac quant, Ord drum, Ord instr) => InstrMap.SoundTable drum -> InstrMap.SoundTable instr -> Performance.T quant (RhyMusic.Note drum instr) -> Score.T fromRhyPerformanceMap :: (RealFrac quant) => InstrMap.ToSound drum -> InstrMap.ToSound instr -> Performance.T quant (RhyMusic.Note drum instr) -> Score.T Scores can be saved to a file save :: FilePath -> Score.T -> IO () type FilePath = String Examples
First we define a function table containing just a sine wave. We
can do this using the pureToneTN :: Score.Table pureToneTN = 1 pureToneTable :: SigExp pureToneTable = tableNumber pureToneTN pureTone :: Score.Statement pureTone = Score.simpleSine pureToneTN
To create an Orchestra, we first create a simple instrument oscPure :: SigExp -> SigExp -> SigExp oscPure = osc AR pureToneTable oe1 :: Mono oe1 = let signal = oscPure (dbToAmp noteVel) (pchToHz notePit) in Mono signal
This instrument will simply oscillate through the function table
containing the sine wave at the appropriate frequency given by
We'll define our own type InstrNum = Int type Instrument = ([Float], InstrNum) instr1 = 1 instr2 = 2
Note that the o1 :: Orchestra.T Mono o1 = Cons hdr [ InstrBlock instr1 0 oe1 [] ] hdr :: Orchestra.Header hdr = (44100, 4410)
where We'll then create a simple tune to play with this instrument. But first of all we have to define our own melody type to cope with custom velocity and parameters. type TutMelody = Melody.T TutAttr data TutAttr = TutAttr {attrVelocity :: Rational, attrParameters :: [Float]} tune1 :: TutMelody tune1 = Music.line (map ($ TutAttr 1.4 []) [ c 1 hn, e 1 hn, g 1 hn, c 2 hn, a 1 hn, c 2 qn, a 1 qn, g 1 dhn ] ++ [qnr])
score1 :: Score.T score1 = pureTone : scoreFromMelody instr1 tune1 type Example out = (Orchestra.T out, Score.T) tut1 :: Example Mono tut1 = (o1, score1)
Or we can have a function to produce tut1 more conveniently by
taking a mkTut :: Output out => Score.T -> [out] -> Example out mkTut score oes = let o = Cons hdr (map (\(i, oe) -> InstrBlock i 0 oe []) (zip [1..] oes)) in (o, score)
so that tut1 = mkTut score1 [oe1] All tutorial examples can be played by function test :: Output out => Example out -> IO () test = uncurry playCS
If you listen to the tune, you will notice that it sounds very thin
and uninteresting. Most musical sounds are not pure. Instead they usually
contain a sine wave of dominant frequency, called a fundamental,
and a number of other sine waves called partials. Partials with
frequencies that are integer multiples of the fundamental are called
harmonics. In musical terms, the first harmonic lies an octave
above the fundamental, second harmonic a fifth above the first one, the
third harmonic lies a major third above the second harmonic etc. This is the
familiar overtone series. We can add harmonics to our sine wave
instrument easily using the twoHarmsTN :: Score.Table twoHarmsTN = 2 twoHarms :: Score.Statement twoHarms = Score.Table twoHarmsTN 0 8192 True (compSine1 [1.0, 0.66, 0.33]) We can again proceed to create complete score and orchestra just above: score2 = twoHarms : scoreFromMelody instr1 tune1 oe2 :: Mono oe2 = let signal = osc AR (tableNumber twoHarmsTN) (dbToAmp noteVel) (pchToHz notePit) in Mono signal tut2 = mkTut score2 [oe2] |