:TITLE[Ether];*Last edited: 15 October 1981 by Fiala

*Ethernet I/O Address Registers
Set[eiData,3];
*Input data used with Input instructions
Set[eimData,Add[LShift[eiTask,4],3]]; *Input data used with memory references

Set[eiHost,1];
*Input data
Set[eStatus,2];
*Status/State register (read)
Set[eoData,1];
*Output data used with Output instructions
Set[eomData,Add[LShift[eoTask,4],1]]; *Output data used with memory references
Set[eState,0];
*State register write
MC[eoState,Or[LShift[eoTask,4],eState]];
*Output control reg from emu
MC[eiState,Or[LShift[eiTask,4],eState]];
*Input control reg from output task

*State Register command words
MC[eSetPurgeMode,260];
*Enables input
MC[eSetOutputEOP,107];
*Enables output, Jam
MC[eEnableInput,220];
MC[eEnableOutput,103];
*Enables Jam
MC[eDisableInput,200];
MC[eDisableOutput,100];
*Clears OutputEOP, disables Jam
MC[eDisableInputOutput,300];
*Disables input, output, clears OutputEOP, Jam


*Status bits (left byte of hardware, right byte of status as posted in memory)
Set[esIColl,200];
*Receiver-detected collision (Jam)
Set[esODL,100];
*Output data late (Underrun)
Set[esIDL,40];
*Input data late (Overrun)
Set[esOColl,20];
*Transmitter-detected collision (Collision)
MC[eCollMask,10000];
*Mask for collision detection
Set[esCRC,10];
*Bad CRC
Set[esOFault,4];
*Output DataFault (masked for now)
Set[esOPar,2];
*Output Bad Parity (masked for now)
Set[esICmd,4];
*Input command issued **Not in hardware:
Set[esOCmd,2];
*Output command issued **for Alto emulation only
Set[esIT,1];
*Incorrectly terminated packet (Bad Alignment)

MC[eiSMask,esIDL,esCRC,esIT];
*Status bits reported for input command
MC[eoSMask,esODL,esOColl];
*Status bits reported for output command
MC[eCmdBits,esICmd,esOCmd];
*Command bits


SetTask[eoTask];

*Registers for output task
Set[eoRB,LShift[And[eoTask,3],4]];
*enforces reg allocation conventions
RV[eoTemp2,Add[eoRB,0]];
RV[eoCount,Add[eoRB,1]];
*Main loop counter
RV2[eoPtr,eoPtrHi,Add[eoRB,2]];
*Buffer base register
RV[eoTemp1,Add[eoRB,4]];
*Temporary registers
RV[eoTemp,Add[eoRB,5]];

SetTask[eiTask];

*RM registers for input task (eoTask+1)
Set[eiRB,LShift[And[eiTask,3],4]];
*enforces allocation conventions
RV[eiTemp2,Add[eiRB,0]];
RV[eiCount,Add[eiRB,1]];
*Main loop counter
RV2[eiPtr,eiPtrHi,Add[eiRB,2]];
*Buffer base register
RV[eiTemp1,Add[eiRB,4]];

RV[eiTemp,Add[eiRB,5]];
*Temporary registers
RV2[eMDS600,eMDS600hi,Add[eiRB,6]];
*Base reg MDS+600 (**Known to Initialize)
RV[eFlag,Add[eiRB,10]];
*input under output flag (reg 10 of eiTask)

*Control block addresses (for Alto emulation, relative to 600)
Set[ePLoc,0];
*Post location
Set[eBLoc,1];
*Interrupt bit mask
Set[eELoc,2];
*Ending word count
Set[eLLoc,3];
*Load mask
Set[eiCLoc,4];
*Input count
Set[eiPLoc,5];
*Input pointer
Set[eoCLoc,6];
*Output count
Set[eoPLoc,7];
*Output pointer
Set[eHLoc,10];
*Host address for address recognition

*Timer masks (slot number is eoTask)
MC[eTimerMask,LShift[5,14]];
*Use Timer State 5 for simple timer

*Microcode post codes (small integer in left half, ones in right half for XOR).
*Note: value is complemented to get constant less than 8 bits. Use XNOR for formation of post code.
MC[esIDon,Not[377]];
*Input done
MC[esODon,Not[777]];
*Output done
MC[esIFul,Not[1377]];
*Input buffer overflowed
MC[esLoad,Not[1777]];
*Load overflow
MC[esCZer,Not[2377]];
*Word count zero in input or output command
MC[esAbrt,Not[2777]];
*Command aborted (by SIO)


%Folklore (HGM 22-Oct-80):

We are emulating a half duplex device with a full duplex controller. That
means that the two portions of microcode have to cooperate. They interact
in 3 places:
1) Output enables Input during retransmission wait if there is a buffer ready.
2) Input resets eFlag when it starts reading a packet.
3) Output disables Input when the timer expires.
Of course, reset has to clear eFlag too.

We can get a timer notify when we don’t want one for two reasons:
1) A packet arrived while we were in retransmission wait (input under output).
2) We were reset (by SIO[3]) during retransmission wait.
In either case, we simply ignore the notify without changing our TPC.
Don’t try to restructure this kludgery without some thought. There is no
way to turn a timer off. It might have expired just as you reset it,
and the hardware doesn’t forget the pending wakeup request in that case.

The silly NOPs in the input microcode are because the input hardware
generates H4 Parity errors. I thought I had them fixed for the Rev P
boards, but they still seem to squeek through occasionally. The fault
handler ingores H4PEs from eiTask. (You can set a flag if you prefer
to crash.) Successful recovery requires several non-memory mi after
Inputs or IOStore4s for three reasons:
1) In the sequence Input (IOStore4) then PFetch, the MC1 microcode does
a wild branch if there is an H4PE. To avoid this 3 non-memory mi are
needed after an Input and 4 after an IOStore4. Interlocking an Input
allows another reference to be made on the mi following the interlock
(?or is one more intervening mi required?; if a PStore tries to store
the data which just got H4PE, is that fatal?).
2) An H4PE may not fault for 2 more mi--i.e., 4 mi following Input or 6
mi following IOStore4 may be executed before the H4PE fault commences.
If an H4PE occurs immediately following LoadPage, it will be impossible
to continue from the fault. Thus a task switch (i.e., Return) can occur
no sooner that the 4th mi following an Input or the 6th mi following IOStore4
because the 1st mi executed by the emulator may in fact be a LoadPage.
3) The fault handler requires that eiTask still be running when the H4PE
fault occurs because it crashes unless current task .eq. eiTask; this
requires 1 mi more than for (2) because the emulator may do a LoadPage as
the 1st mi after wakeup (?Is this accurate--depends upon when CTask is
updated?).

Hence, the requirement is that eiTask task following IOStore4 no sooner
than the 7th mi and following Input no sooner than the 5th mi. If the
Input is interlocked by reading its RM register on the 1st or 2nd following
mi, then the mi doing the interlock counts as the 3rd mi following the Input;
the following mi may then be a PStore1 (?maybe need one intervening mi?);
tasking may occur on the 2nd mi following the interlock.

You need at least 14 cycles (~7 mi) between loads/adds to timers.
The only other place that loads timers is memory refresh in Timer.Mc. There
are 3 mi before that load, and 4 after it before a task switch. Thus we
need at least 4 between our LoadTimer and a return, and 3 before our LoadTimer.

In the Rev N (and earlier) boards, an Output to the state register could set
either/both portions of the flipflops. The 200 and/or 100 bits in the output data
word had to be to enable any action. This causes some confusion since
storing 0 into register 0 of an Ethernet didn’t reset anything. (That’s why
there is an extra loop storing 300 in various hunks of code that are trying
to quiesce all devices.)
For Rev O, the Output must be directed to register 0 of the appropiate task.
(Thus there is no way for the Input task (higher priority) to disable the
output task.) This code will work with either type of board because
1) all the constants include the 100 or 200, and 2) all the Outputs are directed
to the appropiate task. There are only 3 places where this happens:
1) turning on Input from the Output task to enable Input under Output,
2) turning off Input from the Output task because of a reset (SIO[3]) and
3) Turning off things from the Emulator via SIO[3].

This microcode does not correctly emulate some of the fine print of the Alto,
but that doesn’t seem to bother any known software. Examples I have noticed:
1) SIO[1] or SIO[2] during input or output acts like an SIO[3] on the Alto.
2) SIO[1] then SIO[2] leaves input running on Rev P boards.
(You could hear your own packets!)
%

*ETHERNET INITIALIZATION subroutine (executed at eiTask) is only called if
*an Ethernet board is in the machine. It overwrites the mi at eeSIO+1 with:
*
T ← Add[HostN]C, GoToExternal[eeLocB];*T ← host number
*MEMINST, RMOD, RSEL[0:3], ALUF[0:3], BSEL[0:1], F1[0:3]
*MC[ee015hi,0]; MC[ee015lo,0];
*LR, LT, F2[0:3], JC[0:2], JA[0:5], ParITY (Require And[eeLocB,377] odd par)
MC[ee1631hi,041000]; MC[ee1631lo,RShift[And[eeLocB,377],2]];
MC[ee3235,And[eeLocB,3]];
*RSEL[4:5]’, JA[6:7]

*Build the mi "T ← HostNumber, GoToExternal[eeLocB]" from constants
*and the host number read from the controller; ensure that parity is
*correct by xoring F1 and F2 into RSEL[0:3], which are unused.

SetTask[eiTask];

EtherInit:
Input[eiTemp,eiHost], At[EtherInitLoc];*eiTemp ← host number
eiTemp1 ← And[377,eeLocA]C;*eiTemp1 ← eeLocA
eiTemp1 ← (eiTemp1) or (And[7400,eeLocA]C);
T ← LdF[eiTemp,10,4];*T ← Host[0:3] (will be F1)
eiTemp2 ← T;*F1
eiTemp ← LdF[eiTemp,14,4];*F2
T ← eiTemp ← LSh[eiTemp,12];*F2 in position of F2 and RSEL[0:3]
T ← (LSh[eiTemp2,12]) xor T;*T ← F1 xor F2 in RSEL[0:3] field
eiTemp2 ← (eiTemp2) xor T;*Fix parity in RSEL[0:3]
*
eiTemp2 ← (eiTemp2) or (ee015hi);
*
eiTemp2 ← (eiTemp2) or (ee015lo);
eiTemp ← (eiTemp) or (ee1631hi);
eiTemp ← (eiTemp) or (ee1631lo);
T ← ee3235;
LU ← eiTemp2;
APCTask&APC ← eiTemp1;
WriteCS0&2;
LU ← eiTemp, DispTable[1,1,0];*Even placement to preserve TPC
APCTask&APC ← eiTemp1;
WriteCS1;
eMDS600 ← 400C, DispTable[1,1,0];*Even placement
eMDS600 ← (eMDS600) or (200C), Return;

SetTask[0];
*EMULATOR TASK -- Alto SIO, Mesa STARTIO opcode

OnPage[eePage];

*For Alto emulator, return to next opcode after carrying out the action;
*for Mesa, return to caller who exits to next opcode.
**Note that Mesa must save/restore AC0, which is smashed by eeSIO.
*The SIO control bits are in T (bits 16,17).

*eeSIO is assembled in to return 77777b (no Ethernet board present);
*EtherInit overwrites this.
eeSIO:
AC0 ← T;
*Return 77777b if no Ethernet board in machine; overwritten with:
*
T ← Add[HostNum]C, GoToExternal[eeLocB], At[eeLocA];
T ← LdF[AllOnes,1,17], GoTo[eeNone], At[eeLocA];
Dispatch[AC0,16,2], AC0 ← T, NoRegILockOK, At[eeLocB];
RTemp1 ← eDisableInputOutput, Disp[.+1];*AC0 ← host address
*00 -- Do nothing
eeNone:
AC0 ← T, Return, DispTable[4];
*01 -- Start transmitter; form APCTask&APC word to notify output microcode
RTemp ← LoA[eoStartLoc], GoTo[eeSIO1];*Low 8 bits of APC
*10 -- Start receiver; form APCTask&APC word to notify input microcode
RTemp ← LoA[eiStartLoc], GoTo[eeSIO2];*Low 8 bits of APC
*11 -- Reset interface, i.e. abort. Reset Output here,
* then notify Input task to reset Input and post abort.
RTemp ← LoA[eiAbortLoc], GoTo[eeSIO2];*Low 8 bits of APC

eeSIO1:
RTemp ← (RTemp) or (HiA[eoStartLoc,eoTask]), Skip;
eeSIO2:
RTemp ← (RTemp) or (HiA[eiStartLoc,eiTask]);
*Notify appropriate code; also jump here from Initialize.Mc.
eIOReset:
T ← eoState;
*Control returns to caller of eeSIO when emulator runs next
****Long time to task here****
APCTask&APC ← RTemp;
Output[RTemp1], Return;

*INPUT TASK MICROCODE

%Input microcode is notified at eiStart by the emulator (at SIO).
Some initialization is done, and the TPC set up to eiIdle.
Wake up at eiIdle or at eiPostA+1 when the 1st quadword of a new packet
arrives (or the entire packet if less than 4 words long). The wakeup
will be reasserted after tasking whenever there are 4 or more words in
the input buffer or when the last word of a packet is in the buffer.

NOTE: An input data late condition can occur if the receiver is turned
on in the middle of a packet.
%
SetTask[eiTask];

eiStart:
eiTemp ← eEnableInput, Call[eInit], At[eiStartLoc];

*Set up eiPtr and eiCount for single word transfers; eiCount uneven is ok
*because it will be touched before eiPtr, invoking the interlock.
eiIdle:
PFetch2[eMDS600,eiCount,eiCLoc], OddOK;
PFetch1[eMDS600,eiTemp1,eHLoc], Call[ebSetup];*Fetch host address

Input[eiTemp2,eStatus];*Check status for malformed packet
LU ← (eiTemp2) and (100400C);*Jam and bad alignment bits
eiTemp ← eSetPurgeMode, Skip[ALU=0];*Read in first word
Output[eiTemp,eState], GoTo[ERet];*flush bad packet
*Address filtering.
Input[eiTemp2,eiData];
T ← eiTemp1;
LU ← (RSh[eiTemp2,10]) xor T, Skip[ALU#0];
eFlag ← 0C, GoTo[eiBegin];*I am promiscuous host
LU ← RSh[eiTemp2,10], Skip[ALU#0];
eFlag ← 0C, GoTo[eiBegin];*Destination = me
GoTo[eoWrSt,ALU#0];
eFlag ← 0C, GoTo[eiBegin];*Broadcast packet

*Packet accepted by filter.
*EFLAG is set to 0 to tell the output microcode that a packet came in
*(used for input under output).
*ebSetup returns with: eiPtr = IPtr + ICount - 1, eiCount = - ICount
*Check if buffer count zero.
eiBegin:
T ← eiCount ← (eiCount) + 1, Skip[R<0];*R>=0 => count is 0
T ← esCZer, GoTo[eiCount0Post];
PStore1[eiPtr,eiTemp2];
*Compute how many singles before 1st quadword; form loop counter in eiTemp1.
*
Address: x00 => no singles, loop count = -1
*
Address: x01 => 3 singles, loop count = 2
*
Address: x10 => 2 singles, loop count = 1
*
Address: x11 => 1 singles, loop count = 0
*Form start address in T (bypass kludge)
T ← (Zero) + T + 1, Call[ebAlign];
*Loop here until buffer address is quadaligned
eiTemp1 ← (eiTemp1) - 1, GoTo[eiSingle,R>=0];

*Now start quadword input; adjust eiPtr and eiCount for 4-word transfers.
eiQuad:
eiCount ← (eiCount) + (3C), Task;
eiPtr ← (eiPtr) - (6C);
*Loop here to read quadwords from buffer until buffer nearly full or
*IOAtten occurs.
T ← eiCount ← (eiCount) + (4C), GoTo[eiQuadFull,R>=0];
GoTo[eiAttn,IOAtten];
IOStore4[eiPtr,eimData];
*This is so that if the IOStore4 causes an H4PE, it won’t cause a LoadPage
*error in another task. When Return is the 5th mi after IOStore4, the
*6th mi (executed by another task) is aborted on an H4PE, but a LoadPage
*error will be impossible.
Nop;
Nop;
GoTo[ERet];

*Get here when no more room for quadwords; do singles to fill buffer.
*7-eiCount = number of singles remaining in buffer.
*Set up loop counter as (- No. singles), and read in singles.
eiQuadFull:
eiCount ← (eiCount) - (7C);*Even placement
eiPtr ← (eiPtr) + (6C), Call[eiSingle];
*This Nop avoids bypass kludge after PStore1 below and guards against PStore1
*aborted by H4PE and reexecuted without UseCTask true; if that were done,
*IOAtten would be erroneously tested in first mi after tasking.
Nop;
*Can’t test IOAtten in 1st mi after wakeup, so UseCTask below is required.
*On IOAtten, words left in buffer = 1 (CRC) - eiCount
eiSingle:
T ← (eiCount) - 1, GoTo[eiAttnS,IOAtten];*Even placement
Input[eiTemp,eiData];
LU ← eiTemp;**Required interlock for H4PE problem
**Maybe need 1 mi after this before PStore1?
T ← eiCount ← (eiCount) + 1, UseCTask, GoTo[eiBufFull,R>=0];
PStore1[eiPtr,eiTemp], Return;

*We get here when IOAtten is detected while reading quadwords.
*Words left in buffer = 7 - eiCount + 1 (CRC) + Excess count.
eiAttn:
T ← (eiCount) - (10C);
eiAttnS:
Input[eiTemp,eStatus];*Read Status
Nop;*Maybe (?) needed to avoid bypass kludge
T ← (LdF[eiTemp,10,2]) - T;
eiCount ← T;*eiCount ← 8 - eiCount + excess count
eiAttn2:
eiTemp ← RSh[eiTemp,10];*Shift down status
eiTemp ← (eiTemp) and (eiSMask);*Mask out uninteresting status bits
eiTemp ← (eiTemp) xnor (esIDon);*Post input done status
*Store eeCLoc.
eiPost:
PStore1[eMDS600,eiCount,eELoc], Call[eTaskRet];

*Post status, disable interface (purge packet too), and TASK.
*Post status in eiTemp, disable value in eiCount.
eiPostA:
eiCount ← eDisableInput, Call[ePost];*End of packet.
GoTo[eiIdle];*Wakeup here if Input under Output

*We get here when the input buffer is exactly full.
*IOAtten indicates that the last word was the CRC.
eiBufFull:
*Last word input was CRC. Read one more word to see if the next is the CRC
*word (which we will discard).
eiCount ← 0C;*No words left in buffer
T ← esIFul, Call[eTaskRet];
*After wakeup, check IOAtten.
Input[eiTemp,eStatus];*Can’t check IOAtten 1st mi after wakeup
*IOAtten => Word was CRC; else Input buffer overrun => post status
GoTo[eiAttn2,IOAtten];
eiCount0Post:
eiTemp ← (Zero) xnor T;
GoTo[eiPost];**For H4PE problem--one extra mi after
**interlocking Input before PStore1 (?)


*Input microcode is notified here by emulator SIO when AC0[16:17] = 3.
*Manufacture "Abort" status and post. Input hardware will be disabled in case it is on.
eiAbort:
eFlag ← 0C, At[eiAbortLoc];
eiTemp ← eCmdBits;
eiTemp ← (eiTemp) xnor (esAbrt), GoTo[eiPostA];

SetTask[eoTask];

*Output microcode is notified at eoStart by the emulator (at SIO).
* Also get here to try again after a collision.
eoStart:
eoTemp ← eEnableOutput, Call[eInit], At[eoStartLoc];
PFetch1[eMDS600,eoTemp1,eLLoc];*Fetch current load
eoTemp1 ← (LSh[eoTemp1,1]) + 1, Skip[R>=0]; *Form new load, check if old overflowed
eoTemp ← esLoad, GoTo[eoCompPost];*Post Load overflow status
PStore1[eMDS600,eoTemp1,eLLoc];*Store updated load in eLLoc
*Compute countdown interval
*Get random number from "random" register (REFR register used).
T ← (SStkP&NStkP) xor (377C);*Save StkP and
eoTemp2 ← IP[REFR]C;*point to "random" register
StkP ← eoTemp2, eoTemp2 ← T, NoRegILockOK;
T ← LdF[Stack,4,10];*Get bits 4-13 and restore
StkP ← eoTemp2;
eoTemp1 ← (RSh[eoTemp1,1]) and T;*Mask random number
%eoTemp1 had new Load mask, now has desired random interval in Alto ticks.
We would like a tick size of 38 microseconds. The timers on the D0 have a
basic tick size of 64 times the clock speed. If the clock is 100ns, that’s
6.4 microsec. 6*6.4 is 38.4 which is very close. 6*x=2*(2*x)+2*x, so
that’s why there are all those crazy LSHs below.
%
eoTemp1 ← T ← LSh[eoTemp1,1], Skip[ALU#0];
GoTo[eoSetup];
*Before starting timer, check if input is set up.
PFetch1[eMDS600,eoTemp,eiCLoc];
eFlag ← 1C, Task;*Timer wakeups ok now
eoTemp1 ← (LSh[eoTemp1,1]) + T;
T ← (LdF[eoTemp1,7,2]) - 1;
eoCount ← T;*Save high part (minus 1) (2 bits)
LU ← eoTemp;
*Disable output. If the input word count is nonzero, enable the receiver
*while waiting to transmit. Put low 7 bits of random number in eoTemp1.
eoTemp1 ← LdF[eoTemp1,11,7], Skip[ALU=0];
eoTemp ← Or[eDisableOutput!,eEnableInput!]C, Skip;
eoTemp ← eDisableOutput;*No input set up
*Start simple timer with low 7 bits of random number.
*Timer slot is eoTask.
eoLoadTimer:
T ← eTimerMask;*Compute timer word
T ← (CTask) or T;
eoTemp1 ← (LSh[eoTemp1,4]) or T;
*We don’t need to have TPC correct here, since control returns to this task
*via a Timer notify.
LoadTimer[eoTemp1];
eoInToo:
T ← eiState;*Set Input state
Output[eoTemp], GoTo[eoWrSt];

*Timer has expired (notified here by task 16).
eoTimerDone:
eFlag ← 0C, Skip[R Odd], At[eoTimerDoneLoc];
eTaskRet:
Return;* Ignore this wakeup, don’t change TPC

*Check if still more time to elapse before start of transmission
*(High part of random number >=0).
eoMoreTime:
eoTemp1 ← 177C;*Set up maximum timer value
eoCount ← (eoCount) - 1, GoTo[eoLoadTimer,R>=0];
*Enable output and shut off the receiver (in case it was turned on).
eoSetup:
eoTemp ← Or[eDisableInput!,eEnableOutput!]C, Call[eoInToo];
*Set up eoPtr and eoCount for single word transfers; eoCount uneven is
*OK because it will be touched before eoPtr, invoking the interlock.
PFetch2[eMDS600,eoCount,eoCLoc], OddOK, Call[ebSetup];
*Subroutine Returns with: eoPtr = OPtr + OCount - 1, eoCount = -OCount
*Check for zero count.
T ← eoCount, Skip[R<0];*R<0 => count is zero
*Output buffer count is zero. Post (Not[esCZR]).
eoTemp ← esCZer, GoTo[eoCompPost];
*Compute number singles before 1st quadword, and form loop counter in eoTemp1.
*
Address: x00 => no singles, loop count = -1
*
Address: x01 => 3 singles, loop count = 0
*
Address: x10 => 2 singles, loop count = 1
*
Address: x11 => 1 singles, loop count = 2
T ← (eoPtr) + T + 1, Call[ebAlign];*Form start address in T
*Loop here
eoTemp1 ← (eoTemp1) - 1, GoTo[eoSingles,R>=0];
*Start quadword output; adjust eoPtr and eoCount for 4-word transfers.
eoQuad:
eoCount ← (eoCount) + (3C);
eoPtr ← (eoPtr) - (6C), Call[.+1];*Setup loop
*Output from the Main Memory Output Buffer to the Hardware Output Buffer.
T ← eoCount ← (eoCount) + (4C), GoTo[eoQuadEmpty,R>=0];
GoTo[eoAbort,IOAtten];
IOFetch4[eoPtr,eomData], Return;

*Normal exit from Output Loop is here
*7 - eoCount = number of singles remaining
*T is set up for next location.
eoQuadEmpty:
eoCount ← (eoCount) - (7C);
eoPtr ← (eoPtr) + (6C), Call[.+1];
*Final singles
eoSingles:
T ← eoCount ← (eoCount) + 1, GoTo[eoNoMore,R>=0];
PFetch1[eoPtr,eoTemp];
Output[eoTemp,eoData], GoTo[ERet];

*We’re done outputing words. Set OutputEOP.
eoNoMore:
eoTemp ← eSetOutputEOP;
Output[eoTemp,eState], Call[ERet];*Set OutputEOP
*Should wake up here after hardware’s done sending packet or an error
Input[eoTemp,eStatus];*Read Status
eoEnd1:

LU ← (eoTemp) and (eCollMask);*Look at collision bit
*Shift down status
eoTemp ← RSh[eoTemp,10], GoTo[eoColl,ALU#0];*ALU#0 => Collision, try again
*If not collision, form status. Could be good packet or underrun (ODL).
eoCount ← 0C;
eoTemp ← (eoTemp) and (eoSMask);*Remove uninteresting bits
eoTemp ← (eoTemp) xnor (esODon);
eoPost:
PStore1[eMDS600,eoCount,eELoc], Call[eTaskRet];*Store end count
*No more wakeups after ePost returns.
eoCount ← eDisableOutput, GoTo[ePost];

*We arrive here after an IOAtten is detected in the main loop, indicating
*an error condition (a collision or underrun has occurred).
eoAbort:
Input[eoTemp,eStatus], GoTo[eoEnd1];*Now read status

*Collision encountered, disable hardware to clear collision, enable and try again.
eoColl:
eoTemp ← eDisableOutput;
Output[eoTemp,eState], GoTo[eoStart];

eoCompPost:
eoTemp ← (eoTemp) xnor (0C), GoTo[eoPost];

*Task-independent Subroutines. These will work properly if called from
*eiTask or eoTask, due to identical register ordering in the two tasks.

SetTask[And[eiTask,14]];
*Task 0 mod 4 of ei/eoTask block

RV[exTemp2,0];
RV[exCount,1];
RV[exPtr,2];
RV[exPtrHi,3];
RV[exTemp1,4];
RV[exTemp,5];

*Subroutine [ePost] posts the command completion, and starts an interrupt.
*expects post code and status in exTemp; exCount has disable code to send
*to State register.
ePost:
PFetch1[eMDS600,exTemp2,eBLoc];*Fetch wakeup mask
Output[exCount,eState];
*Store ending status in ePLoc and wakeup driver.
LoadPage[DoIntPage];*exCount write completes here
PStore1[eMDS600,exTemp,ePLoc], GoToP[DoIntR];

*Subroutine [ebSetup] returns with:
*
EPtr = Buffer Pointer + Count - 1
*
ECount = - Count
ebSetup:
T ← (exCount) - 1;
exPtr ← (exPtr) + T, UseCTask;*Ptr ← Ptr + count - 1
exCount ← (Zero) - T - 1, Return;*Count ← - Count

ebAlign:
exTemp1 ← (Zero) - T;*Complement, increment
exTemp1 ← (LdF[exTemp1,16,2]) - 1, Return;

*Subroutine [eInit].
*Initialization subroutine called by both input and output task.
*exTemp contains the enable code to be used to enable the hardware.
eInit:
T ← eMDS600hi;
exPtrHi ← T;*Set up high part of Buffer pointer
eFlag ← 0C;* In case of strange sequence of SIOs
eoWrSt:
Output[exTemp,eState];
ERet:
Nop;
exTemp ← exTemp, Return;*Interlock Outputs

:END[Ether];