!********************** !* lmtots/lmtsxy * !* date: 20.may.81 * !********************* %conststring (13) vsn = "lmts...1h " ! Prep options:- t - TS29 - XXX over transport service ! x - xxx ! b - Big buffer vsn #datestring !! stack = 300, streams = 1 %control x'4001' %recordformat xf(%byteinteger unit,fsys,%byteintegerarray fname(0:5)) %include "b_deimosspecs" %begin %owninteger mon = 0 %owninteger quiet = 0; ! 1 = no console op at all %owninteger clock on = 0; ! 1 = time call connects %ownstring (1) snil = "" %constintegername kw11s == k'072540' %constintegername kw11c == k'072544' %recordformat itpf((%byteintegerarray data(0:127) %or %string (127) s)) #if b %recordformat lev3f(%bytearray reserved(0:5), %record (itpf) itp) #else %recordformat lev3f(%bytearray reserved(0:7), %record (itpf) itp) ! itp_data(0) is actually inside the reserved space, as it is ! only used for the length, this should not matter ! In TS29, length byte is overwritten with zero #fi #if ~b %recordformat mef(%record(mef)%name link,%byteinteger len,type, %c (%record(lev3f) lev3 %or %bytearray params(0:241))) %recordformat pf(%byteinteger service,reply,(%byte fn,s1, %c %record(mef)%name mes,%byteinteger gate port, task port %or %c %byte a1, a2, b1, b2, c1, c2)) #else %recordformat mef(%integer buff no, len, %byte owner,type, %c (%record(lev3f) lev3 %or %bytearray params(0:241))) %recordformat pf(%byte service, reply, (%byte fn, s1, %c %integer buff no, %byte gate port, task port %or %c %byte a1, a2, b1, b2, c1, c2)) #fi %record (pf) p %recordformat qf(%record (mef) %name e) %recordformat tcpf(%integer state, con state ind, %c %byteinteger port, ostate, tcpn, term, %c size, max, %integer packets, cons, delay, ticks) %constinteger max conns = 100 %ownrecord (tcpf) %name tcp %ownrecord (tcpf) %array tcpa(0:max conns) ! %constinteger not allocated = 0 %constinteger conn asked = 1 %constinteger connected = 2 %constinteger tcp disconnecting = 3 !****** tcp_ostate states (permission to send) ***** %constinteger idle = 0 %constinteger busy = 1 !*********************************************************** %recordformat consf(%integer cnsl, state) %ownrecord (consf) %array cona(0:100) %ownrecord (consf) %name con %constinteger tt ser=1, gate ser=24, buffer manager=17 %constinteger rd=0, echo off=10 %constinteger request buffer=0, release buffer=1 %constintegername no of small == k'100114' %include "b_ygatecalls" %integer i, node, term, k, flag, tick, conns, x %owninteger initf %owninteger sta, cpu, pkts, sbr, byt, rjei, tim, rjeo, delay, ipkts, calls %owninteger inc users = 0, printall = 0, sesstype %owninteger conn ok, g port, power, kill it, maxc, d1, d2, session, chop %owninteger term char = ':'; ! for EMAS %constbyteintegername change out zero == k'160310' %constinteger t3 ser = 21 %ownrecord(mef) %name mes %ownstring (63) address = "" %ownstring (19) name = "eyre10**" %ownstring (19) pass = "....**" %ownstring (63) users = "obey ob**" %ownstring (7) stopm = "stop**" %routine readstring(%string (*) %name s) %integer i s = "" %cycle readsymbol(i); %exit %if i = nl s = s.tostring(i) %repeat %end %routine get buffer(%integer reason, r2) %integer type type = 1 %if r2 = 255 %then type = 0; ! get big buffer if connect, else small p_service=buffer manager; p_reply=id p_a1=request buffer; p_c1=type; p_c2=reason p_a2 = r2 pon(p) %end #if ~b %routine free buffer(%record(mef)%name mes) p_service=buffer manager; p_reply=id p_a1=release buffer; p_mes==mes pon(p) %end #else %routine free buff no(%integer buff no) ! not mapped, so send it straight back %return %if buff no = 0 p_service= buffer manager; p_reply = id p_fn = release buffer p_buff no = buff no pon(p) %end %routine free buffer(%record (mef) %name mes) %record (pf) p %integer buff no ! nb: routine ASSUMES buffer is mapped on buff no = mes_buff no %unless mes == null %start !There really is a buffer !Tell Buffer Manager it can have its buffer back. p_service = buffer manager ;p_reply = id p_fn = release buffer p_buff no = buff no pon(p) %finish %end ;!of Free Buffer %record (mef) %map map(%integer buff no) ! New compiler - so must get 0 %result == null %if buff no = 0 *mov_1,0 *mov_#8,1; ! desired vm seg no *2 ie 4*2 *iot %result == record(k'100000') %end #fi %routine mon mes(%record (mef) %name mes) %integer i, j, k, n %recordformat itp2f(%bytearray a(0:128)) %record (itp2f) %name itp k = mes_len itp == mes_lev3_itp write(k, 1); space; space j = 0 %cycle i = 0, 1, k write(itp_a(i), 1) j = j+1; %if j = 25 %then j = 0 %and newline %repeat newline %end %routine mon p(%record (pf)%name p) %integer i write(p_gate port, 1); printsymbol('/'); write(p_task port, 0) printstring(" fn ="); write(p_fn, 1) printsymbol(':'); write(p_a2, 1) newline %end %routine to gate(%integer fn, %record (mef) %name mes, %c %integer flag) %if fn = put output %start; ! queue these as necessary %if tcp_state # connected %start; ! throw away free buffer(mes); %return %finish ipkts = ipkts+1 tcp_size = tcp_size+1 tcp_max = tcp_size %if tcp_size>tcp_max %if mon < 0 %start select output(1) printstring("Out "); mon mes(mes) %finish %elseif fn = disconnect tcp_delay = 0 %return %if tcp_state = tcp disconnecting tcp_state = tcp disconnecting %finish p_service = gate ser; p_reply = id p_fn = fn; p_s1 = flag #if b p_buff no = mes_buff no #else p_mes == mes #fi p_task port = tcp_tcpn; p_gate port = tcp_port %if mon < 0 %start select output(1) printstring("l->g"); mon p(p) select output(0) %finish pon(p) %end %routine pack(%record(mef) %name mes, %string (*) %name s) string(addr(mes_params(mes_len))) = s mes_len = mes_len+length(s)+1 %end %routine do connect(%integer type, %record (mef) %name mes) !============================================================ %string (63) facn, cudf, cd2 tcp == tcpa(type) p_service = gate ser; p_reply = own id p_fn = connect p_gate port = 0; p_task port = tcp_tcpn p_s1 = 0; ! 1 for xxx call #if ~b p_mes == mes #else p_buff no = mes_buff no #fi mes_len = 0 facn = address cd2 = "" %if facn -> facn.(" D=").cudf %start string(addr(cd2+4)) = cudf length(cd2) = length(cudf)+4 charno(cd2,1) = 1; charno(cd2,2)=0; charno(cd2, 3)=0; charno(cd2,4)=0 %finish pack(mes, facn) pack(mes, snil); ! calling address (null) facn = "P=128/128" pack(mes, facn) pack(mes, cd2) %if mon < 0 %start select output(1); spaces(5) printstring("xxx: to gate:"); {t} mon p(p) select output(0) %finish pon(p) %if clock on # 0 %start tcp_ticks = kw11c %finish conns = conns+1 tcp_state = conn asked calls = calls +1 %end %routine block(%record (mef) %name mes, %integer cnsl) %integer i, j, k %record (lev3f) %name lev3 %record (itpf) %name itp %switch sw(0:6) lev3 == mes_lev3 itp == mes_lev3_itp cnsl = cnsl-1 con == cona(cnsl) tcp == tcpa(cnsl) %if p_a2 # 0 %then ->sw(6); ! special go-ahead request itp_s = "" -> sw(con_state) sw(0): ! now dummy (sends name in state 1 con_state = con_state+1 -> sw(1) sw(1): ! send name itp_s = name j = 0 -> comm %if session = 4; ! unix - hold user login name %if cnsl >= 10 %start k = cnsl//10 j = k*10 k = k+'1' %if session # 2 %then charno(itp_s, 5) = k %finish k = cnsl-j+'0' %if session # 2 %then charno(itp_s, 6) = k %if sesstype = 'I' %start charno(name, 11) = cnsl+'a'; ! a, b, c etc %finish -> comm sw(2): ! send pass itp_s = pass -> comm sw(3): ! disconnect call %if session = 0 %or chop # 0 %start tcp_state = tcp disconnecting to gate(Disconnect, null, 0) tcp_delay = 0 free buffer(mes) %return %else ! send repeated commands itp_s = users -> comm %finish comm: mes_len = length(itp_s) %if mon < 0 %start select output(1) %if length(itp_s) # 0 %then spaces(3) %and printstring(itp_s) newline select output(0) %finish length(itp_s) = 0; ! set the TS29 byte to zero to gate(put output, mes, 0) con_state = con_state+1 %if con_state = 4 %then con_state = 3 %if con_state = 4 %then con_state = 0 pkts = pkts+1 tcp_packets = tcp_packets+1 %end %routine analyse itp input(%record (mef) %name mes) %record (itpf) %name itp %integer i, j, k, qbit, q %string (127) t,v itp == mes_lev3_itp k = tcp_tcpn qbit = length(itp_s); ! pick up ts29 byte before overwriting it length(itp_s) = mes_len-1 v = itp_s %if qbit # 0 %start %if charno(v, 1) = 1 %then -> disc it %if charno(v, 1)&4 # 0 %start; ! set & read or read length(itp_s) = 128; ! re-instate %if charno(v,1)=4 %start itp_data(2)=1; itp_data(3)=0; mes_len = 3+1 %finish itp_data(1) = 0 to gate(put output, mes, 0) %finish %else free buffer(mes) %return %finish con == cona(k-1) %if mon < 0 %start select output(1) printstring("InPkt:"); write(k, 1); write(con_state, 1) write(itp_data(0), 1) mon mes(mes) %if length(v) > 0 %then printstring(v) newline select output(0) %finish %if mon # 0 %start write(k, 1); printsymbol(':') printstring(v); newline %finish %if v -> t.("**2900").v %start disc it: to gate(Disconnect, null, 0) tcp_state = tcp disconnecting %finish %else %start q = charno(v, length(v))&x'7f'; ! no parity %if session = 0 %or q = ':' %c %or q = term char %start %if delay = 0 %then get buffer(k, 0) %else tcp_delay = delay %finish %if chop # 0 %and con_state = 3 %then -> disc it ! don't wait for prompt on quick disc, do it on ! any output after pass sent %finish free buffer(mes) %end %routine mon tcps %integer i, pkt select output(1) %if chop # 0 %then printstring("Calls =") %and write(calls, 1) printstring(" Current Conns ="); write(conns, 1) pkt = 0 pkt = pkt+tcpa(i)_packets %for i = 0, 1, maxc printstring(" pkts to host ="); write(ipkts, 1) printstring(" per sec ="); write(ipkts//60, 1) printstring(" Data pkts ="); write(pkt, 1) printstring(" per sec ="); write(pkt//60, 1) newline %if printall # 0 %start printstring("Ind Cons Pkts ") %cycle i = 0, 1, maxc tcp == tcpa(i) write(i, 2) write(tcp_cons, 4) write(tcp_packets, 4) %if i&3 = 3 %then newline %else spaces(5) tcp_max = 0; tcp_packets = 0 %repeat newline %finish select output(0) tcpa(i)_packets = 0 %for i = 0, 1, maxc ipkts = 0 calls = 0 maxc = maxc+inc users; sta = maxc %end i = map virt(buffer manager, 5, 4) i = map virt(buffer manager, 6, 5) printstring(vsn) printstring(datestring) newline prompt("Address(TS)?"); readstring(address) prompt("cnsls?"); read(maxc) skipsymbol term char = 124; ! for erte numbers on emas again: prompt("Target(M,A,V,E,U,I,T or S)?"); readsymbol(session) sesstype = session %if session = 'M' %start skipsymbol mon = -1 -> again %finish %if session = '?' %start skipsymbol prompt("Name?"); readstring(name) prompt("Pass?"); readstring(pass) name = name."**"; pass = pass."**" -> again %finish %if session = 'A' %or session = 'Y' %then session = 1 %else %start %if session = 'V' %start session = 2 term char = ' ' name = "ZZZ10**" pass = "fredfred**" %finish %else %start %if session = 'E' %start session = 3; term char = ':' name = "EYRK10**" pass = "BRIN**" %finish %else %start %if session = 'U' %start name = "mark**" session = 4; term char = 32 pass = "frumpies**" %finish %else %start %if session = 'S' %start; ! special loop session = 6 term char = 13; ! cr on end %finish %else %start %if session = 'T' %start; ! torch special session = 4; term char = 32 name = "info**"; pass = "usr**" users = "all**" %finish %else %start %if session = 'I' %start session = 2; term char = '.' name = "login testa**"; pass = "test**" %finish %else session = 0 %finish %finish %finish %finish %finish %finish skipsymbol prompt("Quick Dis(Y/N)?"); readsymbol(i) %if i = 'Y' %then chop = 1 %else chop = 0 skipsymbol prompt("Delay (2 per Sec)?"); read(delay) skipsymbol maxc = maxc-1 sta = maxc %cycle i = 0, 1, 100 tcp == tcpa(i) tcp_tcpn = i+1 %repeat alarm(10) i = length(name) charno(name,i-1) = 13; charno(name,i) = 10 i = length(pass) charno(pass,i-1) = 13; charno(pass,i) = 10 i = length(users) charno(users, i-1) = 13; ! only 'cr' for xxx & ts29 charno(stopm, 5) = 13 %cycle p_service = 0; poff(p) %if p_reply = 0 %start; ! clock %if int # 0 %start %if int = 'U' %start; ! new command prompt("New Command?") readstring(users) length(users) = length(users)+1 charno(users, length(users)) = 13 length(users) = length(users)+1 %finish %if int = 'A' %start kill it = -1 chop = 0 printstring("killing it ") %cycle i = 0, 1, max conns tcp == tcpa(i) to gate(Disconnect, null, 0) %if tcp_state = connected tcp_state = tcp disconnecting %repeat int = 0 %finish %if 'M' <= int <= 'P' %start mon = int-'O'; int = 0 %finish %if '1' <= int <= '9' %start maxc = maxc+int-'0'; sta = maxc %finish %if int = 'I' %then inc users = inc users+1 %if int = 'C' %then users = stopm %if int = 'T' %then use tt(t3 ser) %if int = '*' %then printall = 1-printall %and int = 0 %if int = 'Z' %start %if kill it >= 0 %then printstring("Do int:A first ") %else %stop %finish %if int = 'T' %start clock on = 1-clock on %if clock on = 1 %start map hwr(3) kw11s = k'33'; ! 10khz, no ints, up, multiple %finish %finish %if int='?' %start write(flag, 1) write(pkts, 4); newline mon tcps %finish int = 0 %finish tick = tick+1 %if tick >= 120 %and quiet = 0 %start tick = 0 mon tcps %finish alarm(25); ! 1/2 second #if ~b %continue %if no of small < 15 %or kill it < 0 #else %continue %if kill it < 0 #fi i = initf initf = initf+1; initf = 0 %if initf > maxc %cycle con == cona(i) tcp == tcpa(i) %if tcp_state = 0 %start get buffer(i, 255) tcp_state = conn asked %exit %unless chop = 1; ! several on multi-option %finish %exit %if i = initf i = i+1; i = 0 %if i > maxc %repeat %cycle i = 0, 1, maxc tcp == tcpa(i) %if tcp_delay > 0 %start tcp_delay = tcp_delay-1 %if tcp_delay = 0 %and tcp_state # tcp disconnecting%then get buffer(tcp_tcpn, 0) %finish %repeat %continue %finish %if mon < 0 %and p_reply = gate ser %start select output(1) printstring("g->l") mon p(p) select output(0) %finish %if p_reply = buffer manager %start #if b mes == map(p_buff no) mes_owner = own id #else mes == p_mes #fi %if kill it < 0 %then free buffer(mes) %and %continue %if p_a2 = 255 %then do connect(p_c2, mes) %else %c block(mes, p_c2) %continue %finish %if p_reply = gate ser %start #if b mes == map(p_buff no) mes_owner = own id %unless mes == null #else mes == p_mes #fi node = p_task port-1 tcp == tcpa(node) %if p_fn = accept call %start; ! 2nd reply %if %not mes == null %then free buffer(mes) tcp_port = p_gate port %if kill it < 0 %then to gate(Disconnect, null, 0) %c %and tcp_state = tcp disconnecting flag = p_s1 %if mon # 0 %start write(node, 1); printstring(":call accepted") newline %finish %if clock on # 0 %start i = kw11c; %if i repeat tcp_state = 0 %finish %if conns = 0 %and kill it < 0 %start p_service = 0; poff(p); ! wait for timer tick %stop %finish %continue %finish %if p_fn = enable output %start tcp_size = tcp_size-p_s1 tcp_packets = tcp_packets+p_s1 %continue %finish %if p_fn = input here %start -> junk %if kill it < 0 pkts = pkts+1 to gate(enable input, null, 1) analyse itp input(mes) %continue %finish %if p_fn = control data %start pkts = pkts+1 to gate(enable input, null, 1) junk: free buffer(mes) %continue %finish %if p_fn = reset %start printstring("Reset:"); write(mes_lev3_reserved(2), 1) write(mes_lev3_reserved(3), 1); newline free buffer(mes) to gate(Disconnect, null, 0) tcp_state = tcp disconnecting %continue %finish printstring("funny fn"); write(p_fn, 1) printstring(" from"); write(p_reply, 1); newline %continue %finish %repeat %endofprogram