%list ! !************************************************* !* * !* PSS X-25 Level 2 Protocol Handler * !* * !* XPROT * !* * %conststring (8) datestring="28/08/85" %conststring (8) timestring="11.49.32" !* Version 30.1 22 July 1985 * !* * !************************************************* ! Prep options ! ! q - dqs11 code ! p - dup11 code ! n - kv11 code (n = Newcastle) ! b - Big Buffer version ! k - UKC ! u - UKC - Sgate specific ! d - Buffer tracing (UKC) ! y - Use a second xgate (for psse & small buffer version only) ! ! ! SSSSS GGGGG AAAAA TTTTTTT EEEEEEE ! S S G G A A T E ! S G A A T E ! SSSSS G AAAAAAA T EEEEE ! S G GGG A A T E ! S S G G A A T E ! SSSSS GGGGG A A T EEEEEEE ! !* ! NB: This handler now requires the later version of the Buffer Manager ! that protects itself from double Q manipulation. (see ring version) ! %constinteger big buffer length = 160; ! NB: New Length ****************** %control 1 !* !******************************** !* * !* Declarations * !* * !******************************** %begin !***** Configuration Information ***** !* %include "ercm06.inc_config" %include "ercm06.inc_sers" %owninteger dcedte =0 ;!DCE !* !***** Constintegers ***** ! !*State Values %constinteger waiting for disc =1 ;!DTE %constinteger ua queued 1 =2 ;!DTE & DCE %constinteger sabm queued =3 ;!DTE & DCE %constinteger waiting for ua =4 ;!DTE & DCE %constinteger waiting for sabm =5 ;!DCE %constinteger uaqueued 2 =6 ;!DCE %constinteger disc queued =7 ;!DTE & DCE %constinteger link up =0 ;!DTE & DCE %constinteger dce waiting for ua =1 ;!DCE %constinteger dte waiting for ua = 8 ;!DTE %constinteger dce sarm queued = 9 ;!DCE - LAP-Compatibility code !*Substate values (Values of RSTATE) %constinteger rrsent = 0 %constinteger rrpending = 1 %constinteger rejsent = 2 %constinteger rejpending = 3 %constinteger rnrsent = 5 %constinteger rnrpending = 6 %constinteger rrdeferred = 7 !*Monitor Calls !* %constinteger ok =0 %constinteger line down =1 %constinteger line up =2 %constinteger query =3 %constinteger push error = 4 %constinteger buffers low = 5 %constinteger silo full = 7 %constinteger bad fr = 8 %constinteger dms = 9 %constinteger init msg = 10 %constinteger mon clock tick = 11 %constinteger bad addrs rx = 12 %constinteger spurious uframe rx = 13 %constinteger rrs rx = 16 %constinteger rejs rx = 17 %constinteger rnrs rx = 18 %constinteger iframes rx = 19 %constinteger iseqerss rx = 20 %constinteger sabms rx = 21 %constinteger uas rx = 22 %constinteger discs rx = 23 %constinteger frmrs rx = 24 %constinteger badframes rx = 25 %constinteger null iframes rx = 26 %constinteger grotted 2 = 27 %constinteger grotted 3 = 28 %constinteger grotted 4 = 29 %constinteger grotted 5 = 30 %constinteger poll failure = 31 %constinteger rrs tx = 32 %constinteger rejs tx = 33 %constinteger rnrs tx = 34 %constinteger iframes tx = 35 %constinteger retries tx = 36 %constinteger sabms tx = 37 %constinteger uas tx = 38 %constinteger discs tx = 39 %constinteger frmrs tx = 40 %constinteger mon hw fail = 47 %constinteger funny int = 48 %constinteger buff full = 49 %constinteger bad address = 50 %constinteger spurious data = 51 %constinteger grotted 1 = 52 %constinteger short frame = 54 %constinteger from upper = 56 %constinteger to upper = 57 %constinteger funny state = 58 %constinteger bad function = 59 %constinteger output tx = 61 %constinteger bad ack = 62 %constinteger input rx = 63 %constinteger line no wrong = 64 %constinteger line type wrong = 65 !* !Line and module state values for communicating with XGATE !* %constinteger link established =0 %constinteger link down =1 %constinteger xprot up =2 !* !* X25 Frames !*Information transfer %constinteger iframe =0 !*Supervisory %constinteger rr =1 %constinteger rnr =5 %constinteger rej =9 !*Unnumbered %constinteger sabm =x'2F' %constinteger sarm =x'0F' %constinteger disc =x'43' %constinteger ua =x'63' %constinteger frmr =x'87' ! !***** Hardware control bits ***** ! ! in Interface register %constinteger intAenb = k'04' %constinteger intBenb = k'10' %constinteger RxBCzero = k'20' %constinteger TxBCzero = k'40' %constinteger intB = k'100' %constinteger intA = k'200'; ! bus timeout %constinteger dmaIenb = k'400' %constinteger dmaOenb = k'1000' %constinteger X1 clock = k'4000'; ! set = use external clock %constinteger CLRchip = k'100000'; ! master reset ! in Chip reg 1 %constinteger set DTR = k'002' %constinteger Act Tx = k'100' %constinteger Act Rx = k'200' ! in Chip reg 2 %constinteger auto flag = 1 ! in INTR (NB:can only read once) %constinteger Data set chg = k'10' %constinteger tx bad = k'020' %constinteger tx ok = k'040' %constinteger rx bad = k'100' %constinteger rx ok = k'200' ! in chip status register %constinteger crc err = k'001' %constinteger ovr err = k'002' %constinteger abort rec = k'004' %constinteger Rec idle = k'010' %constinteger Misc In = k'020' %constinteger DSR = k'040' %constinteger Carr det = k'100' %constinteger Ring Ind = k'200' !* !* Values of flags etc !* %constinteger clear =0 %constinteger set =1 %constinteger pending =1 %constinteger sent =2 %constinteger pfset =x'10' %constinteger command =0 %constinteger response =1 %constinteger invalid =-1 %constinteger sfmask =63 %constinteger dce =0 %constinteger dte =1 %constinteger initialise =0 %constinteger line output =2 %constinteger input here =3 %constinteger output done =4 %constinteger modem status = 5 %constinteger rxgo =k'111' %constinteger txgo =k'111' %constinteger input req =1 %constinteger output req =2 %constinteger bounce =3 %constinteger put down =4 %constinteger put up =5 %constinteger poke = 22 %constinteger dead =0 %constinteger timed out =1 %constinteger reset = 2 %constinteger sabm received = 3 %constinteger user request =4 %constinteger read fails = 7 %constinteger uframe in data =6 %constinteger data retries =5 %constinteger full up = 8 %constinteger disc received = 9 %constinteger line timeout = 10 %constinteger no buffs = 11 %constinteger critical = 4 %constinteger big limit = 5; ! level for sending RNR !* !***** Record Formats ***** %recordformat qf(%record (qf) %name link, %integer count) %recordformat hwf(%integer ICcsr, Eaddr, x1, x2, RxAddr, RxBc, TxAddr, TxBc, %c chipR1, chipR2, chipR3, RHR, INTR, chipSTR) %recordformat x25f(%byte add, type, octet1, octet2, octet3) %recordformat parf(%integer type, (%record (x25f) %name b %or %integer address), %c %integer len) %recordformat desf(%integer pt, %byte state, s1, %c %integer maxln, p1, flag, seg, sa, vec, intno) %recordformat des2f(%record (desf) rx, tx) %recordformat m1f(%integer a, b, c, d, e, f, g) %recordformat mef(%record(mef) %name link, %byte len, type, %c %byte d0, d1, d2, %record(x25f) x25) %recordformat pf(%byte ser, reply, ((%integer a, b, c) %or %c (%byte fn, line, %record(mef) %name m, %byte len, c2))) !* !* !***** Monitoring Information ***** !* %owninteger irx, rrrx, rnrrx, rejrx, discrx, uarx, sabmrx, frmrrx, ierrrx, %c nullrx, wcov, silo, abort rx, d1, d2 = 0 %owninteger itx, rrtx, rnrtx, rejtx, disctx, uatx, sabmtx, frmrtx, retrytx = 0 %ownintegerarray moncount(0:63)=0(64) %constbytearray monaction(0:63) = %c 2, 2, 2, 1, 1, 1, 1, 3, 3, 1, 1, 1, 3, 1, 1, 1, 0, 0, 0, 0, 2, 0, 0, 2, 2, 3, 2, 3, 3, 3, 3, 1, 0, 0, 0, 0, 0, 0, 0, 0, 2, 1, 1, 1, 1, 1, 1, 3, 3, 2, 3, 3, 3, 1, 2, 1, 1, 1, 3, 3, 3, 4, 2, 4 !***** INTEGERS ***** !* %owninteger rx watchdog = 0 %owninteger tx watchdog = 0 %owninteger clock0 =0 %owninteger clock1 =0 %owninteger clock2 =0 %owninteger clock3 =0 %owninteger clock4 =0; ! read fails - block too long %owninteger clock5 =0; ! no read buffers for 3 mins %owninteger address = 0 %owninteger type = 0 %owninteger pfbit = 0 %owninteger comres = 0 %owninteger poll =0 ;!"Pending" if we have a Poll bit to send !"Sent" when we have sent it, cleared when we receive a final bit %owninteger final =0 ;!Set when far end sends us a Poll bit. !Cleared when we send back a Final bit %owninteger istate= 0 ;!State of our end of the link %owninteger tstate= 0 ;!Set if far end has RNR up against us %owninteger rstate = 0 %owninteger abort req,abort reason = 0 %owninteger window = 6 %owninteger aaa = 0 ;!Last message ackked by far end %owninteger eee = 0 ;!Next message expected %owninteger ttt = 0 ;!Next message to send %owninteger xxx = 0 ;!High Water Mark !This is the most advanced frame for which a valid ack is possible !It is equal to TTT except during timer recovery (retransmission) !where TTT is the frame just sent and XXX is the most advanced frame %owninteger fff = 0 ;!Last message sent %owninteger active =0 %owninteger max reads = 5 %owninteger t1 = 6 ;!6 Ticks = 2.5 - 3 secs %owninteger n2 = 20 %ownbyte line %ownbyte line type %owninteger i,b = 0 %owninteger txint = -33 %owninteger rxint = -34 %owninteger buffers held = 0 %owninteger quiet idle = 1 %owninteger hold rnr = 0 ;!Hold RNR up for testing %owninteger outstanding buff req = 0 %owninteger intr, chipstr %ownbyte monbyte = 1;!Controls what is monitored to where !* !* Buffer Management Constants etc !* %constintegername ps == k'017776'; ! processor status - in seg 0 %constintegername big buff pt== k'100104' %constintegername small buff pt == k'100106' %constintegername no of small buff == k'100114' %constintegername min no of big == k'100120' %constintegername min no of small == k'100122' %constintegername no of big req == k'100124' !* !****** NAMES ***** !* %include "ercm06.inc_exts" %include "ercm06.inc_various" !***** Arrays ***** !* !* !***** Own and Const Arrays ***** !* %constintegerarray initstate(0:1)=disc queued(2) !* !***** Records and record names ***** !* %ownrecord (pf) p %constrecord (*) %name null == 0 !* variables used by the low-level comms hw driving routines %ownrecord (parf) parb %ownrecord (des2f) %name des %ownrecord (mef) %name mes %ownrecord (des2f) %array %name desx %constrecord (hwf) %name hw == k'3000' %ownrecord (*) %name handler address == 1 %owninteger tx reply, rx reply %owninteger f, cad, oseg, ext bits, save ext bits %owninteger par, pad, x %ownintegerarray raddr(0:7) %recordformat bpf(%record (mef) %name m) %ownrecord (m1f) m1, m2 %recordformat wdse((%record (mef) %name m %or %integer b), %integer len) %ownrecord (wdse) %name wdesc %ownrecord (wdse) %array wspace(0:sfmask) %ownrecord (wdse) %name idesc %ownrecord (wdse) icurr = 0 %ownrecord (qf) ipool %ownrecord (wdse) om %ownrecord (bpf) %name im %ownrecord (bpf) %name me2 %ownstring (7) %array abo reason(0:11) = "Dead", "tmd out", "Reset", "Sabm rx", "User Rq", "Rd Fail", "Ufrm Rx", "Data Tx", "Full Up", "Disc Rx", "Line Tm", "No Buff" !***** Routine Specs ***** ! %routinespec stop(%integer reason) %routine traceid(%record (mef) %name buf, %integer id) !----------------------------------------------------- %recordformat traceblock(%integerarray ids(0:7), %integer top) %record (traceblock) %name trace %integer i %if addr(buf)=0 %then %return %if buf_type & 64 # 0 %then %return; !short buffer trace == record(addr(buf)+236) i = trace_top; !index to last saved item trace_ids(i) = trace_ids(i) & x'ff'; !remove marker from previous top i = (i+1)&7 trace_ids(i) = x'f000' ! id; !add in marker so top item visisble trace_top = i %end ! ! %routinespec abort(%integer reason) %routinespec clock int %routinespec free buffer(%record(mef) %name p) %routinespec handle input %routinespec handle output %routinespec monitor(%record (pf) %name p,%integer type) %routinespec octal(%integer n) %routinespec query processes %routinespec reinitialise hardware %routinespec reset line %routinespec move(%integer len, from, to) %routinespec put read on hardware %routinespec replace read %routinespec to comms hw(%record (parf) %name par) %routinespec to xgate(%integer flag) !****** Others ***** !* !* !****** END OF DECLARATIONS ***** !********************************** !* * !* Main Program * !* * !********************************** map virt(buffer manager,5,4) map virt(buffer manager,6,5) im == m1 ; om_m == m2 change out zero = t3 ser ;!Queued console I/O p_ser=0 ;!Accept all messages poff(p) ;!Wait. Expect an initialisation message monitor(p, init msg) line=p_fn ;!We have only one line. Just record it and use !it for communicating with XGATE. printstring("XPRO (".longnetname(line).") ".datestring." ".timestring) ; newline line type = p_line & 7 ;!0 = DQS11 ;1 = DUP11 2 = DUP11 with read-chained-read DUP driver dcedte = p_line >> 7 ;!0=DCE 1=DTE handler address==p_m rxint=p_len!X'FF00' txint=p_c2!X'FF00' stop(line no wrong) %unless 0 <= line <= 2 stop(line type wrong) %unless 0 <= line type <= 2 istate = initstate(dcedte) reinitialise hardware to xgate(xprot up) alarm(25) ;!Half a second timer tick handle output %cycle ;!Main loop p_ser=0 ;!Accept all messages poff(p) ;!Wait %if p_ser&x'80'#0 %start ;!Interrupt %if p_ser = txint&x'ff' %start; ! type A int (bus timeout) hw_iccsr = hw_iccsr&(~intA) ! nb: timeout will cause a type B int as well %continue %finish ! type B int - Data set change, Input int, Output int OR COMBINATION intr = hw_intr; ! read once only chipstr = hw_chipstr; ! may also change parb_len = intr %if intr&data set chg # 0 %start parb_type = modem status to comms hw(parb) %finish %if intr&(Rx ok!Rx Bad) # 0 %start replace read; ! it needs intr, but used globally for compatibility rx watchdog = 0 handle input %finish %if intr&(Tx ok!Tx Bad) # 0 %start parb_type = output done to comms hw(parb) active = 0 tx watchdog = 0 handle output %finish %continue %finish %if p_reply=0 %start ;!Clock tick !Interrupts: !0-9: Change monitoring level !A: Force a line abort !B:Generate a bad link-level address !E: Force a REJ !N: Close trace file and start a new one !Q: Quiet: Suppress idle RR exchanges !U: Generate a spurious U-frame !R: Force a Transmitted sequence error !S: Force a reset of line by SABM !X: Generate a spurious frame (invalid) !W: Hold up RNR !Z: Stop program moderately tidily monitor(null, mon clock tick) clock int %if int = 0 %then %continue %if int = 'S' %start abort(reset) %elseif int = 'A' abort(user request) ;!Int A aborts line %elseif int='?' query processes monitor(null,query) ;!Int ? produces a status report %elseif '0' <= int <= '9' monbyte = int - '0' %elseif int = 'N' selectoutput(1) ;close output %elseif int = 'Q' quiet idle = 1 - quiet idle %elseif int = 'W' hold rnr = 1 - hold rnr ;!Force RNR for testing %else %if int = 'K' hw_chipR1 = hw_chipR1&(~act rx) hw_chipR1 = hw_chipR1!act rx; ! force a re-synch %finishelse %continue int = 0 %continue %finish monitor(p, from upper) %if p_fn = output req %start ; !"Write to line" from higher level buffers held = buffers held + 1 %if 0 # p_m_type # 64 %then stop(grotted 2) %if istate=link up %start ;!Ignore unless line is up !Xprot maintains a circular array of 64 records. These !point to buffers received from the higher level from the time !they arrive to the time they are acknowleged wdesc==wspace(fff) wdesc_m == p_m wdesc_len = p_len + 2 fff=(fff+1)&sfmask ;!Increment n(s): Sequence no of next frame %if fff = aaa %start !We've filled up our carousel. Nothing for it but to drop !the line to prevent a crash monitor(null, buff full) abort(full up) %finish handle output %else ;!Link down free buffer(p_m) ; p_m == null %finish %elseif p_fn = poke %if istate = link up %then p_len = 1 p_c2 = buffers held i = p_ser ;p_ser = p_reply ;p_reply = i %unless p_m == null %start move(48, addr(irx), addr(p_m_d0)) ; p_m_len = 48 %finish traceid(p_m, p_ser) pon(p) %else monitor(p,bad function) !We Won't free the buffer (Better slowly gobble space than risk crashing BUFF) %finish %repeat !* !**************************************** !* * !* Routines * !* * !**************************************** %routine abort(%integer reason) %integer i, x %if istate = link up %start set prio(1); ! no priority, bm must absorb buffers abort reason = reason %unless reason = 0 %if abort req=0 %start ;!First try at aborting printstring(longnetname(line)) ;printstring(" Line Down at Level 2:") printstring(abo reason(abort reason)); newline monitor(null,line down) to xgate(link down) %finish %if active=2 %start ;!Big block being transmitted abort req=1 %else abort req=0 x = 0; ! restrict concurrent no of release requests %while aaa#fff %cycle ;!Clear up requests wdesc == wspace(aaa) free buffer(wdesc_m) ; wdesc_m == null wdesc_m == null aaa=(aaa+1)&sfmask x = x+1 %if x = 7 %then x = 0 %and set prio(1); ! force it to wait %repeat istate=disc queued ;clock3 = 0 %if abort reason = reset %then istate = sabm queued %if abort reason = sabm received %then istate = ua queued 1 %if abort reason = disc received %then istate = ua queued 2 abort reason = 0 handle output %finish %elseif istate = 1 istate = disc queued ;clock3 = 0 handle output %finish %end ;!of abort %record (mef) %map grab buffer %integer x %record (mef) %name mes ! buffers there, grab one ps = ps!k'340'; ! stop processor interrupts %if no of buff >= critical %start buffers held = buffers held+1 no of buff = no of buff-1 %if no of buff < min no of big %then min no of big = no of buff no of big req = no of big req+1 x = big buff pt; ! get buffer managers free pointer x = x-k'20000'; ! make it my vm (my seg 3 = bm seg 4) big buff pt = integer(x); ! copy rest of free queue ps = ps&(\k'340'); ! allow ints again mes == record(x) mes_type = mes_type & (8_376) ; ! remove 'free' buffer bit traceid(mes, kernel ser) %result == record(x); ! and pass back result %finish ps = ps&(\k'340') %result == null %end %routine free buffer(%record (mef) %name mes) %integer x %record (pf) p !Frees the block pointed at by M traceid(mes, buffer manager) %unless mes == null %start ;!Safety check for NULL pointer buffers held = buffers held - 1 ps = ps!k'340'; ! put processor status = 7 x = addr(mes)+k'20000'; ! address in buff managers VM. %if mes_type # 0 %start; ! small buffer mes_type = mes_type ! 1 ; ! buffer free flag no of small buff = no of small buff+1 integer(addr(mes)) = small buff pt small buff pt = x %finish %else %start ! %if x < Big Boundary %start; ! neg numbers ! printstring("xpr:bad big"); ! octal(x); ! newline ! ps = ps&(\k'340'); ! ints on ! %return; ! ditch bad buffer (its really a short one) ! %finish mes_type = mes_type ! 1 ; ! buffer free flag no of buff = no of buff+1 integer(addr(mes)) = big buff pt; ! copy in top of chain big buff pt = x; ! and remake 1st entry %finish ps = ps&(\k'340'); ! and allow ints again %finish %end ;!of free block %routine handle output %record (x25f) %name x25 %record (mef) %name m %integer len, type, x %return %if active#0 ;!Transmit channel busy %if abort req#0 %then abort(dead) %if istate#0 %start ;!Link setup phase %if istate=sabm queued %start ;!Have sent UA (DTE). Now send SABM type=sabm istate=waiting for ua sabmtx = sabmtx + 1 %elseif istate = uaqueued 1 type=ua %if b = 0 %start ;!LAP-B istate=link up reset line to xgate(link established) %else istate = dce sarm queued %finish uatx = uatx + 1 %elseif istate = uaqueued 2 ;!We have had a DISC from DCE and !must send a UA in reply, with the P/F bit as received type=ua %if dcedte = dte %then istate=sabm queued %else istate = waiting for sabm uatx = uatx + 1 %elseif istate=disc queued ;!We have had either an abort !or a DISC while the link was up. Send a DISC back !and wait for DCE to repoll with DISCs type=disc %if dcedte = dte %then istate = dte waiting for ua %else istate = dce waiting for ua !i.e. down disctx = disctx + 1 %elseif istate = dce sarm queued ;!LAP type = sarm istate = link up reset line to xgate(link established) %else %return %finish -> send unnumbered %else ;!Link up %if rstate = rejpending %start type = rej rejtx = rejtx + 1 rstate = rejsent ;!2 ->send supervisory %elseif rstate = rnrpending ;!6 type = rnr rnrtx = rnrtx + 1 rstate = rnrsent ;!5 ->send supervisory %elseif rstate = rrpending %or (rstate = rejsent %and clock0 >= t1) %or final = set rstate = rrsent %if rstate = rrpending type = rr rrtx = rrtx + 1 clock5 = 0; ! clear the solid RNR Clock ->send supervisory %finish int r: %if ttt#fff %and tstate=0 %and (ttt-aaa)&7#window %start !Something to send/No RNR up from far end/No modulo count runout !respectively %if ttt=xxx %or clock1 >= t1 %start !Branch past this if we are retransmitting and Clock1 is still running wdesc==wspace(ttt) ;!Pick up the top frame on the Q m == wdesc_m x25==m_x25 len=wdesc_len type=(ttt&7)<<1 %if xxx=ttt %start xxx=(xxx+1)&sfmask itx = itx + 1 %else poll=pending retrytx = retrytx + 1 %finish !If we are not retransmitting, keep high water mark abreast of TTT !If we are, this is a retransmission so has the poll bit set ttt=(ttt+1)&sfmask active=2 ;!Big block being transmitted clock1=0 %if int = 'R' %then int = 0 %and active=0 %and ->int r ;!Force a transmit sequence error ->send frame %finish %finish %finish %return send supervisory: send unnumbered: len=2 active=1 x25 == om_m send frame: !In LAPB, I,SABM,DISC are always commands. UA,FRMR are responses. ! RR,REJ,RNR can be either ! We will drive REJ as a reply. RR and RNR will be commands if sent as ! idle line polls and responses if prompted by an I or RR command ! Note they must set the poll bit. pfbit=clear ;!Default %if type&1=0 %or type=sabm %or type=disc %then x=command %else x=response %if type = rr %or type = rnr %start x = comres %if x=command %then poll=pending %finish %if type&3 # 3 %then type = eee<<5 ! TYPE %if x=command %and poll=pending %then pfbit=pfset %and poll=sent %if x=response %and final=set %then pfbit=pfset %and final=clear !Calculate the address byte as follows: PSS algorithm is ! Commands DCE--> DTE Address=3 DTE--> DCE Address=1 ! Responses DCE--> DTE Address=1 DTE--> DCE Address=3 %if x=command %then address=1 %else address=3 !Addresses are the other way round for a DCE. %if dcedte=dce %then address=4-address clock0=0 %if int = 'B' %then address = 2 %and int = 0 ;!Force a bad address %if int = 'U' %then type = ua %and int = 0 ;!Force a spurious UA %if int = 'X' %then type = x'FD' %and int = 0;!Force a bad ctrl byte !For DQS - we may have shuffled the data one byte to the left. !if so, plant address and control bytes in the shuffled position not where !they normally go. x25_add=address x25_type=type ! PFBIT parb_type=line output parb_b==x25 parb_len=len !There's no need for the deferred RR once we've sent a frame of any kind rstate = rrsent %if rstate = rrdeferred monitor(parb, output tx) to comms hw(parb) %end ;!of handle output %routine handle input %record (parf) m %record (x25f) %name x25 %record (wdse) %name imess %integer r, s, x, l x25 == parb_b m_b == x25 ; m_address = m_address - 7 ; ! remove offset to x25 data l = parb_len %if int = 'E' %and type&1 = 0 %then l = -2 %and int = 0 !Force a received sequence error %if l<2 %start ;!Bad frame %if l=-2 %start monitor(null,dms) clock4=clock4+1 %if clock4>24 %then abort(read fails) %elseif l=-1 monitor(null,bad fr) %elseif l=-3 monitor(null,silofull) ;!Keep a count %else monitor(null, short frame) write(l, 3) ;printsymbol(':') write(address, 3) ;write(type, 3) ;write(x25_octet1, 3) newline %finish ->noise %finish %if address&x'FD' # 1 %then monitor(null, bad addrs rx) %and -> noise !Check for bad address. Strictly speaking we should ignore these if we're a DCE pfbit=type&x'10' !Find out what sort of frame this is. We need to know if it is !a command or response (or invalid). x=invalid ;!Guilty till proved innocent %if type&3#3 %start ;!S-frames and I-frames r=(type>>5)&7 ;!Extract N(R) %if type&1=0 %start ;!I-frames. s=(type>>1)&7 ;!Extract N(S) type=iframe x=command %else ;!Supervisory frames type = type & 15 ;!Mask out N(R) and P/F bit %if type=rr %or type=rnr %or type=rej %start ;!Only ones we recognise %if dcedte=dce %then address=4-address ;!Watch out. %if address = 3 %then x = command %else x = response %finish %finish %else ;!Unnumbered frames type = type & x'EF' ;!Mask out P/F bit %if type=sabm %or type=disc %then x=command %if type=ua %or type=frmr %then x = response %finish %if x=command %start comres = response ;!Next frame is a response to this one unless there is a good reason otherwise %if pfbit=pfset %start !Command with poll bit set requires an immediate RESPONSE final=set %if rstate = rrsent %or rstate = rnrsent %start %if no of buff < big limit %or hold rnr # 0 %start monitor(null, buffers low) rstate = rnrpending %finishelse rstate = rrpending %finish %finish %else %if x=response %and poll=sent %start %if pfbit=pfset %then poll = clear %elsestart %if dcedte = dce %then monitor(null, poll failure) %finish %finish %if x=invalid %then monitor(null, badframes rx) %and -> noise %finish ->noise %if abort req#0 %if istate#link up %start %if type=ua %and istate=waiting for ua %then %start istate = link up reset line to xgate(link established) set prio(2); ! link up, so now raise tasks priority level ! important for DUPs when modem signals lost ->valid %finish %if type=sabm %then b = 0 %and istate = uaqueued 1 %and ->valid %if type = sarm %then b = 1 %and istate = uaqueued 1 %and -> valid ;!LAP %if dcedte=dte %start %if type=disc %then istate = uaqueued 2 %and ->valid %if type = ua %then istate = sabm queued %and -> valid %else ;!DCE mode %if type=ua %then istate=waiting for sabm %and ->valid %if type=disc %and istate # dce waiting for ua %and %c istate # disc queued %then istate = uaqueued 2 %and ->valid %finish monitor(null,spurious uframerx) ->noise %else ;!LINK UP %if type&3=3 %start %if type=frmr %start frmrrx = frmrrx + 1 %elseif type = sabm abort(sabm received) %elseif type = disc abort(disc received) %finishelse abort(uframe in data) -> noise %elseif type=iframe %if s = eee %start ;!Sequence OK %if l > 2 %start clock4 = 0; ! No too long frame received p_ser=kernel ser p_reply = own id p_fn=input req p_line=line ;!Redundant here p_m == m_b mes_len=l-2 ;!Length excluding address & control bytes monitor(p,to upper) buffers held = buffers held - 1 irx = irx + 1 ;!Just keep a count traceid(p_m, p_ser) pon(p) x25 == null ; !Avoid freeing buffer %finishelse nullrx = nullrx + 1 eee=(eee+1)&7 ;!Increment received sequence no. %if no of buffnoise %finish %finish %finish ! x=aaa %while x&7#r %cycle %if x=xxx %start monitor(null, badack) ;monitor(null, query) ;write(r, 3) ;newline printstring("Bad Ack ") ->valid %finish x=(x+1)&sfmask %repeat %unless active=2 %and (xxx-x)&sfmask <= (xxx-ttt)&sfmask %start !Ignore ack if it includes one for block currently being transmitted %while aaa#x %cycle ;!Free off ackked blocks wdesc == wspace(aaa) free buffer(wdesc_m) ; wdesc_m == null itx = itx + 1 ;!Just count them wdesc_m == null !I have managed to convince myself that TTT could equal AAA !If we receive an ack for a frame while in mid-retransmit !If we dont do this, TTT and AAA could wind up inside-out. ttt = (ttt+1) & sfmask %if ttt = aaa aaa=(aaa+1)&sfmask ;!Increment sequence no. of first frame not ackked xxx=ttt ;clock1=0 ;window=6 ;!Leave Timer recovery condition clock3=0 %repeat %if ttt#xxx %then ttt=aaa ;!Retransmitting: retransmit first unackked frame %if type=rej %start ttt = aaa ;xxx = ttt %if rstate = rrsent %or rstate = rejsent %then rstate = rr pending %finish !to the first one not ackked If a Reject or retransmission %finish %finish ! valid: ! "Valid" here just means that the CRC was OK and it was a recognisable frame clock2=0 ;!Reset validity timer - chops him if this gets too big. noise: free buffer(m_b) %and m_b == null %unless x25 == null %or m_b == im ! handle output ! %end ;!of handle input %routine clock int alarm(25) ;!Replace 1/2 second timer clock0=clock0+1 %if istate#0 %start %if dcedte=dce %start ;!We are configured to be the DCE %if clock0 >= t1-1 %and istate=dce waiting for ua %then %c istate=disc queued %and poll = pending %if clock0>= t1*n2-1 %and istate=waiting for sabm %then %c istate = disc queued %and poll = clear %else ;!We are the DTE %if clock0 >= t1-1 %start %if istate=waiting for ua %start %if clock3 <= n2 %start clock3 = clock3 + 1 istate=sabm queued poll = pending %else istate = disc queued poll = clear %finish %elseif istate = dte waiting for ua %if clock3 <= n2 %start clock3 = clock3 + 1 istate = disc queued poll = pending %else istate = waiting for disc poll = clear %finish %finish %finish %finish %else ;!Link up %if rstate = rrdeferred %start %if no of buff < big limit %or hold rnr # 0 %then rstate = rnrpending %c %else rstate = rrpending %finish %if no of buff < big limit %start; ! time this out clock5 = clock5 + 1 %if clock5 > 360 %then abort(no buffs) %finish clock2=clock2+1 %if clock2 = n2*t1 %and ttt # aaa %start !No data acknowledged by far end in 80 ticks. abort(line timeout) %finish !Clock 1 is knocked back whenever one of our frames is ackked or !we retransmit. If there is a frame unacknowleged (AAA#TTT) and it !hasnt been ackkecd for 5 seconds we wil retransmit !unless he has RNR up. %if aaa#xxx %then clock1=clock1+1 %if clock1 >= t1 %and aaa#ttt %and tstate=0 %start !Enter Timer Recovery state clock3=clock3+1 ttt=aaa ;window=1 %if clock3 >= n2 %then abort(dataretries) %and %return ;!Retry N2 times and give up %else %if clock0 >= t1*2 %and quiet idle =0 %start ;!RCO-Defined line idle poll comres = command rstate = rnrpending %if no of buff>13) par = par+(pad&k'17700')>>6 %else ;!Otherwise make it a long one icurr_len = big buffer length-7 icurr_m == mes; ! bg 29/8/85 pad = icurr_b + 7 par = raddr(pad>>13) %finish ext bits = (par&k'176000')>>10 cad = par<<6+pad&k'77' hw_rxaddr = cad save ext bits = (save ext bits&x'c')!ext bits hw_Eaddr = save ext bits hw_rxbc = -icurr_len hw_iccsr = hw_iccsr&(~rxBCzero) hw_iccsr = hw_iccsr!dmaIenb %end; ! of put read on hardware %routine stop(%integer reason) %record (pf) p printstring("Xpro ") ;printstring(longnetname(line)) ;printstring(" disaster") write(reason, 1) ;newline !Gracefully. (This may not be a good idea but we'll try it.) %cycle poff(p) ;!Should be better than a tight loop - !a) Scheduler knows we're suspended b) won't fill poff queue %repeat %end ;!of Stop %routine octal(%integer n) %integer i printsymbol((n >> i)&7+'0') %for i = 15, -3, 0 %end ;!of Octal %routine move(%integer len,from,to) ! ! 'Assembler Routine' to emulate EMAS MOVE. ! Note: 1. No action if LEN<=0 ! 2. Registers 1,2 and 3 used. ! %label uploop, downloop, up, return ! *mov_len,1 ;! Load the length *ble_return ;! Return if less than or equal to zero *mov_from,2 ;! Load the FROM address *mov_to,3 ;! Load the TO address *cmp_3,2 ;!Is TO address > FROM address? *bgt_up ;!Yes - Move from top down in case... *beq_return ;!Move in place - Null function ! ! Loop to move LEN bytes FROM -> TO ! downloop: *movb_(2)+,(3)+ ;! Move the byte *sob_1,downloop ;! decrement & Continue if length not exhausted *br_return ! up: *add_1,2 *add_1,3 uploop: *movb_-(2),-(3) *sob_1,uploop return: %return %end ;!of Move %routine replace read !The object of this routine is to get the next read on as fast as possible. !Side-effect is that once the first read after a reinitialise hardware has !been issued it is never taken off. !The old read returns the actual length read plus a flag via des. We !remembered the read base address in PAD. We return.. !read address in parb_ADDRESS !read length in parb_LEN !x25 address in ADDRESS !x25 control in TYPE !These last two fields are passed up separately to avoid their being !overwritten if we are reading into IM %integer x, flag, ext bits, ad %record (mef) %name mx hw_iccsr = hw_iccsr&(~dmaIenb) %if intr&rx Ok # 0 %start; ! nb: intr is global! ! Block in ok flag = 0 parb_len = hw_RXaddr-cad-2 %else ! Block in error %if monbyte >= 8 %start printstring("Err:"); octal(chipstr&x'ff'); newline %finish flag = -1 %if chipstr&abort rec # 0 %then abort rx = abort rx+1 %if chipstr&ovr err # 0 %then wcov = wcov+1 %if chipstr&crc err # 0 %then silo = silo+1 %unless int = '+' %start hw_chipR1 = hw_chipR1&(~act rx); ! force re-synch hw_chipR1 = hw_chipR1!act rx %finish %finish parb_address = pad put read on hardware; ! replace the read now mx == parb_b %unless parb_b == null ! map it on UNLESS its an internal buffer address = mx_x25_add ;type = mx_x25_type %if flag = 0 %and monbyte = 9 %start printstring(" In:"); octal(address); space; octal(type) newline %finish %if flag < 0 %then parb_len = flag %elsestart %if parb_len > big buffer length %start ad = hw_rxaddr printstring("HW: read len > max:") octal(ad) ;space ;octal(cad) ;space ;octal(parb_len) ;newline %finish %finish %end %routine to comms hw(%record (parf) %name p) stop(mon hw fail) %if p_b == null %and p_type # initialise ! Newcastle KV11 specific code %integer i %switch typesw(initialise:modem status) -> type sw(p_type) type sw(initialise): id = get id %for i = 1, 1, 7 %cycle; ! FIND ABSOLUTE ADDRESSES raddr(i) = map abs(i<<13, 256, id); ! MY ADDRESSES f = map abs(i<<13, 0, id); ! AND OFF AGAIN %repeat maphwr(0) p_address = p_address&k'17777'; ! ENSURE ADDRESS IN SEG 0 hw_iccsr = clr chip i = 0 %cycle %exit %if hw_iccsr < 0 i = i+1 %exit %if i < 0 %repeat i = 0; ! allow chip to quiese hw_chipR1 = set DTR %cycle; i=i+1; %exit %if i<0; %repeat %if hw_chipstr&DSR # 0 %start printstring("got DSR ") hw_iccsr = hw_iccsr!x1 clock; ! switch to external clock %else printstring("No dsr ") %finish hw_chipR2 = auto flag; ! start flags hw_iccsr = hw_iccsr!intBenb; ! nb:no intAenb now hw_chipR1 = hw_chipR1!Act Tx rx reply = 0; tx reply = 0 %return type sw(output done): ! TRANSMITTER type = line output %if intr&tx bad # 0 %or txreply = 0 %start !! TRANSMITTER ERROR printstring("TX Error:"); octal(intr); newline p_len = 1 %else %if monbyte = 9 %then printstring("Tx Ok ") p_len = 0 %finish p_type = line output txreply = 0 %return type sw(input here): %return type sw(line output): !! OUTPUT REQUEST %if tx reply # 0 %then -> abort tx reply = id oseg = p_address par = raddr(oseg>>13) %if par = 0 %then -> abort par = par+(oseg&k'17700')>>6; ! ENSURE ACTUAL BLOCK ext bits = (par&k'176000')>>8 x = par << 6+p_address&k'77' save ext bits = (save ext bits&k'3')!ext bits hw_Eaddr = save ext bits hw_TxAddr = x hw_TxBc = -p_len hw_iccsr = hw_iccsr&(~txbczero) hw_iccsr = hw_iccsr!dmaOenb %if monbyte >= 9 %start %finish %return type sw(modem status): ! data set change %if mon byte >= 8 %start printstring("Dschg ") %finish hw_chipR1 = hw_chipR1&(~Act rx) %if chipstr&dsr # 0 %start hw_iccsr = hw_iccsr!x1 clock; ! go external timing %else ! hw_iccsr = hw_iccsr&(~x1 clock); ! internal to stop chip hanging %finish hw_chipR1 = hw_chipR1!Act Rx %return abort: printstring("kv11 Fail ") stop(mon hw fail) %end ;!of to comms hw %routine to xgate(%integer flag) %record (pf) p !Routine to send an 8-byte parameter area to XGATE giving it global !status, namely XPROT UP LINK ESTABLISHED/DOWN. !Differs from RCO-HDLC version in that LINK ESTABLISHED call passes !a Zero as the X25 address. p_ser = kernel ser p_reply = own id p_fn=output req p_line=line p_m == null p_c = flag monitor(p,to upper) pon(p) %end ;!of to XGATE %endofprogram ! !Compiler is apt to do arithmetic in the LHS when compiling statements !such as LHS = . Doesnt usually matter but bad !news if LHS is a hardware register - Arithmetic will twiddle status !bits etc. version hierarchy: !P = DUP11 only !Q = DQS11 only !F = Fast (Monitoring cut out)