perm filename OTLSER.MID[S,NET] blob sn#697645 filedate 1983-01-28 generic text, type C, neo UTF8
COMMENT ⊗   VALID 00010 PAGES
C REC  PAGE   DESCRIPTION
C00001 00001
C00003 00002	X INTFOP INTPTO INTCLK DMLIN ECHARR FCS TBXPND FULTWX XON TLKRNG
C00005 00003	ECHOFF ECHON TYSBLK IMPSET LINCHR XONOFF GAGOFF NTYSTS TERMID CORBEG TERSTR PTINTP NTINTP NTOINP DOQUIT ECHOP NODETP NEWLNP LFFLSP TTYLIN TPCSAV IDLTIM PTIBUF PDL COREND
C00008 00004	INTSER INTSR1 CLKSER
C00011 00005	OTLSER CPYHST 1DIGTP NOTTIP
C00014 00006	NOFLAK MAINL MAINL0
C00017 00007	NTISER NTISR2 NTISR1
C00019 00008	PTISER PTISR0
C00020 00009	NCMSER NOPSER CMDONE DMKSER BRKSER NECSER ECHSER
C00022 00010	SNDMSG MSGLUP ERRDIE INTDIE SUICID DIEDIE ...LIT SVRRTS ERRTNS ERRHAN ERRINS HSTTAB HSTSIX
C00024 ENDMK
C⊗;
;X INTFOP INTPTO INTCLK DMLIN ECHARR FCS TBXPND FULTWX XON TLKRNG

TITLE OTLSER
SUBTTL Definitions

; Mark Crispin, SU-AI, January 1979

; Assembly switches

IFNDEF SVRSKT,SVRSKT==1			; default listen socket
IFNDEF LOKTMO,LOKTMO==5			; # of 15-second frobs of lock timeout
IFNDEF PDLLEN,PDLLEN==50		; stack length

; AC definitions.  0→3 are used by NETWRK

X=4 ? A=5 ? B=6 ? P=17

; Macro to send a TELNET command

DEFINE TELCMD CMDLST
 OUTSTR [ASCIZ/⊗!CMDLST!*
/]
 IRPS CMD,,CMDLST
  MOVEI CMD
  PUSHJ P,NETOCH
 TERMIN
 PUSHJ P,NETSND
TERMIN

; SAIL system bit definitions

INTFOP==040000,,			; PTY clear output buffer
INTPTO==001000,,			; PTY interrupt
INTCLK==000200,,			; clock interrupt
INTQUIT==002000				; (right half) interrupt on QUIT cmd
DMLIN== 040000,,			; terminal is a Datamedia
ECHARR==010000,,			; echo controls with uparrow
FCS==   000020,,			; full character set mode
TBXPND==000010,,			; expand tabs to spaces
FULTWX==000004,,			; no echo
XON==   000002,,			; paper tape mode
TLKRNG==000001,,			; TALKing
;ECHOFF ECHON TYSBLK IMPSET LINCHR XONOFF GAGOFF NTYSTS TERMID CORBEG TERSTR PTINTP NTINTP NTOINP DOQUIT ECHOP NODETP NEWLNP LFFLSP TTYLIN TPCSAV IDLTIM PTIBUF PDL COREND

SUBTTL Data area

; TTYSET command words

ECHOFF:	001400,,(FULTWX)		; echo off
ECHON:	002400,,(FULTWX)		; echo on

TYSBLK==.				; initial commands to do
IMPSET:	034400,,			; IMP TTY
LINCHR:	001400,,(ECHARR\FCS\TBXPND)	; default line characteristics
XONOFF:	002400,,(XON\FULTWX)		; generate LF after CR
GAGOFF:	024400,,			; gag off
NTYSTS==.-TYSBLK

; Terminal location string

TERMID:	'TERMID

CORBEG==.				; start of initialized core storage

TERSTR:	BLOCK 10.			; console location string

; Interrupt flags

PTINTP:	BLOCK 1				; -1 → PTI interrupt
NTINTP:	BLOCK 1				; -1 → NTI interrupt
NTOINP:	BLOCK 1				; -1 → INS interrupt
DOQUIT:	BLOCK 1				; -1 → QUIT interrupt

; Protocol flags

ECHOP:	BLOCK 1				; -1 → remote echoing

; Other flags

NODETP:	BLOCK 1				; -1 → don't detach this guy
NEWLNP:	BLOCK 1				; -1 → starting newline
LFFLSP:	BLOCK 1				; -1 → PTISER's LF flush kludge

; Other storage

TTYLIN:	BLOCK 1				; line number of PTY
TPCSAV:	BLOCK 1				; save of JOBTPC
IDLTIM:	BLOCK 1				; idle time in 15-second units
PTIBUF:	BLOCK 30.			; PTY input buffer
PDL:	BLOCK PDLLEN			; stack

COREND==.-1				; end of initialized storage
;INTSER INTSR1 CLKSER

SUBTTL Interrupt server

;  Interrupts only set flags which the main program (normally in INTW⊗
; state) looks at.

INTSER:	SKIPN X,JOBCNI			; get interrupt status
	 JRST 4,.-1
	TLNE X,(INTPTO)			; PTY int
	 SETOM PTINTP
	TRNE X,INTQUIT			; QUIT int?
	 SETOM DOQUIT
	TLNE X,(INTFOP)			; output reset?
	 JRST [	MOVE JOBTPC
		MOVEM TPCSAV
		INTMSK [0]
		UWAIT
		PUSH P,TPCSAV
		INTMSK [-1]
		DEBREAK
		PUSHJ P,NETINS
		TELCMD [DMK]
		POPJ P,]
	TLNE X,(INTCLK)			; CLK int
	 JRST CLKSER
	TLNE X,(INTINP)			; NTI int
	 SETOM NTINTP
	TLNE X,(INTIMS)			; status change
	 JRST [	INTMSK [0]
		DEBREAK
		JRST SUICID]
	TLNE X,(INTINR)
	 OUTSTR [ASCIZ/*INR*
/]
	TLNN X,(INTINS)			; IMP INS int
	 JRST INTSR1
	SOS NTOINP
	OUTSTR [ASCIZ/*INS*
/]
INTSR1:	MOVSI 1,-1			; requeue into TQ from any queue
	DISMIS 1,

; Service clock interrupt

CLKSER:	AOSGE IDLTIM			; bump idle time
	 JRST INTSR1
	UNLOCK				; idle timeout; unlock
	MOVE TTYLIN
	PTGETL
	TLNE 1,(TLKRNG)			; TALKing?
	 JRST INTSR1			; don't kill him if so!
	TTYJOB
	JUMPN INTSR1
	INTMSK [0]			; no more interrupts
	DEBREAK				; out of interrupt level
	SETOM NODETP			; forget about detaching
	TLNN 1,(DMLIN)
	 JRST CLKSR1			; not a DM, just die
	MOVEI ↑X			; cancel modes
	PUSHJ P,NETOCH
	MOVEI ↑]			; scroll on
	PUSHJ P,NETOCH
CLKSR1:	MOVEI X,[ASCIZ/Autologout
/]
	PUSHJ P,SNDMSG
	JRST SUICID
;OTLSER CPYHST 1DIGTP NOTTIP

SUBTTL Start of program

OTLSER:	CAI
	RESET
	MOVE ['OTLSER]
	SETNAM
	SETZM CORBEG
	MOVE [CORBEG,,CORBEG+1]
	BLT COREND
	MOVE P,[PDL(-PDLLEN)]
	MOVEI [DEBREAK ? EXIT]
	MOVEM JOBAPR
	CLKINT 5.*60.*60.		; must die if around too long
	OUTSTR [ASCIZ/OTLSER started
/]

; Listen for a connection on our socket

	SETOM NODETP			; don't try to detach
	MOVEI SVRSKT
	MOVEM LSNSKT
	PUSHJ P,LISTEN

; Set up interrupts

	MOVEI INTSER
	MOVEM JOBAPR			; set up server location
	CLKINT 60.*15.			; start slow ticking clock
	MOVE [INTPTO\INTFOP\INTCLK\INTINR\INTINS\INTIMS\INTINP\INTQUIT]
	INTENB				; turn on interrupts

; Set up terminal id for interested spies

	MOVEI TERMID
	MOVEM JOBVER

; Log this connection

	OUTSTR [ASCIZ/Connected to /]
	PUSHJ P,MAPHST			; map in host table
	MOVE HOST
	PUSHJ P,HSTNUM			; get HDB
	 CAI				; sorry about errors
	MOVEI A,(1)			; host name
	HRLI A,440700
	SKIPA X,[440700,,TERSTR]
CPYHST:	 IDPB B,X
	ILDB B,A
	JUMPN B,CPYHST
	HLRZ A,1			; pointer to system name
	MOVE B,(A)			; get system name
	MOVE A,FSOCKT			; and ICP socket
	CAMN B,[ASCII/TIP/]		; on a TIP?
	 TRNE A,177774			; just paranoia; make sure a TIP port
	  JRST NOTTIP
	MOVEI B,"#
	IDPB B,X
	LSH A,-16.
	IDIVI A,8.			; ports are octal
	JUMPE A,1DIGTP
	ADDI A,"0 ? IDPB A,X
1DIGTP:	ADDI B,"0 ? IDPB B,X
NOTTIP:	PUSHJ P,SETANM			; set our alias name
	PUSHJ P,UNMHST			; map out the host table
	OUTSTR TERSTR
	OUTSTR [ASCIZ/
/]
	MOVEI X,[ASCIZ/SU-AI Old Protocol TELNET Server.
Please type HELP OTLSER for an important announcement.

/]
	PUSHJ P,SNDMSG
;NOFLAK MAINL MAINL0

SUBTTL Initialize the connection

; Initial protocol commands

	TELCMD [NEC]
	SETOM ECHOP

; Greet the user

	MOVEI X,256			; LASTDISASTERTIME
	PEEK X,
	PEEK X,
	JUMPE X,NOFLAK
	ACCTIM A,
	SUB A,X
	TLZE A,1			; forgive one day
	 ADDI A,24.*60.*60.
	CAILE A,15.*60.			; lost within 15 minutes?
	 JRST NOFLAK
	MOVEI X,[ASCIZ/System is flakey--watch out!
/]
	PUSHJ P,SNDMSG

; Get a PTY, keep its number in A

NOFLAK:	PTYGET A
	 JRST [	MOVEI 254		; MAINTM
		PEEK
		PEEK
		SKIPE
		 SKIPA X,[[ASCIZ/SU-AI - System being debugged, users not allowed on.
/]]
		  MOVEI X,[ASCIZ/SU-AI - All network ports in use.
/]
		PUSHJ P,SNDMSG
		INTMSK [0]
		PUSHJ P,CLOSER
		JRST SUICID]
	HRRZM A,TTYLIN			; dumb interrupts
	MOVSI (A)
	IRPS FOO,,ECHON ECHOFF XONOFF LINCHR GAGOFF IMPSET
	 IORM FOO
	TERMIN
	HRROI ECHOFF
	TTYSET
	MOVEI B,[ASCIZ/Hello
/]
	PTWRS7 A
	MOVE [-NTYSTS,,TYSBLK]
	TTYSET				; turn GAG bit off

; Final initialization

	MOVNI LOKTMO
	MOVEM IDLTIM			; initialize lock timeout
	LOCK				; keep response good
	SETZM NODETP			; okay to detach jobs now
	JRST NTISER			; check network input

; Main program loop

MAINL:	IWAIT				; wait for an interrupt
MAINL0:	MOVEI 2				; check connection status
	MTAPE NET,
	TLNN 1,(CLSS\CLSR)		; send side gronked?
	 TLNE 2,(CLSS\CLSR)		; receive side?
	  JRST SUICID
	AOSG NTINTP			; net input?
	 JRST NTISER
	AOSG PTINTP			; PTY input?
	 JRST PTISER
	AOSG DOQUIT			; QUIT seen?
	 JRST SUICID
	JRST MAINL			; back to sleep for us
;NTISER NTISR2 NTISR1

SUBTTL Network input interrupt

NTISER:	PUSHJ P,NETICH			; get character from the network
	 JRST MAINL0			; network input buffer empty
	SKIPL IDLTIM
	 LOCK
	MOVNI 1,LOKTMO
	MOVEM 1,IDLTIM			; reset idle time
	CAIL 200			; network command?
	 JRST NCMSER
	AOSE NEWLNP			; flush second half of NL?
	 JRST NTISR2
	JUMPE NTISER			; yah, flush nulls or
	CAIN ↑J				; LFs
	 JRST NTISER
NTISR2:	CAIE ↑M				; CR?
	 JRST NTISR1
	SKIPN ECHOP			; if in local mode
	 SETOM LFFLSP			; kludge to prevent system echo of LF's
	SETOM NEWLNP			; maybe flush an LF
NTISR1:	SKIPGE NTOINP			; still in flushify mode?
	 JRST NTISER			; too bad
	MOVE B,
	PTWR1S A			; send character to PTY
	 JRST [	MOVEI ↑G		; bell
		PUSHJ 17,NETOCH
		PUSHJ 17,NETSND		; output it
		JRST NTISER]
	JRST NTISER			; try for more user characters
;PTISER PTISR0

SUBTTL PTY input interrupt

PTISER:	MOVE B,[441140,,PTIBUF]
	PTRDS A				; read buffer from PTY
	ILDB B
	JUMPE [	PUSHJ P,NETSND		; buffer empty, force output out
		JRST MAINL0]
	SKIPL IDLTIM
	 LOCK
PTISR0:	MOVNI 1,LOKTMO
	MOVEM 1,IDLTIM			; reset idle time
	ANDI 377			; flush funny 400 bit
	CAIN ↑J				; LF?  (someday remove this kludge)
	 AOSE LFFLSP			; yes, second part of NL?
	  PUSHJ P,NETOCH		; send character to net
	ILDB B
	JUMPN PTISR0			; more in this buffer
	JRST PTISER			; maybe more buffers to come
;NCMSER NOPSER CMDONE DMKSER BRKSER NECSER ECHSER

SUBTTL Network command server

DEFINE TPC CODE
 CODE
 IRPS NAME,,CODE
  CAIN NAME
   JRST [OUTSTR [ASCIZ/!NAME!/] ? JRST NAME!SER]
 .ISTOP
 TERMIN
TERMIN

NCMSER:	OUTCHR ["*]
	TPC DMK==200			; data mark
	TPC BRK==201			; break
	TPC NOP==202			; no-op
	TPC NEC==203			; no echo
	TPC ECH==204			; echo
	TPC HID==205			; hide input
	TPC ASC==240			; ASCII mode
	TPC TRA==241			; transparent
	TPC IBM==242			; EBCDIC mode
	TPC YRC==243			; your code
	TPC MYC==244			; my code
	OUTSTR [ASCIZ/???/]

; Here when we return from a command (or for commands we no-op)

NOPSER:	HIDSER:	ASCSER:	TRASER:	IBMSER:	YRCSER:	MYCSER:
CMDONE:	OUTSTR [ASCIZ/*
/]
	JRST NTISER

DMKSER:	AOS NTOINP			; data mark
	JRST CMDONE

BRKSER:	MOVEI B,[.BYTE 9 ? 600 ? 600 ? 0]; CALL
	PTWRS9 A
	JRST CMDONE

NECSER:	SETZM ECHOP
	HRROI ECHOFF
	TTYSET
	JRST CMDONE

ECHSER:	SETOM ECHOP
	HRROI ECHON
	TTYSET
	JRST CMDONE
;SNDMSG MSGLUP ERRDIE INTDIE SUICID DIEDIE ...LIT SVRRTS ERRTNS ERRHAN ERRINS HSTTAB HSTSIX

SUBTTL Subroutines

; Send a message, b.p. in X

SNDMSG:	TLOA X,440700			; set up b.p.
MSGLUP:	 PUSHJ P,NETOCH
	ILDB X
	JUMPN MSGLUP			; continue until a null hit
	JRST NETSND

; Here to suicide on network errors or idle timeout

ERRDIE:	INTMSK [0]
SUICID:	OUTSTR [ASCIZ/Connection closed.
/]
	SKIPE NODETP
	 JRST DIEDIE			; logout the guy
	MOVE TTYLIN
	TTYJOB
	JUMPE DIEDIE
	MOVE A,TTYLIN
	MOVEI B,7
	PTJOBX A			; clear PTY's input buffer
	MOVEI 2
	MOVEI B,10			; DETACH
	PTJOBX A
	 JRST [	SLEEP ? JRST .-1]
	SLEEP
	PTRD1S A			; slurp up stuff in buffer
	 CAIA
	  JRST .-2
DIEDIE:	RESET ? EXIT

...LIT:	CONSTANTS

; Wonderful network routines

SVRRTS==-1				; include server routines
ERRTNS==-1				; include error routines
ERRHAN==-1				; include automagic error handling
ERRINS==<JRST ERRDIE>			; error instruction
HSTTAB==-1				; include host table magic
HSTSIX==-1				; and alias name kludge

.INSRT NETWRK

END OTLSER