DIRECTORY Basics USING [UnsafeBlock, LongDiv, LongMult, LowHalf], FS USING [Error], PlayOps USING [PlayTuneProc, BeepProc], Process USING [MsecToTicks, Ticks, TicksToMsec], Rope USING [ROPE, ToRefText], RopeFile USING [Create], BasicTime USING [MicrosecondsToPulses, PulsesToMicroseconds] ; PlayUtils: PROGRAM IMPORTS Basics, FS, Process, Rope, RopeFile, BasicTime EXPORTS PlayOps = { Note: TYPE = MACHINE DEPENDENT RECORD [ SELECT OVERLAID * FROM initial => [ twelfths, octave, duration: CARDINAL, notify: BOOL_FALSE, pause: BOOL_FALSE, x:X_0], intermediate => [ cps: CARDINAL, usecs: Microseconds, ni: BOOL_FALSE, pi: BOOL_FALSE, y:X_0], final => [ freq, pulses: CARDINAL, ticks: Process.Ticks, nf: BOOL_FALSE, pf: BOOL_FALSE, z:X_0], ENDCASE ]; X: TYPE = [0..37777B]; NoteArray: TYPE = REF NoteArrayObject; NoteArrayObject: TYPE = RECORD [SEQUENCE size: CARDINAL OF Note]; Microseconds: TYPE = LONG CARDINAL; initFreq: CARDINAL = LAST[CARDINAL]; lastFreq: CARDINAL _ initFreq; notifyNext: BOOL_FALSE; pauseNext: BOOL_FALSE; PlayString: PUBLIC PlayOps.PlayTuneProc = { ENABLE ABORTED => CONTINUE; rT: REF TEXT; IF music # NIL THEN { IF file THEN music _ RopeFile.Create[name: music, raw: FALSE ! FS.Error => CONTINUE]; rT _ Rope.ToRefText[base: music]; PlayBlock[musicBlock: [LOOPHOLE[@rT.text+SIZE[INTEGER]], 0, rT.length], random: random, beepProc: beepProc, chunkSize: chunkSize]; }; }; PlayBlock: PUBLIC PROCEDURE [ musicBlock: Basics.UnsafeBlock, random: BOOLEAN _ FALSE, beepProc: PlayOps.BeepProc, chunkSize: CARDINAL _ 75, quietFinish: BOOLEAN _ TRUE --wh: Window.Handle _ NIL--] = { initialOctave: CARDINAL = 8; initialDuration: CARDINAL = 128; -- approximately an eighth-note, as default initialBreak: CARDINAL = 48; -- lower-case note gap, 3/64 by default music: LONG POINTER TO PACKED ARRAY [0..0) OF CHARACTER _ musicBlock.base; note: CARDINAL _ 0; -- number of tones so far noteArray: NoteArray _ NEW[NoteArrayObject[chunkSize]]; scale: TYPE = CHARACTER ['A..'G]; twelfths: ARRAY scale OF CARDINAL = [12, 14, 3, 5, 7, 8, 10]; numberPtr: LONG POINTER TO CARDINAL _ NIL; -- where digits go, if anywhere number, numberMin, numberMax, card: CARDINAL _ 0; octave: CARDINAL _ initialOctave; duration: CARDINAL _ initialDuration; break: CARDINAL _ initialBreak; triplet: BOOLEAN _ FALSE; -- gets set to TRUE between parentheses freqA: LONG CARDINAL = 1760; -- highest octave we'll bother with slideStart: CARDINAL _ 0; -- index of first note of slide, if one is in progress slide: CARDINAL _ 0; -- length of current slide, if any, in 64th-notes root: LONG CARDINAL = 10595; -- 12th root of 2, times 10000 root96: ARRAY [0..8) OF LONG CARDINAL = -- 2^(n/96), times 10000, for slides [10000, 10072, 10145, 10219, 10293, 10368, 10443, 10518]; limits: ARRAY {min,max} OF ARRAY BOOLEAN OF RECORD [duration, break, octave: CARDINAL] = [ [[duration: 8, break: 2, octave: 1], -- normal [duration: 64, break: 24, octave: 2]], -- random [[duration: 1024, break: 384, octave: 256], -- normal [duration: 256, break: 96, octave: 16]] -- random ]; Frequency: PROCEDURE [key: Note, tweak: CARDINAL _ 0 -- 96ths -- ] RETURNS [CARDINAL] = { freq: LONG CARDINAL; twelfths: CARDINAL _ key.twelfths; octave: CARDINAL _ key.octave*32; IF octave = 0 OR twelfths = 0 THEN RETURN[twelfths]; freq _ freqA*LONG[32]; IF tweak >= 8 THEN twelfths _ twelfths + (tweak/8); THROUGH [0..twelfths/12) DO octave _ octave/2 ENDLOOP; THROUGH [0..twelfths MOD 12) DO freq _ (freq*root+LONG[5000])/LONG[10000] ENDLOOP; IF tweak # 0 THEN freq _ (freq*root96[tweak MOD 8]+LONG[5000])/LONG[10000]; RETURN[Basics.LongDiv[freq + LONG[octave/2], octave]]; }; ShipOneChunk: PROCEDURE [last: CARDINAL] RETURNS [CARDINAL] = { c: CARDINAL; maxNoteDuration: Microseconds = 1024000; FOR c IN [1..last] DO noteArray[c].cps _ Frequency[noteArray[c]]; noteArray[c].usecs _ Basics.LongMult[noteArray[c].duration, 1000]; IF c > 1 AND noteArray[c].cps = noteArray[c - 1].cps THEN { IF (noteArray[c].usecs _ noteArray[c].usecs + noteArray[c-1].usecs) > maxNoteDuration THEN { noteArray[c].usecs _ noteArray[c].usecs - maxNoteDuration; noteArray[c - 1].usecs _ maxNoteDuration; } ELSE noteArray[c - 1].usecs _ 0; }; ENDLOOP; PlayNotes [last, noteArray--, wh--]; RETURN[0]; }; DonePlaying: PROCEDURE = {beepProc[beepFreq: 0, beepTime: 0]; lastFreq _ initFreq}; Beep: PROCEDURE [note: Note] = { IF note.freq # lastFreq THEN beepProc[beepFreq: (lastFreq _ note.freq), beepTime: Process.TicksToMsec[note.ticks]+BasicTime.PulsesToMicroseconds[note.pulses]/1000, notify: note.notify, pause: note.pause]; }; PlayNotes: PROCEDURE [n: CARDINAL, notes: NoteArray--, wh: Window.Handle--] = { c: CARDINAL; tix: Process.Ticks; FOR c IN [1..n] DO -- convert usecs to ticks and pulses tix _ Process.MsecToTicks[Basics.LongDiv[notes[c].usecs, 1000]]; WHILE Basics.LongMult[Process.TicksToMsec[tix], 1000] > notes[c].usecs DO tix _ tix - 1; ENDLOOP; notes[c].pulses _ Basics.LowHalf [BasicTime.MicrosecondsToPulses [notes[c].usecs]]; notes[c].ticks _ tix; ENDLOOP; FOR c IN [1..n] DO -- play this batch of notes IF notes[c].pulses # 0 THEN { Beep [notes[c]]; }; ENDLOOP; }; NextNote: PROCEDURE [need: CARDINAL] = INLINE { IF slideStart # 0 AND note > slideStart THEN RETURN; -- looking for end of slide IF note >= chunkSize - need THEN note _ ShipOneChunk[note]; note _ note + 1; }; AddToSlide: PROCEDURE [incr: CARDINAL] = { slide _ MIN[chunkSize, slide + incr/limits[min][FALSE].duration]; IF slideStart - 1 + slide > chunkSize THEN { -- slide won't fit, empty the buffer [] _ ShipOneChunk[slideStart - 1]; noteArray[1] _ noteArray[slideStart]; noteArray[2] _ noteArray[slideStart + 1]; note _ note - (slideStart - 1); slideStart _ 1; }; }; SetNotify: PROC = { IF notifyNext THEN noteArray[note].notify _ TRUE; IF pauseNext THEN noteArray[note].pause _ TRUE; notifyNext _ FALSE; pauseNext _ FALSE; }; { ENABLE UNWIND => CONTINUE; IF music # NIL THEN FOR card _ musicBlock.startIndex, card_card+1 UNTIL card=musicBlock.count DO IF numberPtr # NIL AND music[card] NOT IN ['0..'9] THEN { numberPtr^ _ MIN[MAX[number, numberMin], numberMax]; numberPtr _ NIL}; SELECT music[card] FROM IN ['A..'G] => { NextNote[1]; IF slideStart # 0 THEN AddToSlide[noteArray[note].duration]; noteArray[note] _ [ initial[ twelfths[music[card]], octave, IF triplet THEN (duration*2 + 1)/3 ELSE duration]]; SetNotify[]; }; IN ['a..'g] => { NextNote[2]; IF slideStart # 0 THEN AddToSlide[noteArray[note].duration]; noteArray[note] _ [ initial[ twelfths[music[card] + ('A - 'a)], octave, MAX[(IF triplet THEN (duration*2 + 1)/3 ELSE duration), break] - break]]; SetNotify[]; IF slideStart = 0 THEN noteArray[note _ note + 1] _ [initial[0, 0, break]] ELSE noteArray[note].duration _ (IF triplet THEN (duration*2 + 1)/3 ELSE duration); }; '# => IF note > 0 THEN { -- sharps are one twelfth-octave higher IF noteArray[note].octave = 0 THEN -- octave 0 is really the "break" between notes noteArray[note - 1].twelfths _ noteArray[note - 1].twelfths + 1 ELSE noteArray[note].twelfths _ noteArray[note].twelfths + 1; }; '+ => IF note > 0 THEN { -- warning: you can exceed 2147 msecs using ***C++ IF noteArray[note].octave = 0 THEN -- octave 0 is the "break" between notes noteArray[note - 1].duration _ noteArray[note - 1].duration*3/2 + noteArray[note].duration/2 ELSE noteArray[note].duration _ noteArray[note].duration*3/2; }; '- => IF note > 0 THEN { IF noteArray[note].octave # 0 THEN -- octave 0 is the "break" between notes noteArray[note].duration _ noteArray[note].duration/2 ELSE IF noteArray[note - 1].duration > noteArray[note].duration THEN noteArray[note - 1].duration _ noteArray[note - 1].duration/2 - noteArray[note].duration/2 ELSE noteArray[note - 1].duration _ 0; }; '< => octave _ MIN[octave*2, limits[max][random].octave]; '> => octave _ MAX[octave/2, limits[min][random].octave]; '/ => duration _ MAX[duration/2, limits[min][random].duration]; '* => duration _ MIN[duration*2, limits[max][random].duration]; '_ => break _ MAX[break/2, limits[min][random].break]; '^ => break _ MIN[break*2, limits[max][random].break]; '(, ') => triplet _ (music[card] = '(); '% => { NextNote[1]; IF slideStart # 0 THEN AddToSlide[noteArray[note].duration]; noteArray[note] _ [ initial[ 0, octave, IF triplet THEN (duration*2 + 1)/3 ELSE duration]]; SetNotify[]; }; '{ => IF slideStart = 0 THEN { NextNote[3]; -- need room for starting and ending notes, plus slop (see above) slideStart _ note; slide _ noteArray[note].duration _ noteArray[note + 1].duration _ 0; note _ note - 1; -- haven't actually found starting note yet }; '} => IF slideStart # 0 THEN { IF note # slideStart + 1 OR noteArray[note].twelfths = 0 OR noteArray[note - 1].twelfths = 0 OR slide + noteArray[note - 1].duration + noteArray[note].duration < 2 THEN note _ slideStart - 1 -- ignore slide completely ELSE { diff: INTEGER; -- number of 96ths of an octave between the two ends temp, delta: CARDINAL; low: Note; AddToSlide[ noteArray[note - 1].duration + noteArray[note].duration]; diff _ (INTEGER[noteArray[note].twelfths] - INTEGER[noteArray[note - 1].twelfths])*8; temp _ noteArray[note].octave; DO SELECT noteArray[note - 1].octave FROM < temp => {temp _ temp/2; diff _ diff - 96}; > temp => {temp _ temp*2; diff _ diff + 96}; ENDCASE => EXIT; ENDLOOP; low _ noteArray[IF diff < 0 THEN note ELSE note - 1]; FOR temp IN [0..slide) DO delta _ Basics.LongDiv[ Basics.LongMult[ IF diff < 0 THEN (slide - 1 - temp) ELSE temp, ABS[diff]] + LONG[(slide - 1)/2], slide - 1]; noteArray[slideStart + temp] _ [ initial[Frequency[low, delta], 0, limits[min][FALSE].duration]]; SetNotify[]; ENDLOOP; note _ slideStart + slide - 1; }; slide _ slideStart _ 0; }; '; => { note _ ShipOneChunk[note]; slide _ slideStart _ 0; }; '. => IF NOT random THEN { note _ ShipOneChunk[note]; octave _ initialOctave; duration _ initialDuration; break _ initialBreak; triplet _ FALSE; slide _ slideStart _ 0; NextNote[1]; noteArray[note] _ [initial[0, octave, 1000]]; SetNotify[]; note _ ShipOneChunk[note]; }; '[ => notifyNext _ TRUE; '] => pauseNext _ TRUE; IN ['0..'9] => number _ number*10 + music[card] - '0; '@ => IF NOT random THEN { numberPtr _ @duration; numberMin _ limits[min][FALSE].duration; numberMax _ limits[max][FALSE].duration; number _ 0; }; ', => IF NOT random THEN { numberPtr _ @break; numberMin _ limits[min][FALSE].break; numberMax _ limits[max][FALSE].break; number _ 0; }; ENDCASE; ENDLOOP; IF note > 0 THEN [] _ ShipOneChunk[note]; IF quietFinish THEN DonePlaying []; noteArray _ NIL; }; }; }. 0PlayUtils.mesa Last Edited by: Pier, May 25, 1984 2:26:24 pm PDT Last Edited by: Swinehart, July 31, 1984 9:37:57 am PDT -------------------------------------------------------------- TYPEs and Constants -------------------------------------------------------------- -------------------------------------------------------------- Utilities -------------------------------------------------------------- PlayBlock is the main procedure. It interprets its block as follows: A letter from "A" through "G" specifies a note. If the letter is followed by "#" then the corresponding sharp-note is played (meaningful only for C, D, F, G, and A). All notes are eighth-notes, but upper-case letters cause tones that are "held" the full time while lower-case notes last for 3/64 seconds less and followed by a 3/64 rest. C is the bottom of the octave; B is above C. When ">" is encountered, all subsequent notes are an octave higher; a "<" lowers all subsequent notes by an octave. Going up more than 3 octaves is not permitted (additional ">"s are ignored), and notes near the top of the highest octave may not be struck accurately. A "/" in the string halves the note durations, down to a minimum of 64th-notes; a "*" doubles the durations up to a maximum of full-notes. A lower-case 1/16th-note would actually be a 64th-note followed by a 3/64 rest, which may or may not be what you want; a lower-case 32nd-note vanishes completely! To halve and double the amount of implicit rest "stolen" from lower-case notes, use "_" and "^", respectively. Use "%" to get an explicit rest (as distinct from the implicit ones after lower-case notes). The rest is the same length as a note, i.e., initially an eighth-rest, and changed via "/" and "*". A "+" causes the preceding note to be held for an extra 50%. Thus a quarter-note followed by a "+" becomes a 3/8-note, etc. A "-" causes the preceding note's duration to be halved. This is effectively a shorthand for bracketing the note with "/" and "*". A left parenthesis causes subsequent notes and explicit rests to be at 2/3 normal duration, until a right parenthesis is reached. Three notes enclosed in parentheses yield a "triplet". If you think you know exactly what tempo you want, use "@" to give the note duration and/or "," for the lower-case implicit rest, where and are strings of digits representing milliseconds. The values will be constrained to the usual limits (e.g., will be forced between 16 and 1024 ms). Subsequent "*", "_", etc., have their usual effects. Two or more notes and/or rests enclosed in braces, as "{C%%%G#}", yield a "slide" from the first note to the last. The duration of the slide equals the total duration of the notes and rests; observe that upper- and lower-case notes have the same effect. The slide consists of 64th-notes at equally-spaced (logarithmic) frequencies. Warning: This can eat up a lot of array space! If the argument "random" is TRUE, it's assumed the input string is random text, and the limits on octaves and note durations are compressed in order to keep the sounds reasonable. The "@", ",", and "." commands have no effect when in "random" mode. The argument "chunkSize" is the number of tones (including rests, explicit and implicit) that are played as a unit; if you exceed this limit, the first chunk of music gets played and there is a slight pause while the next "chunkSize" notes get parsed. If you know where you want this pause to occur, you can force it by putting a semi-colon at that point in the string. A period (".") in the string causes the buffer to be shipped out, as for a semi-colon, and resets the octave, note duration, and implicit lower-case rest to their initial values. This is for when you're playing an entire file that contains several separate pieces. min max WARNING! Due to a Mesa bug, we have to be careful NEVER have a LONG CARDINAL as large as 2^31; dividing into such a number doesn't work right! if octave is 0, believe whatever's already there; might be precomputed slide combine notes for smoother play (reduce calculation time in PlayNotes) don't let duration sum to over 1 sec, so pulses fits in one word IF UserInput.UserAbort [wh] THEN {DonePlaying []; ERROR ABORTED}; FOR card IN [musicBlock.startIndex..musicBlock.stopIndexPlusOne) DO -- this is where the "slop" mentioned for brackets comes in don't have two notes to work with -- can't slide this fast! Edited on May 25, 1984 2:26:24 pm PDT, by Pier changes to: NextNote to fix >= bug , PlayUtils, PlayUtils Edited on July 31, 1984 9:32:14 am PDT, by Swinehart changes to: PlayUtils, Beep, Beep, AddToSlide, SetNotify Ê ÷˜Jšœ™Jšœ1™1J™7J˜šÏk ˜ Jšœœ+˜7Jšœœ ˜Jšœœ˜'Jšœœ#˜0Jšœœœ ˜Jšœ œ ˜Jšœ œ-˜™>Jšœ™Jšœ>™>J˜š œœœ œœ˜'šœœ˜šœ ˜ Jš œœ œœ œœœ˜T—šœ˜Jš œœœœœ œ˜K—šœ ˜ Jš œœœœœ œ˜U—Jšœ˜ Jšœœ˜J˜——Jšœ œœ˜&Jš œœœœœœ˜AJšœ œœ˜#J˜Jšœ>™>Jšœ ™ Jšœ>™>J˜Jšœ œœœ˜$Jšœ œ ˜Jšœ œœ˜Jšœ œœ˜J˜J˜JšœE™EJšœÓ™ÓJšœº™ºJšœž™žJšœÁ™ÁJšœ™Jšœ¹™¹Jšœç™çJšœý™ýJšœù™ùJšœò™òJšœ‰™‰J˜š Ïn œœœœœ˜GJšœœ˜ šœ œœ˜Jš œœ+œœ œ˜VJšœ!˜!Jšœœ œœM˜‚J˜—Jšœ˜J˜—šž œœ œ˜Jšœ(œœ˜8Jšœ˜Jšœ œœ˜5JšÏcœ˜ Jšœœ˜Jšœœ Ÿ+˜MJšœœŸ'˜EJšœœœœœœœ œ˜JJšœœŸ˜.Jšœœ˜7Jšœœ œ ˜!Jšœ œœœ˜=Jš œ œœœœœŸ˜KJšœ$œ˜1Jšœœ˜!Jšœ œ˜%Jšœœ˜Jšœ œœŸ'˜BJšœœœ Ÿ#˜AJšœ œŸ6˜QJšœœŸ1˜GJšœœœ Ÿ˜<š œœœœœŸ$˜MJ˜9—š œœ œœœœœ˜3šœœ˜'Jšœ™šœ+Ÿ ˜4Jšœ,Ÿ ˜5—Jšœ™šœ,Ÿ ˜5Jšœ+Ÿ ˜4——J˜J˜—JšœD™DJšœJ™Jšž œ œœŸ œ˜BJšœœ˜Jšœœœ˜Jšœ œ˜"Jšœœ˜!J˜Jšœ œœœ ˜4JšœL™LJšœ œ˜Jšœ œ!˜3Jšœœœ˜6šœœ˜Jšœœœœ˜2—šœ ˜Jšœœœœ˜9—Jšœœ˜6J˜Jšœ˜J˜—š ž œ œœœœ˜?Jšœœ˜ J˜(J˜šœœ ˜J˜+JšœB˜Bšœœ)œ˜;JšœF™FJšœ@™@šœC˜Ešœœ˜J˜:J˜)Jšœ˜——Jšœ˜ Jšœ˜—Jšœ˜J˜—J˜$Jšœ˜ J˜Jšœ˜J˜—Jšž œ œ=˜SJ˜šžœ œ˜ šœ˜šœ‡˜‡Jšœ(˜(——Jšœ˜J˜—šž œ œœŸœ˜MJšœ˜Jšœœ˜ J˜šœœœŸ$˜7Jšœ@˜@šœB˜IJ˜Jšœ˜—JšœS˜SJ˜Jšœ˜—šœœœŸ˜.šœœ˜Jšœœœœ™AJ˜Jšœ˜—Jšœ˜—Jšœ˜J˜—J˜šžœ œœœ˜/Jš œœœœŸ˜PJšœœ˜;J˜Jšœ˜J˜—šž œ œœ˜*Jšœœ%œ ˜Ašœ$œŸ$˜RJ˜"J˜%J˜)J˜J˜Jšœ˜—Jšœ˜—J˜šž œœ˜Jšœ œœ˜1Jšœ œœ˜/Jšœ œ˜Jšœ œ˜J˜J˜—Jšœœœœ˜šœ œ˜Jšœœ6™Cšœ+œ˜Lš œ œœ œœ œ˜9Jšœ œœ-œ˜FJ˜—Jšœ ˜˜šœ˜J˜ Jšœœ&˜<˜J˜J˜Jšœ œœ ˜3—J˜ Jšœ˜J˜—šœ˜JšŸ<™—J˜ Jšœ˜J˜—˜šœœ˜JšœŸA˜OJ˜J˜DJšœŸ+˜=Jšœ˜J˜——˜šœœ˜šœœ˜8Jšœ!˜#Jšœ$™$šœ@˜BJšœ˜—Jšœ™JšœŸ˜1—šœ˜JšœœŸ4˜DJšœ œ˜J˜ ˜ J˜9—J˜UJ˜š˜šœ˜&J˜,J˜,Jšœœ˜—Jšœ˜—Jšœœ œœ ˜5šœœ ˜šœ˜šœ˜Jšœ œœœ ˜;Jšœ˜ ——˜ Jšœ.œ ˜@—J˜ Jšœ˜—J˜Jšœ˜—J˜Jšœ˜J˜——Jšœ=˜=J˜˜šœœœ˜J˜J˜J˜J˜Jšœ œ˜J˜J˜ J˜-J˜ J˜Jšœ˜J˜——Jšœœ˜Jšœœ˜Jšœ3˜5J˜˜šœœœ˜J˜Jšœœ ˜(Jšœœ ˜(J˜ Jšœ˜J˜——˜šœœœ˜J˜Jšœœ˜%Jšœœ˜%J˜ Jšœ˜J˜——Jšœ˜—Jšœ˜J˜——Jšœ œ˜)Jšœ œ˜#Jšœ œ˜Jšœ˜Jšœ˜J˜—Jšœ˜™.Jšœ Ïrœ ™9—J™J™™4Jšœ  ,™8—J™J™——…—)FIm