title k20net - Kermit-20 Network Support remark Moved to seperate module as part of 194 to address MCRNEC remark Originally part of [186] subttl Preliminaries search monsym,macsym,cmd,k20unv ;[194] cmdacs ;Clean up p1-p4 definitions sall ; Tidy listing .directive flblst ; We don't need to see all the ASCIZ bytes... extern ttyjfn ; JFN for controlling terminal extern ttyini ; Condition local terminal for connection extern savlnw ; Save terminal length and width extern rstlnw ; Restore terminal length and width extern netjfn ; Holds any kind of communications JFN extern netflg ; Flags returned from GTJFN% (unused) extern nodnam ; Parsed node name extern nodnum ; Converted node number, if we have it extern asgflg ; Flags that we have assigned a device extern asgdev ; Device we assigned (always a PTY) extern srvflg ; If running as a server extern myjob ; My current logged in job extern mytty ; My current attached terminal extern ttynum ; Line number of current connection extern mycaps ; This process' capability vector extern crlf ; Handy way to save two bytes extern %%jser ; JSYS error handler extern errptr ; Pointer to copies of error messages extern symout ; Given an address, types an associated symbol remark Common parsing external data extern pars3 ; Data from third parsed item extern pars4 ; Data from fourth parsed item extern pars5 ; Data from fifth parsed item (rarely used) extern pars6 ;[218] Data from six parsed item (even more rare) extern pars7 ;[236] Whether we're doing .MOSNH extern atmbuf ; The atom buffer remark External linkages for INPUT/OUTPUT extern inpclr ;[209] Clear the buffer extern handsh ;[190] Handshake character remark External Parity routines and working storage (all 233) extern parity ; Type of parity in use extern none ; No parity being enforced extern space ; Space parity routine (0, always) extern mark ; Mark parity routine (1, always) extern even ; Even parity routine extern odd ; Odd parity routine extern parpko ; Non-zero if doing parity on packets, only extern parrck ; Checking parity on recieve in addition to sending extern ttipar ; Total parity errors for session extern movchr ; Translates between 7 and 8 bit extern genpar ; Use string instructions generate a new string extern chkpar ; Use string instructions to check parity extern strc ; Count of characters in temporary buffer extern strptr ; Appropriate pointer to same extern strbuf ; Global address of string buffer remark strbf2 ; Flows into this, too .psect code/ronly ; Pure code, pure heaven subttl Acquire information about local node ; Double checks if the system even has DECnet, just in case. It is ; possible to configure a system without DECnet; in fact, *all* Toad's ; are thus because they can't change the MAC address of their network ; adaptor. ; ; A remarkable oversight, if it was one, but DEC's decision to just ; snag part of the global MAC address space always seemed questionable ; to some. ; ; So we have to do this in order to not break on either a Toad, which ; can never have DECnet (see above) or a monitor built without it. ; ; Code lifted from my rewrite of SETNOD (SETND2) and properly Kermit ; cased... lclnod: entry lclnod saveac ; Wants a few extra registers remark q1, t5 ; Note, t5 aliases q1 setzm ndvfxp ; Assume doesn't have extended verify movei q3, cnfigd ; Resolve area to 18 bit address movx t1, .cfiln ; Length (maximum) setzb t2, t3 ; Create two handy zeros dmovem t1, .cflen(q3) ; Set length, clear processor type dmovem t2, .cfise(q3) ; Clear serial number and microcode dmovem t2, .cfiho(q3) ; Clear hardware and microcode options dmovem t2, .cfiso(q3) ; Clear software options and version dmovem t2, mynode ; Zero local executor and NDVFXP dmovem t2, myname ; Scrub the node name area movx t1, .cfinf ; Want basic configuration move t2, q3 ; Where to put the goodies CNFIG% ; See what this monitor has erjmpr r ; Nothing, forget about the whole thing load t3, cf%wdp,.cflen(q3) ;Load words returned subi t3, ^d1 ; Convert count to offset caige t3, .cfivr ; Need Tops-20 version ret ; Unable to determine Tops-20 version load t3, vi%maj,.cfivr(q3) ;Load Tops-20 major release caige t3, 7 ; Needs Phase IV ifskp. ; So far, so good caie T3, 7 ; Exactly version seven? ifskp. ; Have to check minor version load t3, vi%min,.cfivr(q3) ;Load Tops-20 minor release caige t3, 1 ; Needs .NDINT ret ; Requires Tops-20 minor version one endif. ; Otherwise, OK or after 7 (!) else. ; Otherwise, won't work ret ; Requires at least Tops-20 major version seven endif. move t4, .cfiso(q3) ; Load software options txnn t4, cf%dcn ; So, do we have DECnet? ret ; Nope, System is not configured for DECnet dmove t1, [exp .ndgnm,t3] ;Get local node number NODE% ; In t3 erjmpr r ; Give up, shouldn't ever fail.. cain t3, 0 ; Is DECnet running? ret ; System DECnet node number not configured movem t3, mynode ; Store away my local node number dmove t1, [exp .ndgln,t3] ;Get local node name hrroi t3, myname ; Point to storage NODE% ; In t3 ifje. r ; Failed?? setzb t2, t3 ; Cons up a couple of NUL's dmovem t2 ,myname ; Make sure no name endif. ifme. myname ; Get anything? setzm mynode ; Whack the executor node number ret ; System DECnet node name not configured endif. ; At this point, we know we have DECnet remark ; See if monitor has extended verify (T79) dmove t1, [exp .ndvfx,t3] ;Node name verify, extended hrroi t3, myname ; Point to local node name NODE% ; See if .NDVFX exists ifje. r ; Oh dear, doesn't look promising caxe t1, argx02 ; Monitor doesn't have winning .NDVFX? ret ; That's fine, so don't use it setzb t4, t5 ; Zap flags and so forth endif. ; End node processing txnn t4, nd%num ; Better have gotten a number (as it is us) ret ; .NDVFX response did not get local node number came t5, mynode ; Yes, but is it in fact the local executor? ret ; Inconsistent local node number results aos ndvfxp ; Mark that it fully works ret ; We're done subttl Get the 'name' of the local system ; Because one can be going from one DECSYSTEM-20 to another, the ; message, "Returning to DEC20" might be confusing, particularly if ; one is so lucky as to have multiple parallel transfers happening to ; foreign systems. While uncommon, there is nothing preventing this ; scenario. ; ; Therefore, we pull the system name. We prefer GETAB% over NODE% ; because this should always work, whereas NODE% will give you ; something like "TOPS20" on a non-DECnet site that hasn't configured ; the name in SETSPD. ; ; If, for some reason, we can't do the GETAB% (as in some fascist ACJ ; prevents it on a truly locked down system), we will use NODE%. ; NODE% is supposed to work whether or not DECnet is in monitor (see ; STG). ; ; N.B., Since using GETAB%, we have to do a little parsing of SYSVER ; ; The problem is that SYSVER has too much blather in it and sometimes ; also includes propaganda and system version information. Since the ; first part is simply SYSTEM:MONNAM.TXT (which is supposed to be ; there), we parse the return up to the comma and use that. ; ; Code adapted from UPTIME; expects to be called AFTER lclnod in case ; SYSGT% and/or GETAB% either can't work (because no SC%GTB) or fail. ; ; Counts the string in case somebody needs it, later getnam: entry getnam saveac ; Needs some extra registers setzb t1,t2 ; Cons up a nice long zero dmovem t1,syscnt ; Stomp count and a few characters movx t3,sc%gtb ; GETAB% capability? tdnn t3,mycaps+1 ; We have it, right? jrst getnod ; Most unusual! movx t1,'SYSVER' ; Want system version information SYSGT% ; Pull out first word and table metadata erjmpr getnod ; Gronked?? Try something else movem t2,sysver ; Save table length and index (just in case) hrrz q2,t2 ; Cache the index in a fast place hrlzi q1,^d1 ; Put the table increment in the right place ; Now decide how long to loop hlro t2,t2 ; Turn into a fullword negative number movns q3,t2 ; Positivize it (note arcane use of self) caxle t2,syslen ; Will the table fit? movx q3,syslen ; Sadly, no. Clip it down dmove t3,[exp sysnam,0] ; Address of where to store text, nothing seen ; Fall through with first word do. ; Enter loop context movem t1,(t3) ; Stomp the whole word into memory skipa t2,t1 ; Set up for correct shift do. ; Inner loop to check characters jumpe t2,endlp. ; Processed everything? setz t1, ; clear a 'linked' register for a shift pair lshc t1,^d7 ; Peel off a character (faster than an ILDB) cain t1,"," ; A comma? jrst postab ; Yes, we've finally gone past the name aoja t4,top. ; Otherwise, count the character and inner loop enddo. ; End inner loop to check characters sojle q3,endlp. ; Account for a full word done, maybe terminate add q2,q1 ; Bump to next GETAB% index move t1,q2 ; Load next requested word GETAB% ; Ask for it erjmpr postab ; Failed, just use what we have jumpe t1,postab ; If end, head off for post table processing aoja t3,top. ; Otherwise, handle this word enddo. ; End of GETAB% loop context postab: movem t4,syscnt ; We know the length of the system name!! addi t4,^d1 ; Get past last character (faster than ILDB) adjbp t4,[point 7,sysnam] ; Point to where we stored everything setz t1, ; Cons up a .CHNUL dpb t1,t4 ; Tie off the string (faster than ILDB) ret ; And down remark Handle case of no SC%GTB or SYSGT%/GETAB% failure ; NODE% should always work and one assumes that DECnet is set up on ; all modern systems. However, many systems had no DECnet and only ; ran ARPA code. That is less common as Galaxy assumes DECnet and ; parts of CFS seem to. ; ; As there were also systems with no ARPA code, we use a very old- ; fashioned method for getting the name and are highly defensively ; coded. ; ; Code lifted from my rewrite of SETNOD (SETND2) and properly Kermit ; cased... getnod: dmove t2,myname ; Load what DECnet thinks jumpe t2,niente ; Didn't think much! Just default it came t2,[ascii "TOPS2"] ; First five of standard default? ifskp. ; Yep, let's look at the 2nd word camn t3,[ascii "0"] ; Really standard default?? jrst niente ; Default it to something nicer endif. ; Otherwise, fall through dmove t4,[point 7,sysnam ;Point to text to spew 0 ] ; Zero counter do. ; Enter outer loop context do. ; Enter inner loop context setz t1, ; whack the character accumulator lshc t1,^d7 ; Peel off a character (faster than an ILDB) jumpe t1,endlp. ; End of string? Do next word idpb t1,t4 ; Deposit into target string aoja q1,top. ; Next character enddo. ; End of inner loop context skipn t2,t3 ; Position second word exit. ; Unless we're done setz t3, ; Set a talsiman jrst top. ; Peel a few more characters off enddo. ; End of outer loop context movem q1,syscnt ; Update string length count idpb t3,t4 ; Tie off the string ret ; Done remark Here if we are just not having any luck with the local system name chgsec(code,text) defnam: asciz "DEC-20" ; Clear up where we are Z ; Historically what we called ourselves retsec niente: dmove t1,defnam ; Load default name dmovem t1,sysnam ; Store default name setzm sysnam+2 ; Tie of the string movei t3,^d6 ; Length of unterminated string movem t3,syscnt ; Store the count ret ; And done subttl Set default prompt if doing network ; Sets a default prompt to use when we are NRT'ing in case it ; it is asked for by SET PROMPT (see .setpr: in k20par) setdef: entry setdef ; Called once at startup dmove t1,[point 7,myprom ; Default prompt, if needed point 7,sysnam] ; Source is local system name move t4,syscnt ; Length movei t3, .chdbq ; Load a double quote idpb t3,t1 ; Deposit it in prompt do. ; Enter loop context. ildb t3,t2 ; Load source from local system name idpb t3,t1 ; Deposit it in prompt sojg t4,top. ; All of it enddo. ; Exit loop context. dmove t3,[ .chrpt ; Load right pointy bracket .chdbq ] ; And a double quote idpb t3,t1 ; Make prompt obvious idpb t4,t1 ; Close out default for .cmqst setz t3, ; Cons up a .chnul idpb t3,t1 ; Close out the string ret subttl Perform network connect and initial NRT negotiation ; Call: ; ; nodnam has result of .CMNOD ; ; Return: ; ; +1/ Couldn't open connection ; +2/ Connection open and negotiated with a remote NRT ; t1/ Network JFN we got decnct: entry decnct ; Called by k20mit, also setzm binflg ; Assume we don't have binary setzm nrtflg ; And that we don't have an NRT, either call chknrt ; First see if node itself exists callret clscln ; Failed, scrub storage movem t1,ttynum ; Store node number as line number call openrt ; Perform initial open activities callret clsjfn ; Unless build and open fail call waitcn ; Now wait for NSP negotiation ret ; Return +1, waitcn cleans up correctly call fixnam ; Rewrite remote node name call chktop ; Ensure it suppors Tops-10/20 NRT's ret ; It does't ... chktop cleans up correctly movei t3, .dvdcn ; Opened a DECnet NRT! movem t3, opndev ; Store opened device type setom vtermf ; Set the virtual terminal flag setom local ; We're the local Kermit remark gndpar ;[223] Can't get parity from a network JFN setzm opnpar ;[223] Either way, NRT's do not support parity hrrz t1, netjfn ;[223] Return JFN, no flags retskp ; Connected and ready to go! subttl Checks that the candidate node exists ; Verifies parsed node and attempts to extract some useful ; information. This should not be necessary, because unless CM%PO ; (parse-only) is set, when doing a .CMNOD, Tops-20 itself verifies ; that whats in the atom buffer exists in the monitor's data base. ; ; However we have to do the call to get the node number, which we ; pretend is a terminal number. ; ; Call: ; ; nodnam has ... something (see above) ; ; Return: ; ; +1/ Wasn't a valid DECnet node ; +2/ Valid DECnet node, t1 has node number if monitor supports this chknrt: saveac ; Alias t5 dmove t1,[exp .ndvfx,t3] ;Node name verify, extended skipn ndvfxp ; Has extended verify? movx t1, .ndvfy ; Pity, but still usable hrroi t3, nodnam ; Point to whatever .CMNOD got NODE% ; Get some information ifje. r ; Catch the error move t2, t1 ; Save for debugging setzb t4, t5 ; Zap flags and so forth endif. ; setob t1, nodnum ; Let's assume nothing works txnn t4, nd%lgl ; Double check COMND% .CMNOD, just in case ret ; Then how did it get parsed?? txnn t4, nd%exm ; Legal, but do we know it? ret ; No, we do not txnn t4, nd%num ; Did we get a number? retskp ; Oh well, maybe old monitor movem t5, nodnum ; Save a node number, if we have it move t1, t5 ; Return a number to caller retskp ; And we are out of here! subttl Open DECnet connect to NRT object ; Here to actually open the connect. Check to see if the remote ; system is Tops-10 or Tops-20, in which case we can directly use ; it as if it were a terminal. This is not possible with a CTERM ; or TVT because there would be meta-data to process. ; ; Note, current behavior is that the OPENF% will succeed whether ; or not GJ%FLG is set, but strangely, NO traffic will be possible ; if is not used! If GJ%FLG is issued, then the following flags ; are returned: ; ; Bit Name Comment ; === ====== ================================================ ; 6 GJ%UHV The file used has the highest generation number ; because a generation number of 0 was given in the ; call. This is clearly false because no generation ; number nor extension (type) is supplied. ; ; 12 GJ%GND Files marked for deletion were not considered when ; assigning JFNs. ; ; 17 GJ%GIV Invisible files were not considerd when assigning ; JFNs. ; ; Why this makes it work is anybody's guess... ; ; Call: ; ; nodnam has validated foreign node name ; ; Return: ; ; +1/ Failed to create a JFN to the remote NRT ; +2/ JFN exists for remote object and is open chgsec(code,const) ; Constants nrtadr: nrtobj ; Where to build network file spec to MCBNRT nrtdev: byte (7) "d","c","n",":",.chnul ;Device name for client connections nrtnum: byte (1) 0 (7) .chnul,.chnul,"3","2",.chdas retsec openrt: setzm asgflg ; Certainly will not be assigning DCN:! setzm asgdev ; So don't put it there dmove t1,nrtadr ; Load address of object and device name movem t2, (t1) ; Start with "DCN:" hrli t1,(point 7,0,27) ; Point to ":" movei t3,nodnam ; Resolve address of parsed node name hrli t3,() ; Turn into a local ASCII pointer ; And append the node name do. ; Enter loop lexical context ildb t2,t3 ; Load node name byte jumpe t2,endlp. ; Exit if at end of string idpb t2,t1 ; Append to file specification loop. ; Go get some more enddo. ; end loop lexical context ; Append MCBNRT's object type move t2, nrtnum ; Complete NRT number portion idpb t2,t1 ; Drop in the dash lsh t2,-^d7 ; Shift the "2" into place idpb t2,t1 ; Drop in the "2" lsh t2,-^d7 ; Shift the "3" into place idpb t2,t1 ; Drop in the "3" setz t2, ; Cons up a NUL idpb t2,t1 ; Tie off the line movx t1,gj%sht!gj%flg ; Do a short form GTJFN with flags hrroi t2,nrtobj ; Using the spec just built GTJFN% ; Get DCN connection %jserr (,clscln) ; Scrub storage hrrzm t1,netjfn ; Save JFN for the connection hllzm t1,netflg ; Save returned flags tlz t1,-1 ; But shut them off for downstream ; 8 bit bytes, small buffers and read/write move t2,[fld(^d8,of%bsz)!fld(.gssmb,of%mod)!of%rd!of%wr] OPENF% ; Open the network connection %jserr (,clsjfn) ; Toss the JFN retskp ; Return success subttl Wait for DECnet connection completion ; Once we are done building the connection string and have successfully ; done the OPENF%, we must wait a bit for DECnet to complete network ; level negotiations. ; This was is done by sitting in a loop, waiting a quarter second, ; checking the connection status and, if connected, returning. ; Otherwise we'd go around and do it again for the specified number of ; times. ; ; The new code sets a connection interrupt (mo%cdn) which results in a ; lot snappier response. Moral of the Story: Don't Poll. ;[218] Rewritten for connection interrupts extern dnchb ; DECnet channel bit, defined in k20sub extern dncfld,dndfld ; DECnet channal assignment/deassignment field extern timeon,timdel ; Force a specific time, force a timer delete extern ccon,ccoff2 ; Set up Control-C handler extern cyon, cyoff ; Set up Control-Y handler extern cyseen ; Set if Control-Y typed extern delay ; Default connect time out waitcn: move t1, netjfn ; Load the network JFN dmove t2, [ .moacn ; Code to enable interrupts dncfld ] ; Channel to enable on MTOPR% ; Enable the interrupt %jserr (,clsnet) dmove t1, [ .fhslf ; This process dnchb ] ; DECnet connection channel AIC% ; Turn the channel on %jserr (,clsnet) ;?? call ccon ; Turn on Control-C interrupt jrst waitcc ; Go to the wait Control-C handler call cyon ; Fielding ^Y inquires %ermsg (,) movei t1, waitmo ; Address to go to on time out skipg t2, pars6 ; Use /timeout, if specified move t2, delay ; Otherwise use default ifg. t2 ; Have any reasonable delay? call timeon ; Yes, set connection expiration time endif. ; Otherwise, we are truly patient... do. ; Enter loop context WAIT% ; Wait forever and ever (and ever) $waitj==:. ; Location of JSYS as reported skipn cyseen ; Should only happen for ^Y jrst waitun ; But didn't! Unknown!! call waitpr ; Print something nice ifskp. ; Link is still healthy setzm cyseen ; Stomp ^Y seen else. ; Otherwise, we are ill block. ; Will need a frame saveac ; Save temporaries call shutdn ; Turn off the interrupts endbk. ; Exit block, restoring temporaries call decerr ; Complain and close callret clsnet ; Toss JFN and return endif. txne t3, mo%con ; Connected?? Must have missed the interrupt exit. ; Break out and return success loop. ; And go catatonic again enddo. ; End loop lexical context waitdn: remark ; Forced here by connection interrupt call shutdn ; Get rid of all our interrupts retskp ; Return success subttl Print Connection Information ; Returns +1 if connection went bad, t2 having the DECnet abort code ; +2 if the connection is still good and we continue to wait waitpr: move t1,netjfn ; Load the JFN movx t2,.morls ; Function to read link status MTOPR% ; Do the status read erjmpr r ; Handle error, getting it in t1 txne t3, mo%con ; Connected?? retskp ; Must have missed the interrupt txne t3, mo%abt ; Link aborted?? ret ; Fail and return blat txne t3, mo%syn ; A normal close? ret ; Already? That's pecular... ifxn. t3, mo%wfc ; Still healthy and waiting? txmsg <% Waiting for connection > retskp endif. ifxn. t3, mo%wcc ; Just about done, actually? txmsg <% Waiting for connection confirmation > retskp endif. txmsg <% Unknown status > retskp ; Still OK to wait subttl Connection interrupt time out and shutdown shutdn: movx t1, .fhslf ; This process DIR% ; Shut off the entire interrupt system %jserr (,) call ccoff2 ; Force off Control-C handler call timdel ; Delete the timer call cyoff ; Release ^Y dmove t1, [ .fhslf ; This process dnchb ] ; DECnet connection channel DIC% ; Shut the channel off %jserr (,) ; Carry on move t1, netjfn ; Load the network JFN dmove t2, [ .moacn ; Code to enable interrupts dndfld ] ; Take the interrupt off this channel MTOPR% ; Enable the interrupt %jserr (,) ; Carry on CIS% ; Clear out any other interrupt crud movx t1, .fhslf ; This process EIR% ; Turn the interrupt back on %jserr (,) ; Uh oh... ret waitun: remark ; Here if we don't know why we broke out call shutdn ; Get rid of all our interrupts emsg ; Inform hrli t2, .DCX7 ; Code is unspecified error sxtext (t3,) movei t4,^d16 ; Length of reject message jrst waitm1 ; Join common code waitcc: remark ; ^C event call shutdn ; Get rid of all our interrupts txmsg <% aborting connection attempt > ; Inform hrli t2, .DCX9 ; Code is forced explicit disconnect sxtext (t3,) movei t4,^d15 ; Length of reject message jrst waitm1 ; Join common code waitmo: remark ; Time-out event call shutdn ; Get rid of all our interrupts emsg ; Whine hrli t2, .DCX38 ; Code is no response sxtext (t3,) movei t4,^d16 ; Length of reject message waitm1: move t1,netjfn ; Load DCN: JFN hrri t2, .moclz ; Function to close MTOPR% ; Notify NSP that we are giving up erjmpr decerr ; We can't say "No"? callret clscom ; Toss whatever is left ;[218] End rewrite for connection interrupts subttl Asynchronous DECnet connection event ;[218] Begin code insertion ; Purpose is to break us out of any jsys we might be in (probably the ; WAIT%) and redirect the path of execution to the successful return. dntrap: entry dntrap ; chntab is in k20sub push p, t1 ; Save an accumulator movei t1, waitdn ; Load the connection success address hll t1, pc3 ; Load interrupted PC's flags txo t1, pc%usr ; Force user mode to break out of any JSYS movem t1, pc3 ; Restore as if we came from there pop p, t1 ; Restore the accumulator DEBRK% ; Done with interrupt ;[218] End code insertion subttl Handle a DECnet connection error of some type ; Takes two kinds of errors and honks accordingly ; ; Note assumption: if t1 still has netjfn in it, then it couldn't ; possibly have gotten stomped with an erjmpr ; ; Call: ; ; t1/ JFN or error code ; ; Return: ; ; +1, always, having typed some kind of blat decerr: entry decerr ; Also hit by other modules hrrz t2,t1 ; Save a possible error emsg ;[187] camn t2,netjfn ; JSYS error? ifskp. ; Yes, that's easy enough to complain about movei t1,.priou ; Continue on primary output hrli t2,.fhslf ; Wants this for explicit error setz t3, ; Don't limit length of text ERSTR% ; Type the JSYS failure reason text erjmpr .+2 ; Ignore strange error erjmpr .+1 ; Ignore stranger error hrroi t1, crlf ; Tie off the line PSOUT% ret ; And return endif. ; End JSYS error handling setz t1, ; Let's assume we never found anything tlz t3,-1 ; Scrub to just the bare error movei t4,nsptab ; Load address of error table hrli t4,-nspcnt ; Load negative number of items in table do. ; Enter loop context hlrz t2,(t4) ; Load Disconnect Code Table came t2,t3 ; Did we find the code? ifskp. ; Yes, set up the pointer hrrz t1, (t4) ; Pick up in-section case txo t1, .px7 ; Turn into a OWGP to ASCII text in ETEXT exit. ; Break out of the loop endif. aobjn t4,top. ; Nope, try the next error code enddo. ; End loop context ife. t1 ; Did we find anything? sxtext (t1,) endif. ; Other, can provide extra information ESOUT% ; Give us the bad news hrroi t1, crlf ; Tie off the line and return PSOUT% callret clsnrt ; Close the NRT object (or what's left) subttl DECnet Disconnect Code Table (from MONSYM) .endps code ; Pointers to extended text don't go in code ; Note that the codes are stipulated by the NSP specification and ; may have meanings that are not directly implied by the comments define nsperr(e,t,%et) < xwd e,%et ;;DECnet error code and in-section address chgsec(const,etext) ;;Text goes in extended section %et: asciz\'t\ ;;Drop text into extended section retsec ;;Gets back into const .psect cleans(<%et>) ;;Don't clutter listings with generated symbol >;;nsperr .psect const ; Pointer table to extended text goes in const .psect nsptab: nsperr(.DCX0,) nsperr(.DCX1,) nsperr(.DCX2,) nsperr(.DCX3,) nsperr(.DCX4,) nsperr(.DCX5,) nsperr(.DCX6,) nsperr(.DCX7,) nsperr(.DCX8,) nsperr(.DCX9,) nsperr(.DCX10,) nsperr(.DCX11,) nsperr(.DCX21,) nsperr(.DCX22,) nsperr(.DCX23,) nsperr(.DCX24,) nsperr(.DCX32,) nsperr(.DCX33,) nsperr(.DCX34,) nsperr(.DCX35,) nsperr(.DCX36,) nsperr(.DCX37,) nsperr(.DCX38,) nsperr(.DCX39,) nsperr(.DCX40,) nsperr(.DCX41,) nsperr(.DCX42,) nsperr(.DCX43,) nspcnt==.-nsptab ; Number of items in table cleans() ; No need for symbol in listings, Etc. .psect code ; Back in code subttl Canonicalize remote node name ; Rewrite the node name in case it was aliased. At least get it into ; UPPER case, which is what everybody wants. Also keeps gross CaMel ; case input from offending the sensitive fixnam: skipg t2, netjfn ; Load JFN ret ; Unless there isn't one ifmn. ndvfxp ; Have .ndvfx? move t3, nodnum ; Load previous node number movem t3, oldnum ; Store as old number endif. ; Otherwise, will have to compare characters... dmove t3, nodnam ; Load connected node name dmovem t3, oldnam ; Save (will hold six characters plus .chnul) setzb t3, t4 ; Cons up 10 .chnul's dmovem t3, nodnam ; Scrub storage enough hrroi t1, nodnam ; Rewriting the node nam dmove t3, [ fld(.jsaof,js%nam) ; Just the file name 0 ] ; No strange prefix JFNS% ; Rewrite the node name erjmpr r ; ?? movni t2,^d3 ; Getting before the dash adjbp t2,t1 ; back the pointer up idpb t4,t2 ; Stomp the dash, tying off the string idpb t4,t2 ; Also stomp the "2" and the ... idpb t4,t2 ; ... "3" to allow word compares ret ; Return everything all pretty subttl Check if a connecting to a machine that supports Tops-20 NRT ; Only these support a meta-data free NRT that we can use ; N.B., These aren't just Tops-10 or Tops-20 machines! Ultrix-32 implements ; Tops-20 NRT. cnflen==200 ; Maximum characters allowed chktop: saveac ; Fiddling with raw DECnet byte order setzb t1,t2 ; Cons up some zeros dmovem t1, nrtros ; Initialize unknown OS types dmovem t1, nrtflg ; and also NRT and network binary flags setzm nrtprt ; and also the NRT protocol skipg t1, netjfn ; Load network JFN ret ; Unless there isn't one dmove t2,[exp .morls,0] ; Read link status MTOPR% ; Request from the monitor erjmpr decerr ; Handle error ifxn. t3,mo%eom ; Has an entire message? setz 2, ; Assume it's a lie SIBE% ; See what the deal is skipa ; Have some goodies to read, actually anskp. ; Or doesn't caile t2,cnflen ; Exceeds buffer length? anskp. ; clip it down movn t3,t2 ; Load exact length to read else. ; Otherwise use default length movni t3,cnflen ; Default maximum characters allowed endif. move t2,[point ^d8,cnfmsg] ;Note 8 bit pointer to config message SINR% ; Read Configuration message erjmpr decerr ; Gronked?? remark ; Begin configuration message parsing ldb t1,[point ^D8,cnfmsg,7] cain t1,^d1 ; Is this a configuration message, actually? ifskp. ; No, so let's type it emsg movei t1,.priou ; Output to primary move t2,[point ^d8,cnfmsg] ; Pointer to data from remote host movei t4,cnflen(t3) ; Get count received-1 movn t3,t4 ; Now have output count SOUT% ; Type data on users terminal erjmpr .+1 ; Too bad for user, but ignore it hrroi t1, crlf ; Tie off PSOUT% ; the line callret clsnrt ; Close the connection endif. ; End case connection message repeat 0,< ;;We don't look at the next two ldb t3,[point ^d8,cnfmsg,15] ; DEC ECO ldb t3,[point ^d8,cnfmsg,23] ; Customer ECO > ldb t3,[point ^d8,cnfmsg,34] ; Operating System type, high order byte lsh t3, ^d8 ; shift over and load the low order byte ldb t4,[point ^d8,cnfmsg+1,7] move q1, t4 ; Save constructed OS type txmsg <[Remote system > ; Begin connection banner hrroi t1,nodnam ; Remote system PSOUT% ; Type it txmsg <:: is running > block. ; Enter block context for easier control flow caige t4, 0 ; Negative OS number?? ret ; That will never work caile t4, hsttyn ; Out of range? ret ; Don't know that, either skipn hsttyp(t4) ; But!! Is this entry 'known'? ret ; Nope (note table has 'reserved' gaps) retskp ; Otherwise, it's fine endbk. ; Return out of block context, one way or another ifskp. ; Skip means we know the remote OS code move t1, hsttyp(t4) ; Load OWGP to OS type string movem t1, rosnpt ; Save it for k20dsp PSOUT% ; Print it else. ; Non-skip means we didn't know it sxtext (t1,) ; Give it something to type movem t1, rosnpt ; if it wants something to type txmsg < an unknown operating system type: > ; Begin the blat movei t1, .priou ; Still going to the terminal move t2, t4 ; Load the code we got movei t3, ^d10 ; These are in base 10 NOUT% ; Blat the code erjmpr .+1 ; Catch and ignore the error endif. ; End OS tyoe check txmsg <] > ldb q2,[point ^d16,cnfmsg+1,23] ; Supported protocol types bit field ifxe. q2, TOPNRT ; Anything we understand? hrroi t1, nodnam ; Begin complaining ESOUT% ; about the node txmsg <:: does not support Tops-10/Tops-20 Network Remote Terminal protocol > callret clsnrt ; Close the connection endif. movem q1, nrtros ; If NRT, remote operating system type movem q2, nrtprt ; Save NRT protocols offered by remote setom nrtflg ; Flag this is a valid NRT setom binflg ; Flag we will do binary retskp ; Won!! subttl List of known DECnet host operating system types ; The base list comes from the venerable SETHOS (hence the similar ; variable names), but it has been updated with additional systems ; from the fine folks on HECnet. ; ; Be aware that these is not the same list as the DAP list!! ; (naturally...) They're not even the same between CTerm and NRT! hsttyp: intern hsttyp ; Used by k20dsp, twoo eascii ;^d0 eascii ;^d1 eascii ;^d2 eascii ;^d3 eascii ;^d4 eascii ;^d5 eascii ;^d6 eascii ;^d7 eascii ;^d8 (TOPS20) eascii ;^d9 (TOPS10) eascii ;^d10 eascii ;^d11 (!!) eascii ;^d12 eascii ;^d13 (the DN20!!) 0 ;^d14 Reserved 0 ;^d15 Reserved 0 ;^d16 Reserved 0 ;^d17 Reserved eascii ;^d18 hsttyn=.-hsttyp-1 ; Number of defined operating system types subttl DECnet interrupt message processing (unused by Kermit) ; Gets an prints a DECnet interrupt message (which should never happen) ; and prints it on the user's terminal. No interrupt is enabled for ; this and the condition is checked for most irregularly. intmsg: entry intmsg saveac ; Be transparent dmove t2, [ .morim ; Read interrupt message point 7,intbuf] ; Use this area MTOPR% ; Grab the message %jserr (,r) txmsg <[KERMIT-20: DECnet Interrupt Message: > dmove t1, [ .priou ; Typing on terminal point 7,intbuf] ; Point where we read this foolishness movn t3,t4 ; Doing a counted print SOUT% ; Display what we got %jserr (,r) txmsg <] > ; Close alert and tie off line ret ; Return with a clean register file subttl Initialize PTY parameters (adapted from BATCON) inipty: entry inipty movx t1, 'TTYJOB' ; Terminal line to job number and 'hungry' SYSGT% ; Get the values ifje. r ; Fetch error for debugger setzb t2, ttygtb ; Set an impossible value else. ; Otherwise, JSYS worked movem t2, ttygtb ; So store something useful endif. ; End case JSYS error handling movx t1, 'PTYPAR' ; pseudo terminal configuration info SYSGT% ; Get the values ifje. r ; Fetch error for debugger move t3,t1 ; Save error setob t1,t2 ; Load a impossible values endif. ; End case JSYS error handling hrrem t1,pty1st ; Save TTY number of first PTY hlrem t1,ptycnt ; Save count of pseudo-terminals movem t2,ptygtb ; GETAB% index (which we'll never use) ret ; Done subttl PTY acquisition ; Assign a PTY to use. This is necessary because, between the time we ; find a free PTY and the time we actually OPENF% it, somebody else may ; have already grabbed it. ; ; Another way to 'lock' the PTY for exclusive use is simply to open it. ; The approach of doing an ASND% is superior to this because the PTY ; can be opened as convenient and, if closed, can still be reused. ; Otherwise we'd have to go through this whole rigmarole again. ; ; Adapted from BATCON, which does an assign by ASND% as apposed to Phase ; II NRTSRV which assigns by OPENF%. ; ; Returns: ; ; t1/ Loopback terminal line ; t2/ Assigned PTY designator ; ; N.B., Always have to start with the first PTY and go through all of ; them because one of them may have become free. ; ; Be aware that, if you have more than one Kermit fork in a job doing ; pseudo-terminal based transfers, then this code will do the wrong ; thing because a single PTY is assumed to be used per job. There is ; no expectation of any problem as pseudo-terminals are only used for ; debugging, testing and prototyping. asipty: entry asipty ; Called by k20mit, also saveac ; Leave the registers alone setzm ptyflg ; Not doing pseudo-terminals setzm binflg ; Not doing binary ifmn. asgflg ; Did we have an assigned device? skipn t1,asgdev ; That is, if we still know it anskp. ; Shouldn't happen, but... DVCHR% ; Pull the device characteristics ifje. r ; Trap error, record it move t4,t1 ; Get the error out of the way setzb t1,t2 ; Claim impossible values endif. ; End JSYS error trap came t1,asgdev ; Double check; it's the same, right? anskp. ; Different somehow, so don't try to reuse it ldb t4,[pointr t2,dv%typ] ;Load the device type caie t4,.dvpty ; Is it a pseudo-terminal? anskp. ; No, so it is useless for loop back hlre t4,t3 ; Pick up the assigned job came t4,myjob ; Is it me? anskp. ; No, get our own, then remark t1,t2 ; Device designator and charteristics words loaded setom ptyflg ; Flag we have a pseudo-terminal setom binflg ; And that it will do binary retskp ; Return success, device string already built endif. ; End case attempting device reu-se setzm asgflg ; Nothing assigned setzm asgdev ; So no assigned device skipg q1,ptycnt ; Load and check count of ptys ret ; Give up right now skipge q2,pty1st ; Load line number associated with 1st PTY ret ; Don't work with junk from SYSGT% setz q3, ; Initial pseudo-terminal is PTY0: do. ; Enter loop context movsi t1,.dvdes+.dvpty ;Load pseudo-terminal device designator hrr t1,q3 ; Load the current PTY number DVCHR% ; Get device characteristics for this PTY ifje. r ; Pick up error for debugger setz t2, ; Default to not available endif. ; End case device ifxn. t2,dv%av ; Free? (available) dmove t3,t1 ; Save designator words ASND% ; Quick! Assign it!! annje. ; Failed, do next PTY dmovem t3, ndvchr ; Save network device characteristics setom asgflg ; Assigned it. Set this flag to remember. movem t3, asgdev ; save assigned device exit. ; Got it! We're done endif. ; End availibility/assignment attempt dadd q2,[exp 1,1] ; Bump both PTY and TTY numbers (clever) sojg q1,top. ; Try next pty ret ; Otherwise, couldn't get anything, fail enddo. ; Exit loop context move q3,t1 ; Save assigned PTY device move t2,t1 ; Use it here, too hrroi t1,ptynam ; Point to area to write PTY specification DEVST% ; Turn device into string erjmpr r ; Fail, we just assigned the device! movei t2,":" ; Load terminating device punctuation idpb t2,t1 ; Complete device syntax setz t2, ; Load .chnul idpb t2,t1 ; Tie off the string movsi t2,.dvdes+.dvtty ; Load terminal device designator hrr t2,q2 ; Build complete terminal designator movem t2,ptytty ; Store in case we need to manipulate it hrroi t1,ttynam ; Point to area to write TTY specification DEVST% ; Turn device into string erjmpr r ; Fail, we just assigned the device! movei t2,":" ; Load terminating device punctuation idpb t2,t1 ; Complete device syntax setz t2, ; Load .chnul idpb t2,t1 ; Tie off the string setom ptyflg ; Flag we have a pseudo-terminal setom binflg ; And that it will do binary dmove t1,q2 ; Load terminal number and PTY designator retskp ; Done subttl Externals for Alternate Network Code extern doesc ; Label of main loop for escape character handling extern duplex ; Whether we're echoing or not extern echo ; Routine for local echoing extern escape ; Escape character for connecting (default ^\) extern vtermf ; Not running on real copper extern netlgx ; Label to continue error log handling extern ttfork ; Fork number of the connect receive fork. extern ttinch ; Label of main keyboard input loop extern tter1 ; Label for terminal error handling extern carier ; Carrier flag (also means connected) extern $connx ; Close connection for a physical line extern frkchn ; Fork channel interrupt number extern mdmlin ; -1 = modem-controlled line, 0 = not. extern sesjfn ; Session log file JFN. extern sesflg ; Whether the session log is active subttl Execute the SET LINE command ; SET LINE is almost exactly like CONNECT, except that confirming a ; CONNECT with no arguments reconnects to an existing connection ; whereas confirming a SET LINE with no arguments CLOSES the ; connection. A subtle difference... ; ; $CONNE now has all the hairy connection logic, no matter the ; connection type, PTY, line, NRT, Etc. This routine is simply taking ; care of a historical special case. ; ;Call: ; ;pars3/ Parse type: .cmkey, .cmnod, .cmnum, Etc. ;pars4/ Device information: type, unit, line number, Etc. $setln: entry $setln saveac ;[218] Parse item dmove q1, pars3 ;[218] Load parse type and unit caie q1, .cmcfm ;[218] Wanted to close? ifskp. ;[218] We did, so let's do that skiple q3, netjfn ;[218] Umm, do we have a connection? ifskp. ;[218] We do not, so nothing to do emsg ;[218] ret ;[218] Nothing further to do endif. ;[218] Otherwise, something is up call clsjfn ;[218] Stomp the network connection txmsg <[Connection closed] > ;[218] Say it's all over ret ;[218] End we're done endif. ;[218] End case confirming to close callret $conne ;[218] The rest is just like CONNECT subttl CONNECT command ;[151] CONNECT code totally rewritten as Edit 151. Formerly, CONNECT was ; accomplished by running a program TTLINK in a lower fork. Now, the ; code is integrated into this program. This was done for two reasons: ; ; 1. V6 of TOPS-20 doesn't allow multiple JFNs on the same TTY device. ; [V7 has yet to be vetted] ; 2. TTLINK was interrupt-driven and therefore did not work under batch. ; ; This method, similar to that used in Mark Crispin's TELNET program, uses ; separate input and output forks. It works under batch because the "pty" ; is always "hungry". ; ;[187] This isn't quite true. TELNET can't run well under Batch precisely ; BECAUSE of the asynchronous forks. Actually, it really doesn't work ; at all. ; ; The Batch paradigm is fundamentally line half-duplex. This means ; that a line of input is pushed into a PTY and a response is checked ; for. The PTY may, in fact, NOT be hungry because the program is ; busy performing the requested command. ; ; When running asynchronously, the PTY will ALWAYS look hungry since ; the fork that is waiting for the input may not even be on the same ; system. This means that BATCON will continuously stuff input until ; something goes wrong. If a command fails, then a number of commands ; will have been typed ahead with unpredictable (or even catastrophic) ; results. ; ; A local modification to BATCON implements a Batch WAIT command, ; which causes BATCON to ignore PTY hungry for the indicated number of ; seconds to give whatever is on the other side of the PTY time to ; type something. It is, at best, a hack. ; ; It's best to not use the fork at all and go with a CONNECT/STAY and ; from there user use the INPUT and OUTPUT commands. ; ; Parse results usage: ; ; pars3/ COMND% parse type (.cmkey, .cmcfm,.cmnod, Etc.) ; pars4/ COMND% parsed value (number, node, device or fork handle) ; pars5/ Whether connecting immediately or staying at local host ; pars6/ Value of /TIMEOUT parameter, if given ; pars7/ Whether using MTOPR% .MOSNH or handling communications in user mode $conne: entry $conne ;[186] Invoked from k20mit extern ttsfrk ;[186] Joins k20mit here skipge t1, pars3 ;[186] Load the parse type movx t1, .cmcfm ;[186] If junk, use confirm caie t1, .cmcfm ;[186] Confirmed (reconnect)? ifskp. ;[186] Yes, let's see if that makes sense skiple t2, opndev ;[186] Load currently connected device ifskp. ;[186] Junk?? emsg ;[186] Shouldn't happen. Ever ret ;[186] Do not continue endif. ;[186] End case absurd open device ifme. local ;[186] Remote? movei t1, .cmnum ;[186] Can't connect to ourself move t2, mytty ;[186] So pretend we tried dmovem t1, pars3 ;[186] Stomp the parse jrst $conn1 ;[186] and carry on, eventualy to fail endif. ;[186] End case remote reconnect caie t2, .dvpty ;[186] Reconnect a PTY? ifskp. ;[186] Yes, fake that out movei t1, .cmkey ;[186] Pretend we parsed a keyword dmovem t1, pars3 ;[186] Stomp that in jrst $conn1 ;[186] Continue (re)connect endif. ;[186] End case PTY reconnection caie t2, .dvtty ;[186] Reconnect a physical terminal? ifskp. ;[186] Yes, fake that out movei t1, .cmnum ;[186] Pretend we parsed a number move t2, ttynum ;[186] Which is the currently open terminal dmovem t1, pars3 ;[186] Stomp that in and continue jrst $conn1 ;[186] Continue (re)connect endif. ;[186] End case terminal reconnection caie t2, .dvdcn ;[186] Reconnect an NRT? ifskp. ;[186] Yes, fake that out movei t1, .cmnod ;[186] Pretend we parsed a node dmovem t1, pars3 ;[186] Stomp that in skipe forkls ;[236] Wasn't in a forkless connect? setom pars7 ;[236] Pretend we parsed the /FORKLESS switch dmove t3, nodnam ;[186] Load current node name dmovem t3, atmbuf ;[186] Pretend we parsed it jrst $conn1 ;[186] Continue (re)connect endif. ;[186] End case NRT reconnection ermsg% (, r) endif. ;[186] End case ,cmcfm $conn1: caie t1, .cmnum ;[186] Parsed a number? ifskp. ;[186] Yes, wants a physical line skipl t2, pars4 ;[186] Sanity check the number ifskp. ;[186] Don't let's be silly... emsg ;[186] An appropriate Vulcan response ret ;[186] And get out of here endif. ;[186] End case negative number came t2, mytty ;[186] Is the requested line the same as ours? ifskp. ;[186] It is silly to connect to ourselves emsg ;[187] Advise user of their confusion ret ;[186] And get out of here endif. ;[186] End case self-connect remark ;[186] Fine, let's try to use it hrli t1, .dvtty ;[186] Requesting a terminal hrr t1, t2 ;[186] This line jrst $conn2 ;[186] Go blat about the connection endif. ;[186] End case physical line caie t1, .cmkey ;[186] Parsed a keyword? ifskp. ;[186] Yes, let's see about that hrrz t1, pars4 ;[186] Load the requested device caie t1, .dvnul ;[186] Wants to close out? ifskp. ;[186] Yes, so break the connection ifme. local ;[186] Already remote? emsg ret ;[186] Nothing to do, bye endif. ;[186] End case not local call clsnet ;[186] Close whatever might be open txmsg <[Connection closed] > ;[186] Should say connection with what... ret ;[186] Proceed no further endif. ;[186] End case closure caie t1, .dvpty ;[186] Wants local loopback, differet job? ifskp. ;[186] Fine, let's try to use it hrloi t1, .dvpty ;[186] We don't specify the pseudo terminal jrst $conn2 ;[186] Go blat about the connection endif. ;[186] caie t1, .dvpip ;[186] Local connection, same job? ifskp. ;[186] Ok, handle that emsg () ret ;[186] Nothing to do, bye endif. ;[186] End case doing a pipe caie t1, .fhinf ;[205] Wants to get rid of the terminal fork? ifskp. ;[205] Does, so no 'network' activity skiple t1, ttfork ;[205] Load the fork handle ifskp. ;[205] Unless there isn't one emsg ;[205] Blat about it else. ;[205] Otherwise, get rid of it KFORK% ;[205] BYE!! erjmpr .+1 ;[205] Ignore error and carry on txmsg <[Killed remote terminal fork] > ;[205] endif. ;[205] End fork determination actions setzm ttfork ;[205] Remember its demise ret ;[205] And we're done endif. ;[205] End case terminal fork management ermsg% (,r) ;[186] endif. ;[186] End case .cmkey caie t1, .cmnod ;[186] Parsed a node? ifskp. ;[186] Yes, wants to have excitement and adventure! block. ;[186] Allocate an anonymous stkvar anstkv(t4,<.ndnum+1>);[186] Allocate a block for NODE% hrroi t1, atmbuf ;[186] Point to whatever user typed movem t1, .ndnod(t4) ;[186] Store in block setzb t1, t2 ;[186] Cons up some zeros dmovem t1, .ndflg(t4) ;[186] Stomp flags and number movei t1, .ndvfx ;[186] Node name verify, extended skipn ndvfxp ;[186] Has extended verify? movx t1, .ndvfy ;[186] Unfortunate, but still doable move t2, t4 ;[186] Load base of block NODE% ;[186] Should work because .cmnod validates ifje. r ;[186] Failed?? setzb t2, t3 ;[186] Whack any supposed flags else. ;[186] Otherwise, worked dmove t2, .ndflg(t4) ;[186] Load flags and maybe number endif. ;[186] End JSYS error processing endbk. ;[186] End block, restore stack ifxe. t2, nd%lgl ;[186] Illegal in some way? emsg ;[186] Blat about it hrroi t1, atmbuf ;[186] Point to what was typed PSOUT% ;[186] Type it hrroi t1, crlf ;[186] Tie off the line PSOUT% ;[186] Type it ret ;[186] Proceed no further endif. ifxe. t2, nd%exm ;[186] Syntax correct, but do we know about it? emsg ;[186] Blat about it hrroi t1, atmbuf ;[186] Point to what was typed PSOUT% ;[186] Type it hrroi t1, crlf ;[186] Tie off the line PSOUT% ;[186] Type it ret ;[186] Proceed no further endif. txne t2, nd%num ;[186] Did T79 give us a number? movem t3, nodnum ;[186] Yes, store it dmove t1, atmbuf ;[186] Grab the atom buffer dmovem t1, nodnam ;[186] Pass to openrt hrli t1, .dvdcn ;[186] Outgoing DECnet connection hrr t1, t3 ;[186] Use node number, if we have it jrst $conn2 ;[186] And open the connection endif. ;[186] End case node:: typed ermsg% (,r) ;[186] ; Set up controlling TTY for talk mode, issue connect message. $conn2: call openet ;[186] Go open (or reopen) the connection ret ;[186] Couldn't; proceed no further movem t1, netjfn ;[186] Store as network JFN skipn pars5 ;[205] Don't init terminal if staying call ttyini ;[186] Init controlling TTY. txmsg <[KERMIT-20: > ifmn. nrtflg ;[186] Active NRT connection? txmsg hrroi t1,nodnam ;[186] and don't claim it is a terminal PSOUT% ;[186] instead, type the node name txmsg <::> ;[211] DECnet node punctuation else. ;[186] Otherwise, use the physical line ifmn. ptyflg ;[186] Unless using a pseudo-terminal txmsg ;[186] hrroi t1,sysnam ;[186] Load local node name PSOUT% ;[186] Remind us of where we are txmsg <:: via > ;[186] some more details hrroi t1,ptynam ;[186] Give pseudo-terminal number PSOUT% ;[186] Type that txmsg < as > ;[186] load final clause else. ;[186] Otherwise, physical line txmsg ;[186] endif. ;[186] End case pseudo-terminal txmsg ;[186] Type message. numout ttynum,^d8 ;[186] movei t1,":" ;[186] Extra colon to punctuate PBOUT% ;[186] DECnet node name endif. ;[186] ifme. pars5 ;[205] Staying at remote? txmsg <, type > ;[205] No, normal blat movei t1, 74 ; Left pointy bracket... PBOUT txmsg move t1, escape ; (tell escape character) addi t1, "A"-1 PBOUT movei t1, 76 ; ...Right pointy bracket PBOUT txmsg < to return.] > ; Tell about session log, if any. else. ;[205] No, staying, so different blat movei t1, "]" ;[205] Not much blat PBOUT% ;[205] But say what there is of it... endif. ;[205] skipg t2, sesjfn ;[195] Logging? ifskp. ;[186] No, just tie off the line txmsg < [KERMIT-20: Logging session to > ; Yes, tell them now. movei t1, .priou ; Type the filename. caie t2, .nulio ;[195] Just dumping it? ifskp. ;[195] Yep that's easy dmove t2, nul4## ;[195] In k20dsp SOUT% ;[195] %jserr (,) ;[195] else. ;[195] Otherwise, a real file setzb t3, t4 ;[195] JFNS% %jserr (,) endif. ;[195] ifme. sesflg ;[195] Active? txmsg < (Disabled)> ;[195] Nyet endif. ;[195] txmsg <] > ;[195] else. ;[195] Otherwise just hrroi t1,crlf ;[195] tie off the line PSOUT% endif. ;[195] remark Connection is open, determine what else to do with the terminal setzm forkls ;[236] Clear /FORKLESS connect unless explicitly set ifmn. pars7 ;[236] Wants /FORKLESS? ifme. nrtflg ;[236] Yes, BUT!! Are we an active NRT connection? setzm pars7 ;[236] Force parse of normal connect txmsg <% /FORKLESS is only valid for DECnet connections > ;[236] Gently advise that this won't work... jrst $conn3 ;[236] And get on with it the olde-fashioned way endif. ;[236] End case clearing /FORKLESS for non-NRT remark ;[236] Otherwise, flag other code we're doing /FORKLESS setom forkls ;[236] Flag doing a forkless NRT connect skipe pars5 ;[236] But! Doesn't actually want to connect yet? ret ;[236] We're done callret frklsc ;[236] Falls into the below (but saves a JRST endif. ;[236] End case handling a /FORKLESS connection $conn3: skipe pars5 ;[218] Doesn't want to connect terminal yet? ret ;[218] We're done callret ttsfrk ;[218] Otherwise, set up the forks and terminal subttl Forkless terminal connect frklsc: entry frklsc ;[236] Invoked by K20MIT, also block. ;[236] Otherwise, connect terminal via the monitor!! anstkv(t4,.shlen) ;[236] Allocate a block for the MTOPR% remark ;[236] Construct block items movx t1, .shlen ;[236] Load length of argument block hrrz t2, ttyjfn ;[236] Only connecting our controlling terminal hrrz t3, escape ;[236] Load the escape character skipe flow ;[236] Doing flow control? txo t3, sh%lpm ;[236] Yes, turn on local page mode remark ;[236] Populate the block dmovem t1, .sharg(t4) ;[236] Set first two words of the argument block movem t3, .shesc(t4) ;[236] Third word is escape character and flags remark ;[236] Finally do the connect!!! hrrz t1, netjfn ;[236] Load the network JFN movx t2, .mosnh ;[236] Function is monitor NRT connect move t3, t4 ;[236] Load address of argument block MTOPR% ;[236] Do the connect %jserr (,r) ;[236] hrrz t1, .shtty(t4) ;[236] Load terminal identifier we used BIN% ;[236] Swallow escape character it leaves in buffer %jserr (,r) ;[236] hrrz t1, netjfn ;[236] Load the network JFN call chkdcn ;[236] Returned; get link status ifme. carier ;[236] Got disconnected? ifxn. t3,mo%syn ;[236] Normal close and andxe. t3,mo%abt ;[236] not aborted? setz t4, ;[236] Flag a normal close txmsg (<[KERMIT-20: >) ;[236] Yes, begin blat ']' (emacs) hrroi t1,nodnam ;[236] Point to the remote node PSOUT% ;[236] Type it txmsg <:: has closed> ;[236] else. ;[236] Otherwise, abnormal close seto t4, ;[236] Flag an ABNORMAL close emsg () ;[236] Begin an error message hrroi t1,nodnam ;[236] Point to the remote node PSOUT% ;[236] Type it txmsg <:: has aborted> ;[236] endif. ;[236] End case link closure analysis txmsg (< the NRT connection because: >) ;[236] call gdscpt ;[236] Get pointer to disconnect reason PSOUT% ;[236] Type it txmsg <. Returning to > ;[236] Emphasize we're not there anymore hrroi t1,sysnam ;[236] Load local node name PSOUT% ;[236] and type it txmsg <::> ;[236] Punctuate the local node name ife. t4 ;[236] Did it close normally? movx t1,135 ;[236] It did, so load a closing brocket PBOUT% ;[236] Type it to close off the message endif. ;[236] End case properly formating informative message hrroi t1, crlf ;[236] Tie off the line PSOUT% ;[236] call clsnrt ;[236] Toss the NRT connection ret ;[236] Either way, return; we're done endif. ;[236] End case disconnected retskp ;[236] Otherwise, worked and they typed the escape endbk. ;[236] End block context ifskp. ;[236] Worked? callret doesc ;[236] It did, and the user typed the escape character else. ;[236] Something failed ret ;[236] Just get out of here endif. ;[236] subttl BOUTR% - BOUT% a Record ; Necessary when doing DECnet to get a character pushed ; ; t1/ Network JFN ; t2/ Character to send ; ; Inefficient, you say? Clearly you haven't seen the code in the ; monitor that does a 'push'... ; ; Note use of anonymous stkvar to enable full re-entrancy while ; limiting symbol table usage. ; ; To do: Is a ROT and movem faster? Probably BOUTR%: entry BOUTR% ; Used in mainline ifme. vtermf ; Not a Virtual Terminal? BOUT% ; Just send the character out %jserr (,r) retskp ; Otherwise, worked!! endif. ; End case regular line ; Otherwise, need to push it out the door remark t1,t2 ; t1 has JFN, t2 has character saveac ; Save a few things anstkv (t4,^d1) ; Allocate a one word anonymous stack variable ; Now have something for SOUTR% to use setzm (t4) ; Clear memory (unnecessary for counted SOUTR%) hrli t4,(point 8,) ; Convert to an eight bit pointer move t3, t4 ; Make a copy of it idpb t2, t3 ; Pop the character at BEGINNING of word move t2, t4 ; Load pristine pointer for I/O setob t3, t4 ; Doing one character, no stop character SOUTR% ; Output, setting PSH ifje. r ; Catch error move t4, t1 ; Put this someplace for debuggers %ermsg (,) ; Whine call netvtx ; Whine some more ret ; Return failure endif. ; End case JSYS error retskp ; Return success subttl Alternate network input code (assumes upper fork context) ; Special cased for NRT's in order to 'push' data on DECnet. Tested ; on PTY's, also. ; ; Characters are sent out with a 'push' by doing a record out, which ; gets them over to the remote NRT host immediately. Checks to see ; if we can bum BIN%'s with a SIN%. PTY code uses this, too. ; ; SIBE% is fine because we are looking at the local TTY ; ; N.B., We ALWAYS read 7-bit ASCII from our control terminal and may or ; may not put parity on it in for output vtmpsh: entry vtmpsh ; Jumped to by ttinch: remark q1, ; Have to validate that q1 is not in flight here do. ; Enter loop context. move t1, ttyjfn ; Wait for data on TTY BIN% ; Wakes up on anything %jserr (,tter1) ; What could happen? aos vbict ; Count a BIN% on a virtual terminal movei t4,177 ; 7 bit mask andb t2,t4 ; Stomp any foolish parity everywhere camn t2, escape ; Is it the escape character? jrst doesc ; Yes, go process single-char command. SIBE% ; Any more data to read maybe? ifskp. ; Nope, then just had this poor character ifn. t2 ; If zero, then no error and nothing to do %ermsg (,) ; But continue endif. ; End case t2 having JSYS error code remark ; Yet contribute nothing to total move t2,t4 ; Load the character for duplex skipe duplex ; Have to echo locally? call echo ; Yes, do. move t1, t4 ;[223] Load in case parity call @parity ;[223] Do parity if asked move t2, t1 ;[223] Put whatever parity did in the right place move t1, netjfn ; Load JFN of our DCN: connection call BOUTR% ; Write and push to network %ermsg (,tter1) ; If error, go check. aos vboct ; Count it as a BOUT% else. ; Otherwise, maybe save us a few BIN%'s cail t2,linlen ; Rolling buffer plus BIN%? movei t2, ;Clip it down to fit the character we got move t3,t2 ; Load amount to read (positive!!) move t5,t2 ; Save a handy copy addm t5,vsitc ; Number of characters slurping up camle t5,vsimx ; Larger than largest we ever saw? movem t5,vsimx ; Yes, remember that aos vsict ; Count a SIN% move t2,[point 7,nrtbuf] ;Seven bit traffic idpb t4,t2 ; Deposit the BIN%'ed character move t4,escape ; Stop reading on escape character SIN% ; Slurp in a bunch of characters from user %jserr (,tter1) ; Handle any errors. call vtmout ; Output it jrst tter1 ; Failed somehow jumpn t5,doesc ; Use talisman to handle escape endif. ; Done handling results from SIBE% loop. ; Go back and do it some more enddo. ; Exit loop context ; Should never get here, but... jrst ttinch ; Go back and do it again from the top subttl Network fork data writer ; Write whatever data we have to the network, type it, log it, Etc. ; ; On entry: ; ; t1/ ttyjfn ; t2/ Updated byte pointer (buffer will have at least the BIN%'ed character) ; t3/ Remaining characters in buffer ; t4/ Escape character that may have stopped us ; t5/ Original buffer length ; ; AC usage: ; ; t5/ 0, Complete buffer written ; -1, Wasn't (hit an escape) ; ; q2/ Copy of orginal t3 (remaining characters) ; q3/ Number of characters we're actually writing ; q4/ Parity (if doing parity) vtmout: saveac ; Save misc. things move q4, parity ;[223] Load parity skipn parpko ;[223] Not if packets-only cain q4, none ;[223] But!! Doing anything at all, really? setz q4, ;[223] No, so make it easier to do nothing aos q3,t5 ; Store original count + BIN% setz t5, ; Let's assume didn't hit the escape skipe q2,t3 ; Save and check remaining count seto t5, ; Hit an escape... subb t3,q3 ; Calculate complete buffer size jumpe q3,r ; Don't do a push of an empty buffer movn t1,q3 ; Pick up POSITIVE count of characters addm t1,vsotc ; Add in total camle t1,vsomx ; Greater than max? movem t1,vsomx ; Update maximum aos vsoct ; Count a SOUTR% move t2,[point 7,nrtbuf] ;Seven bit traffic ifn. q4 ;[223] Parity? move t1,[point 8,parbuf] ;[223] Eight bit traffic call genpar ;[223] Generate a new string with parity endif. ;[223] End case generating parity move t1, netjfn ; Load JFN of our DCN: connection SOUTR% ; Write and 'push' %jserr (,r) ; If error, return +1 skipn duplex ; Half duplex? ret ; No, nothing to echo ; Ugh... Let's get to it saveac ; Wants another register move q2,[point 7,nrtbuf] ;Load a pointer to the buffer movn q4,q3 ; Do a positive counter (unnecessary) do. ; Enter loop lexical context ildb t2,q2 ; Pick up a character from the buffer call echo ; Type it sojg q4,top. ; Do all of them enddo. ; Exit loop lexical context ret ; Done, finally ; To do, this is an awful lot of instructions just to echo. ; Could temporarily restore the COC's and PSOUT%. Also could ; do a MOVST from from an eight byte buffer and overwrite it ; with a seven bit buffer with the control characters? subttl Code for receive fork. ; Rewritten for efficiency to use less JSYI and avoid stack clash ; ; Runs forever, asynchronously, till killed. ; ; The algorithm is to wait for a character and then slurp up anything ; that might be in the monitor's input buffer for the line (or NRT). ; This can substantially cut down on BIN%/BOUT% overhead while still ; maintaining performance because the fork is effectively always waiting ; for remote output. ; ; Partially adapted from a much modified SETNOD. ; ; Be aware of a subtle Tops-20 bug! Once created, the terminal fork ; should NEVER be killed, but rather frozen. Previous Kermit behavior ; was to always kill the fork on a close, keeping the network JFN open, ; recreating the fork on every connect. While this was inefficient ; (fork creation being expensive), it was fine for a pseudo-terminal. ; ; However, killing the fork while it was waiting for NRT data caused ; Tops-20 DECnet to lose track of the buffers, the result being that ; whatever was last in the buffer was read again when the fork was ; recreated. ; ; Trying to force the monitor buffers to be correct with SINR% only ; partially worked. Output was not repeated, but a timing anomaly was ; then exposed that the result of a SIBE% was less than what was ; available, the consequence being that the SINR% would fail with ; a IOX10 error (Record is longer than user requested), the extra ; data then being dumped (into oblivion). ; ; Freezing and resuming the terminal fork prevents this situation and ; is more efficient, anyway. Therefore, make certain that the FFORK% ; at $CONX2+5 is NEVER changed back to a KFORK%! ; ; However, this does not fix the problem of output getting repeated ; into the main fork once the subfork is frozen. In particular, ; suppose the user does something very reasonable and connects to a ; remote system to sign on. Escaping back will now work fine, but if ; before this happens, the user runs a Kermit and puts it into server ; mode, the main fork will now see all the junk that the recreated ; inferior used to see plus a large pile of NUL's thrown in to boot!! ; ; Therefore, whenever we escape back, a clrbuf is done for an NRT. linlen==^d1024 ; Maximum characters we'll swallow at once netin: entry netin ; Jumped to by main character read loop remark q1,q2,q3,q4,p1,p2,p3 ;No need to save these in seperate fork move p,[iowd pdlsiz,frkpdl] ; Can't share stacks... movei t1, netinh ; Load Address of a halt routine push p, t1 ; Just in case we want to return over the top movei q1, frkbuf ;[223] Always using the same buffer move t1, parity ;[223] Load parity setting cain t1, none ;[223] Are we doing anything? ifskp. ;[223] Some kind of parity being done, so check further skipe parpko ;[223] Only doing parity on packets? anskp. ;[223] Yes, so better leave this alone skipn parrck ;[223] Checking parity on receive and not just sending? anskp. ;[223] No, so don't pay any attention move p3, t1 ;[223] Set the flag with the parity value hrli q1,<(point 8,0)> ;[223] Do it all 7 bit ASCII with a parity bit else. ;[223] Otherwise, not doing anything special setz p3, ;[223] So clear the flag hrli q1,<(point 7,0)> ;[223] And do it all straight 7 bit ASCII endif. ;[223] End case parity determination do. ; Enter loop context seto q2, ; Assume we get at least one chracter hrrz t1, netjfn ; Always prefer a network JFN ife. t1 ; Unless there isn't one hrrz t1, ttyjfn ; Use terminal if nothing else endif. ; End case no network JFN BIN% ; Wait for input %jserr (,neterr) ; Handle any errors. aos nbict ; Network BIN% count move q3, t2 ; Tuck that character safely away for now move t4, t1 ; Get the PTY JFN out of the way call clrest ; Find out what awaits us ifskp. ; Worked!! move p1, t1 ; Save the count (which might be zero) else. ; Failed?? %ermsg (,neterr) endif. ife. p1 ; Nothing but one dinky character? ifn. p3 ;[223] Are we doing parity? move t1, q3 ;[223] Yes, so load the character call (p3) ;[223] Do some kind of parity came t1, q3 ;[223] Does it check? call parier ;[223] No, go complain endif. ;[223] End case parity checking move t2, q1 ; Load the pointer idpb q3, t2 ; Drop the character in call ntecho ; Finally echo it else. ; Otherwise, save us many BIN%'s!! do. ; Enter read/write loop move t2, p1 ; Load the total from clrest cail t2, linlen ; Rolling buffer plus BIN%? movei t2, ;Clip it down to fit the character we got camle t2, nsimx ; Smaller than biggest? movem t2, nsimx ; Nope, update total addm t2, nsitc ; Network SIN% total characters movn t3, t2 ; Calculate amount to read sub p1, t2 ; Subtract from total known sub q2, t2 ; Account for previous byte in write total move t2, q1 ; Load the pointer idpb q3, t2 ; Drop the character in Ifl. t3 ; BUT!! Are we actualy going to do anything? aos nsici ; Network SIN%'s Issued move t1, t4 ; Load the network JFN SIN% ; Get that data! %jserr (,neterr) ;Handle any errors endif. ; End sanity check ifn. p3 ;[223] Doing any kind of parity? dmove t2, q1 ;[223] Load what will be passed to ntecho call chkpar ;[223] Check the parity call parier ;[223] Bad, go complain endif. ;[223] End case parity checking call ntecho ; Go echo the output jumpg p1, top. ; Still more data pending, read it enddo. ; End inner input/output loop endif. ; End decision to read more than one character loop. ; Otherwise, go to the top and wait for more enddo. ; End outer loop subttl echo what we read from the network ; Called from various places in netin lower fork code to display data ; ; Expects: ; ; ttyjfn/ Valid JFN or terminal designator ; q1/ Pointer to beginning of data read ; q2/ Negative count of data (I.E., counted SOUT% ready ; p3/ Parity scrubber flag ; ; +1, always ; ; Trashes t1, t2 and t3. ; ; If doing parity, we have a buffer with eight bit bytes in it which ; must have the parity bit stripped off. If this is not done, then ; Tops-20 is going to write in 'image' mode, which can produce funny ; output on terminal emulators. ; ; The routine simply picks up an eight bit byte and replaces it with a ; seven bit byte, overwriting the storage in place. Since the 7 bit ; ASCII stream will always trail the 8 bit stream, we will never run ; out of space nor clobber anything. ntecho: jumpe p3,ntech2 ;[223] Any parity to strip off? jumpe q2, r ;[223] If nothing to do, we're done! hlrz t1, q1 ;[223] A quick sanity check of the pointer width cain t1, <(point 7,0)> ;[223] Is this a waste of time, anyway? jrst ntech2 ;[223] It is, so skip all of this caxge q2,-^d4 ;[223] Characters at which movslj wins (we think) jrst ntech1 ;[223] Go win big with extended instruction! ntech0: saveac ;[223] Doesn't need quite so many registers... move t2, q1 ;[223] Load 8 bit source hrli q1, <(point 7,0)> ;[223] Stomp in the right pointer width move t3, q1 ;[223] Load 7 bit destination movn t4, q2 ;[223] We get less confused by positive numbers ... do. ;[223] Enter loop context ildb t1, t2 ;[223] Pick up an 8 bit byte idpb t1, t3 ;[223] And deposit as 7 bit, stripping parity sojg t4, top. ;[223] Do the rest of them enddo. ;[223] End loop lexical context jrst ntech2 ;[223] And go type something ntech1: saveac ;[223] Convert from 8 to 7 bit ASCII dmove q3, q1 ;[223] Save original arguments movn t1, q2 ;[223] movslj wants positive counts move t4, t1 ;[223] Smaller width can never overflow move t2, q1 ;[223] Section local eight bit pointer hrrz q1, t2 ;[223] Same starting address hrli q1, <(point 7,0)> ;[223] Stomp in the right pointer hll q3, q1 ;[223] And remember that new width setzb t3, q2 ;[223] Section local pointers extend t1, movchr ;[223] Repack the string in place (which is safe) nop ;[223] Ignore any odd non-skip dmove q1, q3 ;[223] Restore updated calling arguments ntech2: move t1, ttyjfn ;[223] ; Load local terminal dmove t2,q1 ; Load pointer and length SOUT% ; Display incoming characters on screen. %jserr (,) skipg t1, sesjfn ; Logging? ifskp. ;[195] Possibly doing it skipn sesflg ;[195] Unless not active anskp. ;[195] In which case, skip it dmove t2,q1 ; Load buffer pointer and length SOUT% ; Write it to the log %jserr (,netlgx) ;[195] endif. ;[195] End case logging ret ; Done subttl Table to map DECnet close reason code to text ;[238] Begin table insertion ; Handle all the .psect stuff by hand. Have to be careful because we ; are going to the outermost .psect, which will have the wrong location ; counter. Also, getting this wrong will cause LINK to fail with a ; most informative message of "Illegal memory WRITE at SY.FP5+1", which ; is almost--but not quite--completely and utterly useless. .endps code ; Get out of code .psect .dcxmx==.dcx43 ; Maximum code .psect const ; Put all the constants in the const .psect dsctab: remark ; Just create a label in .psect .endps const ; End of const .psect define dsctxt (n,t,%et) < ;;Macro to put pointers to messages in the right place .psect const ;;Assume in const .psect reloc dsctab+n ;;Get to correct location in table .px7!%et ;;Emit pointer to text in extended text section .endps const ;;Get out of const .psect .psect etext ;;Get into extended text .psect %et: asciz \'t\ ;;Emit the actual text of the disconnect reason .endps etext ;;Close out extended text .psect cleans(<%et>) ;;Clean up generated symbol on second pass >;;dsctxt dsctxt(.dcx0,) dsctxt(.dcx1,) dsctxt(.dcx2,) dsctxt(.dcx3,) dsctxt(.dcx4,) dsctxt(.dcx5,) dsctxt(.dcx6,) dsctxt(.dcx7,) dsctxt(.dcx8,) dsctxt(.dcx9,) dsctxt(.dcx10,) dsctxt(.dcx11,) dsctxt(.dcx21,) dsctxt(.dcx22,) dsctxt(.dcx23,) dsctxt(.dcx24,) dsctxt(.dcx32,) dsctxt(.dcx33,) dsctxt(.dcx34,) dsctxt(.dcx35,) dsctxt(.dcx36,) dsctxt(.dcx37,) dsctxt(.dcx38,) dsctxt(.dcx39,) dsctxt(.dcx40,) dsctxt(.dcx41,) dsctxt(.dcx42,) dsctxt(.dcx43,) .psect const ; Put all the constants in the const .psect reloc dsctab+.dcxmx+1 ; Back to end of dsctab .endps const ; End of const .psect ;[238] End table insertion subttl convert DECnet close reason code to text remark Given a disconnect code, return a pointer to descriptive text ;[238] Begin code insertion ; Call: ; ; T3/ Contains result of .MORLS ; ; Return: ; ; T1/ OWGP to informative text .psect etext ; Get to extended text .psect unkdec: asciz "Unknown disconnect code" .endps etext ; Close out extended text .psect .psect code ;;Get back into the code .psect gdscpt: hrrz t2, t3 ; Pick up disconnect code caile t2, .dcxmx ; Out of range? ifskp. ; No, it's fine skipn t1, dsctab(t2) ; Load OWGP to informative text anskp. ; Unless there isn't any ret ; Otherwise, return it else. ; Otherwise, out of range or no text move t1,[.px7!unkdec] ; Say as much ret ; Return at least something endif. ; End case range and pointer check ;[238] End code insertion subttl Parity Error Handler honk: byte (7) .chbel, .chnul ;[223] Just honk the terminal parier: push p, t1 ;[223] Save the accumulator hrroi t1, honk ;[223] Point to the alert ESOUT% ;[223] Beep the terminal erjmpr .+1 ;[223] Catch and ignore error aos ttipar ;[223] Count a parity error pop p, t1 ;[223] Restore the accumulator ret ;[223] Done subttl Error handler for network TTY. neterr: ifmn. vtermf ;[186] Virtual terminal? move t1, netjfn ;[186] Load network JFN call chklin ;[186] Get network status skipn carier ;[186] dropped carrier? call netvtx ;[186] Yep, we're down endif. ;[186] End special case for non-physical line skipn mdmlin ; Modem controlled line? jrst netin ; No, go back. call chklin ; Go check for carrier. skipn carier ; Still have it? jrst $connx ;[186] No, close the connection. jrst netin ; Yes, keep plugging away till they disconnect. subttl Handles signal of failure of network input fork frtrap: entry frtrap extern pc3 ; Level we interrupt on push p, t1 ; Save any AC we touch push p, t2 push p, t3 skipn t1,ttfork ; Load the handle of network input fork ifskp. ; If there is one.... KFORK% ; Ditch it erjmpr .+1 ; Ignore the error setzm ttfork ; Forget about the handle; it's gone endif. ; End case fork handler call clsnet ; Whack any kind of network connection movx t1,pc%usr ; Get into user mode. iorm t1,pc3 ; Resume at previous PC pop p, t3 ; Restore AC's and beat it pop p, t2 pop p, t1 DEBRK% subttl Sends a DECnet interrupt message when BREAK is requested nrtmsg: bldmsg () nrtbrk: entry nrtbrk ; Experimental; not really used ret ; This hangs a Tops-10 connection, don't do it saveac ; Save just because we don't know move t1,netjfn ; Load network JFN movei t2,.mosim ; Function to send DECnet interrupt message dmove t3,[point 7,nrtmsg ;Point to interrupt message nrtlen ] ; Length of same MTOPR% ; Bombs away! %jserr(,r) ret subttl clrbuf Clear Line Input Buffer ;[211] All rewritten and enhanced for non-physical terminals ; Call: ; ; Nothing: appropriate thing is done based on connection context. ; ; Returns: ; ; +1/ Some problem ; +2/ Success ; t1/ Total characters chewed ; ; N.B., While SIBE% and SOBE% will work on any JFN, CFIBF% and ; CFOBF%'s will *ONLY* work with terminal lines. For PTY's ; and NRT's, we have to read the input (and toss it). flushc==^d200 ; Maximum characters to swallow clrbuf: entry clrbuf ; Inform link of our location call inpclr ;[209] Chuck any waiting input skipe ptyflg ; Pseudo-terminal? callret ptyfls ; Yes, that has to be flushed from both sides skipe nrtflg ; DECnet NRT? callret dcnfls ; Yes, CFIBF% won't work ; Otherwise, a physical line on an FE!!!! hrrz t1, netjfn ; Although a real line, prefer network JFN ife. t1 ; Unless there isn't one hrrz t1, ttyjfn ; Use terminal if nothing else endif. ; End case no network JFN setzb t2, t3 ; No current read, no accumulated read do. ; Enter loop context SIBE% ; Skip if input buffer empty ifskp. ; Empty? jumpe t2, endlp. ; If zero, then no error; exit loop %ermsg (,r) ;[211] else. ; Otherwise, have some junk in there add t3, t2 ; Add to total cleared CFIBF% ; Chuck the input %jserr (,r) ; Boo... loop. ; See if anything else shows up endif. ; End of SIBE% action logic enddo. ; End flush loop move t1, t3 ; Load grand total flushed retskp ; Return success!!! subttl DECnet flush ; Somewhat similar logic to physical terminal, except that ; CFIBF% won't work, so we have to read (and toss) the data. ; ; N.B., Can't use SINR% because it will discard an unknown number ; of characters. Sigh... dcnfls: saveac hrrz t1, netjfn ; Pick up the network JFN ife. t1 ; Have to have this for an NRT! ermsg% (,r) endif. ; End of that particular sanity check move q1, t1 ; Save whatever JFN we're using (q1 unused) setz q3, ; No initial grand tally do. ; Enter loop context SIBE% ; Skip if input buffer empty ifskp. ; Empty? jumpe t2, endlp. ; If zero, then no error; exit loop %ermsg (,r) else. ; Otherwise, have some junk in there move q2, t2 ; Load for inner loop do. ; Enter inner loop context skipn t4, q2 ; Load remaining characters exit. ; If no more, then we're done caile t4, flushc ; More than maximum we can swallow at once? movx t4, flushc ; Yep, well just take a mouthful remark t1, q1 ; JFN is still in there move t2, [point 8,flushb] ; Load pointer to the 'flush' buffer movn t3, t4 ; Reading exactly that much SIN% ; Swallow whatever junk is in there %jserr (,r) add t4, t3 ; Keep track of what we didn't read sub q2, t4 ; Subtract from remaining add q3, t4 ; And add to total done jumpg q2, top. ; Loop if anything left to do enddo. ; End context inner loop endif. ; End SIBE% results handling loop. ; See if anything else there enddo. ; End loop lexical context addm q3, vchrcn ; Update grand total characters ever flushed move t1, q3 ; Return total characters whacked this time retskp ; Return success remark Special actions to flush a PTY ; Note that while a CFIBF% will not work on the PTY JFN, a CFOBF% ; *WILL* work on the terminal side for which we have the device ; designator. Since we assigned the PTY which maps to the TTY, we ; retain certain rights to the terminal, one of which is that a CFOBF% ; will work and we don't have to read anything. ; ; None the less, we check to see if anything made it over to the PTY ; buffer so we can toss that. ; ; Does not return until *both* the SOBE% and SIBE% produce zero. ptyfls: remark ; Has to work both sides of the device saveac hrlz q1, netjfn ; Pick up the network JFN ife. q1 ; Have to have this for a PTY!! ermsg% (,r) endif. ; End of that particular sanity check hrr q1, ptytty ; Load this PTY's associated terminal line txo q1, .ttdes ; Force alternate form of terminal designator setzb q2, q3 ; Zero working read and grand total do. ; Enter loop context hrrz t1, q1 ; Load terminal designator SOBE% ; Skip if output buffer empty ifskp. ; Empty? ifn. t2 ; If zero, then no error and nothing to do %ermsg (,r) endif. ; End case t2 having JSYS error code setz q4, ; Whack this round's output else. ; Otherwise, have some junk in there add q3, t2 ; Accumulate in grand tally move q4, t2 ; Flag non-zero buffer, this round CFOBF% ; Clear out any blocked up crud %jserr (,r) endif. ; End SOBE% results handling hlrz t1, q1 ; Load the PTY side SIBE% ; Skip if input buffer empty ifskp. ; Empty? ifn. t2 ; If zero, then no error; carry on %ermsg (,r) endif. ; End case empty input buffer else. ; Otherwise, have some junk in there add q4, t2 ; Add to this round's tally move q2, t2 ; Load for inner loop do. ; Enter inner loop context skipg t4, q2 ; Load remaining characters exit. ; If no more, then we're done caile t4, flushc ; More than maximum we can swallow at once? movx t4, flushc ; Yep, well just take a mouthful remark t1, q1 ; JFN is still in there move t2, [point 8,flushb] ; Load pointer to 'flush' buffer movn t3, t4 ; Reading exactly that much SIN% ; Swallow whatever junk is in there %jsErr (,r) ;[211] add t4, t3 ; Keep track of what we didn't read add q3, t4 ; And add to total done sub q2, t4 ; Subtract from remaining jumpg q2, top. ; Loop if anything left enddo. ; End context inner loop endif. ; End SIBE% results handling jumpg q4, top. ; If got anything, take another look enddo. ; End of loop lexical context addm q3, vchrcn ; Update grand total characters ever flushed move t1, q3 ; Return total characters whacked this time retskp ; Return success subttl clrest Give an estimate of characters in input buffer ; Call: ; ; Nothing: appropriate thing is done based on connection context. ; ; Returns: ; ; +1/ Some problem ; +2/ Success ; t1/ Total characters in various buffers ; ; N.B., A pseudo terminal can have characters on 'both sides', that ; is, the character's in the PTY's input buffer *AND* the ; characters in the associated TTY's output buffer that have not be ; transferred into the PTY's input buffer, yet. ; ; Thus, the use of SOBE% for pseudo-terminals in addition to the ; expected SIBE%. clrest: entry clrest ; World callable saveac ; Needs a few accumulators hrrz t4, netjfn ; Always prefer a network JFN ife. t4 ; Unless there isn't one hrrz t4, ttyjfn ; Use terminal if nothing else endif. ; End case no network JFN setzb t2, t3 ; Clear all totals ifmn. ptyflg ; If pseudo-terminal, look at both sides hrrz t1, ptytty ; Load this PTY's associated terminal line txo t1, .ttdes ; Force alternate form of terminal designator SOBE% ; Skip if output buffer empty ifskp. ; Empty? ifn. t2 ; If zero, then no error and nothing to do %ermsg (,r) endif. ; End case t2 having JSYS error code else. ; Otherwise, have some junk in there move t3, t2 ; Keep track of TTY's output side setz t2, ; Keep nice and tidy for SIBE% endif. ; End SOBE% results handling endif. ; End PTY special case move t1, t4 ; Load whatever JFN we decided to use SIBE% ; Skip if input buffer empty ifskp. ; Empty? ifn. t2 ; If zero, then no error and nothing to do %ermsg (,r) endif. ; End case t2 having JSYS error code else. ; Otherwise, have some junk in there add t3, t2 ; Add to any running tally endif. ; End SIBE% results handling move t1, t3 ; Return grand total seen retskp ; Return success subttl clread Return buffer of what we cleared ; Call: ; ; Nothing: appropriate thing is done based on connection context. ; ; Returns: ; ; +1/ Some problem ; +2/ Success ; t1/ Total characters read ; t2/ (Eight bit) pointer to buffer ; ; N.B., be aware of the following: ; ; 1) clread should be repeatedly called until it returns zero as ; there may be more data than we can read. ; ; 2) Can't use SINR% because it will discard an unknown number of ; characters. Sigh... clread: entry clread ; Called from K20PAR saveac remark call ;[209] Display something call inpclr ;[209] Chuck any waiting input hrlz q1, netjfn ; Prefer the network JFN ife. q1 ; But!! Do we have one? hrlz q1, ttyjfn ; Use terminal if nothing else endif. ; End case no network JFN ifmn. ptyflg ; Pseudo-terminal? hrr q1, ptytty ; Load this PTY's associated terminal line txo q1, .ttdes ; Force alternate form of terminal designator endif. ; End case pseudo-terminal dmove q4, [ flushc ; Load total remaining in buffer point 8, flushb ] ; Load pointer to 'flush' buffer do. ; Enter loop context jumpe q4, endlp. ; If buffer full, then return hrrz t1, q1 ; Load terminal designator ifn. t1 ; But did we ever have one? SOBE% ; Skip if output buffer empty ifskp. ; Empty? ifn. t2 ; If zero, then no error and nothing to do %ermsg (,r) endif. ; End case t2 having JSYS error code setz t4, ; Whack this round's PTY portion else. ; Otherwise, have some junk in there move t4, t2 ; Flag non-zero buffer, this round endif. ; End SOBE% results handling else. ; Otherwise no PTY setz t4, ; So no PTY contribution endif. ; End special case for pseudo-termina hlrz t1, q1 ; Now load whatever JFN we have SIBE% ; Skip if input buffer empty ifskp. ; Empty? ifn. t2 ; If zero, then no error; carry on %ermsg (,r) endif. ; End case empty input buffer else. ; Otherwise, have some junk in there add t4, t2 ; Add to this round's tally endif. ; End SOBE% results handling jumpe t4, endlp. ; If nothing there, we're done camle t4, q4 ; More than what we have left? move t4, q4 ; Yep, don't overflow the buffer move q2, t4 ; Position for inner loop setz q3, ; Zero inner loop tally do. ; Enter inner loop context remark t1, q1 ; JFN is still in there from SIBE% move t2, q5 ; Load updated pointer movn t3, t4 ; Reading exactly that much SIN% ; Swallow whatever junk is in there %jsErr (,r) add t4, t3 ; Keep track of what we did NOT read add q3, t4 ; And add to loop total done sub q2, t4 ; Subtract from remaining jumpg q2, top. ; Loop if anything left enddo. ; End context inner loop sub q4, q3 ; Subtract from total buffer size move q5, t2 ; Store updated pointer for next round jumpg q4, top. ; If got anything, take another look enddo. ; End of loop lexical context movx t1, flushc ; Load largest possible buffer sub t1, q4 ; Subtract total remaining addm t1, vchrcn ; Update grand total characters ever flushed move t2, [point 8,flushb] ; Return pointer to 'flush' buffer retskp ; Finally return success subttl Routine to unstop an XOFF'd line, added as edit 91. ttxon: entry ttxon ;[211] Partly rewritten for PTY's and NRT's saveac ;[211] Needs an extra register call clrbuf ;[211] Call our new friend to toss data ret ;[211] But couldn't; give up skipe t1, netjfn ;[186] Load the network JFN ifskp. ;[186] Unless we don't have one... skipe local ;[186] Are we remote? ermsg% (,r) ;[186] Punt skipn t1, ttyjfn ;[186] Yes, so just use the terminal JFN ermsg% (,r) ;[186] endif. ;[186] Hopefully have SOMETHING ... hrlz q1, t1 ;[211] Save the JFN (sans flags) for later ifmn. ptyflg ;[211] A pseudo-terminal? hrrz t1, ptytty ;[211] Yes, don't do this to the PTY half txo t1, .ttdes ;[211] Do it to the TTY half endif. ;[211] End PTY-FE/NRT decision hrr q1, t1 ;[211] Save some terminal descriptor ;[157] If we're doing flow control, send a ^Q (XON) to unstick the other side. skipn flow ; Doing flow control? ret ; No, done. skipe nrtflg ;[211] An NRT? callret ttxon3 ;[211] Skip this terminal stuff ;[211] Will never work with a DCN: JFN ttxon2: hrrz t1, q1 ;[211] Get some terminal descriptor RFMOD ; Yes, get terminal mode. erjmp r move t3, t2 ; Save it. txze t2, tt%dam ; Data mode? ifskp. ;[211] No, so no need to change call ttxon3 ; No, binary, just send it. else. ;[211] Otherwise, tweak the mode SFMOD ; Put in binary mode. erjmpr r ;[211] call ttxon3 ; Send the XON. hrrz t1, q1 ;[211] Reload the terminal descriptor move t2, t3 ; Load original settings SFMOD ; Put back in data mode. erjmpr r ;[211] endif. ;[211] End terminal mode tweaking ret ttxon3: hlrz t1, q1 ;[211] Use the real JFN movei t2, xon ; Send an XON. BOUT erjmp r ret ;[211] End clrbuf rewrite for non-physical terminals subttl clsnet -- Close any kind of 'network' connection remark ; Has to be before first reference!! syn clscom,clsfe ; Close the terminal syn clscom,clspty ; Close the pseudo-terminal ; Ignores local setting, uses netjfn, regardless. Checks the JFN, ; regardless of it possibly being absurd. clsjfn: entry clsjfn ; Invoked by Kermit exit saveac ;Don't touch anything move t1, netjfn ; Use whatever is there, no matter what jrst chkcls ; Just get started with the JFN ; Expects nothing; checks local to see if we would even have the JFN ; and sanity checks the JFN clsnet: entry clsnet ; Callable by anybody extern local ; Set if we are not using .priou for transfers skipn local ; Are we not using our own terminal for packets? ret ; We are, so there is nothing to clean up saveac ;Don't touch anything skipg t1, netjfn ; If we are local, then we will have a JFN jrst clsasg ; Unless we are in some odd state remark chkcls ; falls through chkcls: remark ; Here to check if we can close it GTSTS% ; Now let's find out about the JFN ifje. r ; Catch and ignore the error move t4, t1 ; Save any error code for later setz q1, ; Whack the bits, assume nothing hrrz t1, netjfn ; Reload the JFN else. ; Otherwise, worked move q1, t2 ; Save the status bits endif. jxe q1, gs%nam, clscln ; Nothing there? Just scrub the storage DVCHR% ; JFN might work ifje. r ; But didn't move t4, t1 ; Save any error code for later setob q2, q4 ; Phoney device designator and assignment setz q3, ; No characteristics else. ; Otherwise, worked. Promising... dmove q2, t1 ; Save device designator and characteristics move q4, t3 ; And assignment word endif. jxe q1, gs%opn, clsrlj ; If it isn't open, don't close it ; Load the device type ldb t4,[pointr q3,dv%typ] cain t4, .dvtty ; Physical (front end) terminal? jrst clsfe ; Clean that up and deassign cain t4, .dvpty ; Pseudo terminal? jrst clspty ; Clean that up and deassign cain t4, .dvdcn ; Outgoing NRT? jrst clsnrt ; Clean that up (no deassign) ermsg% (, clscom) subttl Various JFN closure routines remark ; See required location of SYN's, above remark clsfe ; Close the terminal remark clspty ; Close the pseudo-terminal nrtend: point 7, .+2 ; Point to message ^d12 ; Its length ASCIZ "Kermit Close" ; Informative message... clsnrt: hrrz t1, netjfn ; Load the network JFN move t2, [.dcx40,,.moclz] ;Object initiated close dmove t3, nrtend ; Message for remote NRT server to ignore MTOPR% ; Try to deliver the bad news ifje. r ; Catch and ignore error move t4, t1 ; Leave around for debugger endif. remark clscom ; And proceed ...(falls through) clscom: hrrz t1, netjfn ; Common close for any kind of JFN CLOSF% ; Make our first attempt ifje. r ; Catch and ignore the error move t4, t1 ; Save error for later caie t1, clsx1 ; File not open? jrst clsabt ; No, try to abort it jrst clsrlj ; Otherwise, just try to let go of it endif. jrst clsasg ; Go clean up assignments and storage clsabt: hrrz t1, netjfn ; Load the JFN, no flags txo t1, cz%abt ; Set the abort flag CLOSF% ; Toss it with reckless abandon ifje. r ; Catch and ignore the error move t4, t1 ; Save error for later caie t1, desx3 ; JFN not assigned anymore> jrst clsabt ; No, just try to let go of it jrst clsasg ; Otherwise, release assignments endif. jrst clsasg ; Go clean up assignments clsrlj: hrrz t1, netjfn ; Just try to let go RLJFN% ; and hope for the bext ifje. r ; Catch and ignore the error move t4, t1 ; Save error for later endif. remark clsasg ; Clean up assignments subttl Release any assigned terminals, pseudo or otherwise clsasg: ifmn. asgflg ; Do we think anything assigned? move t1, asgdev ; Grab assigned device RELD% ; Punt it ifje. r ; Sigh move t4, t1 ; What if different from q2? endif. endif. ; Do a consistency check hlre t3, q4 ; Load job assignment came t3, [-1] ; Not assigned? camn t3, [-2] ; Allocator has it? Jrst clscln ; Then nothing else to do came t3, myjob ; Do we have this device? jrst clscln ; No, then surely cannot release it move t1, q2 ; Load JFN's device designator camn t1, asgdev ; Did we already release it, actually? jrst clscln ; Yes, so no inconsistency ; No, something extra left lying around... hlrz t2, t1 ; Pick up the device type hrrz t3, t1 ; Pick up the unit number ife. t2 ; But!! Any device type? trzn t3, .ttdes ; Universal terminal? jrst clscln ; No, some odd thing. Leave it alone camn t3, mytty ; It's a terminal. Ourself? jrst clscln ; Yes, LOGIN% or CRJOB% gave it to us hrrz t1, t3 ; Load bare terminal number hrli t1, .dvdes!.dvtty ;Give a general device designator else. ; Otherwise, fullword move t4, t2 ; Make a copy of the device designator trz t4, .dvdes ; Shut off the device designator caie t4, .dvtty ; A terminal? anskp. ; Not a terminal, so can't be our terminal camn t3, mytty ; It's a terminal. Ourself? jrst clscln ; Yes, LOGIN% or CRJOB% gave it to us endif. ; To RELD% RELD% ; Try to punt it, anyway ifje. r ; Sigh move t4, t1 ; Save error number for debuggers endif. remark clscln ; Fall through to storage clean up subttl Finally obliterate JFN related storage ; Leaves ASCII device or node names alone for possible later reporting clscln: setzm asgflg ; Nothing assigned setzm asgdev ; No relec of it, either setzm netjfn ; Not no JFN, not no how setzb t1, t2 ; In case we have adjacent words dmovem t1, ndvchr ; Whack the characteristics double word setzm vtermf ; No kind of virtual terminal setzm nrtflg ; Not a DECnet NRT connection setzm ptytty ; No terminal assigned via PTY, either setzm ptyflg ; No a pseudo-terminal connection setzm ttyflg ; Not using a physical terminal setzm ttydev ; So don't have a device designator move t3, mytty ; Use our local terminal movem t3, ttynum ; Use that setzm local ; We are no longer local setom opndev ; No opened device ret ; One way or another, finally done subttl Lost virtual terminal connection, shut everything down netvtx: entry netvtx ;[196] extern frkchb ;[218] Convert channel number to bit txmsg < [KERMIT-20: Lost > ifmn. ptyflg txmsg hrroi t1, ptynam ; Point to pseudo-terminal device name PSOUT% ; Type that txmsg < (> hrroi t1, ttynam ; Point to associated terminal device name PSOUT% ; Type that txmsg <) > endif. ifmn. nrtflg txmsg hrroi t1,nodnam ; Point to the remote node PSOUT% ; Type it txmsg <:: > ; Trailing punctuation endif. txmsg ; Find out where this blew up move t1, (p) ; See who called us txz t1, klflgs ; Flags aren't part of the address call symout ; Symbollically! txmsg <. Returning to > hrroi t1,sysnam ; Load local node name PSOUT% ; Type it, not "DEC-20" dmove t1, [ .fhsup ;[218] Signaling superior Kermit frkchb ] ;[218] Inter-fork signal IIC% ; Give it a poke ifje. r ; Failed?? caie t1, FRKHX2 ; Wait! Tried to poke the wrong guy? %ermsg (,neter2) movei t1, .fhslf ;[186] We must be the inferior IIC% ;[186] So poke ourselves %jserr (,) ;[186] txmsg <:: (Sup)] > jrst $connx ;[186] In self-case, close some other things endif. ;[186] End signaling analysis and recovery txmsg <:: (Inf)] > neter2: HALTF ; Halt this fork. jrst neter2 ; Should never get here... netinh: push p, t1 ; Save t1, just in case useful push p, t2 ; Ditto others push p, t3 hrroi t1, netinm ; Load error message ESOUT% ; Give ourselves an error movei t1,.priou ; Continue on primary output hrloi t2,.fhslf ; Wants this for explicit error setz t3, ; Don't limit length of text ERSTR% ; Type the JSYS failure reason text erjmpr .+2 ; Ignore strange error erjmpr .+1 ; Ignore stranger error hrroi t1, crlf ; Tie off the line PSOUT% pop p, t3 ; Restore them pop p, t2 ; all of pop p, t1 ; them jrst neter2 ; Go drop dead and stay dead netinm: asciz /Network input subfork unexpectedly halted, / subttl Open Net -- Opens network connection to somewhere ; Call: ; ; t1/ LH: device type number - .dvpty, .dvdcn, .dvtty ; RH: unit number, if applicable (-1, otherwise) ; ; Return: ; ; +1/ t1, Gubbish ; t2, Ditto ; ; +2/ t1, JFN ready to use ; t2, Associated device designator (which may have been assigned) ; ; N.B., Assumes we are not treating a disk as a terminal openet: entry openet ; World callable extern flow ; Used for ^S/^Q processing saveac ;Save some things move q1, t1 ; Let's get that out of the way skipg t1, netjfn ; Is anything maybe open? ifskp. ; Yes, let's get some information GTSTS% ; Get file status of JFN annje. ; Give up; JFN has to be ill ifxn. t2, gs%nam ; Don't go any further if nothing there andxn. t2, gs%opn ; And it has to be open move t4, t2 ; Save the status word DVCHR% ; Get the device characteristics ifje. r ; Catch and record error txo t4, gs%err ; Pretend the file is in error else. ; Otherwise, worked move q2, t1 ; Save device designator dmove q3, t2 ; Save characteristics and assignment endif. ; End DVCHR error handling endif. ; End case file status checking else. ; Otherwise, whack everything setzb t4, q2 ; No status or device designator setzb q3, q4 ; No device characteristics or assignment endif. remark ; See if we need to ditch the JFN ifxn. t4, gs%nam ; Is there a JFN already? andxn. t4, gs%err ; Any kind of error, phoney or otherwise? call clsjfn ; Yes, stomp it endif. ; End case JFN status check hlrz t1, q1 ; Finally have a look at the device type number ldb t2,[pointr q2,dv%typ];Load JFN's device type number caie t1, .dvpty ; Wants a pseudo-terminal? ifskp. ; Yes, let's see if we are reconnecting came t1, t2 ; Already has one? ifskp. ; Fine, give him the same one hrrz t1, netjfn ; Reload the JFN retskp ; Return success endif. ; Otherwise, wants to go somewhere else txne t4, gs%opn ; Anything already open? call clsjfn ; Yes, stomp it callret opnpty ; Yes, go assign and open one endif. ; End case pseudo-terminal connection caie t1, .dvtty ; Wants a physical terminal? ifskp. ; Yes, let's see if we are reconnecting came t1, t2 ; Already has one? ifskp. ; Yes, maybe reusing the current one hrrz t1, q1 ; Pick up requested unit number ldb t2,[pointr q2,dv%unt] ;Load JFN's device type number came t1, t2 ; Are they the same? anskp. ; No, release the old one and get out of here hlre t1, q4 ; Pick up assigned job came t1, myjob ; Is it me? anskp. ; Strange, don't risk reusing it hrrz t1, netjfn ; Reload the JFN retskp ; Return success endif. txne t4, gs%opn ; Anything already open? call clsjfn ; Yes, stomp it callret opntty ; Go assign terminal and open it endif. ; End case physical terminal caie t1, .dvdcn ; Wants a DECnet NRT?? ifskp. ; Yes, maybe going to the same place came t1, t2 ; Already there someplace? ifskp. ; Fine, give him the same one ifmn. ndvfxp ; Has extended verify? call chknrt ; OK, so check the node name ifskp. ; Worked, let's compare the numbers came t1, oldnum ; Going to same node? anskp. ; No, so close up shop and go elsewhere hrrz t1, netjfn ; The same; reload the JFN retskp ; Return success endif. ; Done remark ; Otherwise falls out and gets new connection else. ; Otherwise, have to compare characters dmove t1, [ -1,,oldnam ; Old node name -1,,nodnam ] ; Current node name STCMP% ; Compare them ifje. r ; Failed?? move t3, t1 ; Save error code seto t1, ; For sure not equal endif. ife. t1 ; Equal? hrrz t1, netjfn ; The same; reload the JFN retskp ; Return success endif. endif. ; End same destination checks endif. txne t4, gs%opn ; Anything already open? call clsjfn ; Yes, stomp it callret decnct ; Go connect somewhere endif. ; End case DECnet MCB terminal ermsg% (,r) subttl Open a psuedo terminal connection opnpty: remark ;These are already saved call asipty ; First, assign a PTY ret ; Unless we couldn't ... setom local ; We're the local Kermit dmove q1, t1 ; Load terminal line and PTY designator movem t1,ttynum ; Store associated line number movem t2,ptydev ; Store assigned PTY designator movei t3, TOPS20 ; On a pseudo-terminal (I.E., a loopback) move t4, hsttyp(t3) ; Load OWGP to OS type string dmovem t3, nrtros ; The 'remote' OS is always Tops-20... remark asgflg ; asipty sets the assigned flag remark asgdev ; Ditto the assigned device remark ptyflg ; Ditto pty and bin flags setzm flow ; Don't do control flow (although works) setzm netjfn ; No network JFN, yet dmove t1, [ gj%sht!gj%flg ; Want flags -1,,ptynam ] ; asipty built this for us GTJFN% ; Try to open it ifje. r ; Catch the error move t4, t1 ; Record for debugger %ermsg (,) ; Bizarre, we just got the device move t1, q2 ; Load assigned designator call deadev ; Go deasign the device ret ; Return failure else. ; Otherwise worked hrrzm t1, netjfn ; Save as network JFN hllzm t1, netflg ; Ditto the flags (just in case) move q5, t1 ; Save a copy for recovery endif. ; End case JSYS failure tlz t1,-1 ; Whack flags them so OPENF% doesn't choke movx t2, fld(8,of%bsz)!of%wr!of%rd ; 8-bit bytes, read & write access. OPENF% ; Open the device. ifje. r ; Catch the error move t4, t1 ; Record for debugger %ermsg (,) ; Bizarre, we just got the device hrrz t1, q5 ; Load the JFN, sans flags callret clsjfn ; Call JFN and device clean up and scrub endif. ; End case JSYS results handling ;[223] Find out about the associated terminal move t1, q1 ;[223] Load the terminal line txo t1, .ttdes ;[223] Turn it into a terminal designator call gndpar ;[223] Go find out about the parity setz t2, ;[223] Failed somehow, so no parity ifxn. t2, gd%par ;[223] Will it tolerate parity?? setom opnpar ;[223] It will else. ;[223] ...Otherwise... setzm opnpar ;[223] It won't endif. ;[223] hrrz t1, q5 ;[223] Load the PTY JFN, sans flags movei t2, .chcnc ;[186] PTY *must* have a ^C to get going call BOUTR% ;[186] Push it out, either way %ermsg (,r) ;[186] move t2, q2 ; Load PTY device designator movei t3, .dvpty ; Opened a pseudo-terminal movem t3, opndev ; Store opened device type setom vtermf ; Set the virtual terminal flag retskp ; Won!! subttl Used to deassign anything during opening failure deadev: DVCHR% ; Pull the device characteristics erjmpr clscln ; Ignore error and scrub storage dmove q2, t1 ; Position designator and characteristics move q4, t3 ; Where clsarg wants them callret clsasg ; Go hand off to release device and scrub subttl Open a physical line ; Assumes q1 has an (octal) line number opntty: saveac ;[223] For a copy of the JFN hrrz t1, q1 ; Load the unit number (the terminal line) came t1, mytty ; Is it us? ifskp. ; Yes, LOGIN% or CRJOB% assigned it setzm asgflg ; Not assigned setzm asgdev ; So get rid of artifacts setzm ttydev ; all of them hrrz t2, q1 ; Begin build for DEVST% hrli t2, .dvdes!.dvtty ;Turn into a device designator move q2, t2 ; Save that, just in case jrst gttyjf ; Now go get a TTY JFN endif. hrli t1, .dvdes!.dvtty ; Turn into a device designator move q2, t1 ; Save that for later tlz t1, -1 ; Shut them back off for NTINF% caml t1, pty1st ; Into virtual range? ermsg% (, clscln) move t1, q2 ; Load final requested device ASND% ; Assign it, so no possible login %jserr (,clscln) aos asgflg ; Flag we have a terminal assigned movem t1, asgdev ; Store global movem t1, ttydev ; Store as terminal device designator move t2, t1 ; Position for DEVST% gttyjf: aos ttyflg ; At this point, commiting to the open hrroi t1,ttynam ; Point to area to write TTY specification hrrzm t2, ttynum ; Store as foreign terminal DEVST% ; Turn device into string %jserr (,deadev) movei t2,":" ; Load terminating device punctuation idpb t2,t1 ; Complete device syntax setz t2, ; Load .chnul idpb t2,t1 ; Tie off the string setzm netjfn ; No network JFN, yet dmove t1, [ gj%sht!gj%flg ; Want flags -1,,ttynam ] ; asipty built this for us GTJFN% ; Try to open it ifje. r ; Catch the error move t4, t1 ; Record for debugger %ermsg (,) ; Bizarre, we just got the device move t1, q2 ; Load assigned designator call deadev ; Go deasign the device ret ; Return failure else. ; Otherwise, worked hrrzm t1, netjfn ; Save as network JFN hllzm t1, netflg ; Ditto the flags (just in case) move q5, t1 ;[223] Save a copy for recovery endif. ; End case JSYS failure remark 8-bit bytes, image mode, read & write access. movx t2, fld(8,of%bsz)!fld(.gsimg,of%mod)!of%wr!of%rd tlz t1,-1 ; Whack flags them so OPENF% doesn't choke OPENF% ; Open the device. ifje. r ; Catch the error move t4, t1 ; Record for debugger %ermsg (,) ; Bizarre, we just got the device move t1, t3 ; Load the JFN callret clsjfn ; Call JFN and device clean up and scrub endif. ; End case JSYS failure move t1, q5 ;[223] Load terminal JFN and flags call gndpar ;[223] Go find out about the parity setz t2, ;[223] Failed somehow, so no parity ifxn. t2, gd%par ;[223] Will it tolerate parity?? setom opnpar ;[223] It will else. ;[223] ...Otherwise... setzm opnpar ;[223] It won't endif. ;[223] End case parity discovery hrrz t1, q5 ;[223] Load just the JFN hrrz t4, q1 ; Load the unit number again came t4, mytty ; Is it us? ifskp. ; Yes, then don't do a few things setzm local ; Mark us as remote else. ; Otherwise, we are going places setom local ; We're the local Kermit movei t2, .chcrt ; Send a CR down the line to get things going. call BOUTR% ; Get it going %ermsg (,r) ;[186] endif. remark t1, netjfn ;[223] Still has JFN move t2, q2 ; Load TTY device designator movei t3, .dvtty ; Opened a terminal movem t3, opndev ; Store opened device type setzm vtermf ; Clear the virtual terminal flag retskp ; Won!! subttl Check the line whose JFN is in t1. ; Set flags MDMLIN if line is remote, CARIER if line has carrier up. ; SPEED is set to a nonnegative number if known, -1 otherwise. ; ; Returns +1 always, with t1 unchanged, t2-t4 modified. chklin: entry chklin ;[186] Identify location for LINK extern mdmlin,speed,carier ;[186] And of everyone's necessaries saveac ; Save the JFN!!! setzm mdmlin ;[186] Assume line not modem-controlled. setzm carier ;[186] And no carrier setom speed ;[186] Assume speed is unknown hrrzs t4, t1 ;[186] Save the JFN, sans flags cain t1, .nulio ;[186] Wants to talk with nobody? ret ;[186] That's never online call chkljf ;[186] Check basic JFN health ret ;[186] It's sick, somehow move t1, t4 ;[186] restore jfn's rightful place dvchr% ;[186] get the device characteristics ifje. r ;[186] failed?? move t4, t1 ;[186] retrieve and return error code %ermsg(,r) endif. ;[186] get out of here, nothing further to do exch t1, t4 ;[186] Get the JFN back, save device ldb t3,[pointr t2,dv%typ] ;[186] Pick up a device type cain t3, .dvdcn ;[186] Is this an NRT? jrst chkdcn ;[186] Then can't "Read Speed" cain t3, .dvpty ;[186] pseudo-terminal? jrst chkpty ;[186] Can't check terminal through the PTY cain t3, .dvtty ;[186] A terminal?? jrst chktty ;[186] Yes, go handle a physical line remark t3, .dvpip ;[186] A pipe? (a place holder) remark chkpip ;[186] Yes, go handle that ;[186] Otherwise, failure ermsg% (,r) subttl Case of physical line (on a DH or DL) or controlling line chktty: extern setspd, monv ;[186] Physical line additional necessaries exch t4, t1 ;[208] Save the JFN, restore device remark t1, JFN ;[186] Still has terminal JFN call ntidev ;[208] Find out about it ifskp. ;[208] Worked saveac ;[208] Save for getnti results dmove q1, t1 ;[208] So save the results else. ;[208] Otherwise gronked. Sad... %ermsg (,r) endif. ;[208] block. ;[208] Enter block context for better control flow caie q1, nw%nnt ;[208] Not a network terminal? ret ;[208] It is a network tty, so this makes no sense caie q2, nw%fe ;[208] DL or DH? (front end terminal) ret ;[208] No, so these won't make sense retskp ;[208] Exit block, +2; physical line endbk. ;[208] End block. lexical context ifskp. ;[208] Real hardware!! move t1, t4 ;[208] Restore the original JFN else. ;[208] Otherwise, a 'soft' terminal remark carier ;[208] Go with chkljf's GTSTS% result ret ;[208] and done endif. movei t2, .morsp ; "Read Speed" MTOPR ; Flag bits are returned in LH(T2) ifje. r ;[186] Unless it FAILS move t4, t1 ;[186] Save the error, could be useful %ermsg(,r) endif. ;[186] Don't try to process junk--leave hrres t3 ; No split speed. ifxe. t2, mo%rmt ;[194] Is carrier valid? movem t3, speed ; No, it's local, so speed is valid. setom carier ; Say local always has carrier ret ; Don't have to worry about carrier. else. ;[194] Otherwise line is a real dial up setom mdmlin ; Yes, flag for SHOW LINE, etc. endif. ;[194] ifme. setspd ;[161] Was speed NOT explicitly SET for this line? ifmn. monv ;[194] TOPS-20 V6 or later? movem t3, speed ; Yes, so we can believe the speed. else. ;[194] Otherwise, some kind of geeser (or KS) came t3, speed ; Pre-V6. Does this agree with what was set? seto t3, ; No, so we don't really know the speed. movem t3, speed ; Save the speed or else -1 for don't know. endif. ;[194] endif. ;[194] setzb t2, carier ; See if we have carrier. RFMOD ; Get mode word. %jserr(,r) ;[186] txne t2, tt%car ; Carrier? setom carier ; Yes. ret subttl DECnet Network Remote Terminal Checking chkdcn: remark t1, ; Has NRT JFN movx t2,.morls ; Function to read link status MTOPR% ; Do the status read erjmpr decerr ; Handle error, getting it in t1 ifxn. t3,mo%con ; Connected? setom carier ; Yes, everything is still fine else. ; Otherwise, the party is OVER setzm carier ; So drop 'carrier' endif. ; End case connection check txne t3,mo%int ; Any interrupt message goofyness? call intmsg ; Yes, handle this oddity ret ; Finally get out of here subttl Pseudo-terminal status, a bit different chkpty: remark ; Case of PTY: device repeat 0,< ; Apparently, this isn't true ifxe. q1, gs%eof ; On a PTY:, EOF is an error condition setzm carier ; So 'drop' carrier ret ; and get out of here else. ; Otherwise, might still be good setom carier ; So assume OK, for the moment endif. ; End case GTSTS% analysis for PTY > skipn t1, ttygtb ; Load GETAB% table length and number ret ; Unless there is none... hrl t1, ptytty ; Load PTY's associated terminal line tlz t1, .ttdes ; Just in case (shouldn't be on) GETAB% ; Get associated job and 'hunger' erjmpr r ; Get and ignore error, returning jumpge t1, r ; Still connected? Just return setzm carier ; No job there anymore, so 'drop' carrier ret ; And get out of here subttl Check Line JFN ; Call t1/ JFN ; ; +1 / JFN is unhealthy in some way ; +2 / JFN works and is not in error, q1 has GTSTS result ; ; Sets 'carier' accordingly chkljf: saveac ; Basic JFN health GTSTS% ; Get the status of whatever it is ifje. r ; Failed?? move t4, t1 ; Save code for debuggers setzb t2, q1 ; Assume we have no carrier. %ermsg(,r) else. ; Otherwise, worked move q1, t2 ; So save the JFN's status endif. txc t2, gs%nam!gs%opn ; Complement the required bits txce t2, gs%nam!gs%opn ; Is it any good at and is it open? ret ; No, then there is certainly no carrier txne t2,gs%err ; Any kind of error? ret ; Yes, we're done setom carier ; Groovy, let's say we have 'carrier' retskp ; Finally get out of here subttl Get Network Terminal Information ; NTINF%, which was introduced in 6.0 series Tops-20 and is now known ; to work in 7.0 series PANDA monitor and XKL. I believe there are ; also standard patches to the DEC monitor to make it work. ; ; Wants a terminal designator in t1 ; ; Question: does this break for a PIP: JFN? Should it? ; ; +1 t1/ Last error code ; +2 t1/ Line Network Type (zero if not network) ; t2/ Line Terminal type or protocol getnti: entry getnti ;[194] Inform LINK of our location txo t1, .ttdes ;[186] Convert line to a device designator ntidev: remark ;[208] Alternate entry if called with a device id movem t1 ,ntiblk+.NWLIN ;[182] Store requested terminal dmove t1,[exp ntblen,.NWRRH] ;[182] Requesting remote host information dmovem t1,ntiblk+.NWABC ;[182] Store length and request type hrroi t1, ntihst ;[186] Point to host area movem t1, ntiblk+.NWNNP ;[182] return remote host information setzb t1, t2 ;[182] Everything else is zero movem t1, tvtflg ;[182] Assume not on a TVT dmovem t1, ntihst ;[186] Stomp 20 character DECnet node dmovem t1, ntihst+2 ;[186] name (which is impossible) dmovem t1,ntiblk+.NWTTF ;[186] Stomp terminal type and flags setzm ntiblk+.nwnu1 ;[186] and the node number movei t1, ntiblk ;[182] Load the address of the argument block NTINF% ;[182] finally try to see out what's going on %jserr (,r) ;[186] Phooey, return +1 ;[182] Load network type and line type ldb t1,[POINTR(,nttype)] ldb t2,[POINTR(,ntline)] retskp ;[186] Won! subttl chktvt - check to see if we are using a TVT line ; We use NTINF% (see above) when the user sets TVT-Binary mode to ; automatic which is an additional keyword (used to be just on or ; off). Automatic is the default, but we still allow overide. ; ; If the NTINF% fails, then we try recover by using STAT% to ; indentify whether the line is in the range of TVT's. This should ; work on any ARPAnet monitor with TCP support; MRC noted that the ; monitor "requires STAT% to be there" ; ; PANDA monitor verified to have 400000,,RSKP in NVTDOD (see [129]) ; ; Call: nothing passed ; ; Checks to see whether we are in automatic mode and if so, we ; execute the determination code in some form. Otherwise, we ; are in override mode and we skip any checks. ; ; Return: +1, always (although may complain about Jsyi errors) ; ; tvtflg may be side-effected by our (possible lack of) discovery chktvt: entry chktvt ;[194] Inform LINK of our location extern tvtchk, tvtflg ;[194] And of our necessaries skipn tvtchk ;[182] Are we supposed to figure out if TVT? ret ;[182] No, so skip all this cruft setzm tvtflg ;[194] Stompt TVT flag because not known, yet call getnti ;[186] Get network terminal information jrst bbntvt ;[186] Try it the old fashioned way cain t1, NW%TCP ;[182] Is the network type NOT TCP? caie t2, NW%TV ;[182] or is this NOT a TVT? ret ;[182] Leave line set as not a TVT aos tvtflg ;[182] Okay, set TVT-BInary to ON ret ;[182] subttl Check for TVT line using BBN interface ; The following code is not used because a BBN TCP jsys is called. ; It is fall-back because NTINF% is preferred. However, it should ; always work, no matter the monitor version. ; ; [129] Largely adapted from MODEM.MAC bbntvt: extern ttynum ;[194] Inform LINK of our necessary movx t1, tcp%nt ;[129] Want aobjn ptr for tvts STAT% ;[129] Get it %jserr (,r) ;[182] Just give up hrrz t3, ttynum ;[129] TTY line we're useing hrrz t1, t2 ;[129] Get first TVT camge t3, t1 ;[129] Are we less than the firsT? ret ;[182] Yes hlres t2 ;[129] Calculate last TVT sub t1, t2 ;[129] ... subi t1, 1 ;[129] ... camg t3, t1 ;[129] Are we .le. last TVT? aos tvtflg ;[182] Yes, flag for later ret ;[182] subttl Line routines ;[190] all moved from K20MIT to reduce its size ; INILIN -- Initialize the communication line for file transfer. ; inilin: entry inilin ;[220] Used in k20srv, too skipe inited ;[177] Already init'd? Don't do it again. ret ;[177] ; Set all the terminal mode bits for transparent i/o. inil2: ifme. vtermf ;[186] Physical line? call dobits ; Go do the bits. ret ; Pass along any failures. call doarpa ; Set up any Arpanet stuff. endif. call clrbuf ;[194] Clear any NAK's nop ;[186] Ignore any errors setom inited ;[177] Flag we've done this. ret ; Set communication line bits for transparent i/o. ; Returns +1 on failure, +2 on success. dobits: entry dobits ;Used by k20ioc saveac ;[186] Used for device designator skipe q1, netjfn ;[186] Load the network JFN ifskp. ;[186] Unless we don't have one... skipe local ;[186] Are we remote? ermsg% (,r) ;[186] Just punt skipn q1, ttyjfn ;[186] Yes, so just use the terminal JFN ermsg% (,r) ;[186] endif. ;[186] Hopefully have SOMETHING ... move t1, q1 ;[186] ; JFN for connection to other system. movx t2, .mornt ; Read system message status. MTOPR %jserr (,dobit2) movem t3, sysmsg ; Save here for later restoral. movx t2, .mosnt ; Now refuse system messages. movx t3, .mosmn MTOPR %jserr (,dobit2) dobit2: movx t1, ;[147] Clear/Refuse links, hrr t1, ttynum ;[147] on the line used for file transfer. txo t1, .ttdes ;[147] (TLINK wants a device designator.) seto t2, TLINK erjmp dobit3 ;[147] Ignore any failure. dobit3: move t1, q1 ;[186] ; JFN for the file transfer line. movei t2, .morxo ; Get terminal pause end-of-page status. MTOPR% %jserr (,r) movem t3, oldpau ; Save the old pause mode. movei t2, .moxof ; Now set to... movei t3, .mooff ; no pause on end. MTOPR% %jserr (,r) movei t2, olddim ;[185] Point to line block call savlnw ;[185] Save this JFN's length and width RFMOD% ; Get current mode for this line. %jserr (,r) setom carier setzm mdmlin ;[130] Assume line not modem-controlled. txne t2, tt%car ;[130] Is it? setom mdmlin ;[130] Yes, flag. movem t2, oldmod ; Save the present mode. ;[97] Turn off undesired bits (program echoing, links, translation). ;[97] Turn on desired bits (full duplex; TTY has form feed, tab, lowercase). ;[97] Note that any other settings are left intact, in particular TT%ECM, which ;[97] can cause a TAC to do its own echoing if turned off. dobit4: ; No echo, no links, no advice, no data mode, full duplex. txz t2, ;[129] Add TT$DUM ; No wakeup stuff, infinite width & length. txz t2, ;[127] ; No formfeed/tab/case interpretation, use XON/XOFF. txo t2, ;[129] REMOVE TT%DUM!!! skipn handsh ;[155] Doing handshake? skipn flow ;[155] Doing flow control? txz t2, tt%pgm ; Handshake, or no flow - don't do XON/XOFF. SFMOD% ; Set the bits. %jserr (,) STPAR% %jserr (,) retskp ;[181] PANDA Network Binary Mode routines panda < ;[181] Only if doing Panda ;[181] Returns true if we have network binary mode MTOPR% ;[181] Preserves ACs, always returns +1, havnbm: is side-effected chknbm: entry chknbm ;[190] saveac ;[181] Save the registers that MTOPR% trashes dmove t1,[ exp .CTTRM,.MORLT ] ;[181] Read local status MTOPR% ;[181] Can the monitor process this request? ifje. r ;[194] No, assume this isn't in the monitor setzm havnbm ;[181] so don't try to use it setzm setlts ;[181] and never try to restore status else. ;[194] setom havnbm ;[181] Otherwise, we have winning endif. ;[194] ret ;[181] Panda Network Binary Mode! ;[181] Sets network binary mode ;[181] Assumes it can stomp acumulators t1 through t3 ;[181] Returns to doarpa's caller on success ;[181] on failure, assumes we don't have network binary mode, ;[181] clears the flag and tries it the old way setnbm: skipe setlts ;[181] Did we already sucessfully set this? ret ;[181] Yes, why bother doing it twice? skipe t1, netjfn ;[186] Load the network JFN ifskp. ;[186] Unless we don't have one... skipe local ;[186] Are we remote? ermsg% (,r) ;[186] Just punt skipn t1, ttyjfn ;[186] Yes, so just use the terminal JFN ermsg% (,r) ;[186] endif. ;[186] Hopefully have SOMETHING ... movx t2,.MORLT ;[181] Read local status MTOPR% erjmp nbmerr movem t3,OLDLTS ;[181] save old terminal status txo t3,MO%NBI!MO%NBO ;[181] network binary mode (input AND output) movx t2,.MOSLT ;[181] want to set it MTOPR% erjmp nbmerr movx t2,.MORLT ;[181] now see what actually happened MTOPR% erjmp nbmerr xorx t3,MO%NBI!MO%NBO ;[181] flip binary mode status txne t3,MO%NBI!MO%NBO ;[181] they should have been BOTH set ... jrst nbmerr aos setlts ;[181] flag that we set terminal line status ret nbmerr: setzm havnbm ;[181] We don't have network binary mode callret doarpa ;[181] Maybe the olde fashioned way works? ;[181] un-Sets network binary mode ;[181] Assumes it can stomp acumulators t1 through t3 ;[181] Returns to unarpa's caller on success ;[181] on failure, assumes we don't have network binary mode, ;[181] clears the flag and tries it the old way unsnbm: setz t1, ;[181] whatever the current state is, exch t1,setlts ;[181] say that it is no longer set jumpe t1,r ;[181] However: did we ever set nbm?? skipe t1, netjfn ;[186] Load the network JFN ifskp. ;[186] Unless we don't have one... skipe local ;[186] Are we remote? ermsg% (,r) ;[186] Just punt skipn t1, ttyjfn ;[186] Yes, so just use the terminal JFN ermsg% (,r) ;[186] endif. ;[186] Hopefully have SOMETHING ... movx t2,.MOSLT ;[181] Read local status move t3,OLDLTS ;[181] get former status MTOPR% ;[181] try to restore it ifje. r ;[194] Failed, don't use this any longer setzm havnbm ;[181] How could this have failed? callret unarpa ;[196] Get out of here and turn some more endif. ;[196] things off ret > ;[181] End Panda conditional ;[129] Do any required ARPAnet stuff. ; ; Important Note: The ability to send binary mode telnet negotiations ; depends on the monitor NOT doubling IACs on TVT lines. Some versions of ; TOPS-20 (particularly BBN's TCP monitor) will do this. ; ;[181] Use SOUTR% instead of SOUT% to ensure that ;[181] we flush the data to the TAC ; ; Returns +1 always, but prints warning on failure. ; doarpa: entry doarpa ;[190] skipn tvtflg ; Are we on tvt? ret panda < skipe havnbm ;[181] Does the monitor support network callret setnbm > ;[181] binary mode? saveac ;[186] Used for device designator skipe q1, netjfn ;[186] Load the network JFN ifskp. ;[186] Unless we don't have one... skipe local ;[186] Are we remote? ermsg% (,r) ;[186] Just punt skipn q1, ttyjfn ;[186] Yes, so just use the terminal JFN ermsg% (,r) ;[186] endif. ;[186] Hopefully have SOMETHING ... move t1, q1 ;[186] ; Yes, talk binary. dmove t2,[exp ,-3] SOUTR% ;[181] This code adapted from MODEM.MAC %jserr(,doarpx) movei t1,^d4000 ; Sleep four seconds. DISMS% move t1, q1 ;[186] Tell TVT "do binary". dmove t2,[exp ,-3] SOUTR% %jserr(,doarpx) movei t1,^d4000 DISMS ret doarpx: txmsg < %KERMIT-20: Warning -- Can't negotiate binary mode with TAC > ret ; RESLIN -- Reset/Restore the communications line. ; ; Restore old terminal modes, links, length & width, etc. ; Turn off control-C trap. ; ; CALL RESLIN does nothing if server. ; CALL RRSLIN restores the line even if server. extern filjfn ;[190] reslin: entry reslin ;[190] skipe srvflg ; Server? ret ; Yes, forget it. rrslin: entry rrslin ;[220] Used by k20srv call ccoff2 ; REALLY reset the line. rrsl2: entry rrsl2 ;[220] Used by k20srv skipg t1, filjfn ; Were we doing something with a file? ifskp. ;[194] Maybe so tlz t1, -1 ;[193] Just carefully toss any flags cain t1, .nulio ;[193] Not needed for NUL: anskp. ;[193] So bum the CLOSF CLOSF erjmpr .+1 ;[193] Catch and ignore error endif. ;[194] setzm filjfn ;[194] Either way, no file ifme. vtermf ;[186] Physical line? call unarpa ; Undo Arpanet TAC binary mode. call unbits ; Restore terminal bits. call ttxon ; Clear up any XOFF condition. endif. ;[186] call clrbuf ;[194] Clear terminal buffers nop ;[186] Ignore any failure setzm inited ;[177] Flag we're back to normal. ret ; Undo the effect of DOBITS -- restore all the communication line's ; old bits & modes. ; unbits: entry unbits ;Used by K20IOC saveac ;[186] Used for device designator skipe q1, netjfn ;[186] Load the network JFN ifskp. ;[186] Unless we don't have one... skipe local ;[186] Are we remote? ermsg% (,r) ;[186] Just punt skipn q1, ttyjfn ;[186] Yes, so just use the terminal JFN ermsg% (,r) ;[186] endif. ;[186] Hopefully have SOMETHING ... move t1, q1 ;[186] ; Get the line. movei t2, .moxof ; Set the terminal pause on end mode... move t3, oldpau ; to what it was before. MTOPR% %jserr (,) move t1, q1 ;[186] ; Communication line JFN. move t2, oldmod ; Get the previous mode. SFMOD% %jserr (,) STPAR% %jserr (,) movei t2, olddim ;[185] Point to this JFN's dimensions call rstlnw ;[185] Restore length and width movx t2, .mosnt ; Restore system msg refuse/accept. move t3, sysmsg MTOPR %jserr (,) ; Restore links and advice if necessary. setz t1, ; Restore links & advice. move t2, oldmod ; From old tty mode word. txne t2, tt%alk ; Was receiving links before? txo t1, ; Yes, so receive links. txne t2, tt%aad ; Was receiving advice before? txo t1, ; Yes, so receive links. jumpe t1, r ; Skip to next part if no bits to set. hrr t1, ttynum ; Must set bits, form tty designator txo t1, .ttdes ; ... setz t2, ; Don't leave garbage in here... TLINK ; Restore the settings. erjmp .+1 ; Ignore any errors. ret ; Turn off Arpanet TAC binary mode. unarpa: skipn tvtflg ; Are we on a tvt? ret ; No, skip this. panda < skipe havnbm ;[181] Does the monitor support network callret unsnbm > ;[181] binary mode? saveac ;[186] Used for device designator skipe q1, netjfn ;[186] Load the network JFN ifskp. ;[186] Unless we don't have one... skipe local ;[186] Are we remote? ermsg% (,r) ;[186] Just punt skipn q1, ttyjfn ;[186] Yes, so just use the terminal JFN ermsg% (,r) ;[186] endif. ;[186] Hopefully have SOMETHING ... move t1, q1 ;[186] ;[181] Get the line. dmove t2, [exp ,-3] SOUT% ; Yes, turn off binary mode. %jserr(,unarpx) movei t1, ^d4000 ; Wait 4 secs. DISMS% move t1, q1 ;[186] ; Send the command. dmove t2, [exp ,-3] SOUT% %jserr(,unarpx) movei t1, ^d4000 ; Wait another 4 secs. DISMS% ret ; Done. unarpx: txmsg < %KERMIT-20: Warning -- Can't clear binary mode with TAC > ;[129] Error message for any of the above. ret ;[129] And return subttl Get Network Device Status ;[223] Begin Code Insertion ; ; N.B., Be aware that the result of GDSTS% has to be CAREFULLY checked ; because it may not throw an error, even when followed by an ; ERJMP! In certain error scenarios, the process's last error may ; not be changed, so messing around with a before-SETER% / after- ; GETER% won't catch the problem, either. We carefully check for ; such a situation and, if detected, set the process's last error ; appropriately. Sigh... ; ; On klh10, the only line currently known to tolerate parity is the CTY. ; On a PANDA monitor, PTY's will do parity ; ; Call: ; ; t1/ JFN on device (assumed opened in 8 bit mode) ; ; *OR* ; ; t1/ .ttdes+line number ; ; Returns: ; ; +1/ Some kind of bad ; +2/ Worked ; t1/ JFN, always ; t2/ Device-dependent status bits [If device supported GDSTS%] ; t3/ Device-dependent information [If device supported GDSTS%] ; t4/ Possible GDSTS% error gndpar: entry gndpar ; Also called from k20sub saveac ; Needs some extra registers move q1, t1 ; Save JFN and any flags (which we don't use) setz q5, ; Second JFN on line ifxn. q1, .ttdes ; Terminal device? call gndfil ; Yep, go get the JFN move q5, t1 ; Store it for later jrst devpar ; Go find out if it 'tolerates' parity endif. ; End case terminal device tlz t1, -1 ; Stomp the flags GTSTS% ; Get file status of JFN erjmpr r ; Failed, no way to know the parity txne t2, gs%nam ; Sanity check: does this JFN exist? txnn t2, gs%opn ; And is it open? ret ; No to one is a calling error ; Pick up and save the mode ldb t4,[pointr t2,gs%mod] move t3, t2 ; Save the entire status word, too RFBSZ% ; Get the opened byte size erjmpr r ; Failed, better not go any further block. ; Build a stack frame for better control flow caie t2, ^d7 ; Open in seven bit mode? ret ; Nope, have to have a new file caie t4, .gsnrm ; Opened in normal mode? ret ; No, so won't do parity txne t3, gs%err ; Nothing wrong, right? ret ; Better get our own copy retskp ; Otherwise, OK to check this JFN endbk. ; Either way, come out of the block ifskp. ; Skip means OK to check this JFN move q5, q1 ; So reuse it else. ; Otherwise, we need a copy call gndfil ; Go get a copy move q5, t1 ; Store it for later endif. ; End of reuse determination logic remark devpar ; Now check the parity (falls through) remark Now that we have a JFN, see if it will do parity devpar: move q5, t1 ; Save terminal (copy) JFN and flags panda < tlz t1, -1 ; Stomp JFN flags so MTOPR%'s don't choke movx t2, .morlt ; PANDA can extract parity status MTOPR% ; So try to get it ifje. r ; Sigh... seto q4, ; Set a talisman and do nothing else else. ; Otherise, got something! move q4, t3 ; Save current settings, first txo q4, 1b0 ; Be optimistic and assume parity exists and is on txne t3, mo%par ; Any parity? anskp. ; Nothing further to do or undo move q4, t3 ; Try turning it on, saving current settings, first txo t3, mo%par ; Turn on (even) parity txz t3, mo%nbi!mo%nbo ; Shut network binary so that doesn't get in the way movx t2, .moslt ; Function to set PANDA mode bits MTOPR% ; Give it a whirl ifskp. ; Might not be in this monitor seto q4, ; So better leave it alone endif. ; End .moslt analysis endif. ; End .morlt recovery and interpretation >;panda dmove t1, [ .fhslf ; Can't believe result of GDSTS% all the time... lstrx1 ] ; So let's assume it worked SETER% ; and set no errors whatsoever %jserr(,) ; VERY strange... hrrz t1, q5 ; Load the JFN we got setzb t2, t3 ; Let's assume the JSYS doesn't work GDSTS% ; Finally try a device status on it ifje. r ; Catch the error (hopefully) move t4, t1 ; Put error code someplace for debugger %ermsg(,) ;[223] Complain, but carry on else. ; Otherwise, worked. Maybe... andx t2, gd%par ; Toss everything but accepts parity move t4, t2 ; Get possible status out of the way setz t2, ; Let's assume GETER% fails (impossible) movei t1, .fhslf ; This process GETER% ; Get the last error %jserr(,) ; VERY strange... tlz t2, -1 ; Shut off idiotic fork handle... exch t2, t4 ; Put the last error in a common place endif. ; End case JSYS handling caie t4, lstrx1 ; Any error? ifskp. ; No. Supposedly; let's double check caie t2, desx9 ; No entry in device dispatch table for GDSTS%? anskp. ; No, assume it's fine... move t4, t2 ; Yep, device doesn't support it movei t1, .fhslf ; This process SETER% ; Force it to be our last error %jserr(,) ; VERY strange... endif. ; End case silent failure cain t4, lstrx1 ; So... No error, right? ifskp. ; Something happened... ;;;; remark We handle this properly; uncomment for debugging or prototyping ;;;; %ermsg(,) setzb t2, t3 ; Cons up no status whatsoever endif. panda < skipge t3, q4 ; Did we have to restore anything? ifskp. ; Ok, so a bit of cleaning up to do, then move t4, t2 ; Save the precious gd%par bit! hrrz t1, q5 ; Pick up the terminal JFN, no flags movx t2, .moslt ; Function to set PANDA mode bits MTOPR% ; Try to set it back to the way it was erjmpr .+1 ; Failed?? We just changed it! move t2, t4 ; Restore the precious (scrubbed) gd%par bit else. ; Otherwise, looked negative camn t3, [-1] ; Is it our talisman? ifskp. ; No, so carry forward the parity setting andx t3, mo%par ; Just keep the parity on bit or t2, t3 ; And carry that on with a possible gd%par endif. ; End case parity setting endif. ; End .morlt recovery and interpretation >;;panda remark t2, gd%par ; So will the thing do parity? camn q1, q5 ; Reused the JFN? retskp ; We did, so nothing further to do move q3, t2 ; Save the precious device-dependent status bits dmove t1, [ devclt ; On time-out, hit device close timeout ^d2500 ] ; Give it two and half seconds to make up its mind call timeon ; Start the timer going hrrz t1, q5 ; Load the JFN, no flags CLOSF% ; Close it %jserr(,) ; But carry on anyway call timdel ; Toss the timer, we won move t2, q3 ; Restore the device-dependent status bits retskp ; Return success, anyway remark ; Here on device parity close timeout devclt: dmove t1, [ devabt ; On time-out, hit device abort timeout ^d2500 ] ; Give it two and half seconds to make up its mind call timeon ; Start the timer going hrrz t1, q5 ; Load the JFN, no flags and set up to txz t1, cz%abt ; abort it, we mean business this time CLOSF% ; Bombs away! erjmpr devabt ; That didn't work, just try to let go of it call timdel ; Toss the timer, it's chucked move t2, q3 ; Restore the device-dependent status bits retskp ; Return some kind of success devabt: dmove t1, [ devabf ; On time-out, hit device abort timeout ^d2500 ] ; Give it two and half seconds to make up its mind call timeon ; Start the timer going hrrz t1, q5 ; Load the JFN, no flags and set up to RLJFN% ; Just try to let go of it erjmpr devabf call timdel ; Toss the timer, it's chucked devabf: remark ; If hit here, just ignore what's going on, oh well.. move t2, q3 ; Restore the device-dependent status bits retskp ; Return some kind of success subttl Get a seven bit handle on a (terminal) device remark Constants definitions js%all==0 ; Has our JFNS% formatting bits .xcref js%all ; Not needed in the cross reference define jsb(b) < ;;Macro to accumulate bits js%all==js%all! ;;OR in to completed word .xcref js%all ;;Keep off the cross reference!!!! >;;jsb define jsf(m,v) < ; Macro to accumulate values ifb , ;;If no value, then always output ifnb , ;;If value, then use that .xcref js%all ;;Either way, keep off the cross reference >;;jsf remark ; Finally cons up the formatting jsf(js%dev) ;;Device jsf(js%dir) ;;Directory jsf(js%nam) ;;Name jsf(js%typ) ;;Type jsf(js%gen) ;;Generation jsb(js%paf) ;;Punctuate all fields chgsec(code,const) ; Not code, constants allfld: js%all ; Output everything in the file name 0 ; No goofy prefix retsec ; Return from CONST psec subttl Code to do the job ; N.B., This surely will NEVER work for a pipe or a file ; ; Call: ; ; t1/ JFN on device (assumed open) ; ; *OR* ; ; t1/ .ttdes+line number ; ; Return: ; ; +1/ Some problem ; t1/ Last JSYS' error ; t3/ Possible OPENF% error code ; t4/ Possible RLJFN% error code ; ; +2/ Worked! ; t1/ New JFN and flags gndfil: saveac anstkv. (q2,mxfilw) ; Stack space for text of JFN movx t1, ; Length of storage to zero move t2, q2 ; First location to zero movei t3, 1(t2) ; Second location to zero setzm (t2) ; Whack the first location erjmpr r ; Must have bumped into a guard page or off section xblt. t1 ; And away we go! erjmpr r ; Must have bumped into a guard page or off section hrro t1, q2 ; Tops-20 ASCIZ pointer to text area hrrz t2, q1 ; Load the JFN, sans flags jumpe t2, r ; Gubbish? txnn t2, .ttdes ; A terminal designator? ifskp. ; Yes, JFNS% will choke on it DEVST% ; So turn designator into a string erjmpr r ; But couldn't dmove t2, [exp ":",0] ; Load appropriate suffix idpb t2, t1 ; Punctuate the device idpb t3, t1 ; Tie off the string (does not allow append) else. ; Otherwise, a JFN which JFNS% can handle dmove t3, allfld ; Load formatting bits, no goofy prefix JFNS% ; Turn the JFN into text erjmpr r ; But couldn't endif. movx t1, gj%old!gj%flg ; Return flags hrro t2, q2 ; Load Tops-20 ASCIZ pointer to constructed text GTJFN% ; Get a duplicate JFN erjmpr r ; Failed?? move q3, t1 ; Save file JFN and flags tlz t1, -1 ; Shut off flags so OPENF% doesn't choke movx t2, fld(7,of%bsz)!fld(.gsnrm,of%mod)!of%wr!of%rd ; Force 7 bit mode!! setzb t3, t4 ; Scrub an error returns OPENF% ; Open the file (I hope) ifje. r ; Failed... move t3, t1 ; Save the error code else. ; Otherwise, worked!! hll t1, q3 ; Return the flags, too retskp ; Return success endif. ; End initial JSYS handling hrrz t1, q3 ; Reload the new JFN RLJFN% ; Toss its miserable remains ifje. r ; Failed?? move t4, t1 ; Return error code as talisman endif. ret ; Fail the call ;[223] End Code Insertion subttl Final code particulars xlist ; Save the trees!! lit ; Dump literals into code psect list ; Safe to look .endps code ; Close out the code area subttl Misc. data storage .psect data ; Writeable area!! cnfigd: block .cfiln ; Space for CNFIG% .CFINF data block 1 ; And slop mynode:: block 1 ; Number of local executor (us) myname:: block 2 ; Local executor name ndvfxp:: block 1 ; Whether monitor has extended node verify syscnt:: block 1 ; Count of characters in system name sysnam:: block syslen ; Name of local system we're running on myprom:: block 3 ; Prompt built off system name sysver: block 1 ; GETAB% table for system name cnfmsg: block <+1> ; Space for configuration message block 1 ; And slop ... remark ;[190] ; Various line bits of interest inited: 0 ;[190] ;[177] inilin/reslin flag. oldmod: 0 ;[190] ; Previous mode of the line. olddim: 0 ;[190] ;[185] Old line dimensions oldpau: 0 ;[190] ; Previous terminal pause on end mode. sysmsg: 0 ;[190] ;[82] Accept/refuse system message status. panda < remark ;[181] Storage for PANDA monitor TVT support havnbm: 0 ;[181] Non-zero if we have network binary mode setlts: 0 ;[181] set if we set terminal status oldlts: 0 ;[181] Old terminal status > ;[181] remark Do not reorder next two! nrtros:: block 1 ; If NRT, remote operating system type rosnpt:: block 1 ; Remote operating system name pointer nrtflg:: block 1 ; Set if a valid Network Remote Terminal binflg:: block 1 ; Set if terminal will do binary (they all do) nrtprt: block 1 ; NRT protocol supported forkls:: block 1 ;[236] ; NRT connection is forkless job: 0 ;[218] ;[7] Number of job that has TTY I want. oasflg: 0 ;[218] ;[7] -1 if we assigned the previous TTY. osgdev: 0 ;[218] ;[186] Old device I had assigned oldjfn: 0 ;[218] ; JFN on previous line. oldnum: 0 ; Previous DECnet node number oldnam: exp 0, 0, 0, 0 ; Previous DECnet node name nrtobj: block <+1> ; Area to build object name for GTJFN% block 2 ; And slop intbuf: block ^d<<16/5>+1> ; Space for interupt message block 3 ; And generous slop... (it is DECnet, after all) frkpdl: block pdlsiz ;[186] Fork's PDL ;[223] If a buffer is large enough for 8 bit, it will be large enough for 7 bit frkbuf: block +1 ;[223] Buffer for fork to read into (if 8 bit) nrtbuf: block +1 ;[223] Buffer for sending loop (if 8 bit) parbuf: block +1 ;[223] Buffer if building parity from terminal input remark pseudo-terminal information ttygtb: block 1 ; Terminal line to job mapping GETAB% pty1st: block 1 ; Terminal line number of first pseudo-terminal ptycnt: block 1 ; Count of pseudo-terminals ptygtb: block 1 ; PTYPAR GETAB% index (which we'll never use) ndvchr:: block 2 ; Device characterstics double word ptyflg:: block 1 ; Set if doing pseudo-terminal I/O ptynam:: block 3 ; ASCII name of pseudo-terminal ptydev:: block 1 ; Assigned PTY device designator ptytty:: block 1 ; Line number associated with pseudo-terminal ttyflg: block 1 ; Flag for physical terminal ttydev:: block 1 ; Assigned TTY device designator ttynam:: block 3 ; ASCII name of associated terminal opndev: -1 ;[186] Device type we are open on opnsts:: block 2 ;[223] GDSTS% on the open JFN opnpar:: 0 ;[223] Whether device supports parity vbict:: 0 ;[186] Virtual Terminal BIN% Count vboct:: 0 ;[186] Virtual Terminal BOUT% Count (simulated) vsict:: 0 ;[186] Virtual Terminal SIN% Count (number done) vsitc:: 0 ;[186] Virtual Terminal total characters SIN%'ed vsimx:: 0 ;[186] Virtual Terminal SIN% Maximum length vsoct:: 0 ;[186] Virtual Terminal SOUTR%'s Issued vsotc:: 0 ;[186] Virtual Terminal SOUTR% Total Characters vsomx:: 0 ;[186] Virtual Terminal SOUTR% Maximum length nbict:: 0 ;[186] Network BIN% count nsici:: 0 ;[186] Network SIN%'s Issued nsitc:: 0 ;[186] Network SIN% total characters nsimx:: 0 ;[186] Network SIN% maximum length vchrcn:: 0 ;[211] Characters flushed from virtual line flushb: block +1 ;[211] Flush buffer in words, eight bit bytes ntiblk::block ntblen ;[210] ;[182] NTINF% block for TVT ntihst: block ^d20 ;[186] Remote DECnet host .endps data ; Close out the data area .xcmsy ;[194] Ditch MACSYM junk end ; Local Modes: ; Mode:MACRO ; Comment Column:32 ; Comment Start:;[236] ; Comment Begin:;[236] ; Auto Fill Mode: 0 ; End: