Sample Solution for Assignment 2 > module Assignment2 where > import Haskore.Interface.CSound.Orchestra as Orchestra > import Haskore.Interface.CSound.Score as Score > import Haskore.Interface.CSound.Generator > (compSine1, compSine2, cubicSpline, lineSeg1) > import Haskore.Interface.CSound.Render (playCS) > import qualified Haskore.Performance as Performance > import qualified Haskore.Performance.Context as Context > import qualified Haskore.Performance.Player as Player > import Haskore.Music as Music > import Haskore.Melody as Melody > import qualified Haskore.Music.Rhythmic as RhyMusic Problem 1 (a) Suppose that we create a wavetable containing 200 elements of a pure sine wave. Using a sampling rate of 44.1kHz, at what frequency will aliasing occur? (b) If we are only interested in reproducing audible sounds, how large should the wavetable be to ensure that aliasing does not occur? (c) In practice, do you think that there is any advantage to using a wavetable either larger or smaller than the answer to (b)? Answer: (a) aliasing will occur when frequency is greater than or equal to half of the sampling rate 44.1kHz. (b) table size normally has nothing to do with aliasing, but it has to be greater than 2 in order to generate a wave. (c) greater table size reduces the error between the shape of output signal and the one in wave table. Problem 2 (a) Create a signal using amplitude modulation, in which the carrier frequency is the note pitch p, and the modulating frequency varies between 0 and p/2. But in addition, you should modulate the modulating frequency (!) with some other fixed frequency of your choice. (b) Now do the same thing, but use frequency modulation. Answer: (a) > score2 = pureTone : scoreFromMelody instr1 > (Music.line [c 2 bn (TutAttr 1.5 [])]) > hw2a :: Mono > hw2a = let pch = pchToHz notePit > amp = dbToAmp noteVel > fixSig = oscPure 1.0 1000 > modSig = Orchestra.line CR 0 noteDur (pch / 2) > modSig' = oscPure ((fixSig + 1) / 2) modSig > carrier = oscPure ((modSig' + 1) / 2 * amp) pch > in Mono carrier > > hws2a = mkTut score2 [hw2a] (b) > hw2b :: Mono > hw2b = let pch = pchToHz notePit > amp = dbToAmp noteVel > fixSig = oscPure 1.0 1000 > modSig = Orchestra.line CR 0 noteDur (pch / 2) > modSig' = oscPure amp ((fixSig + modSig) / 2) > carrier = oscPure amp ((pch + modSig') / 2) > in Mono carrier > > hws2b = mkTut score2 [hw2b] Problem 3 Create a wavetable that implements a "trapezoidal" envelope -- it rises linearly from zero to some value, then sustains that value, then drops linearly back to zero. The width of the base of the trapezoid should be the note duration. Use this envelope to control the signal in (2) above. Answer: we first define the trapezoidal envelope. > trapenv :: SigExp > trapenv = lineSeg CR 0 (0.3*noteDur) 1 [(0.3*noteDur, 1), (0.4* noteDur, 0)] (a) the envelope is used here to control the final amplitude of the signal in 2(a). > hw3a :: Mono > hw3a = let pch = pchToHz notePit > amp = dbToAmp noteVel > fixSig = oscPure 1.0 1000 > modSig = Orchestra.line CR 0 noteDur (pch / 2) > modSig' = oscPure ((fixSig + 1) / 2) modSig > carrier = oscPure (trapenv * (modSig' + 1) * amp / 2) pch > in Mono carrier > > hws3a = mkTut score2 [hw3a] (b) the envelope is used here to control the final amplitude of the signal in 2(b). > hw3b :: Mono > hw3b = let pch = pchToHz notePit > amp = dbToAmp noteVel > fixSig = oscPure 1.0 1000 > modSig = Orchestra.line CR 0 noteDur (pch / 2) > modSig' = oscPure amp ((fixSig + modSig) / 2) > carrier = oscPure (trapenv * amp) ((pch + modSig') / 2) > in Mono carrier > > hws3b = mkTut score2 [hw3b] Problem 4 (a) Create tremolo and vibrato effects by taking two p-fields, one for each effect, which specify the depth of the effect. The tremolo depth should be a fraction of the note amplitude (velocity), and vibrato effect should be a fraction of the note pitch. For example, a note "c 4 qn [a, t, v]" could be a quarter-note middle C with amplitude a, tremolo t, and vibrato v. If t is .1 then the note's amplitude should vary by 10% of a, and if v is .05 then the note's pitch should vary by 5% of the frequency corresponding to middle C. You can use a fixed rate for both the tremolo and vibrato. (b) use the envelope in (3) above to control these effects over the duration of a note -- i.e. the effect is zero at the beginning, then ramps up to the depth specified by the p-field, then drops back to zero. Answer: (a) We first create a custom tune to make use of the two-fields. > tune4 = Music.line [c 2 bn (TutAttr 1.5 [0.10, 0.10])] The variation is controlled by a square wave at 100HZ. > score4 = pureTone : squareT : scoreFromMelody instr1 tune4 > > hw4a :: SigExp -> SigExp -> Mono > hw4a tremolo vibrato = > let pch = pchToHz notePit > amp = dbToAmp noteVel > fixSig = osc AR squareTable 1.0 100 > pch' = pch * (1 + fixSig * vibrato) > amp' = amp * (1 + fixSig * tremolo) > carrier = oscPure amp' pch' > in Mono carrier > > hws4a = mkTut score4 [hw4a p6 p7] (b) The variation is also controlled by a trapozoidal envelope. > hw4b :: SigExp -> SigExp -> Mono > hw4b tremolo vibrato = > let pch = pchToHz notePit > amp = dbToAmp noteVel > fixSig = osc AR squareTable 1.0 100 > pch' = pch * (1 + trapenv * fixSig * vibrato) > amp' = amp * (1 + trapenv * fixSig * tremolo) > carrier = oscPure amp' pch' > in Mono carrier > > hws4b = mkTut score4 [hw4b p6 p7] Problem 5 Write a HasSound program that uses the first p-field in a note statement to specify the number of odd harmonics added to the fundamental, which should be a pure sine wave. (This is harder than it sounds... in particular, you may have to limit the total number of harmonics.) Answer: Because it is not possible to convert SigExp to number, it isn't possible to generate a list of the size of the p-field value. Alternatively, we'll impose a limit to the max number of odd harmonics, and only "select" a number of those within human hearing range. The max number of harmonics within human hearing range is 20000Hz / 20Hz = 1000, hence the max number of odd harmonics is 1000 / 2 = 500. > tune5 = let attr t = TutAttr 1.4 [t] > in c 1 hn (attr 5) +:+ > e 1 hn (attr 7) +:+ > g 1 hn (attr 12) +:+ > c 2 hn (attr 5) +:+ > a 1 hn (attr 4) +:+ > c 2 qn (attr 5) +:+ > a 1 qn (attr 12) +:+ > g 1 dhn (attr 21)+:+ qnr > > score5 = pureTone: scoreFromMelody instr1 tune5 > > hw5 :: SigExp -> Mono > hw5 pa = > let pch = pchToHz notePit > amp = dbToAmp noteVel > null = oscPure 0 0 > nums = map constInt [1..500] > pchs = map (\n -> ifthen (n <=* pa) ((2 * n - 1) * pch) 0) nums > sigs = map (\p -> ifthen ((p <* 20000) &&* (p >* 0)) > (oscPure (amp / pa) p) null) pchs > signal = sum sigs > in Mono signal > > hws5 = mkTut score5 [hw5 p6] End of Assignment 5. All the helper functions go below > pureToneTN :: Score.Table > pureToneTN = 1 > pureToneTable :: SigExp > pureToneTable = tableNumber pureToneTN > pureTone :: Score.Statement > pureTone = Score.simpleSine pureToneTN > squareTN :: Score.Table > squareTN = 2 > squareTable :: SigExp > squareTable = tableNumber squareTN > squareT :: Score.Statement > squareT = square squareTN > oscPure :: SigExp -> SigExp -> SigExp > oscPure = osc AR pureToneTable > type InstrNum = Int > > type Instrument = ([Float], InstrNum) > > instr1 :: InstrNum > instr1 = 1 > hdr :: Orchestra.Header > hdr = (44100, 4410) > type TutMelody = Melody.T TutAttr > > data TutAttr = TutAttr {attrVelocity :: Rational, > attrParameters :: [Float]} > > type Drum = () > > musicFromMelody :: InstrNum -> TutMelody -> RhyMusic.T Drum Instrument > musicFromMelody instrId = Music.mapNote ( > \(Melody.Note (TutAttr vel params) p) -> > RhyMusic.Note vel (RhyMusic.Tone (params, instrId) p)) > scoreFromMelody :: InstrNum -> TutMelody -> Score.T > scoreFromMelody i m = > (Score.fromRhyPerformanceMap > (error "no drum map defined") id) $ > (Performance.fromMusic Player.fancyMap > (Context.setDur 1 Context.deflt)) $ musicFromMelody i m > type Example out = (Orchestra.T out, Score.T) > 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) > test :: Output out => Example out -> IO () > test = uncurry playCS