! Ether processes ! This file contains the processes responsible for interfacing to the ! Ether station. There are three distinct operations involved: ! (a) reading packets from the Ether station and buffering them ! internally until such time as the filestore is ready to ! process them; ! (b) at a convenient time, the packet is split apart into its ! constituent "command" and "data" parts (crunged), the ! resulting buffer being queued for processing by the ! file system; ! (c) dequeueing buffers which are to be sent to the Ether ! and forwarding them to the station. ! The notion of a buffer "context" is maintained in the filestore, in ! order that the validity of the Uno or Xno can be determined. This ! is identical with the (local) port assigned to the client. Unos and ! Xnos are only valid if used in the correct context. %option "-nocheck-nostack-noline" %constinteger depth limit = 3 {DAK}%constinteger facility msftime = 11 {DAK}%include "System:MSFSys.Inc" %include "Config.Inc" %include "System:Common" %include "System:Utility.Inc" %include "System:Schedule.Inc" %include "Inc:FS.Imp" %include "Inc:Util.Imp" %ownrecord(common fm)%name common %externalrecord(common fm)%mapspec common area ! Crunge an ether packet into a filestore buffer. ! The packet is split apart (at the first NL character) into ! its component command and data parts. If this succeeds, then ! fill in the fields of the internal buffer and return 0 (success). ! Otherwise fill in the fields of the internal buffer with an ! appropriate error message and return -1 (an error). %integerfn crunge buffer(%record(ether buffer fm)%name ebuff, %integername cbuff) %record(port fm)%name pi %integer i, remaining, nl limit %string(255)%name text %string(255) qqq %record(buffer fm)%name cb %bytename ch c buff = claim buffer ! We now (should) have an internal buffer. (We ignore the ! case where there aren't any free......) %if cbuff < 0 %start pdate printstring("*** Crunge buffer -- no free buffers!!!") newline %result = -1 ! Ignore it and hope it goes away..... %finish %if common_diags & ether diags # 0 %start pdate printstring("Crunge ether buffer into "); write(c buff, 0) printstring(" ("); write(ebuff_bytes, 0); printstring(" bytes)") newline %finish cb == common_buffer(c buff) -> reject %if ebuff_bytes = 0; ! null packet -- not allowed cb_ether bytes = ebuff_bytes; ! diagnostic field only ch == ebuff_data(0) text == cb_text; text = "" %if ebuff_bytes < 255 %then nl limit = ebuff_bytes %c %else nl limit = 255 ! now look for the NL %for i = 1, 1, nl limit %cycle %if ch = nl %start ! found it remaining = ebuff_bytes - i %if remaining = 0 %start ! command only, no data cb_bytes = 0 %else ! data too, so move it into buffer bulk move(remaining, ch[1], cb_b(0)) cb_bytes = remaining %finish cb_context = ebuff_context; ! note context %if common_diags & ether diags # 0 %start pdate printstring("OK, text "); write(length(cb_text), 0) printstring(" + data") %if cb_bytes # 0 printstring(", context "); write(cb_context, 0) newline pdate qqq = cb_text; zap login(qqq) printstring("Text is """); printstring(qqq) print symbol('"'); newline %finish %result = 0 %else ! not a NL yet, so copy the char into the command part text = text . to string(ch) ch == ch[1] %finish %repeat ! No NL found, so drop through..... reject: pdate printstring("*** Bad ether packet: port ") write(ebuff_context, 0) printstring(" (") %if 0 < ebuff_context <= ports %start pi == common_port info(ebuff_context) %if pi_state = 0 %start printstring("free ??") %else phex2(pi_remote); print symbol('.') phex2(pi_port) %finish %else printstring("**bad port**") %finish printstring("), size "); write(ebuff_bytes, 0) printstring(", command ") %if 'A' <= ebuff_data(0) <= 'Z' %or 'a' <= ebuff_data(0) <= 'z' %start print symbol(ebuff_data(0)) %else print symbol('?') %finish newline ! Fill in appropriate error response cb_text = "-1 Bad ether packet" . snl cb_bytes = 0 cb_context = ebuff_context %result = -1 %end ! Put a buffer onto the Ether TX queue. It will be removed and ! transmitted when one of the Ether TX processes becomes free. %externalroutine enqueue ether request(%integer request) %integername x %if common_diags & ether diags # 0 %start pdate printstring("Request transmission of "); write(request, 0) printstring(" to Ether"); newline %finish common_buffer(request)_link = 0 ! Ensure list is properly terminated! ! Now chain down looking for the end... iof x == common_ether request queue x == common_buffer(x)_link %while x # 0 ! Found it -- insert the buffer and kick the TX processes x = request ion kick(ether TX request) %end !! ! Diagnostic routine -- print out the first few bytes of a buffer !! !! %routine print buffer(%integer buffer) !! %record(buffer fm)%name b !! %record(ether buffer fm)%name e !! %integer i !! %return %unless 0 < buffer <= buffs !! b == common_buffer(buffer) !! %return %unless 0 <= b_ether packet <= ether buffers !! e == common_ether buffer_buffer(b_ether packet) !! pdate !! printstring("In: ") !! %for i = 0, 1, e_bytes - 1 %cycle !! print symbol(' '); pxb(e_data(i)) !! %exit %if i = 20 !! %repeat !! newline !! pdate !! printstring("Out:") !! %for i = 1, 1, length(b_text) %cycle !! print symbol(' '); pxb(charno(b_text, i)) !! %exit %if i = 20 !! %repeat !! newline !! pdate !! printstring("Out:") !! %for i = 0, 1, b_bytes - 1 %cycle !! print symbol(' '); pxb(b_b(i)) !! %exit %if i = 20 !! %repeat !! b_ether packet = -1 !! %end ! Chain down a list of buffers freeing them and kicking any waiting processes %routine zap buffer list(%integername x) %record(buffer fm)%name b %integer next, it it = x; x = 0 %while it # 0 %cycle %unless 0 < it <= buffs %start pdate printstring("*** Zap buffer list: bad buffer ") write(it, 0) newline ! Write off the rest %return %finish b == common_buffer(it) %if b_sync # 0 %start ! Kick anyone waiting kick(b_sync) b_sync = 0 %finish next = b_link release buffer(it) it = next %repeat %end ! Port control stuff follows.... %constinteger port free = 16_00000000 %constinteger port allocated = 16_00000001 %constinteger port active = 16_80000000 %routinespec deallocate port(%integer port) ! Find a port for a client. %result is +p %if the client is new ! -p %if the client has revived ! 0 %if there are no free ports %integerfn allocate port(%integer remote, port) %integer i %record(port fm)%name p ! First check if we know the client %for i = 1, 1, ports %cycle p == common_port info(i) %if p_state # port free %and %c p_remote = remote %and p_port = port %start ! Known -- reuse the port p_state = port allocated p_NAK last = -1 zap buffer list(p_buffer) p_retries = -1 time stamp(p_opened stamp_date, p_opened stamp_time) p_active stamp = p_opened stamp %result = -i %finish %repeat %for i = 1, 1, ports %cycle p == common_port info(i) %if p_state = port free %start ! Found a free port p_state = port allocated p_remote = remote p_port = port p_retries = -1 time stamp(p_opened stamp_date, p_opened stamp_time) p_active stamp = p_opened stamp %if p_buffer # 0 %start pdate printstring("*** Closed port "); write(i, 0) printstring(" has buffers pending") newline zap buffer list(p_buffer) %finish %result = i %finish %repeat %result = 0 %end ! Free a port -- clear down info and close it %routine free port(%integer port) %record(port fm)%name p %record(buffer fm)%name b %unless 0 < port <= ports %start pdate printstring("*** Bad port "); write(port, 0) printstring(" (Free port)"); newline %return %finish p == common_port info(port) zap buffer list(p_buffer) p_NAK last = -1 p_state = port free ether close(port) iof ack = ack ! (1 << port) nak = nak ! (1 << port) ion %end %externalintegerfn client station(%integer port) %result = port %if port < 0 %unless 0 < port <= ports %start {} %result = port %unless qsart present = 0 pdate printstring("*** Bad port "); write(port, 0) printstring(" (Client station)"); newline %result = -1 %finish %result = common_port info(port)_remote %end %externalroutine print client address(%integer port) %record(port fm)%name p %unless 0 < port <= ports %start printstring("unknown port ") write(port, 0) %return %finish p == common_port info(port) phex2(p_remote) print symbol('.') phex2(p_port) %end ! For use by file system processes (particulary when Z-ing). ! %true if the last packet sent through the port was NAKed. %externalpredicate NAKed(%integer port) %unless 0 < port <= ports %start %false %unless qsart present = 0 pdate printstring("*** Bad port "); write(port, 0) printstring(" (NAKed)"); newline %true %finish %true %if common_port info(port)_NAK last # 0 %false %end ! Ether receiver handler. Called by the Ether receiver process ! when a DTX bit is set to indicate a packet has arrived. ! Incoming packets are buffered in a circular list where they ! await future processing. %routine ether packet available(%integer port no) %record(ether buffer area fm)%name ether buffer %record(ether buffer fm)%name buffer %record(port fm)%name port info %unless 0 < port no <= ports %start pdate printstring("*** Bad port "); write(port no, 0) printstring(" (Ether packet available)"); newline %return %finish port info == common_port info(port no) %if port no # 0 %and port info_state = port free %start pdate printstring("*** Port "); write(port no, 0) printstring(" should be closed -- packet arrived??!") newline ! Attempt to dump it ether close(port no) iof dtx = dtx & (\ (1 << port no)) ion %return %finish ether buffer == common_ether buffer %if common_diags & ether diags # 0 %start pdate printstring("Ether packet available, port = ") write(port no, 0) printstring(", ether buffer = ") write(ether buffer_next to use, 0) newline %finish common_monitor_ether reads = common_monitor_ether reads + 1 ! For the console log. buffer == ether buffer_buffer(ether buffer_next to use) ! Get the next buffer to use buffer_bytes = ether read(port no, buffer_data(0), ether packet size) %if buffer_bytes = 1 %and %c (buffer_data(0) = 4 %or buffer_data(0) = 12) %start ! Special command -- free the port deallocate port(port no) %return %finish buffer_context = port no %if common_diags & ether diags # 0 %start pdate write(buffer_bytes, 0); printstring(" bytes received") newline %finish ether buffer_next to use = (ether buffer_next to use + 1) & ether buffers ! Bump pointer in circular list, then kick the next stage of processing. kick(ether RX request) %end ! Ether transmission stuff follows..... ! Open an ether port. The remote address and remote port have already ! been filled in by the port allocation function. %routine open port(%integer port) %record(port fm)%name p p == common_port info(port) %if common_diags & ether diags # 0 %start pdate printstring("Open port "); write(port, 0) printstring(" to remote "); phex2(p_remote) printstring(", port "); write(p_port, 0) newline %finish ether close(port); ! tidy things up, just in case ether open(port, p_remote << 8 ! p_port) %end ! Send a buffer to the ether. It must first be converted from a nice ! tidy fixed format into the nasty variable format required by the ! protocol (data separated from response by a NL). Since there will ! be sevaral incarnations of this process extant in a filestore we ! use to keep track of the particular one current. NB if we find ! that the port is already active then we simply queue the buffer until ! such time as the ACK from the previous packet is processed. %routine send buffer(%integer buffer, us) %record(buffer fm)%name b %record(port fm)%name p %bytename t %integer size, ato, port, depth = depth limit, port mask %integername x %bytearray out buffer(0 : 1023) %unless 0 < buffer <= buffs %start pdate printstring("*** Send buffer: bad buffer ") write(buffer, 0) newline %return %finish b == common_buffer(buffer) port = b_context %unless 0 <= port <= ports %start %if qsart present = 0 %start pdate printstring("*** Send buffer -- bad port ") write(port, 0) newline %else send qsart buffer(buffer) %finish %return %finish %if common_diags & ether diags # 0 %start pdate printstring("Send buffer "); write(buffer, 0) printstring(" to port "); write(port, 0) newline %finish port mask = 1 << port p == common_port info(port) %if port # 0 %and p_state = port free %start pdate printstring("*** Sending packet to closed port ") write(port, 0); printstring("??!") newline -> fake NAK %finish ! Now check the activity level of the port %if p_state < 0 %start ! Port is already active %if port = 0 %start ! Self-defence time.... If port 0 is active then dump ! the request without sending it. The client will ! hang, but that's tough. The alternative is to ! allow the filestore to be swamped.... %if b_sync # 0 %start ! Shouldn't be, but..... pdate printstring("*** Sync port 0 (self-defence) ??!") newline kick(b_sync) b_sync = 0 %finish release buffer(buffer) %return %finish ! Otherwise queue the buffer. x == p_buffer depth = depth - 1 %and x == common_buffer(x)_link %while x # 0 %if depth <= 0 %start ! Self-defence again. The client has sent in a request ! without waiting for the previous response to be ACKed. ! Note that we allow a little leeway for clients, but ! not too much..... pdate printstring("Port "); write(port, 0) printstring(" ("); phex2(p_remote) print symbol('.'); phex2(p_port) printstring(") exceeded send-ahead limit") newline %if b_sync # 0 %start ! Kick requested kick(b_sync) b_sync = 0 %finish release buffer(buffer) %return %finish x = buffer ! Ensure proper termination of list b_link = 0 %return %finish p_state = p_state ! port active %if b_text # "" %start ! First we move the text of the response (if any). bulk move(length(b_text), byteinteger(addr(b_text) + 1), out buffer(0)) size = length(b_text) t == out buffer(size) %else ! No response text (usually from Z) t == out buffer(0) size = 0 %finish ! printstring("Size = "); write(size, 0) ! printstring(", out buffer(0) at "); phex(addr(out buffer(0))) ! printstring(", T == "); phex(addr(t)) ! newline %if b_bytes # 0 %start ! Move the data (if any). bulk move(b_bytes, b_b(0), t) size = size + b_bytes %finish time stamp(p_active stamp_date, p_active stamp_time) common_monitor_ether writes = common_monitor_ether writes + 1 ! All set up, so send the packet to the ether. %if common_diags & ether diags # 0 %start pdate printstring("Sending "); write(size, 0) printstring(" bytes to port ") write(port, 0) newline %finish ether write(port, out buffer(0), size) ! The packet is on its way. Wait here for the ACK. wait for ack(port, us) %if nak & port mask = 0 %start ! The packet got through. Note the fact. p_NAK last = 0 %if b_sync # 0 %start ! The requesting filestore process asked to be ! notified when the packet has gone (it is ! probably in the middle of a Z loop, and ! wants to maintain proper synchronisation with the ! other end). %if port = 0 %start pdate printstring("*** Sync port 0 ??!") newline %finish kick(b_sync) b_sync = 0; ! just in case -- only kick when asked %finish %else ! The packet didn't get through. iof nak = nak & (\ port mask); !? ion pdate printstring("NAK port ") write(port, 0) printstring(", client ") %if port = 0 %start phex2(out buffer(0)) print symbol('.') phex2(out buffer(1)) %else phex2(p_remote) print symbol('.') phex2(p_port) %finish common_monitor_ether errors = common_monitor_ether errors + 1 newline fake NAK:p_NAK last = 1; ! note the NAK %if b_sync # 0 %start ! kick the requesting process, if required %if port = 0 %start pdate printstring("*** Sync port 0 ??!") newline %finish kick(b_sync) b_sync = 0 %finish %finish p_state = p_state & (\ port active) release buffer(buffer); ! finished with this buffer, so free it %while p_buffer # 0 %cycle ! Another buffer queued for this port. Dequeue it from the ! port wait queue and enqueue it on the ether TX queue. NB don't ! just process it here, as we must %return to unblock any ! higher priority processes. buffer = p_buffer p_buffer = common_buffer(buffer)_link enqueue ether request(buffer) %repeat %end ! VAX date/time reading. This is used during the boot sequence, when ! the date and time is obtained from VAX, if possible, %externalstring(31)%fn VAX date %bytearray b(0 : 31) %integer i b(1) = 6 ether open(1, 16_7200) ether write(1, b(1), 1) %for i = 1, 1, 200 000 %cycle ! Time out if no response -> OK %if dtx & 2 # 0 %repeat ether close(1) %result = "" OK: i = ether read(1, b(1), 31) ether close(1) b(0) = i %result = string(addr(b(0))) %end ! Enqueue buffers for the filestore processes %routine enqueue process request(%integer request) %integername x %if common_diags & ether diags # 0 %start pdate printstring("Enqueue "); write(request, 0) printstring(" for punter process") newline %finish common_buffer(request)_link = 0 ! Ensure list is properly terminated iof x == common_proc request queue x == common_buffer(x)_link %while x # 0 ! Chain down to the end, then insert the current request ! buffer there and kick the filestore processes. x = request ion kick(proc request) %end ! Check if connects are allowed. This should really be programmable ! from the console.... %predicate connect allowed(%integer remote) %true %if remote = 16_34 %or remote = 16_1E %c %or remote = 16_14 %or remote = 16_15 %or remote = 16_1B %false %end ! Deallocate ports. Queue a clear request to the filestore service queue ! and zap the port (clear request has -ve bytes of data). %routine deallocate port(%integer port) %record(buffer fm)%name b %integer x %unless 0 < port <= ports %start pdate printstring("*** Deallocate port -- bad port ") write(port, 0) newline %return %finish ! pdate ! printstring("Station on port "); write(port, 0) ! printstring(" disconnecting") ! newline x = claim buffer %if x > 0 %start ! Enqueue a cleardown request to the filestore ! server queue (if there is a buffer available). b == common_buffer(x) b_bytes = -1 b_context = port enqueue process request(x) %finish trace(port, trace in, "Disconnecting") free port(port) %end ! Port 0 handler comes next. It is required to check the incoming ! facility request code (should be 2 for a 1976-filestore). If this ! is valid, then attempt to allocate a (local) port, returning ! either a failure message or the number of the allocated port. !DAK 22/05/85 facility 16_0B added to permit MSF clock time access %recordformat p0 buffer fm(%byte ra, rp, z1, z2, z3, z4, req fac, %bytearray x(0 : 127)) %ownrecord(p0 buffer fm) p0 buffer = 0 %string(7)%fn p0 address %result = to string(p0 buffer_ra) . to string(p0 buffer_rp) . %c to string(0) . to string(0) . to string(0) . to string(0) %end %routine port allocation %record(buffer fm)%name b %record(port fm)%name p %string(255) text %integer alloc p %integer x, ato, i %if common_diags & ether diags # 0 %start pdate printstring("Port allocation") newline %finish x = ether read(0, p0 buffer_ra, 134) %unless p0 buffer_req fac = facility code %start ! Not for a 1976-filestore {DAK} %if p0 buffer_req fac = facility msftime %start {DAK} text = get MSF time !DAK get MSF time returns the data as retreived from MSF clock decoder board {DAK} %else text = "-6 Unsupported facility" . snl %finish %else %if common_system open & system open = 0 ! Connects have been disabled text = "-6 System not open" . snl %else alloc p = allocate port(p0 buffer_ra, p0 buffer_rp) ! Try to allocate a (local) port for the client %if alloc p = 0 %start ! Weren't any. pdate printstring("*** Station "); phex2(p0 buffer_ra) printstring(" port "); write(p0 buffer_rp, 0) printstring(" failed to connect -- no ports") newline ! ! Display the port connection map ! %for i = 1, 1, ports %cycle ! spaces(7) %if i & 7 = 1; ! Instead of pdate ! write(i, 3) ! p == common_port info(i) ! %if p_state = port free %start ! printstring(" *free* ") ! %else ! space; phex2(p_remote) ! print symbol('.'); phex2(p_port) ! spaces(2) ! %finish ! newline %if i & 7 = 0 ! %repeat ! newline %if ports & 7 # 0 ! Return an error to the client text = "-6 No ports" . snl %else ! Got one. %if alloc p < 0 %start ! Already known. Port number negated in this case. %if common_diags & ether diags # 0 %start pdate printstring("Client already known") newline %finish alloc p = -alloc p ! printstring("Claiming buffer"); newline x = claim buffer %if x > 0 %start ! Enqueue a cleardown request to the filestore ! service queue. b == common_buffer(x) b_bytes = -1 b_context = alloc p enqueue process request(x) %finish trace(alloc p, trace in, "Connect (known client)") ether close(alloc p) %finish %if common_diags & ether diags # 0 %start pdate printstring("Station x'"); phex2(p0 buffer_ra) printstring("' port "); write(p0 buffer_rp, 0) printstring(" connecting to port "); write(alloc p, 0) newline %finish %if common_system open & allow connects # 0 %c %or connect allowed(p0 buffer_ra) %start ! System open to the client. Send the (local) ! port number allocated. open port(alloc p) text = hdx1(alloc p) . snl %else ! System not open (probably maintenance). text = "-6 Connects are disabled" . snl free port(alloc p) %finish %finish %finish x = claim buffer %if x > 0 %start ! Send the reply to the client. (If we're out of ! buffers it'll just hang.....) b == common_buffer(x) b_text = p0 address . text b_context = 0 b_bytes = 0 enqueue ether request(x) %finish %end ! Process main entry points follow.... ! Packet reception process. Grab stuff from the Ether station ! as fast as possible -- it can be processed properly at leisure. %externalroutine packet main entry %integer i %cycle wait for(packet arrived) %while dtx # 0 %cycle ! ie, don't wait until we're sure we've got the lot! %for i = 1, 1, ports %cycle ether packet available(i) %if dtx & (1 << i) # 0 %repeat port allocation %if dtx & 1 # 0 %repeat %repeat %end ! Now we can afford to take the time to process the head of the ! incoming packet queue. %externalroutine ether RX main entry %record(buffer fm)%name buffer %record(ether buffer area fm)%name ether buffer %record(ether buffer fm)%name ebuff %record(port fm)%name port info %integer allocated, x, i %byte dummy ! First we initialise this module. common == common area ether buffer == common_ether buffer common_port info(i) = 0 %for i = 0, 1, ports ! Now clear the station twait; ethc = 15; twait dtx = 0; ack = -1; nak = 0 pdate printstring("Filestore ether address is ") phex2(ether station) newline %cycle wait for(ether RX request) %if ether buffer_next to process # ether buffer_next to use %start ! Message from a client available for processing ebuff == ether buffer_buffer(ether buffer_next to process) ! ebuff_context contains port number %if common_diags & ether diags # 0 %start pdate printstring("Message from port ") write(ebuff_context, 0) newline %finish x = crunge buffer(ebuff, allocated) %if x = 0 %start ! valid packet received -- enqueue it on the filestore ! service queue. buffer == common_buffer(allocated) trace(buffer_context, trace in, buffer_text) enqueue process request(allocated) %else ! bad packet -- enqueue the error response to the Ether enqueue ether request(allocated) %if allocated > 0 %finish ether buffer_next to process = %c (ether buffer_next to process + 1) & ether buffers ! bump head of circular list. Kick ourselves if there is ! more to do. NB, don't just go round again, as the ! scheduling %isn't pre-emptive and we don't want to ! block higher priority processes (in particular the ! process which grabs packets from the station). kick(ether RX request) %c %if ether buffer_next to process # ether buffer_next to use %finish %repeat %end ! Wait for packets destined for the Ether. Dequeue them and send them ! on their way. %externalroutine ether TX main entry %owninteger who = 0 %record(buffer fm)%name buffer %record(port fm)%name port info %integer x, us us = who; who = who + 1 ! This allows the various incarnations of this process ! to maintain their own separate identities (particularly ! in the ACK wait state). %cycle wait for(ether TX request) %if common_ether request queue # 0 %start ! Request that something be sent to the Ether iof x = common_ether request queue buffer == common_buffer(x) common_ether request queue = buffer_link ion ! This buffer has been dequeued. Kick our other ! selves if there is anything more on the queue. ! NB don't just go round again -- the scheduling ! isn't pre-emptive and we might block something.... kick(ether TX request) %if common_ether request queue # 0 %if common_diags & ether diags # 0 %start pdate printstring("Forward buffer "); write(x, 0) printstring(" to port "); write(buffer_context, 0) newline %finish trace(buffer_context, trace out, buffer_text) %if buffer_context # 0 send buffer(x, us) %finish %repeat %end %end %of %file