*-----------------------------------------------------------------------------------------
Title[DMesaMusic...January 27, 1981 2:57 PM...gmcd];
*-----------------------------------------------------------------------------------------
%*+++++++++++++++++++++++++++++++++++++++++++++++++++++

CONTENTS, by order of occurence
MUSIC opcodes -- Part of Miscellaneous opcode -- catchall for many sins

Special operations defined on Dorado only:
alpha=244bstart music
alpha=245bStop music
alpha=246bwrite/read dwatch
%*+++++++++++++++++++++++++++++++++++++++++++++++++++++
TopLevel;

%*+++++++++++++++++++++++++++++++++++++++++++++++++++++
Here is a pseudo mesa version of the work done by this microcode.

-- Begin w/ "global variables". They correspond to dedicated RM registers and dedicated base registers.

iX: INTEGER;
-- index into input array. IF iX<0 THEN no Inputvec
oX: INTEGER;
-- like iX, except for output
liX, loX: INTEGER;
-- last acceptable iX, oX
channel: CARDINAL;
-- current channel we’re looking at
counter: CARDINAL;
-- counter for time
lChannel: CARDINAL=12;
-- last acceptable channel number
inputVal: UNSPECIFIED;
-- value provided to us from hardware

tInterruptStatus: {good, halt, NoBuffer}

pMusicControl: POINTER to LONG POINTER TO tMusicControl;

iBR, oBR, inVec, outVec: LONG BASE POINTER TO tMusicTable;
-- base registers for input and output

-- consider making inVec, outVec one BR and making the scratch area bigger so that we can add a fixed number (20B?) to the channel number to address the output registers given the base register points to the input registers

tMusicControl: TYPE = MACHINE DEPENDENT RECORD[
pInput: LONG POINTER TO tMusicBlock,
pOutput: LONG POINTER TO tMusicBlock,
inputStatus: tInterruptStatus,
outputStatus: tInterruptStatus,
intsIn: WORD,
intsOut: WORD,
vec: LONG POINTER TO ARRAY[0..25] OF UNSPECIFIED,
-- microcode storage
MusicSeal: CARDINAL=75145B,
time: LONG CARDINAL ]; -- time must be zero’d before initing music microcode, or issue a reset before seriously using the microcode

tMusicBlock: TYPE = MACHINE DEPENDENT RECORD[
pNext: LONG POINTER TO tMusicBlock,
size: INTEGER,
nEntries: INTEGER,
status: WORD,
data: ARRAY[0..0) OF tMusicEvents ]

tMusicEvents: TYPE = MACHINE DEPENDENT RECORD[
channel:[0..17B],
val:[0..7777B],
time: CARDINAL ]

-- Here is the code. First the main loop, then the support procedures.

DO
-- this is the main loop that does everything
WAIT musicWakeup;
doInput[];
doOutput[];
IF (channel← channel+1)>lastChannel THEN checkNewEvents[];
ENDLOOP;


doInput: PROCEDURE={
inputVal← INPUTnoPE;
IF inputVal#inVec[channel] THEN newInput[];}

doOutput: PROCEDURE={
OUTPUT← BITOR[inputVal, outVec[channel]];};

newInput: PROCEDURE={
inVec[channel]← inputVal;
-- update our scratch registers
nextIX[];
IF iX<0 THEN RETURN;
musicEvent← tMusicEvent[channel:channel, val: inputVal, time: counter];
iBR.data[iX]← musicEvent;};

checkNewEvents: PROCEDURE={
time← counter← counter+1;
IF counter=0 THEN newTimeWraparound[];

getOX[];
IF oX<0 THEN RETURN;
-- no output table

IF oBR.data[oX].channel=timeWraparound
-- waiting for wraparound?
THEN IF counter#0
THEN RETURN
ELSE nextOX[];
-- on to next output event
IF oX<0 THEN RETURN;
-- much check oX after every increment

WHILE counter>= oBR.data[oX].time DO
IF oBR.data[oX].channel=timeWraparound THEN RETURN;
IF oBR.data[oX].channel=timeReset THEN BEGIN
counter← 0;
nextOX[];
IF oX<0 THEN RETURN;
LOOP;
END;
temp← oBR.data[oX].channel;
outVec[temp]← BITOR[oBR.data[oX].value];
IF channel=lChannel THEN outVec[temp]← BITOR[outVec[temp], 100000B]
nextOX[];
IF oX<0 THEN RETURN;
ENDLOOP;
};

newTimeWraparound: PROCEDURE={
nextIX[];
IF iX<0 THEN RETURN;
musicEvent← tMusicEvent[channel:timeWraparound, val: 0, time:0];
iBR.data[ix]← musicEvent };
%*+++++++++++++++++++++++++++++++++++++++++++

* January 27, 1981 2:56 PM

* The RM and BR definitions assume that no other part of the emulator or io microcode will use them. Beware. This is an important dependency that must be guaranteed by the programmer!

SetRMRegion[Region15];
RVN[counter];
RVN[iX];
RVN[ox];RVN[liX];RVN[loX];
RVN[iChnl];
RVN[oChnl];RVN[lChannel];RVN[musicVal];
RVN[musicTemp0];
RVN[musicTemp1];RVN[musicRet0];RVN[musicRet1];
RVN[musicRet2];
RVN[viX];RVN[voX];

BR[inVecMusicBR, 3];
* temp storage for music input values
BR[outVecMusicBR, 6];
* temp storage for music output values
BR[musicControlBR, 12];
* point to master music control block
BR[iBR, 13];
* point to current music input control block
BR[oBR, 16];
* point to current music outpout control block

mc[musicStartLocC, 361];
* absolute addresses for starting and stopping
mc[musicStopLocC, 362];
* the music task.

mc[musicTaskC, 5];
set[musicTask, 5];

mc[mu.Tioa, lshift[2, 10]];
* This is the music Tioa address
mc[mu.sftb, 100000];
* STart the music hardware From The Bottom of fifo
mc[mu.stopMusic, 40000];
* turn off running in music hardware.

* MUSIC CONTROL BLOCK

mc[mu.iMusic0C, 400];
mc[mu.iMusic1C, 15];* located at MDS[415]

msc[iInput0S,0];
msc[iInput1S, 1];* LONG pointer to input block
msc[iOutput0S,2]; msc[iOutput1S,3];
* LONG pointer to outoput block
msc[iStatusS,4];
* music status word
msc[iIntsInS, 5];
* input interrupt word
msc[iIntsOutS, 6];
* output interrupt word
mc[mu.iMusicControlRegs, 7];
* LONG pointer to InRegs,,Outregs
msc[iRegs0S, 7];
mc[mu.iMusicSeal, 11];
* must be "seal" for us to believe it
mc[mu.timeLowBits, 12];
* LONG CARDINAL=time
mc[mu.timeHiBits, 13];

set[seal, 75145];
* MUSIC Control Block must have "seal" value
mc[mu.sealHiC, AND[seal,177400]];
* otherwise, microcode will ignore it.
mc[mu.sealLoC, AND[seal,377]];

* Status Values. "left" half is input, "right" half is outpout.

mc[mu.statusInputOff, lshift[1,10]];
mc[mu.statusOutputOff, 1];
mc[mu.statusInputDry, lshift[2,10]];
mc[mu.statusOutputDry, 2];
mc[mu.statusInDone, lshift[4,10]];
mc[mu.statusOutDone, 4];
mc[mu.statusOutputMaskC, 377];
mc[mu.statusInputMaskC, 177400];

* FORMAT of values received from music hardware.
* <channel: 4 bits>,, <musicData: 12bits>

set[mu.channelSZ, 4];
set[mu.channelPos, 14];
mc[mu.wraparoundVal, 17];
mc[mu.WraparoundChannel, 170000];
mc[mu.resetTimeChannel, 16];
mc[mu.dataMaskC, 7777];

* MUSIC BLOCK. Input and output blocks look the same to us.

msc[ipNext0S, 0]; msc[ipNext1s, 1];
* LONG pointer to next block
msc[iMaxEntriesS, 2];
* used for Input blocks
msc[inEntriesS, 3];
* we set this during input done
*msc[iStatusS,4];
* music status word (defined above)
mc[mu.dataOffsetC, 5];
* offset to data entries

StartMusic: MiscTable[244];
subroutine;
t← musicStartLocC;
taskingOff;
link←t;
t← musicTaskC;
top level;
LdTpc← t;
taskingOn;
notify[musicTask];
Stkp-1, IFUNext0;

StopMusic: MiscTable[245];
subroutine;
t← musicStopLocC;
taskingOff;
link←t;
t← musicTaskC;
top level;
LdTpc← t;
taskingOn;
notify[musicTask];
Stkp-1, IFUNext0;

%
This code inits the music task’s BRs and RM.
%
set[xtask,1];
MusicStart:
MemBase← MDS, at[musicStartLocC!];
t← mu.TIOA;* set TIOA very early.
TIOA← t;
RBase← rbase[counter];
call[makeMusicControl];* accommodate microd by setting rbase separately
branch[musicErrHalt, ALU=0];* pMusicControl=0

* do nothing if music seal is incorrect.

iMusicSeal:
t← mu.iMusicSeal;
Fetch←t;
t← mu.sealHiC;
t← t or (mu.sealLoC);
(Md) # (t);
branch[.+2, ALU=0], t← viX← -2C;* init viX, voX to -2 as initial states
branch[stopMusic];* seal is incorrect, do nothing

iMusicBrs:
oX←t;
iX←t;* for paranoia!
voX← t, call[makeMusicInputPtrs];* init iBR
call[makeMusicOutputPtrs], memBase← musicControlBR;* init oBR

* now init inVecMusicBR, outVecMusicBR
* bad error when we don’t get any scratch registers (musicControlBR.pRegs=0).


MemBase← musicControlBR;
t← mu.iMusicControlRegs;
t← (Fetch←iRegs0S)+1;
Fetch←t, t← Md;

(musicTemp0←Md) or t;
branch[.+2,ALU#0], MemBase← inVecMusicBR;
branch[musicStop];

BrLo←t;* inVecMusicBR← musicControl.pRegs
BrHi← musicTemp0;

MemBase← outVecMusicBr;* outVecMusicBR← musicControl.pRegs+13
t← t+ (15C);
branch[.+2, carry’], musicTemp0← musicTemp0;
musicTemp0← (musicTemp0)+1;
BrLo← t;
BrHi← musicTemp0, t← a0;

iMusicHwre:
* channel, lChannel, & initial music hardware init is left.

lChannel← 14C;* [0..11] are acceptable channels (13 total)

iChnl← a0;
oChnl← 3C;* 12 channels and 16 wds in Fifos: we’ll precess

musicTemp0← mu.stopMusic;* turn off music before we use it. this
Output← musicTemp0;* guarantees Fifo pointers begin at zero!

counter← t;* time begins w/ 0
musicTemp1← Cnt;* save & restore Cnt
musicTemp0← 13C;* 12 consecutive 0s into Fifo
Cnt← musicTemp0;

iMusicFifo:
taskingOff;* turn off tasking and fill the output fifo
Output← t;* t=0 from above
musicTemp0← t← mu.sftb;
(Output←t), t←a0;* First output
branch[.,CNT#0&-1], Output←t;* 12 more outputs: 16 wds to Fills up
Output←musicTemp0;* begin new series (we’ve done 13 outputs)
Output←t;* output 15
Output←t;* output 16. NOW, Fifo output pointer is 0

taskingOn;
MemBase← inVecMusicBR;
Cnt← musicTemp1;
branch[mainLoop], Fetch←iChnl, block;


MusicStop:
t←mu.stopMusic, at[musicStopLocC!];
musicStop2:
branch[.],OUTPUT←t , block;
musicErrHalt:
branch[musicStop2];

%
September 18, 1980 12:18 PM

There are two pointers, one into the current input table and one into the current output table. The value we input from the music hardware corresponds to iChnl, and the value we output corresponds to oChnl.
The main loop for music begins w/ the assumption that Md=inVec[iChnl]. Compare the new input value with the old, and update the old value if required. The output value should reflect whatever the user wants done (contents of the output table) or’d with whatever the synthesizer claims is happening at the keyboard. Thus the output value = inVec[oChnl] OR outVec[oChnl]. Increment iChnl, oChnl and fetch in old input value for that channel before we block.
%
KnowRbase[counter];

mainLoop:
musicVal← InputNoPe, t←Md;* assume Md= inVec[iChnl];
PD← musicVal;
Branch[.+2, ALU=0];
nop;
t#(musicVal), MemBase← outVecMusicBR;
branch[updateMusicInput, ALU#0], Fetch← oChnl;

musicOutput:
MemBase← inVecMusicBr;
Fetch← oChnl, t←Md;
t← (Md) or t;* t← inVec[oChnl] OR outVec[oChnl]
Output← t, t← iChnl← (iChnl)+1;* increment for next wakeup
MemBase← inVecMusicBr, (lChannel)- t;
branch[.+2, ALU>=0], t← oChnl← (oChnl)+1;
iChnl← a0;* fix input channel wraparound
(lChannel)-t;
branch[mainLoop, ALU>=0], Fetch← iChnl, block;

checkNewEvents:
oChnl← a0;
call[getMusicControl], counter← (counter)+1;* increment time counter.
(Pd)← Md;
branch[musicIsOff, ALU=0];
musicTemp0←mu.timeLowBits;
call[setMusicControl];
t← musicTemp0;

* If music is still turned on we update the LONG CARDINAL in the control block
*
I believe that since we set MemBase to be MusicControlBR (above) that we may be able to bum-out some microcode below. think about it.

Store←t, DBuf←counter, PD←counter;
branch[checkNewCont, ALU#0], t← t+1;
Fetch←t;* counter was zero. update hibits of time and
musicTemp0← (Md)+1;* check for music input event on wraparound
branch[musicWraparound], Store←t, DBuf←musicTemp0;

* January 23, 1981 4:24 PM

checkNewCont:
nop;

checkNew1:
* see if the current output event is a time wraparound event. If not, keep going. Otherwise, we will just return unless counter=0 (ie., the time wraparound has occured).

call[getOX];* Leaves MemBase as oBR
branch[checkNewRet, ALU<0], t← (Fetch←oX)+1;
nop;
call[musicGetChannel], Fetch← t, musicTemp0←Md;
t#(mu.wraparoundVal);
branch[musicWaitForWrap, ALU=0], t#(mu.resetTimeChannel);
branch[checkNewL, ALU#0], (counter)-(Md);
branch[resetCounter], t←mu.timeLowBits;

checkNewL:
* Enter w/ Pd= counter-eventTime, musicTemp0=wd0 of current event. If the time has come we’ll add the current event to outVec. Otherwise we exit the loop.

branch[.+2, ALU=0], MemBase← outVecMusicBR;
branch[checkNewRet2], MemBase← inVecMusicBR;*not yet time for next event
nop;

call[musicGetChannel];* rtns t=channel number
t#(mu.resetTimeChannel);
branch[checkNewNoReset, ALU#0], musicTemp0← (musicTemp0)and(mu.dataMaskC);

* Zero counter and goto next event
branch[resetCounter], t←mu.timeLowBits;

checkNewNoReset:
Store←t, DBuf← musicTemp0;* update outVec[channel]
t#(lChannel);
branch[.+2, ALU#0], musicTemp0← (musicTemp0) OR (mu.sftb);
Store←t, DBuf←musicTemp0;* set sftb IF this is last channel
nop;

checkNewL2:
* get next music output event, loop to checkNewL if we find one.
call[nextOX];
branch[checkNoBuf, ALU<0], t← (Fetch←oX)+1;
Fetch←t, musicTemp0← Md;
branch[checkNewL], (counter)-(Md);

* return to main music loop

checkNewRet:
MemBase← inVecMusicBR;
checkNewRet2:
branch[mainLoop], Fetch← iChnl, block;

* reset the counter values in the music control block. Enter w/ t=mu.timeLowBits. After zerong the counter values we proceed to checkNewL2 where we look for the next ouptupt event.

resetCounter:
MemBase← MusicControlBR, counter←a0;
t← (Store←t)+1, DBuf← counter;
branch[checkNewL2], Store←t, DBuf← counter;

checkNoBuf:
branch[checkNewRet2], MemBase← inVecMusicBR;

musicWaitForWrap:
* current output event is to wait for wraparound
PD← counter, MemBase← inVecMusicBR;
branch[.+2, ALU=0];* just return unless we’ve just wrapped around
branch[checkNewRet2];

* we were waiting for wrap and got it. move on to next output event
call[nextOX];
branch[checkNew1];* see if new event is wraparound event.

musicWaitNo:
branch[checkNewRet2], MemBase← inVecMusicBR;


*
We could use this subr in a conditional call. However, micro/d doesn’t
*
support that sort of use.

musicGetChannel: subroutine;
return, t←ldf[musicTemp0, mu.channelSZ, mu.channelPos];
top level;

musicIsOff:
* come here after we find that the programmer has zeroed our pointer to the music control block. Generate the appropriate interrupts w/ "halted" status, turn off the music wakeup and commit suicide. Only another task can restart us.

MemBase← musicControlBR;
t← mu.statusInputOff;
t←t or (mu.statusOutputOff);
Store←iStatusS, DBuf← t;
Fetch← iIntsInS;
Fetch← iIntsOutS, t←Md;
RBase← RBASE[nww];* accommodate MdI’s delay
t←t or (Md);
t← t and (77777C);
nww← (nww) or t, RBase← RBASE[counter];
reschedule, t←a0;
branch[musicStop];* turn off our wakeup.
musicDead:
branch[.], OUTPUT← t, block, breakpoint;

* we’ve incremented counter and wrapped around. Add a wraparound event to the user’s input table if there’s a table and room in it. We return to checkNew1.

musicWraparound:
call[nextIX];* returns w/ PD=iX
branch[.+2, ALU>=0], MemBase← iBR;
branch[checkNew1];

t← mu.WraparoundChannel;
t← (Store← iX)+1, DBuf← t;
branch[checkNew1],Store←t, DBuf← counter;



* come here when we discover the new input value is different from the old input value. We may have to add a new event to the user’s input block (if there is a block with room).

updateMusicInput:

MemBase← inVecMusicBR, t← iChnl;
Store← t, DBuf← musicVal, call[nextIX];* get pointer (>=0) into user’s input block

branch[updateMusicRet, ALU<0],t← lsh[iChnl, mu.channelPos];
t←t or (musicVal);
t← (Store← iX)+1, DBuf←t;* wd0← [iChnl#, inputVal]
Store←t, DBuf← counter;* wd1← [time]

updateMusicRet:
MemBase← outVecMusicBR;
branch[musicOutput], Fetch← oChnl;

%
Come here when we want the index for the next input event to go into the user’s input block. This routine returns with PD←iX to facilitate easy testing. IF iX<0 then there’s no input slots available. IF ix>=0 THEN MemBase=iBR upon return

Upon entry, viX=-2 means that we’ve a new block to use (for initial starup conditions, etc.)
%

nextIX: subroutine;
musicRet0← link;
top level;
MemBase← musicControlBR, call[isMusicOff];
branch[.+2, ALU=0];
branch[nixRet], ix←-2C;
call[makeMusicInputPtrs];* returns ALU<0 if buffer ptrs=0
branch[nixRet, ALU=0], iX←-2c;

t←(viX)+1;* nixNewBuffer depends upon musicTemp0, t.
branch[.+2, ALU>=0];* incremented viX<0 means no current block
branch[nixNewBuffer], ix← mu.DataOffsetC;
Store← inEntriesS, DBuf← t;* update iBr.nEntries
t← viX← (viX)+1;
(liX)-t;* goto next buffer of overflow
branch[nixBuffer, ALU<0], t← t+t;
branch[nixRet2], iX← t← t+(mu.dataOffsetC);* compute true offset = (2*viX)+offset

nixRet: subroutine;
MemBase← iBR;
nixRet2:
link← musicRet0;
return, PD← iX;* leave w/ MemBase=iBR when iX>=0
top level;
%
Come here when we discover that this is initial entry

MemBase=musicControlBR
%
nixNewBuffer:
MemBase← musicControlBR;
nixBuffer:
* we’ll update iBR.status if there’s no
call[getMusicInputPtrs];* next block. THEREFOR assume iBR valid!
branch[nixOut, ALU=0], iX← mu.dataOffsetC;* assume new block (ix←0)
nop;* for placement
call[setMusicInputPtrs];* update iBR for next efforts.

Fetch← iMaxEntriesS;* We’ll wait a while before using Md
MemBase← musicControlBR;* update musicControl.pInput -- 2 words
Store← iInput0S, DBuf← t;
Store← iInput1S, DBuf← musicTemp0;

Pd←(viX)+1;* see if all new game or we just completed
branch[.+2, ALU<0], liX←Md;* one block and we’ve moved on to next one.
call[setMusicInputStatus], t←mu.statusInDone;* leave MemBase=iBr
Pd← liX;* if new block has maxEntries=0, try next one
branch[nixBuffer2, ALU#0], viX← a0;
branch[nixBuffer], MemBase← iBR;* release this buffer & try next one.

nixBuffer2:
branch[nixRet], iX← mu.dataOffsetC;

* Come here when we’ve no more blocks to process.

nixOut:
MemBase← musicControlBR, t←a0;* musicControl.pInput←0
Store← iInput0S, DBuf←t;
Store← iInput1S, DBuf←t, iX←not(t);* ix=-1 means no input blocks
call[setMusicInputStatus], t←mu.statusInputDry;
viX← -2c;
branch[nixRet2], MemBase← iBR;

nixTurnedOff:
t←viX← -2C;
ix←t;
call[setMusicInputStatus], t←mu.statusInputOff;
branch[nixRet2], MemBase← iBR;

setMusicInputStatus: subroutine;
musicRet1← link;
top level;
MemBase← musicControlBR, musicTemp0←t;
call[musicSetNWWfromMd], Fetch← iIntsInS;
Fetch←iStatusS;
t←Md;
t←t and (mu.statusOutputMaskC);
t←t or (musicTemp0);
Store← iStatusS, DBuf←t;
MemBase← iBR;
Store←iStatusS, DBuf← musicTemp0;
subroutine;
link← musicRet1;
return;

musicSetNWWfromMd: subroutine;
RBASE← rbase[nww], t←Md;
t←t and (77777C);
nww← (nww)or t, reschedule;
return, RBASE← rbase[counter];

getOX: subroutine;
* Return current value of oX. IF voX<0 (no output block), invoke getIX to see if one has appeared recently.

PD← voX, MemBase← oBR;
branch[.+2, ALU<0];
return, PD← oX;
musicRet2← link;
top level;
call[nextOX];* see if user has provided any output
subroutine;
link← musicRet2;
return, PD← oX;

%
Come here when we want the index for the next output event to go into the user’s output block. This routine returns with PD←oX to facilitate easy testing. IF oX<0 then there’s no output slots available. IF ox>=0 THEN MemBase=oBR upon return

When this routine gets control the user may have recently zeroed the output pointer in the main music control block. We must accommodate this situation. Also, the user may recently have placed a non zero value in the formerly zero output pointer of the control block.

IF viX=-2 upon entry, it means that the output block used to be zero.
%

nextOX: subroutine;
musicRet0← link;
top level;

t← (voX)+1;* IF no current output block, see if
branch[isNoxOff, ALU<0], musicTemp1← t;* musicControlBR.pOutput #0. We depend upon musicTemp1 validity across call to getMusicOutputPtrs.

* must be so:
*
musicControlBR#0
*
oBR#0
*
musicControlBR.pOutput=0 means user recently zero’d it.

MemBase← musicControlBR;
call[getMusicOutputPtrs];* musicPtrs=0 ==> user turned off Output
branch[noxTurnedOff, ALU=0], t← musicTemp1;* noxTurnedOff depends upon old voX

(loX)-t;* goto next buffer if overflow
branch[noxBuffer, ALU<0], MemBase← oBR;
voX←t;* we are happy w/ increment. update voX, oX
t←t+t;
branch[noxRet2], oX← t← t+(mu.dataOffsetC);* compute true offset = (2*voX)+offset

noxRet: subroutine;
MemBase← oBR;
noxRet2:
link← musicRet0;
noxRet3:
return, PD← oX;* leave w/ MemBase=oBR when oX>=0
top level;

noxCheckNew:
branch[noxRet];* fix this later
%
Come here when we’re checking the next buffer pointer for non-zero. We have exhausted the current output block.

MemBase=oBR
%
noxBuffer:
call[getMusicNextPtrs];* see if oBR.pNext#0
branch[noxOut, ALU=0], MemBase← oBR;
BrLo←t;* assume new block
BrHi← musicTemp0;* oBR now points to new output block

Fetch← inEntriesS;* We’ll wait a while before using Md

* Come here from isNoxOff when we discover a new output pointer.
noxBuffer2:
MemBase← musicControlBR;* update musicControl.pOutput -- 2 words
Store← iOutput0S, DBuf← t;
Store← iOutput1S, DBuf← musicTemp0;

loX← (Md)-1;
call[setMusicOutputStatus], t←mu.statusOutDone;* leave MemBase=iBr
Pd← loX;
branch[noxBuffer3, ALU#0], voX← a0;
branch[noxBuffer], MemBase← oBR;* new buffer is empty. see if next one non-empty.

noxBuffer3:
branch[noxRet], oX← mu.dataOffsetC;* now: voX=0, oX=mu.dataOffset


noxTurnedOff:
* Come here if we’ve been turned off.
call[setMusicOUtputStatus], t← mu.statusOutputOff;
t← voX← -2C;
branch[noxRet2], oX←t;

* Last time around we were turned off. See if its still true.
isNoxOff:
MemBase← musicControlBR, call[makeMusicOutputPtrs];* noxBuffer2 depends upon t, musicTemp0
branch[.+2, ALU#0];
branch[noxRet3], link← musicRet0;
branch[noxBuffer2], Fetch← inEntriesS;


noxStillOff:
branch[noxRet];

* Come here when we’ve no more blocks to process.

noxOut:
MemBase← musicControlBR, t←a0;* musicControl.pOutput←0
Store← iOutput0S, DBuf←t;
Store← iOutput1S, DBuf←t, oX←not(t);* ix=-1 means no output blocks
call[setMusicOutputStatus], t←mu.statusOutputDry;
voX← -2c;
branch[noxRet2], MemBase← oBR;


setMusicOutputStatus: subroutine;
Pd← (voX)+1, MemBase←musicControlBR;
branch[.+2, ALU>=0], musicRet1← link;
return;
top level;
Fetch← iIntsInS, musicTemp0←t;* Perform fetch separate from call since
call[musicSetNWWfromMd];* musicSetNWWfromMd called from nix, nox(microd problem)
Fetch←iStatusS;
t←Md;
t←t and (mu.statusInputMaskC);
t←t or (musicTemp0);
Store← iStatusS, DBuf←t;
MemBase← oBR;
Store←iStatusS, DBuf← musicTemp0;
subroutine;
link← musicRet1;
return;

%
These routines read musicControlBR or a current input/output block to pointers to the next block of interest.

CAUTION: Some subroutines store into musicRet1.

The "get" and "make" subroutines leave t= low bits of ptr, musicTemp0=hi bits.
They also return w/ PD←(musicTemp0) or t (this allows an easy test for "next pointer=0"

The "set" routines assume pointer values from "get" and also set memBase themselves. The Set routines will set MemBase. The "get" routines do not set membase!
%

getMusicNextPtrs:
getMusicInputPtrs: subroutine;
Fetch← iInput0s;
Fetch← iInput1S, t←Md;
return, (musicTemp0←Md) or t;
ife[iInput0s!, ipNext0s!,,err[index.error.w/.getMusicNextPtrs]];

getMusicOutputPtrs: subroutine;
Fetch← iOutput0s;
Fetch← iOutput1S, t←Md;
return, (musicTemp0←Md) or t;
top level;

setMusicInputPtrs: subroutine;
MemBase← iBR;
setMusicBRs:
BrLo←t;
return, BrHi← musicTemp0;

setMusicOutputPtrs: subroutine;
branch[setMusicBrs], MemBase← oBR;

makeMusicInputPtrs: subroutine;
musicRet1← link;
top level;

call[getMusicInputPtrs];
call[setMusicInputPtrs];
subroutine;
link← musicRet1;
return, (musicTemp0) or t;
top level;

makeMusicOutputPtrs: subroutine;
musicRet1← link;
top level;

call[getMusicOutputPtrs];
call[setMusicOutputPtrs];
subroutine;
link← musicRet1;
return, (musicTemp0) or t;
top level;

getMusicControl: subroutine;
musicTemp1← mu.iMusic0C;
musicTemp1← (musicTemp1) or (mu.iMusic1C);
MemBase← Mds;
Fetch← musicTemp1, return;
setMusicControl: subroutine;
MemBase← musiccontrolBR, t←a0;
BrHi← t;
t← Md;
return, BrLo← t;

makeMusicControl: subroutine;
* returns w/ PD← Md==> Pd← musicControlBR
musicRet1← link;
top level;

call[getMusicControl];
call[setMusicControl];
subroutine;
link← musicRet1;
return, Pd← Md;

isMusicOff: subroutine;
* RETURNS ALU=0 IF seal is ok
musicRet1← link;
top level;
call[getMusicControl];
call[setMusicControl];
t← mu.iMusicSeal;
Fetch←t;
t← mu.sealHiC;
t←t or (mu.sealLoC);
t← (Md)#t;
branch[.+2, ALU#0], t←a0;* rtns ALU#0 if seal ok
t← not(t);* get here if seal is good. rtns ALU=177777
subroutine;
link← musicRet1;
return, t← not(t);
top level;