/Firmware for Old Ether Station Boards /as deployed in Interdatas and Vax /RWT May 1982 /Revised protocol with 3-5 control characters date=23<<4+02<<7+84 buffers=6; ports=32; maxport=31; channels=64 retrlim=20; retrgap=100 /formerly both 70 intloc=3*1024-8 /DMA particulars erbit=0;etbit=1;hrbit=2;htbit=3;tcstop=16_40 dmaer=0;dmaet=2;dmahr=4;dmaht=6;dmac=8 /Other device addresses etc erfifo=16;erfilt=17;etcoll=18;etdefer=19;hr=20;ht=22 crcbit=7;collbit=6;fifobit=5;dmabit=4;errmask=16_E0 /Control characters rdy=16_20; stx=16_40; dtx=16_60 err=16_c0; nak=16_80; ack=16_e0; etx=16_0b put=16_0e; sna=6; ssa=7; reset=16_0f /********************************************************** /* Idle process responsibilities: * /* Detect timeouts * /* Detect collisions * /* Detect DMA completions * /* * /* Events: Actions: * /* HT DMA completes: Schedule HT owner * /* HR DMA completes: Simulate ETX (non-prot) * /* ET DMA completes: Schedule ET owner, release ET * /* ER DMA completes: (Overrun) Reset and ignore * /* ET collides: Retransmit * /* ER has something: Deal with it * /* HR has something: Deal with it * /* Timeout period expires: Schedule victim * /********************************************************** /*********************************************************** /* All NORMAL processes run non-interruptably, each one * /* being associated with a data buffer. When a process is * /* suspended, only PC is preserved. * /* Only the IDLE process is interruptable. Its registers * /* are preserved by register-set-switching, PC and PROCESS * /* are stacked. The idle process does not use PORT. * /*********************************************************** /Process control block components process=ix; pre=12 header=6+6+2;data=512+20 dmaerc=16_4000+header+data+4 /2:size, 2:crc, (1)fornoTC area process; loc -pre var qnext, /Next process on queue var myport,,pc, /saved context var tnext, /Next process on watchdog list var timebomb /Info for Watchdog var lives /no of retransmissions before giving up var size, /size of data portion of packet /Beginning of packet buffer (at displacement 0 from PROCESS) var dest,,,,,,source,,,,,,type,seq procsize=pre+header+data+6 /2:size, 2:crc, 2:guard /Port control block components /The port control block contains a semi-prepared /acknowledgement packet (at displacement 0 from PORT) port=iy area port; loc 0 var remote,,,,,,local,portno,,,,,acktype,inseq var outseq,state /state bits openbit=7 /proffbit=6 pendbit=5 /sotbit=4 var stxexp, /Pro expecting data frame var rdyexp, /Pro expecting RDY var ackexp, /Queue of pros expecting Ack packets var dtxq, /Queue of pros waiting to say DTX var wnext, /Next port waiting for a process portsize=.+2 /** Assumed to be 28 in SELECT ** /Process blocks and port blocks may be linked up using, /respectively, their QNEXT and WNEXT fields. /When the high-order byte of a pointer to such a block /is zero, the pointer is deemed NIL and the low-order /byte is ignored. /Variables ramtop=16_1000 rambot=16_2000 stack=rambot area 1; loc ramtop /Scalar variables var soft,,,, /Current station and network address var erfault /0, or, after DMA ER overflow, =1< enqueued var massacre, /Killing a queue involved more than one death var dmamtc, /Multiple channels TCed together var eroflow, /ER DMA overflow var pmretr, /Retransmissions in prot-mode var bored, /Give-ups after retransmissions var crcerr, /ER hardware detected errors var colerr, var fiferr, var badsize, /Received packet with sizeS data frame not ETXed ramend: /Code area 0; loc 0 /Initial entry (and reset re-entry) jp begin /(actual values configured at blow-time) hard: 16_7f /(Initial) Station address 0; 0; 0; 0 /(Initial) Network address /********************************************** /* Routines * /* The first few of these are callable by RST * /* and the longest of those continue outside * /* the RST area. * /********************************************** /Initiate DMA: /C contains DMA subdevice address, /HL contains buffer address, /DE contains maxsize-1+IObit, /A contains enable bit /Interrupts should be disabled loc 16_08 dmaon: out (c),hl inc c out (c),de ld hl,#dmacom; or (hl) jp dm1 /Or A "out of" DMA Command register loc 16_18 dmaoff: cpl; ld hl,#dmacom and (hl); jp dm1 /Compute port control block address from port number loc 16_20 select: and maxport ld e,a; ld d,0 jp se1 /Wait indefinitely for a character /from the host and read it loc 16_28 hrsym: in a,(hr+1); rla jr nc,hrsym in a,(hr); ret /Wait indefinitely for any pending character /to be flushed out of the host transmitter buffer loc 16_30 hfsym: in a,(ht+1); rla jr cy,hfsym; ret /Log event in 16-bit counter, the address of which /follows the call. No registers corrupted. loc 16_38 log: ex (sp),hl; push de /Preserve HL,DE ld e,(hl); inc hl /Get address of counter jr log0 /Firmware version date loc 16_3e w date /Test for DMA completion dmatest: ld hl,#dmacom di; ld a,(hl) /+ DMAON and DMAOFF continued dm1: ld d,a / D = newactive+currentactive xor a; out (dmac),a /stop all while inspecting in a,(dmac); ld e,a / E = those stopped recently cpl; and d / A = newactive out (dmac),a; ld (hl),a ld a,e; inc hl /HL = #dmasta or (hl); ld (hl),a; ret /remember which have stopped /SELECT continued se1: ld hl,de add hl,hl /*2 add hl,hl /*4 add hl,hl /*8 or a; sbc hl,de /*7 add hl,hl /*14 add hl,hl /*28 ld de,port0 add hl,de push hl; pop port; ret /LOG continued log0: ld d,(hl); inc hl ex de,hl /HL->counter, DE=retad inc (hl); jr nz,log1 inc hl; inc (hl) log1: pop hl /HL=oldDE ex de,hl /DE=oldDE, HL=retad ex (sp),hl; ret /HL=oldHL /Send control character (in A), /plus port number (signature) /Return with A=Portno sign: push af; rst hfsym; pop af add a,portno out (ht+1),a ld a,portno ret /Simulate interrupt as if from beginning /of idle process sint: di ld hl,#idle; ex (sp),hl /retrieve retad, preserve pseudo-PC push process /preserve rest of context jp (hl) /Put calling process on queue of /processes expecting certain events expstx: ld hl,#stxexp jr expect expack: ld hl,#ackexp jr expect exprdy: ld hl,#rdyexp jr expect dtxwait: ld hl,#dtxq expect: push port; pop de; add hl,de /Point HL at actual queue /Put PROCESS on queue HL enqueue: ld c,(hl); inc hl; ld a,(hl) / AC = (HL) or a; jr z,enq1 /End of queue found -> ld h,a; ld l,c / HL = #QNEXT(AC) ld de,#qnext; add hl,de jr enqueue enq1: push process; pop de /Append this process ld (hl),d; dec hl; ld (hl),e / (HL) = PROCESS /+ Suspend current process and /return to idle process wait: pop hl ld pc,hl / +Jump to here to return (from interrupt) /to idle (watchdog) process intret: ex af,af; exx pop process intign: ei; ret /Return process to free list die: ld timebomb,0 pop hl; set 7,h /Mark as dead ld pc,hl ld hl,freeq ld qnext,hl ld freeq,process /Test for HT semaphore queue ld a,htpro(1) or a; jr nz,die1 /HT in use -> ld a,htq(1) or a; jr z,die1 /no-one waiting -> ld process,htq ld hl,qnext ld htq,hl call go /Test for ET semaphore queue die1: ld a,etpro(1) or a; jr nz,die2 ld a,etq(1) or a; jr z,die2 ld process,etq ld hl,qnext ld etq,hl call go /Test for port waiting for process die2: ld a,proq(1) or a; jr z,intret /None waiting -> ld port,proq ld hl,wnext ld proq,hl ld wnext(1),0 ld process,freeq ld hl,qnext ld freeq,hl push port; pop hl ld myport,hl jp hrstart /Enter new process /CALLed rather than JPed to in case we /need to go to GOSH after a faut pas. go: ld hl,myport push hl; pop port go1: ld hl,pc bit 7,h; jr z,go2 set 6,pc(1) /Mark as zombie jr gosh go2: pop de /Discard trace address jp (hl) /Internal error detected: /attempting to schedule a dead process: /cast it adrift and try to recover /after logging the error gosh: pop hl; ld lastfp,hl rst log; #fauxpas jp intret /Release HT semaphore /(Scheduling of queue done at process death) relht: xor a; ld htpro(1),a ret /Back off PC to repeat CALL RELHT/ET /and suspend current process backoff: pop de dec de; dec de; dec de push de rst log; #clfail jp enqueue /Claim HT semaphore claimht: ld a,htpro(1) ld hl,#htq or a; jr nz,backoff /Not free => ld htpro,process ret /Claim ET semaphore claimet: ld a,etpro(1) ld hl,#etq or a; jr nz,backoff ld etpro,process ld dmaeta,process /Set up efault DMA paramaters ld de,size ret /Put port control block into a defined state. /PORT points at control block already, and A /contains initial value for STATE field. clopen: ld state,a ld hl,stxexp /Kill all associated processes call kill ld hl,rdyexp call kill ld hl,ackexp call kill ld hl,dtxq call kill ld a,soft /Set up addresses for the ACK packet ld local,a ld hl,soft(1) ld local(2),hl ld remote(2),hl ld hl,soft(3) ld local(4),hl ld remote(4),hl xor a /Clear most everything in sight ld inseq,a ld outseq,a ld stxexp(1),a ld rdyexp(1),a ld ackexp(1),a ld dtxq(1),a ret /Kill all processes on queue HL kill: ld a,h; or a; ret z /queue empty ld de,freeq ld freeq,hl ld process,freeq k1: ld timebomb,0 /Prevent resurrection set 7,pc(1) /Guard against internal error ld hl,qnext ld a,h; or a; jr z,k2 /end of queue found -> push hl; pop process rst log; #massacre jr k1 k2: ld qnext,de ret /Remove PROCESS from ACKEXP queue unchain: push port push process; pop de ld bc,#ackexp un1: add port,bc ld hl,(port) push hl ld a,h; or a; jr z,un9 /Not found => sbc hl,de ld a,h; or l; jr z,un2 /Found -> pop port ld bc,#qnext jr un1 un2: ld hl,qnext ld (port),hl ld qnext(1),0 pop hl; pop port; ret un9: pop hl; pop hl jp gosh /(use UNCHAIN return address) /Transmit packet of length DE starting at (DMAETA) /(after appending the size at the end) transmit: xor a ld hl,dmaeta add hl,de ld (hl),e; inc hl; ld (hl),d inc de; set 7,d ld dmaetc,de ld hl,dmaeta ld c,dmaet out (etdefer),a ld a,1<>8; ld i,a im2 /Clear store ld hl,ramtop ld bc,rambot-ramtop b1: ld (hl),0; inc hl dec bc; ld a,b; or c jr nz,b1 /Copy default station and network address /and send station address to hardware filter ld hl,hard ld de,#soft ld bc,5 ld a,(hl); out (erfilt),a ldir /Initialise process blocks, setting up /a linear queue of free processes and /a circular list for timeout watchdog ld b,buffers-1 ld de,procsize ld process,buff0 ld hl,buff0 ld freeq,hl b2: add hl,de ld qnext,hl ld tnext,hl ld pc(1),16_80 /Mark as untouched add process,de djnz b2 ld qnext(1),0 ld hl,buff0 ld tnext,hl ld pc(1),16_80 /Open port 0 ld port,port0 ld a,16_80 /Openbit + port number call clopen /Initialise all port records (exc 0) with port number ld port,maxport*portsize+port0 ld b,maxport ld de,0-portsize b3: ld portno,b add port,de djnz b3 /Allocate two buffers to Ether Receiver, /connecting one and keeping the other up our sleeve. ld process,freeq ld spare,process ld hl,qnext ld qnext(1),0 ld erpro,hl ld process,erpro ld de,qnext ld qnext(1),0 ld freeq,de ld c,dmaer ld de,dmaerc ld a,(hard) /Station address to filter out (erfilt),a ld a,1< di; ld a,timebomb or a; jr z,idle1 /False alarm -> dec a; ld timebomb,a jr nz,idle1 /time not up -> call sint call go /*BNAG* idle1: in a,(etcoll) /Test for collision rra; jp cy,collided /Has occurred -> call dmatest /Have any DMA channels completed? jp z,idle /No -> /Deal with DMA completion. We know at least one channel /requires service, and we deal here with only one, /catching any others the next time round. /A still contains DMASTA and HL its address. ld (hl),a /Update DMA status cpl; dec hl /and turn off those stopped and (hl); ld (hl),a inc hl; ld a,(hl) rst log; #dmadun dec a; and (hl); jr z,idle2 /Only one bit set -> rst log; #dmamtc idle2: ld a,(hl) bit etbit,a; jr nz,etdone bit htbit,a; jr nz,htdone bit erbit,a; jr nz,erover /HR DMA overflow (presumably in non-protocol mode) res hrbit,(hl) /Clear TC and Active bits call sint ld a,hrpro(1); or a call z,gosh /unexpected? ld process,hrpro xor a; ld hrpro(1),a call go /ER DMA overflow (error: reset and ignore) erover: res erbit,(hl) rst log; #eroflow ld hl,erpro /Re-use same buffer ld de,dmaerc ld c,dmaer ld a,1< call sint ld a,etpro(1); or a call z,gosh ld process,etpro xor a; ld etpro(1),a /Auto-release call go /HT DMA completion htdone: res htbit,(hl) call sint ld a,htpro(1); or a call z,gosh ld process,htpro call go /Deal with collision collided: ld a,1< ld a,1< call log #badetx /Deal with non-ETX by deferring process that /was waiting for the ETX. Give priority to /the latest control character. push port call hrdefer /(Back here after priority process returns) di; exx; ex af,af pop port call go1 hrdefer: push process jp hr1 hr0: in a,(hr) /Read the control character hr1: ld b,a and 16_e0; jr z,hr2 /not port-specific -> ld a,b rst select ld a,b; and 16_e0 rrca; rrca; rrca; rrca add a,32 jr hr3 hr2: ld a,b; and 15; add a,a /(Controlchar&15)<<1 hr3: add a,cctable&255; ld l,a /Switchjump ld h,cctable>>8 ld a,(hl); inc hl; ld h,(hl); ld l,a jp (hl) /The following deals with control characters from host. /Note that B still contains the control character, /which, for port-specific operations, contains the /port number in its low-order nibble. /Erroneous control character: send error response. herror: rst hfsym ld a,b; and 15 add a,err; out (ht+1),a jp intret /Enquire Network Address (ENA) hrena: rst hfsym ld a,sna; out (ht+1),a ld hl,#soft+1 ld b,4 hrena1: rst hfsym; ld a,(hl); out (ht),a inc hl; djnz hrena1 jp intret /Enquire Station Address (ESA) hresa: rst hfsym ld a,ssa; out (ht+1),a rst hfsym ld a,soft out (ht),a jp intret /Disable all broadcasts (BOF) hrbof: ld hl,#spectrum ld b,#channels>>3 bof1: ld (hl),0; inc hl djnz bof1 jp intret /Enable broadcasts (BON) hrbon: rst hrsym call prism or (hl); ld (hl),a jp intret /Set Network Address (SNA) hrsna: ld hl,#soft+1 ld b,4 hrsna1: rst hrsym ld (hl),a; inc hl; djnz hrsna1 jp intret /Set Station Address (SSA) /Host is responsible for safety of this: /all ports should be closed. hrssa: rst hrsym ld soft,a out (erfilt),a ld port,port0 /Ensure port 0 knows about the new address ld a,16_80 call clopen jp intret /Set Peek-Poke Pointer (PTR) hrptr: rst hrsym; ld l,a rst hrsym; ld h,a hrend: ld pointer,hl jp intret /Load firmware into ram (LOD) hrlod: ld hl,ramtop hrlod1: ld de,0 hrlod2: in a,(hr+1); rla jr nc,hrlod3 inc de ld a,d; or e; jr nz,hrlod2 ld sp,ramtop jp ramtop hrlod3: in a,(hr); inc hl jp hrlod1 /Peek (GET) hrget: rst hfsym ld a,put; out (ht+1),a rst hfsym ld hl,pointer ld a,(hl); out (ht),a /followed by data inc hl; jr hrend /Poke (PUT) hrput: rst hrsym ld hl,pointer; ld (hl),a inc hl; jr hrend /Host is ready to receive data frame (RDY) hrrdy: ld hl,rdyexp ld rdyexp(1),0 rdystx: ld a,h; or a jp z,herror /not expected -> push hl; pop process /Consistency check: should agree as to port push port; pop hl ld bc,myport sbc hl,bc call z,go1 call gosh /Host is about to send data frame (STX) hrstx: ld hl,stxexp ld stxexp(1),0 jr rdystx /Host wishes to discard data frame (ACK) hrack: ld hl,rdyexp ld rdyexp(1),0 ld a,h; or a jp z,herror push hl; pop process call die /Request to close port (CLS) hrcls: ld a,portno; or a jr nz,hrc1; ld a,16_80 /Keep port 0 open but hrc1: call clopen /clobber it anyway jp intret /Request to open port (OPN) hropn: ld a,portno; or a /Close it first jp z,herror /But exempt port 0 xor a; call clopen opndtx: bit pendbit,state jp nz,herror /Previous OPN/DTX still pending => set pendbit,state ld a,freeq(1) /Is there a process for the guy? or a; jr z,prowait /No - he'll have to wait -> ld process,freeq /Fix him up with new process ld hl,qnext ld freeq,hl ld qnext(1),0 push port; pop hl ld myport,hl jp hrstart prowait: ld hl,proq ld wnext,hl ld proq,port jp intret /Host wishes to send a packet (DTX) hrdtx: bit openbit,state jp z,herror /Port not open => jp opndtx /************************** /* Host-to-Ether transfer * /************************** /We come here as a result of OPN or DTX. /If we are closed, the command was OPN. hrstart: call claimht /Claim Host Transmitter ld a,rdy /Send RDY call sign call relht /Release HT call expstx /Wait for STX res pendbit,state ld hrpro,process /Grab HR and read data frame bit openbit,state jr z,hraf /OPN:(Address frame) -> ld hl,hrpro /Set up for data frame (default) ld de,header; add hl,de ld de,16_4000+data-1 ld a,portno or a; jr nz,hrrf /Non-zero port -> ld de,-6; add hl,de /Set up for addr+data frame ld de,16_4000+data+6-1 jr hrrf hraf: ld hl,myport /Set up for addr frame ld de,16_4000+6-1 hrrf: ld c,dmahr /Read frame ld a,1< ld a,portno or a; jr nz,hrsetup /Non-zero port -> push process; pop hl /Disentangle address and data ld de,header-6; add hl,de ld de,myport ld bc,6 ldir hrsetup: call setheader hrtrans: call claimet /Transmit the packet call transmit ld a,dest /Was this a broadcast? or a; jr z,hrdone /yes -> ld timebomb,retrgap /Wait for acknowledgement call expack ld a,timebomb /Did we time out? or a; jr z,retrans /Yes: retransmit ld timebomb,0 /Otherwise defuse timer hrdone: call claimht /Send Ack to host ld a,ack lastword: call sign /Send ACK/NAK call relht call die retrans: call unchain /Remove us from ACKEXP queue dec lives jr z,giveup rst log; #pmretr jr hrtrans giveup: rst log; #bored call claimht /Send NAK ld a,nak jr lastword /**************************** /* Ether receiver interrupt * /**************************** erint: push process /Preserve context exx; ex af,af ld process,erpro ld c,dmaer /Read DMA end address in hl,(c) push hl ld hl,spare /Go back on the air right away ld erpro,hl ld spare,process ld de,dmaerc ld a,1< bit crcbit,a; jr z,erd1 rst log; #crcerr erd1: bit collbit,a; jr z,erd2 rst log; #colerr erd2: bit fifobit,a; jr nz,erd3 jp intret erd3: rst log; #fiferr jp intret erd4: rst log; #badsize jp intret erd5: rst log; #closed jp intret erd6: rst log; #badack jp intret erd7: rst log; #toobusy jp intret erd8: rst log; #badad jp intret /An undamaged packet has arrived. /Work out how big it is and verify that its /size is consistent. /Check that the addressee port is open, /then check the destination address. er1: rst log; #heard dec hl; dec hl /Back past CRC dec hl; ld b,(hl) /stored size to BC dec hl; ld c,(hl) ld de,spare sbc hl,de /actual size to HL or h; jp n,erd4 /?negative? => sbc hl,bc; jr nz,erd4 /inconsistent => ld hl,-header; add hl,bc /Information size ld size,hl ld a,dest or a; jr z,erbro /Broadcast -> / ld hl,#soft / sub (hl); jr nz,erd8 /station addr wrong => ld a,dest(1) /Which port is this for? rst select ld myport,hl bit openbit,state jr z,erd5 /A closed one -> ld hl,spare inc hl; inc hl /Point at Network address ld de,#soft+1 ld bc,4 er2: ld a,(de); inc de /Check it cpi jp nz,erd8 /Mismatch (not for us) => jp pe,er2 /We have a packet with the right network address. /Decide whether it is an Information packet or /an Acknowledgement packet. bit 7,type jr z,er3 /Info packet -> / Deal with acknowledgement packet ld d,seq ld bc,#ackexp ackloop: add port,bc ld hl,(port) ld a,h; or a jp z,erd6 /no process expecting ack -> push hl; pop process ld a,seq; cp d jr z,gotit /found expector -> push hl; pop port ld bc,#qnext jr ackloop gotit: ld hl,qnext /Unchain ld (port),hl ld qnext(1),0 call go halt / Deal with information packet erbro: xor a; rst select er3: ld a,freeq(1) or a; jp z,erd7 /No spare buffer: ignore it push process /Preserve identity ld process,freeq /Get a new process to stand by ld hl,qnext xor a; or h; jr z,er4 /No spare for H->E: ignore ld qnext(1),0 ld freeq,hl ld spare,process pop process /Restore identity jr ers0 er4: pop process jp erd7 /************************** /* Ether-to-Host transfer * /************************** /Deal with source address. ers0: push process; pop hl ld de,#source; add hl,de /HL -> source push port; pop de /DE -> remote ld bc,6 ld a,portno or a; jr z,ers2 /Port 0 -> ers1: ld a,(de); inc de /Compare source addresses cpi call nz,die jp pe,ers1 jr ers3 ers2: ldir /Copy for port 0 /Acknowledge the packet. ers3: ld a,dest /Unless it was a broadcast or a; jr z,ers4 ld a,type cp 1 call nz,die /ignore unless type=data call claimet /Claim Ether Transmitter ld a,inseq /remember previous seq no ld lives,a ld a,seq /copy sequence number ld inseq,a ld a,type /copy packet type set 7,a ld acktype,a ld dmaeta,port ld de,portsize-2 /piggy-back entire port status call transmit /Test the sequence number. If it is non-zero and /the same as the last one we heard for this port, /then discard the packet, because it has obviously /been unnecessarily retransmitted. ld a,portno or a; jr z,ers4 /Port 0 always accepts -> ld a,seq or a; jr z,ers4 /seqnum=0: accept -> sub lives /Different from previous? call z,die /No: ignore => ers4: ld a,rdyexp(1) /Don't pile up DTX's or a; call nz,dtxwait call claimht /Claim Host Transmitter ld a,dtx /Send DTX call sign call relht /Release Host Transmitter call exprdy /wait for RDY /Send data frame to host, encapsulated /in STX-ETX, possibly including address part call claimht /Re-claim HT ld a,stx /Send STX call sign or a; jr nz,erdata /Not port 0 -> or dest jr nz,ernobro /Not broadcast -> rst hfsym; xor a; out (ht),a /Bung out 00 rst hfsym; ld a,dest(1) out (ht),a /Bung out the channel number ernobro: ld hl,#source /Bung out the 6 address bytes push process; pop de; add hl,de ld de,16_8005 ld c,dmaht; ld a,1< ld c,dmaht set 7,d; dec de ld a,1< push process /Transfer one pro from DTXQ ld bc,qnext /to next head of run q push hl; pop process ld de,qnext ld dtxq,de ld qnext,bc pop process ld qnext,hl call die romend: loc intloc-32-16 rombot: /Switch vector for control characters /16 non-port-specific ones, /followed by 16 port-specific ones. /Table assumed not to cross a 256-byte boundary cctable: w herror /00 w herror /01 w herror /02 w hrlod /03 Load firmware into ram w hrena /04 Enquire Network Address w hresa /05 Enquire Station Address w hrsna /06 Set Network Address w hrssa /07 Set Station Address w hrptr /08 Set peek/poke pointer w hrbon /09 Broadcast on w hrbof /0A Broadcasts off w herror /0B ETX: handled separately w herror /0C (EOT) w hrget /0D Peek w hrput /0E Poke w begin /0F Reset Station w herror /00 (non-port specific) w hrrdy /20 Ready for data frame w hrstx /40 Start of data frame w hrdtx /60 Request to transmit w herror /80 (NAK) w hropn /A0 Open port w hrcls /C0 Close port (also ERR) w hrack /E0 Discard packet /Interrupt switch vector w erint w hrint w erint w intign /The last two words are outwith the ROM w rambot-ramend /amount of spare RAM w rombot-romend /amount of spare ROM end