MusicProcess.mesa
Copyright (C) 1981, 1984 Xerox Corporation. All rights reserved.
Author: John Maxwell
last modified: December 18, 1981 8: 47 AM
Edited by Doug Wyatt, June 14, 1984 3:44:56 pm PDT
DIRECTORY
ImageDefs USING [AddCleanupProcedure, CleanupItem, CleanupProcedure, CleanupMask],
InlineDefs USING [BITSHIFT, HighHalf, LowHalf],
IODefs USING [WriteLine, WriteNumber, WriteString],
Mopcodes USING [zMISC],
MusicDefs,
MusicHardwareDefs,
Note USING [Duration, GetBackTie],
Piece USING [AddSync, NearestSync],
ProcessDefs USING [CV, DisableInterrupts, EnableInterrupts, GetPriority, InterruptLevel, Priority, SetPriority, SetTimeout],
Real USING [Fix],
Sync USING [AddNote],
SystemDefs USING [AllocateSegment],
Score USING [AddToPitch, GetKey, GetMetrenome],
Screen USING [DisplayMessage, InvertListen, InvertPlay],
Utility USING [NewNote, NewSync],
Voice USING [ClearState, SetState, State, StatePTR];
MusicProcess: CEDAR MONITOR
IMPORTS ImageDefs, InlineDefs, IODefs, MusicDefs, Note, Piece, ProcessDefs, Real, Sync, SystemDefs, Score, Screen, Utility, Voice
EXPORTS MusicDefs, Score
= BEGIN OPEN MusicDefs, MusicHardwareDefs;
listen: CONDITION; -- microcode signals whenever a buffer is ready for listenProcess
play: CONDITION; -- microcode signals whenever it is through with a buffer
listenProcess, playProcess: PROCESS;
scoreIN: PiecePTR ← NIL;
scoreOUT: PiecePTR ← NIL;
playPhysical: BOOLFALSE;
offset: LONG CARDINAL; -- since we can't set musicIO.time, we use an offset to start in the middle of a piece.
meter: INTEGER; -- speed of play (halftime, normal, doubletime). NOT metrenome!
******************************************************************
code necessary to initialize the processes
******************************************************************
cleanup: ImageDefs.CleanupItem;
InitializeSynthesizer: PUBLIC PROC = {
originalLevel: ProcessDefs.Priority ← ProcessDefs.GetPriority[];
cleanup ← [NIL, ImageDefs.CleanupMask[Finish]
+ImageDefs.CleanupMask[Save]
+ImageDefs.CleanupMask[Restore]
+ImageDefs.CleanupMask[Checkpoint]
+ImageDefs.CleanupMask[Restart],
CleanupMicrocode];
ImageDefs.AddCleanupProcedure[@cleanup];
InitMicrocode[];
ProcessDefs.SetTimeout[@play, 1];
ProcessDefs.SetPriority[2];
listenProcess ← FORK ProcessBuffer;
playProcess ← FORK ProcessScore;
ProcessDefs.SetPriority[originalLevel];
};
StartListening: PUBLIC PROC[s: PiecePTR]= {
IF playing THEN RETURN;
meter ← 128;
sync ← NIL;
offset 𡤀
IF debugInput THEN IODefs.WriteLine["offset reset--input"];
counter ← 0;
scoreIN ← s;
setOffset ← TRUE;
partial ← ALL[[pressed, 0, 0]];
keyboardIN ← ALL[[0,[up, up, up, up, up, up]]];
StartMicrocode[listening];
};
StopListening: PUBLIC ENTRY PROC = {
StopMicrocode[listening];
NOTIFY listen;
};
StartPlaying: PUBLIC ENTRY PROC[s: PiecePTR, first: CARDINAL, physical: BOOL,
displayCursor: PROC[time: LONG CARDINAL]]= {
IF listening AND (scoreIN[0]#NIL OR ~Empty[INbuffer]) THEN RETURN;
IF ~physical THEN StopMicrocode[listening];
pendingArray ← ALL[[NIL, NIL, 0, up, FALSE, 0]];
pending ← NIL;
scoreOUT ← s;
in ← 0; -- in and out are used by the cursor displayer
out ← 1;
start ← first;
setOffset ← TRUE;
SELECT TRUE FROM
BlueBug[] => meter ← 256;
RedBug[] => meter ← 64;
ENDCASE => meter ← 128;
playPhysical ← physical;
DisplayCursor ← displayCursor;
StartMicrocode[playing];
IF ~microcode THEN RealStopMicrocode[];
NOTIFY play; --you fool! you forgot to loadmb music.mb!
};
StopPlaying: PUBLIC PROC = {
StopMicrocode[playing];
IF listening AND scoreIN[0]=NIL AND Empty[INbuffer]
THEN StopListening[];
};
Empty: PROC[b: EventBufferPTR] RETURNS[BOOL] = {
IF b=NIL THEN RETURN[TRUE];
FOR i: CARDINAL IN [0..b.length) DO
IF b.data[i].htoc<100 THEN LOOP; -- transient garbage
RETURN[FALSE];
ENDLOOP;
RETURN[TRUE];
};
DisplayCursor: PROC[time: LONG CARDINAL];
******************************************************************
this submodule is responsible for translating from events to notes
******************************************************************
the microcode passes us a buffer of keystates and their times.
we must compare successive keystates to see where changes occur.
the keystates may include spurious "bounce".
channel=15 means that the microcode's clock wrapped around (it's only 16 bits).
setOffset: BOOLFALSE; -- so we know when to determine the offset
counter: CARDINAL; -- number of times the microcode clock has wrapped around
ProcessBuffer: ENTRY PROC = {
c, channel: CARDINAL ← 0;
compare: ChannelWord;
event: MusicEvent;
DO --wait until a buffer is ready and then process it
WHILE ~listening AND INbuffer.length=0 DO WAIT listen; ENDLOOP;
WHILE INbuffer = musicIO.headOfInputList DO WAIT listen; ENDLOOP;
IF ~microcode THEN RealStopMicrocode[];
IF debugInput THEN WriteBuffer[INbuffer];
FOR c IN [0..INbuffer.length) DO
INbuffer.data[c].channelWord.channel ← --! hack to work around bug in the microcode
SELECT INbuffer.data[c].channelWord.channel FROM
12 => 0,
15 => 15,
ENDCASE => INbuffer.data[c].channelWord.channel + 1;
event ← INbuffer.data[c];
channel ← event.channelWord.channel;
IF channel = 15 THEN counter ← counter + 1;
IF channel > 12 THEN LOOP;
IF counter=0 AND event.htoc < 100 THEN LOOP; --transient garbage
compare ← keyboardIN[channel];
ExtractTransitions[compare, event.channelWord, event.htoc];
keyboardIN[channel] ← event.channelWord;
ENDLOOP;
IF ~listening THEN FOR i: CARDINAL IN [0..12] DO
IF keyboardIN[i].key = [up, up, up, up, up, up] THEN LOOP;
compare ← keyboardIN[i];
event.channelWord ← [i,[up, up, up, up, up, up]];
event.htoc ← MAX[event.htoc, InlineDefs.LowHalf[musicIO.time]];
ExtractTransitions[compare, event.channelWord, event.htoc];
keyboardIN[channel] ← event.channelWord;
ENDLOOP;
GetNextInputBuffer[];
ENDLOOP;
};
ExtractTransitions: INTERNAL PROC[x, y: ChannelWord, time: CARDINAL]= {
OPEN InlineDefs;
delta, pitch: INTEGER;
channel: CARDINAL=y.channel;
transition: RECORD[a, b, c: KeyState];
e: MusicEvent ← [LOOPHOLE[time], counter];
toc: LONG CARDINALLOOPHOLE[e];
toc ← Scale[toc, meter, 128]+offset;
IF setOffset THEN {setOffset ← FALSE; offset ← 500-toc; toc ← 500;
IF debugInput THEN {WriteLong[offset]; IODefs.WriteLine[" (offset)"]}};
each channel has 6 keys, and there might be more than one transition
FOR i: CARDINAL IN [0..6) DO
IF x.key[i]=y.key[i] THEN LOOP;
pitch ← Pitch[channel, i];
delta ← InlineDefs.LowHalf[(toc-partial[pitch].toc)];
IF delta<0 THEN delta ← 32000;
transition ← [partial[pitch].last, x.key[i], y.key[i]];
SELECT transition FROM
[pressed, up, pressed] => partial[pitch].toc← toc;
[up, pressed, up] => partial[pitch].toc← 0; -- ignore transient bounce
[up, pressed, down] => NULL; --partial[pitch].loudness← delta;
[down, pressed, down] => NULL;
[pressed, down, pressed] => partial[pitch].duration← delta;
[pressed, down, up] => {partial[pitch].duration← delta; AddNote[pitch]};
[down, pressed, up] => AddNote[pitch];
ENDCASE => Error[];
partial[pitch].last ← x.key[i];
ENDLOOP;
};
AddNote: INTERNAL PROC[pitch: CARDINAL] = {
note: NotePTR;
IF partial[pitch].toc=0 THEN RETURN;
IF partial[pitch].duration=0 THEN Error[];
note ← Utility.NewNote[];
note^ ← []; --defaults to the values listed in MusicDefs
note.pitch ← pitch;
note.toc ← partial[pitch].toc;
note.duration ← partial[pitch].duration;
note.loudness ← partial[pitch].loudness;
SELECT TRUE FROM
note.pitch IN [79..92] => { note.stemUp ← FALSE; note.staff ← 0; };
note.pitch IN [68..78] => { note.stemUp← TRUE; note.staff ← 0; };
note.pitch IN [55..67] => { note.stemUp ← FALSE; note.staff ← 1; };
note.pitch IN [44..54] => { note.stemUp← TRUE; note.staff ← 1; };
note.pitch IN [34..43] => { note.stemUp ← FALSE; note.staff ← 2; };
note.pitch IN [22..33] => { note.stemUp← TRUE; note.staff ← 2; };
note.pitch IN [12..21] => { note.stemUp ← FALSE; note.staff ← 3; };
note.pitch IN [5..11] => { note.stemUp← TRUE; note.staff ← 3; };
ENDCASE;
IF sync=NIL OR ABS[note.toc - sync.time*MusicDefs.TF] > 200
THEN sync ← scoreIN[Piece.NearestSync[scoreIN, note.toc/MusicDefs.TF, TRUE]];
IF sync=NIL OR ABS[note.toc - sync.time*MusicDefs.TF] > 200
THEN {
sync ← Utility.NewSync[];
sync.type ← notes;
sync.time ← note.toc/MusicDefs.TF;
Piece.AddSync[scoreIN, sync];
};
Sync.AddNote[sync, note];
partial[pitch].toc ← 0;
partial[pitch].duration ← 0;
};
sync: SyncPTR ← NIL;
Pitch: PROC[channel, note: CARDINAL] RETURNS[CARDINAL]=
INLINE { RETURN[channel*6 + note+12]; };
partial: ARRAY [0..100) OF RECORD[last: KeyState, toc: LONG CARDINAL, duration: CARDINAL--, loudness: CARDINAL--];
keyboardIN: ARRAY [0..12] OF ChannelWord;
******************************************************************
this submodule is responsible for translating from notes to events
******************************************************************
start: CARDINAL ← 0;
ProcessScore: PROC = {
endOfTime: LONG CARDINAL ← 0;
endOfTime ← endOfTime-1; -- wraps around to largest long cardinal
trill ←InlineDefs.LowHalf[Scale[512, 128, 70]];
trillDur ←(3*trill)/4;
grace ←InlineDefs.LowHalf[Scale[300, 128, 70]];
graceDur ←(3*grace)/2;
DO -- forever
WHILE NOT playing DO WaitOnPlay[]; ENDLOOP;
musicIO.time ← 0;
OUTbuffer.data[0] ← reStart;
OUTbuffer.length ← 1;
lastTOC ← 0;
InitKeyboardOUT[];
IF debugOutput THEN IODefs.WriteLine["processing score"];
IF playPhysical THEN TranslatePhysical[] ELSE TranslateLogical[];
done with the main score, clean out pending
IF debugOutput THEN IODefs.WriteLine["pending array"];
FlushPending[endOfTime]; -- flushes everything
GetNextOutputBuffer[]; -- has side effect of writing current buffer
WHILE playing DO -- wait for microcode to finish
IF musicIO.headOfOutputList=NIL
THEN StopPlaying[]
ELSE WaitOnPlay[];
ENDLOOP;
ENDLOOP;
};
TranslatePhysical: PROC = {
n: NotePTR;
sync: SyncPTR;
time, maxTime, lastFlush, duration: LONG CARDINAL ← 0;
FOR i: CARDINAL IN [start..maxScoreLength) DO
IF NOT playing THEN EXIT;
IF (sync ← scoreOUT[i])=NIL THEN EXIT;
FOR j: CARDINAL IN [0..syncLength) DO
IF (n ← sync.event[j])=NIL THEN EXIT;
IF n.rest THEN LOOP;
IF n.tie#NIL AND n.tie.pitch=n.pitch THEN LOOP; -- skip the second note of a tied pair
IF voice AND n.voice#selectedVoice THEN LOOP;
IF n.toc=0 THEN time ← n.sync.time*TF ELSE time ← n.toc;
IF n.duration=0 THEN duration ← Duration[n, 128] ELSE duration ← n.duration;
maxTime ← MAX[maxTime, time];
ProcessNote[MAX[time, lastFlush], duration, n.pitch, loudness]
ENDLOOP;
IF maxTime>1000 THEN lastFlush ← maxTime-1000;
FlushPending[lastFlush];
ENDLOOP;
};
TranslateLogical: PROC = {
i, j: CARDINAL;
n: NotePTR ← NIL;
vs: Voice.State;
sync: SyncPTR ← NIL;
now, delta, toc, max: Time ← 0;
lastDuration, lastNow, lastToc: Time ← 0;
pitch, metrenome, count: INTEGER ← 0;
isLogicalSync, wasLogicalSync, nonGraceSync: BOOLTRUE;
metrenome ← Score.GetMetrenome[scoreOUT[start].time];
index ← [0, 0];
Voice.ClearState[@vs];
FOR i: CARDINAL IN [0..maxVoice] DO vs[i].sum ← 10*trill; ENDLOOP;
FOR i IN [start..maxScoreLength) DO
IF NOT playing THEN EXIT;
IF (sync ← score[i])=NIL THEN LOOP;
handle all of the syncs that don't contain notes
IF sync.type=repeat1 THEN PushRepeat[i, stack1]; -- encountered a left-paren repeat
IF sync.type=repeat2 THEN { -- encountered a right-paren repeat
IF TopRepeat[stack2]=i THEN -- we've repeated once, don't repeat again.
{ [] ← PopRepeat[stack2]; LOOP; };
IF NoRepeat[stack1] THEN LOOP;
PushRepeat[i, stack2]; -- save repeat so we won't repeat twice
i ← PopRepeat[stack1]; -- go to beginning of the repeat
};
IF sync.type=metrenome THEN metrenome ← sync.value;
IF sync.type#notes THEN LOOP;
handle syncs that contain notes
is this a logical sync? what is its toc?
isLogicalSync ← FALSE; toc ← 0;
nonGraceSync ← FALSE;
FOR j IN [0..syncLength) DO
IF (n ← sync.event[j])=NIL THEN EXIT;
toc ← MAX[toc, sync.event[j].toc];
IF ~n.grace THEN nonGraceSync ← TRUE;
IF sync.event[j].value#unknown THEN isLogicalSync ← TRUE;
ENDLOOP;
determine the time to play for the whole sync.
handle boundarys between physical and logical sections
max ← Voice.SetState[@vs, sync, metrenome];
IF wasLogicalSync AND isLogicalSync THEN
IF max > now THEN now ← max ELSE now ← lastNow+lastDuration;
IF wasLogicalSync AND ~isLogicalSync THEN {
IF lastToc#0 THEN delta ← lastNow-lastToc ELSE delta← (lastNow+lastDuration)-toc;
now← toc+delta};
IF ~wasLogicalSync AND ~isLogicalSync THEN
now ← toc+delta;
IF ~wasLogicalSync AND isLogicalSync THEN
IF toc#0 AND toc+delta>now AND toc+delta<lastNow+lastDuration+4*trill
THEN now ← toc+delta
ELSE now← lastNow+lastDuration;
SetSum[@vs, now];
IF nonGraceSync THEN PlayGraceNotes[now, i];
play all non-grace notes
FOR j IN [0..syncLength) DO
IF (n ← sync.event[j])=NIL THEN EXIT;
IF voice AND n.voice#selectedVoice THEN LOOP;
IF n.grace THEN LOOP;
Associate[now, i]; -- so we can display the cursor later
PlayLogical[n, now, metrenome];
ENDLOOP;
set up wasLogicalSync, lastNow, lastToc and lastDuration for the next iteration
wasLogicalSync ← isLogicalSync;
lastNow ← now; -- just to make it easier to understand
lastToc ← toc;
lastDuration ← 0;
IF isLogicalSync
THEN FOR j IN [0..maxVoice] DO
IF vs[j].found THEN lastDuration ← MAX[lastDuration, vs[j].duration];
ENDLOOP
ELSE FOR j IN [0..syncLength) DO
IF sync.event[j]=NIL THEN EXIT;
lastDuration ← MAX[lastDuration, sync.event[j].duration];
ENDLOOP;
lastDuration ← (4*lastDuration)/3;
IF nonGraceSync THEN FlushPending[now];
ENDLOOP;
};
PlayGraceNotes: PROC[now: Time, i: CARDINAL] = {
n: NotePTR;
oldLoudness: CARDINAL;
nonGraceSync: BOOL;
count, start: CARDINAL ← 0;
how many grace syncs? where do they start?
FOR j: CARDINAL DECREASING IN [0..i) DO
IF score[j]=NIL THEN LOOP;
IF score[j].type#notes THEN LOOP;
count ← count+1;
nonGraceSync ← FALSE;
FOR k: CARDINAL IN [0..syncLength) DO
IF (n ← score[j].event[k])=NIL THEN EXIT;
IF ~n.grace THEN nonGraceSync ← TRUE;
ENDLOOP;
IF nonGraceSync THEN {start ← j; EXIT};
ENDLOOP;
now we can play them
oldLoudness ← loudness;
loudness ← (7*loudness)/8;
FOR j: CARDINAL IN [start..i) DO
IF score[j]=NIL THEN LOOP;
IF score[j].type#notes THEN LOOP;
FOR k: CARDINAL IN [0..syncLength) DO
IF (n ← score[j].event[k])=NIL THEN EXIT;
IF ~n.grace THEN LOOP;
PlayLogical[n, now-count*grace, 128];
ENDLOOP;
count ← count-1;
ENDLOOP;
loudness ← oldLoudness;
};
SetSum: PROC[vs: Voice.StatePTR, sum: LONG CARDINAL] = {
FOR i: CARDINAL IN [0..maxVoice] DO
IF vs[i].found THEN vs[i].sum ← sum;
ENDLOOP;
};
trill, trillDur: INTEGER;
grace, graceDur: INTEGER;
grace notes and trills are played at a constant rate independent of metrenome
PlayLogical: PROC[n: NotePTR, toc: LONG CARDINAL, metrenome: INTEGER] = {
key: INTEGER;
duration: LONG INTEGER;
IF n.rest THEN RETURN;
IF voice AND n.voice#selectedVoice THEN RETURN;
IF n.tie#NIL AND n.tie.pitch=n.pitch AND NOT Trilled[n] THEN RETURN; -- skip the second note of a tied pair
IF n.value#unknown THEN duration ← Duration[n, metrenome] ELSE duration ← n.duration;
IF n.embellish#none OR n.tie#NIL THEN key ← Score.GetKey[n.sync.time];
SELECT TRUE FROM
n.embellish=trill OR (n.tie#NIL AND n.tie.pitch=n.pitch) => { -- n.tie is tied back to a trill
time: LONG CARDINAL ← toc;
duration ← Note.Duration[n, metrenome];
ProcessNote[time, trillDur, n.pitch, loudness];
ProcessNote[time+trill, trillDur, Score.AddToPitch[key, n.pitch, 1], loudness];
time ← time+2*trill;
duration ← duration-2*trill;
WHILE duration>=2*trill DO
ProcessNote[time, trillDur, n.pitch, loudness];
ProcessNote[time+trill, trillDur, Score.AddToPitch[key, n.pitch, 1], loudness];
time ← time+2*trill;
duration ← duration-2*trill;
ENDLOOP;
};
n.embellish=mordent1 => {
ProcessNote[toc-2*trill, trillDur, n.pitch, loudness];
ProcessNote[toc-trill, trillDur, Score.AddToPitch[key, n.pitch, 1], loudness];
ProcessNote[toc, duration, n.pitch, loudness];
};
n.embellish=mordent2 => {
ProcessNote[toc-2*trill, trillDur, n.pitch, loudness];
ProcessNote[toc-trill, trillDur, Score.AddToPitch[key, n.pitch,-1], loudness];
ProcessNote[toc, duration, n.pitch, loudness];
};
n.grace => ProcessNote[toc, graceDur, n.pitch, loudness];
ENDCASE => ProcessNote[toc, duration, n.pitch, loudness];
};
Trilled: PROC[n: NotePTR] RETURNS[BOOL] = {
WHILE n.tie#NIL DO
IF n.tie.pitch#n.pitch THEN RETURN[FALSE];
IF (n ← n.tie).embellish=trill THEN RETURN[TRUE];
IF n.embellish#none THEN RETURN[FALSE];
ENDLOOP;
RETURN[FALSE];
};
Duration: PROC[n: NotePTR, metrenome: INTEGER] RETURNS[INTEGER] = {
l: REAL ← 1;
tie: NotePTR;
d: Time ← Note.Duration[n, metrenome];
IF n.grace THEN d ← grace;
WHILE n.tied DO
IF n.embellish=trill THEN EXIT;
tie ← Note.GetBackTie[n];
IF n.pitch#tie.pitch THEN EXIT;
d ← d + Note.Duration[tie, metrenome];
n ← tie;
ENDLOOP;
RETURN[InlineDefs.LowHalf[MIN[7*(d/8), 32000]]];
};
Scale: PROC[time, top, bottom: LONG CARDINAL] RETURNS[LONG CARDINAL] = {
l: REAL ← 1;
RETURN[Real.Fix[l*top*time/bottom]];
};
loudness: INTEGER ← 90;
******************************************************************
procedures needed to handle repeats correctly
******************************************************************
PushRepeat: PROC[i, s: CARDINAL] =
{ stack[s][index[s]] ← i; index[s] ← index[s] + 1; };
PopRepeat: PROC[s: CARDINAL] RETURNS[CARDINAL] =
{ IF NoRepeat[s] THEN Error; index[s] ← index[s] - 1; RETURN[stack[s][index[s]]]; };
TopRepeat: PROC[s: CARDINAL] RETURNS[CARDINAL] =
{ RETURN[IF NoRepeat[s] THEN 10000 ELSE stack[s][index[s]-1]]; };
NoRepeat: PROC[s: CARDINAL] RETURNS[BOOL] =
{ RETURN[index[s]=0] };
stack: ARRAY [1..2] OF ARRAY [0..10] OF CARDINAL;
index: ARRAY [1..2] OF CARDINAL ← [0, 0];
stack1: CARDINAL = 1;
stack2: CARDINAL = 2;
******************************************************************
Waiting and displaying cursor
******************************************************************
We want to display the cursor near the note that the microcode is playing, not the one we are processing.
All we know about the microcode is its current time. (musicIO.time)
We save the actual times we said to play syncs long enough to guess what sync is being played.
WaitOnPlay: ENTRY PROC = {
time: Time;
sync: SyncPTR;
WAIT play;
WHILE dataStructureInFlux DO WAIT play; ENDLOOP;
IF musicIO.headOfOutputList=NIL THEN RETURN;
time ← Scale[musicIO.time, meter, 128]+offset;
IF playPhysical
THEN DisplayCursor[time]
ELSE IF (sync ← GetSync[time])#NIL THEN DisplayCursor[sync.time];
};
Associate: PROC[time: LONG CARDINAL, sync: CARDINAL] = {
IF list[in] = [time, sync] THEN RETURN;
in ← (in+1) MOD listLength;
list[in] ← [time, sync];
};
GetSync: PROC[time: LONG CARDINAL] RETURNS[SyncPTR] = {
IF out = (in+1) MOD listLength THEN RETURN[NIL];
WHILE list[(out+1) MOD listLength].time<time+520 DO
out ← (out+1) MOD listLength;
IF out = (in+1) MOD listLength THEN RETURN[NIL];
ENDLOOP;
RETURN[scoreOUT[list[out].sync]];
};
list: ARRAY [0..listLength) OF
RECORD[time: LONG CARDINAL, sync: CARDINAL];
listLength: CARDINAL = 70;
in, out: CARDINAL;
******************************************************************
Adding a physical note (pitch, time, duration, loudness) to a buffer
******************************************************************
Each note must be converted into three events: key pressed, key down, and key up.
The time between pressed and down is LOUDNESS
The time between pressed and up is DURATION
Because of multiple voices, the same pitch may be played twice in an overlapping manner.
IF the second pitch is pressed after the first becomes down, then separate the notes, else merge them.
To separate the notes: stop the first note just before the second begins.
To merge the notes: use the earlier start time, the longer duration, and the greater loudness.
Events in the buffer must be in order by their time of occurrance.
Once you put an event in the buffer, there is no turning back.
lastTOC: LONG CARDINAL; -- all future events must occur AFTER this time.
pending: POINTER TO PendingEvent ← NIL; -- list of events produced that we don't want to put in the buffer yet because events to come may actually occur before these events.
ProcessNote: PROC[time, duration: LONG CARDINAL, pitch: INTEGER, loudness: CARDINAL] = {
merge: BOOLFALSE;
temp: POINTER TO PendingEvent;
WHILE pitch<12 DO pitch ← pitch+12; ENDLOOP; -- make the note fall on the keyboard
WHILE pitch>87 DO pitch ← pitch-12; ENDLOOP; -- ditto
IF pitch>72 THEN loudness ← (2*loudness)/3; -- adjust for dynamics of keyboard
IF setOffset THEN {offset ← (IF time>500 THEN time-500 ELSE 0); setOffset ← FALSE;
IF debugOutput THEN {WriteLong[offset]; IODefs.WriteLine[" (offset)"]}};
time ← Scale[(time-offset), 128, meter]; -- adjust for tempo (not metrenome!)
duration ← Scale[duration, 128, meter];
duration ← MAX[duration, 2*loudness];
time ← MAX[time, lastTOC];
FOR temp ← pending, temp.next WHILE temp#NIL DO
find out if there is another note pending at this pitch and time
IF temp.pitch#pitch THEN LOOP;
IF temp.toc<time THEN LOOP;
IF temp.state=illegal THEN LOOP;
IF temp.state=up THEN { -- separate the two notes
temp.state ← illegal;
AddPending[pitch, up, time-2];
duration ← MAX[duration, temp.toc-time];
EXIT};
IF temp.state=pressed AND temp.toc>time+loudness THEN { -- separate them
temp.state ← illegal;
AddPending[pitch, up, MAX[temp.toc, time+duration]];
duration ← MIN[duration, temp.toc-time-2];
EXIT};
ENDCASE: merge the two notes
merge ← TRUE;
EXIT; ENDLOOP;
IF merge THEN FOR temp ← pending, temp.next WHILE temp#NIL DO
nullify incorrect entries. (don't want to resort pending list)
IF temp.pitch#pitch THEN LOOP;
IF temp.toc<time THEN LOOP;
IF temp.state=illegal THEN LOOP;
IF temp.state=pressed AND time<temp.toc THEN -- make it as early as possible
{temp.state ← illegal; AddPending[pitch, pressed, time]};
IF temp.state=down AND time+loudness<temp.toc THEN -- make it as loud as possible
{temp.state ← illegal; AddPending[pitch, down, time+loudness]};
IF temp.state=up AND time+duration>temp.toc THEN -- make it as long as possible
{temp.state ← illegal; AddPending[pitch, up, time+duration]};
IF temp.state=up THEN RETURN;
ENDLOOP;
AddPending[pitch, pressed, time];
AddPending[pitch, down, time+loudness];
AddPending[pitch, up, time+duration];
};
AddPending: PROC[pitch: INTEGER, state: KeyState, toc: LONG CARDINAL] =
keeps pending list sorted by toc {
i: CARDINAL ← 0;
p: POINTER TO PendingEvent;
IF toc<lastTOC THEN Error[]; -- runtime check of invariant
IF LOOPHOLE[toc, LONG INTEGER]<0 THEN Error[];
UNTIL pendingArray[i].used = FALSE DO i ← i + 1; ENDLOOP;
IF i >= pendingLength THEN Error[];
pendingArray[i] ← [NIL, NIL, pitch, state, TRUE, toc];
IF pending = NIL OR toc < pending.toc
THEN {
pendingArray[i].next ← pending;
pending ← @pendingArray[i]}
ELSE FOR p ← pending, p.next DO
IF p.next = NIL OR toc < p.next.toc THEN {
pendingArray[i].next ← p.next;
pendingArray[i].back ← p;
IF p.next#NIL THEN p.next.back ← @pendingArray[i];
p.next ← @pendingArray[i];
EXIT};
ENDLOOP;
};
FlushPending: PROC[time: LONG CARDINAL] = {
temp: POINTER TO PendingEvent;
IF time<offset THEN time ← offset;
time ← Scale[(time-offset), 128, meter]; -- adjust for metrenome
WHILE pending#NIL AND time> pending.toc DO
enter pending events
AddEvent[pending.pitch, pending.state, pending.toc];
temp ← pending;
pending ← pending.next;
temp.used ← FALSE;
ENDLOOP;
};
AddEvent: PROC[pitch: CARDINAL, state: KeyState, toc: LONG CARDINAL] = {
OPEN InlineDefs;
i, lastEvent: CARDINAL;
IF state=illegal THEN RETURN;
pitch ← pitch-12;
SetPitchOUTState[pitch, state];
IF toc<lastTOC THEN Error[]; -- runtime check of invariant
insert any spacers necessary
FOR i IN [0..(InlineDefs.HighHalf[toc]-InlineDefs.HighHalf[lastTOC])) DO
lastEvent ← OUTbuffer.length;
IF lastEvent>=OUTbuffer.maxLength THEN {lastEvent ← 0; GetNextOutputBuffer[]};
OUTbuffer.data[lastEvent] ← nullEvent;
OUTbuffer.length ← lastEvent + 1;
ENDLOOP;
add the event
lastEvent ← OUTbuffer.length;
IF lastEvent >= OUTbuffer.maxLength THEN {lastEvent ← 0; GetNextOutputBuffer[]};
OUTbuffer.data[lastEvent].channelWord ← keyboardOUT[Channel[pitch]];
OUTbuffer.data[lastEvent].htoc ← InlineDefs.LowHalf[toc];
OUTbuffer.length ← lastEvent + 1;
lastTOC ← toc;
};
SetPitchOUTState: PROC[pitch: INTEGER, state: KeyState] = {
channel: CARDINAL ← Channel[pitch];
index: CARDINAL ← pitch MOD 6;
IF debugOutput THEN {
IF keyboardOUT[channel].key[index]=pressed AND state=up THEN Error[];
IF keyboardOUT[channel].key[index]=up AND state=down THEN Error[]};
keyboardOUT[channel].key[index] ← state;
};
InitKeyboardOUT: PROC = INLINE {
FOR i: CARDINAL IN [0..12] DO
keyboardOUT[i] ← [i,[up, up, up, up, up, up]];
ENDLOOP};
Channel: PROC[pitch: CARDINAL] RETURNS[CARDINAL] =
INLINE {RETURN[IF pitch<6 THEN 12 ELSE pitch/6 -1]};
keyboardOUT: ARRAY [0..12] OF ChannelWord;
nullEvent: MusicEvent = [[15,[up, up, up, up, up, up]], 0];
reStart: MusicEvent = [[14,[up, up, up, up, up, up]], 0];
pendingArray: ARRAY [0..pendingLength) OF PendingEvent;
pendingLength: CARDINAL=140;
PendingEvent: TYPE = RECORD[next, back: POINTER TO PendingEvent,
pitch: [-100..300],
state: KeyState,
used: BOOL,
toc: LONG CARDINAL];
******************************************************************
Microcode and buffers
******************************************************************
the microcode gets all of its information through musicIO
musicIO has two queues of buffers: one for input, and one for output.
The microcode only listens if there is an empty buffer on the input queue.
When a buffer gets full, it NOTIFY's listen. The full buffer is found on the input queue.
The microcode will play any buffer on the ouput queue.
There are two pools of buffers. When a buffer has been processed, we put it at the end of its queue.
musicIO: MusicIODescriptor;
INbuffer: EventBufferPTR; -- pointer to current input buffer
unprocessedBuffers: EventBufferPTR;--buffers that haven't been processed by ProcessBuffer
OUTbuffer: EventBufferPTR; -- pointer to current output buffer
temporaryRegisters: ARRAY [0..26) OF CARDINAL;
started: BOOLFALSE;
playing: PUBLIC BOOLFALSE;
listening: PUBLIC BOOLFALSE;
playChannel: ProcessDefs.InterruptLevel;
listenChannel: ProcessDefs.InterruptLevel;
microcode: BOOLTRUE; -- debugging switch
Error: PROC =
{ RealStopMicrocode[]; ERROR; };
InitMicrocode: PROC = {
playBit, listenBit: CARDINAL;
playBit ← FindBit[0];
playChannel ← GetLevel[playBit];
listenBit ← FindBit[playChannel];
listenChannel ← GetLevel[listenBit];
IF playBit=listenBit THEN ERROR;
musicIO ← [NIL, NIL,, listenBit, playBit,@temporaryRegisters, 75145B, 0];
INbuffer ← unprocessedBuffers ← LinkBuffer[];
OUTbuffer ← LinkBuffer[];
};
Gene's procedures for getting a process level
FindBit: PROC[i: CARDINAL] RETURNS[bit: CARDINAL] = {
x, channel: ProcessDefs.InterruptLevel;
FOR x IN ProcessDefs.InterruptLevel DO
IF ProcessDefs.CV[x]#NIL THEN LOOP;
IF x=i THEN LOOP;
channel ← x;
EXIT; ENDLOOP;
bit ← InlineDefs.BITSHIFT[1, LOOPHOLE[channel, CARDINAL]];
};
GetLevel: PROC[bit: CARDINAL] RETURNS[lvl: ProcessDefs.InterruptLevel] = {
cursor: CARDINAL ← 1;
lvl ← 0;
IF bit=0 THEN ERROR;
UNTIL bit=1 DO
bit ← InlineDefs.BITSHIFT[bit, -1];
lvl ← lvl+1;
ENDLOOP;
};
StartMicrocode: PROC[mode: {playing, listening}] = {
IF mode=listening AND listening THEN RETURN;
IF mode=playing AND playing THEN RETURN;
ProcessDefs.DisableInterrupts[];
IF mode=listening
THEN ProcessDefs.CV[listenChannel] ← @listen
ELSE ProcessDefs.CV[playChannel] ← @play;
IF mode=listening THEN
{
musicIO.headOfInputList ← unprocessedBuffers;
INbuffer ← unprocessedBuffers;
listening ← TRUE;
};
IF mode=playing THEN playing ← TRUE;
ProcessDefs.EnableInterrupts[];
IF mode=listening THEN Screen.InvertListen[];
IF mode=playing THEN Screen.InvertPlay[];
IF started THEN RETURN;
RegisterInit[];
MainMusicPTR^ ← @musicIO;
started ← TRUE;
RealStartMicrocode[! ANY => {
IF mode=listening THEN Screen.InvertListen[];
IF mode=playing THEN Screen.InvertPlay[];
Screen.DisplayMessage["Please load microcode!!! (loadmb music.mb)"];
listening ← playing ← FALSE;
started ← FALSE;
flash ← TRUE;
CONTINUE}];
IF debugOutput THEN IODefs.WriteLine["music started"];
};
RegisterInit: PROC = {
i: CARDINAL;
FOR i IN [0..25) DO musicIO.microcodeTemps[i] ← 0; ENDLOOP;
musicIO.microcodeTemps[25] ← 100000B;
};
StopMicrocode: PROC[mode: {playing, listening}] = {
IF mode=playing THEN {
IF ~playing THEN RETURN;
ProcessDefs.DisableInterrupts[];
ProcessDefs.CV[playChannel] ← NIL;
musicIO.headOfOutputList ← NIL;
playing ← FALSE;
ProcessDefs.EnableInterrupts[];
Screen.InvertPlay[];
IF listening THEN RETURN};
IF mode=listening THEN {
IF ~listening THEN RETURN;
ProcessDefs.DisableInterrupts[];
ProcessDefs.CV[listenChannel] ← NIL;
musicIO.headOfInputList ← NIL;
listening ← FALSE;
ProcessDefs.EnableInterrupts[];
Screen.InvertListen[];
IF playing THEN RETURN};
IF ~started THEN RETURN;
MainMusicPTR^ ← NIL;
RealStopMicrocode[];
started ← FALSE;
};
CleanupMicrocode: ImageDefs.CleanupProcedure =
{
RealStopMicrocode[];
};
RealStartMicrocode: PROC =
MACHINE CODE { Mopcodes.zMISC, 244B };
RealStopMicrocode: PROC =
MACHINE CODE { Mopcodes.zMISC, 245B };
initialize the EventBuffers
LinkBuffer: PROC RETURNS[b: EventBufferPTR] = {
j: EventBufferPTR;
i: EventBufferPTR;
j ← SystemDefs.AllocateSegment[2*bufferLength+7];
j^ ← [NIL, bufferLength, 0,, ALL[[LOOPHOLE[0], 0]] ];
i ← SystemDefs.AllocateSegment[2*bufferLength+7];
i^ ← [j, bufferLength, 0,, ALL[[LOOPHOLE[0], 0]] ];
b ← SystemDefs.AllocateSegment[2*bufferLength+7];
b^ ← [j, bufferLength, 0,, ALL[[LOOPHOLE[0], 0]] ];
RETURN;
};
length: CARDINAL; -- debugging aid
GetNextInputBuffer: PROC = {
length ← INbuffer.length;
INbuffer.length ← 0;
unprocessedBuffers ← INbuffer.chainPTR;
INbuffer.chainPTR ← NIL;
Append[unprocessedBuffers, INbuffer];
INbuffer ← unprocessedBuffers;
IF musicIO.headOfInputList=NIL AND listening THEN {
musicIO.headOfInputList ← unprocessedBuffers;
IF debugInput THEN IODefs.WriteLine["add to musicIO input."]};
IF debugInput THEN WriteList[musicIO.headOfInputList,"headOfInputList= "];
IF debugInput THEN WriteList[INbuffer,"INbuffer list= "];
};
GetNextOutputBuffer: PROC = {
WriteCurrentOutputBuffer[];
IF OUTbuffer = NIL THEN Error[];
WHILE OUTbuffer = musicIO.headOfOutputList DO WaitOnPlay[]; ENDLOOP;
OUTbuffer.length ← 0;
};
WriteCurrentOutputBuffer: PROC = {
l: EventBufferPTR;
IF debugOutput THEN WriteBuffer[OUTbuffer];
l ← OUTbuffer.chainPTR;
OUTbuffer.chainPTR ← NIL;
Append[l, OUTbuffer]; -- l is most likely already on musicIO.headOfOutputList
IF musicIO.headOfOutputList = NIL AND playing
THEN { -- but if it isn't, then put OUTbuffer on
musicIO.headOfOutputList ← OUTbuffer;
IF debugOutput THEN IODefs.WriteLine["add to musicIO output."];
};
OUTbuffer ← l;
IF debugOutput THEN WriteList[musicIO.headOfOutputList,"headOfOutputList= "];
IF debugOutput THEN WriteList[OUTbuffer,"OUTbuffer list= "];
};
Append: PROC[list, buffer: EventBufferPTR] = INLINE {
p: EventBufferPTR;
IF list = NIL THEN RETURN;
FOR p ← list, p.chainPTR DO
IF p.chainPTR = NIL THEN { p.chainPTR ← buffer; EXIT; };
ENDLOOP;
};
******************************************************************
testing procedures
******************************************************************
debugInput, debugOutput: BOOLFALSE;
WriteList: PROC[b: EventBufferPTR, header: STRING] = {
OPEN IODefs;
p: EventBufferPTR;
WriteString[header];
IF b=NIL THEN { WriteLine["NIL"]; RETURN; };
FOR p ← b, p.chainPTR DO
IF p=NIL THEN { WriteLine[";"]; EXIT; };
WriteNumber[LOOPHOLE[InlineDefs.LowHalf[p], CARDINAL],[8, FALSE, TRUE, 7]];
ENDLOOP;
};
WriteBuffer: PROC[b: EventBufferPTR] = {
OPEN IODefs;
i, oldtoc: CARDINAL ← 0;
e: MusicEvent;
WriteLine[""];
WriteString["buffer="];
WriteNumber[b.length,[10, FALSE, TRUE, 4]];
WriteLine[""];
WriteLong[musicIO.time];
WriteLine[""];
FOR i IN [0..b.length) DO
{
e ← b.data[i];
IF e.channelWord.channel = 15 THEN
{ WriteLine["wrap around"]; LOOP; };
IF e.channelWord.channel = 14 THEN
{ WriteLine["reset clock to 0"]; LOOP; };
WriteString["channelword="];
WriteNumber[e.channelWord.channel,[10, FALSE, TRUE, 3]];
FOR i: CARDINAL IN [0..6) DO
WriteNumber[e.channelWord.key[i],[10, FALSE, TRUE, 2]];
ENDLOOP;
WriteString[" htoc="];
WriteNumber[e.htoc,[10, FALSE, TRUE, 6]];
IF e.htoc < oldtoc
THEN WriteLine["!!!!!"]
ELSE WriteLine[";"];
oldtoc ← e.htoc;
}; ENDLOOP;
};
WriteLong: PROC[lc: LONG CARDINAL] = INLINE {
IODefs.WriteNumber[InlineDefs.HighHalf[lc],[10, FALSE, TRUE, 4]];
IODefs.WriteNumber[InlineDefs.LowHalf[lc],[10, FALSE, TRUE, 4]];
};
END.