Google
 

Trailing-Edge - PDP-10 Archives - decuslib10-11 - 43,50525/ptyccl.mac
There are no other files named ptyccl.mac in the archive.
TITLE PTYCCL -Monitor commands through a PTY-
SUBTTL DEVELOPERS: Bill Geraci & Alan MacInnes
;
; PTYCCL is a relocatable subroutine callable by COBOL
; or MACRO which opens a PTY, logs in under the controlling
; job's PPN and issues a monitor command to that PTY returning
; an error or first informational message encountered
; by the the program.

COMMENT \

Edit	By who	Date		Description

00	AL-WMG	May-30-81	.......Creation

01	WMG-AL	July-15-81	The first planned release

02	AL	Aug-27-81	PTY is logged in with TTY WIDTH 255 to allow
				long commands and return-lines.
				Check is made to not over-write LINBUF
[end of revision history]
\
	FTMDC==-1		;is -1 for MDC sites, 0 for non-MDC	[M2]
SUBTTL Search definitions, Version location and Symbols
;
; Search requirements
;
	SALL
	ENTRY	PTYCCL		;entry point from calling program
	EXTERN	FUNCT.		;Fortran and Cobol core allocator/deallocator
	SEARCH	JOBDAT,UUOSYM	;Use these symbols for the job data area
	SEARCH	MACTEN		; and uuo symbols
;
;	Definition for the edit constructs

	MDCVER==1		;Major release of this product
	MDCEDT==2		;Latest edit of this release

; Make sure MDCEDT is incremented by 1 for every edit added to program
;
; Set up location for the version and edit number

	LOC	.JBCST		;Location of the "customer" version number

	MDCVER,,MDCEDT		;released version,,edit number
	RELOC
;
; Definitions of all AC's, flags and symbols

	T1=1			;temporary accumulator
	T2=2			;temporary accumulator
	T3=3			;temporary accumulator
	T4=4			;temporary accumulator
	T5=5			;temporary accumulator

	P1=6			;permanent accumulator
	P2=7			;permanent accumulator
	P3=10			;permanent accumulator
	P4=11			;permanent accumulator

	C=12			;Used to transfer PTY I/O characters
	X=16			;pointer to argument list for COBOL to MACRO
	P=17			;Push-down stack pointer
SUBTTL Defined flags and symbols
;
; Flag word and all symbols associated with it

	F=0			;the flag accumulator

	LOGIO==1B0		;Bit = 1 use login command, else use logout cmd
	F.PASS==1B1		;Bit = 1 error in COBOL argument list 
	F.PLIN==1B3		;Bit = 1 byte pointer is from PTY buffer
	F.FLSH==1B4		;Bit = 1 flush the PTY output buffer
	F.NEWL==1B5		;Bit = 1 searching for next line in PTY output
	F.EATL==1B6		;Bit = 1 eating characters in discarded line
;
;	Other symbols
;

	DSP7==640,,0		;DISPLAY-7 argument type code
	M.ASC==1B3		;ascii argument type bit
				;passed to the macro PTYCCL
	OCTAL==10		;octal conversion radix
	DECIMA==12		;decimal conversion radix
	CR==15			;ASCII carraige-return
	LF==12			;ASCII line-feed
	PTY==15			;channel for PTY I/O
	BUFLIM==^D80		;size of return-line buffer in COBOL progam
	ARGSIZ==-5		;Size of LIBOL/FOROTS argument block
	GOT==6			;Get core function
	ROT==7			;release core function

SUBTTL	Macro Definitions
;
;	The ERROR macro calls the routine ERRMSG, passing the error
;	message number "ERRNUM", and then returns to the COBOL program.
;	This is accomplished as a JRST to a literal because this macro is
;	invoked as the error return following the PUSHJ to various routines.
;
	DEFINE	ERROR	(ERRNUM)
<
	JRST	[	MOVEI	T1,ERRNUM	;pass error code in this AC
			PUSHJ	P,ERRMSG	;return error text to COBOL prog
			JRST	RETURN	]	;return to COBOL program
>
SUBTTL Memory Definitions
;
; All memory locations are defined at this point


LINCNT:	BLOCK	1	;keep count of char in LINBUF		[M2]
LINBUF:	BLOCK	^D16		;scratch buffer to hold complete PTY output lines
CURPRI:	BLOCK	1		;current priority of text in return-line
				;buffer, should start out as -2

;
;  OTS argument passing block

ARGCNT:	XWD	ARGSIZ,0	;Size negated length of argument block
ARGBLK:	XWD	0,FCTCOD	;Pointer to the function code
ERRCOD:	XWD	0,ERRWRD	;for error code
STATUS:	XWD	0,STATWD	;Pointer to status word
ARG1:	BLOCK	1		;For first argument
ARG2:	XWD	0,PTYSIZ	;For second argument
;

FRECOR:	BLOCK	1		;Starting address of PTY I/O buffers
PTYSIZ:	BLOCK	1		;Size of PTY buffers is stored here
FCTCOD:	XWD	0,2		;Function code in right half
ERRWRD:	BLOCK	1		;Where error code is stored from the OTS
STATWD:	BLOCK	1		;The status should be zero for successful call
;
INHDR:	BLOCK	1		;Header control word for IN uuo to PTY
INPTR:	BLOCK	1		;Pointer to first character in the PTY
INCNT:	BLOCK	1		;Number of characters in the PTY
;
OUTHDR:	BLOCK	1		;Header control word for OUT uuo to PTY
OUTPTR:	BLOCK	1		;Pointer to first character in the PTY
OUTCNT:	BLOCK	1		;Number of characters in the PTY
;
; FILOP argument block

FILBLK:	EXP	0		;Extended channel,function code
	EXP	.IOASC		;ASCII mode
	SIXBIT	/PTY/		;device to open
	XWD	OUTHDR,INHDR	;open for output and input
	XWD	-1,-1		;Number of buffers for I/O (use monitor default)
SUBTTL Pure Storage -nothing changes is this area
;
;	Pure Storage
;
; Linked list pointers for buffers
;
LGNCMD:	ASCIZ/LOGIN /		;The beginning of the LOGIN command
LGNCM1:	ASCIZ\/NOOPT/WIDTH:255\	;The end of the LOGIN command	[M2]
LGOCMD:	BYTE(7)"C"-100,"C"-100,"K","/","N",0 ;2 control C's and "K/N"
	

;
;	The following is an address table of the error messages tnat
;	could be returned to the COBOL program if some error in PTYCCL
;	itself occurs.
;
MSGPTR:	point 7,MSG0
	point 7,MSG1		;pointers to text error messages
	point 7,MSG2		; to return to calling program
	point 7,MSG3
	point 7,MSG4
	point 7,MSG5
;
; Priority delimiters for messages returned
; to the controlling job.

PRITAB:	EXP	"."		;table of first characters of
	EXP	"["		; PTY output in
	EXP	"%"		; increasing priority
	EXP	"?"
	PRISIZ==.-PRITAB
SUBTTL Ascii error message strings
;
;	Here are the PTYCCL-related error messages, see the macro "ERROR" and 
;	the routine "ERRMSG".
;
MSG0:	ASCIZ	/?PTYNCB No Core For Buffers/
	ERRNMA==0
MSG1:	ASCIZ	/?PTYIAL Incorrect Arguments to PTYCCL/	;message text
	ERRBAG==1				;error message number
MSG2:	ASCIZ	/?PTYPTE PTY Error/
	ERRPTE==2
MSG3:	ASCIZ	/?PTYCLO Cannot Logout PTY/
	ERRCLO==3
MSG4:	ASCIZ	/?PTYCOP Cannot Open PTY/
	ERRCOP==4
MSG5:	ASCIZ	/?PTYCLP Cannot Login PTY/
	ERRCLI==5

	SUBTTL	Mainline Subroutine
;
;	This is the entry point of the call from COBOL, all of the
;	main routines required to process the monitor command are
;	invoked from here.
;
PTYCCL:	HRLZI	T1,-1			;get current program
	HRRI	T1,.GTPRG		; name
	GETTAB	T1,			; from Monitor table
	 SETZ	T1,			;should never non-skip
	PUSH	P,T1			;save name on stack
	MOVE	T1,[EXP 'PTYCCL']	;we are called PTYCCL while
	SETNAM	T1,			; we run
	HRROI	T1,-2			;next line from PTY will have higher
	MOVEM	T1,CURPRI		; priority, ensures that some line gets
					; returned to COBOL program
	PUSHJ	P,GTARGS		;get what we want from arg list
	 ERROR	ERRBAG			;arg list not in expected format
	PUSHJ	P,OPNPTY		;open a PTY for us to use
	 ERROR	ERRCOP			;can't do it
	TXO	F,F.NEWL		;must search for first line in PTY buffer
	TLO	F,(LOGIO)		;specify "log-in" function
	PUSHJ	P,LOGINO		;log the PTY in
	 ERROR	ERRCLI 			;can't log in
	MOVSS	P3,P3			;get length of monitor command
	MOVNS	P3,P3			;Make an AOBJN counter
CMOV:	ILDB	C,P2			;Get 1 character
	PUSHJ	P,PTYCHR		;Move a character to the PTY output buffer
	AOBJN	P3,CMOV			;Go move another character
	PUSHJ	P,OUTPTY		;input the monitor command on the PTY
	 ERROR	ERRPTE			;some PTY error
	PUSHJ	P,GETBUF		;Get all buffers from the PTY
	 ERROR	ERRPTE			;some PTY error
LOGOUT:	TXZ	F,LOGIO			;set function to "log-out"
	PUSHJ	P,LOGINO		;log-out the PTY
	 ERROR	ERRCLO			;can't log the job out
	PUSHJ	P,CLSPTY		;all done with the PTY
	PUSHJ	P,CORBAK		;Go give the PTY buffers back
	 JFCL				;ignore if can't give them back
RETURN:	POP	P,T1			;get user's program name
	SETNAM	T1,			; and set it back
	POPJ	P,			;Leave on Good terms, all cleaned up
	SUBTTL	Read COBOL Argument List
;
;	This routine verifies that the COBOL argument list is in the expected
;	format and extracts the required information.
;
;		Call:
;			PUSHJ	P,GTARGS
;			 error return		;incorrect arguments passed
;			normal return
;
;		Outputs:
;			P1 contains byte pointer word for return-line buffer
;			P2 contains byte pointer word for monitor command-line
;			P3 contains number of characters in monitor command
;
;		AC's modified: T1,T2
;
;	Note: THE DECSYSTEM-10 SOFTWARE DISPATCH 15 MAY 81 has correct
;	documentation relating to COBOL argument lists.
;
GTARGS:	MOVS	T1,-1(X)		;get argument count
	CAIE	T1,-2			;correct number of arguments?
	TLO	F,(F.PASS)		;set the error for bad pass
	HLRZ	T1,(X)			;get data type
	CAIE	T1,(DSP7)		;code for DISPLAY-7?
	TLO	F,(F.PASS)		;set the error for bad pass
	HLRZ	T1,1(X)			;get data type of second argument
	CAIE	T1,(DSP7)		;code for DISPLAY-7?
	TLO	F,(F.PASS)		;set the error for bad pass
	HRRZ	T1,(X)			;get address of 2-word descriptor
	MOVE	T2,1(T1)		;get its second word
	CAME	T2,[XWD 40000,^D80]	;should be this
	TLO	F,(F.PASS)		;set the error for bad pass
	MOVE	P1,(T1)			;get byte pointer word for this argument
	HRRZ	T1,1(X)			;get address of next 2-word decriptor
	MOVE	T2,1(T1)		;get status word
	TLNN	T2,(M.ASC)		;is this argument ASCII?
	TLO	F,(F.PASS)		;set the error for bad pass
	HRRZ	P3,T2			;get number of characters in monitor cmd
	MOVE	P2,(T1)			;get byte pointer word for this argument
	TLZN	F,(F.PASS)		;Skip if error bit is set, go to error
	JRST	CPOPJ1			;normal return
BADCAL:	POPJ	P,			;error return
	SUBTTL	Open a PTY for the Controlling job w/ associated memory buffers
;
;	ROUTINE: OPNPTY inits the PTY to the controlling job using an
;		 extended channel. It gets the memory from the Object
;		 Time System  and sets  up the  default number of I/O 
;		 ring  buffers, thus  it is  non-conflicting with the 
;		 OTS.
;
;		Call:
;			PUSHJ	P,OPNPTY
;			 error return		;can't open a PTY
;			normal return
;
;		Outputs:
;			device is open on channel CHANUM
;
;		AC's modified: T1
;
OPNPTY:	PUSHJ	P,GETSIZ		;Get size of buffer from TOPS10
	 POPJ	P,			;Some type of error
	PUSHJ	P,GETCOR		;Get some free core from the OTS
	 POPJ	P,			;Some type of error
	MOVE	T1,[FO.ASC!.FOSAU]	;Set function for extended channels
	MOVEM	T1,FILBLK		;Set FILOP for buffer setup
	MOVE	T1,[XWD	5,FILBLK]	;Set up the argument list for OPEN
	FILOP.	T1,			;Set up channels and buffers
	 POPJ	P,			;buffer setup failure
	HRRI	T1,.FOINP		;Set default buffer pointers for
	HRRM	T1,FILBLK		; the 'output' buffer for PTY
	MOVE	T1,[1,,FILBLK]		;Set for doing in INPUT oou
	FILOP.	T1,			;Initialize the byte pointer and count
	 POPJ	P,			;Return in error mode
	HRRI	T1,.FOOUT		;Set default buffer pointers for
	HRRM	T1,FILBLK		; the 'input' buffer to PTY
	MOVE	T1,[1,,FILBLK]		;Set for doing an OUTPUT uuo
	FILOP.	T1,			;Initialize the byte pointer and count
	 POPJ	P,			;Return in error mode
	PJRST	CPOPJ1			;Good return buffer pointers setup


SUBTTL Remove the PTY from the system
;
;	This routine releases the PTY and the channel
;	from the controlling job.
;
;		Call:
;			PUSHJ	P,CLSPTY
;			normal return
;
;		AC's modified: T1
;
CLSPTY:	HRRI	T1,.FOREL		;Get function for the channel release
	HRRM	T1,FILBLK		;Store in argument block
	MOVE	T1,[1,,FILBLK]		;Pointer to argument block
	FILOP.	T1,			;Release the PTY
	 POPJ	P,			;always return
	POPJ	P,			;return
	SUBTTL	Process Line Output From PTY
;
;	This routine moves a PTY output line to the COBOL return-line
;	buffer.
;
;		Call:
;			PUSHJ	P,BUFLIN
;			normal return
;
;		Inputs:
;			P4 contains byte pointer to line
;
;		AC's Modified:	T1,T2,T3,T4
;
BUFLIN:	MOVE	T4,P4		;get copy of byte pointer word - source
	MOVE	T2,P1		;get copy of byte pointer word - destination
	SETZ	T3,		;clear character count
NXTC:	ILDB	T1,T4		;get next character
	IDPB	T1,T2		;deposit in COBOL buffer
	AOJ	T3,		;bump character count
	CAIL	T3,BUFLIM	;reached limit of buffer?
	JRST	BUFEXT		;yes, truncate rest of line
	SKIPN	T1		;null?
	JRST	[	MOVEI	T1,CR		;replace null with
			DPB	T1,T2		; CRLF
			MOVEI	T1,LF
			IDPB	T1,T2
			AOJ	T3,		;bump character count
			JRST	GETSPC	]	;go pad buffer w/spaces
	CAIE	T1,LF		;end of line?
	JRST	NXTC		;no
GETSPC:	MOVEI	T1," "		;for padding
PAD:	CAIL	T3,BUFLIM	;are we at end of buffer?
	JRST	BUFEXT		;no
	IDPB	T1,T2		;deposit another space
	AOJA	T3,PAD		;bump char count, insert next space
BUFEXT:	POPJ	P,		;return
	SUBTTL	Get Next Line From PTY Output
;
;	This routine processes the next buffer from the PTY,
;	constructing full lines of output and passing them to BUFLIN.
;
;	Call:
;			PUSHJ	P,GETLIN
;
;		Inputs:
;			T2 has current byte pointer value to scratch buffer
;
;		Outputs:
;			T2 updated for next call
;
;		AC's Modified:	T1,T2
;
GETLIN:	TXNN	F,F.NEWL	;looking for new line in PTY buffer?
	JRST	CHKEAT		;no
GETLN2:	MOVE	T2,[POINT 7,LINBUF]	;yes, establish a byte pointer word to
	MOVEI	T1,^D80		;max chars in this buffer		[M2]
	MOVEM	T1,LINCNT					;	[M2]
	MOVE	P4,T2		; scratch buffer and save its initial value
;
;	Here we look for the beginning of the next line in the PTY buffer
;
SRCHTX:	PUSHJ	P,GETC	;get next character from PTY
	 POPJ	P,		;must go back for new buffer
	CAIGE	T1," "		;got some real text here?
	JRST	SRCHTX		;no, ignore line-feeds and other junk
	TXZ	F,F.NEWL	;we have found a new line
	PUSHJ	P,PRICHK	;should we return it to COBOL program?
	 JRST	[	TXO	F,F.EATL	;no, eat this
			JRST	EATC	]	;line
	JRST	DEPC		;move character to scratch buffer
CHKEAT:	TXNN	F,F.EATL	;are we eating a discarded line?
	JRST	NXTBYT		;no
;
;	Here we eat the characters of a PTY output line that is to
;	be discarded
;
EATC:	PUSHJ	P,GETC	;get next character
	 POPJ	P,
	CAIN	T1,LF		;a line-feed?
	JRST	.-3		;no, eat more
	TXZ	F,F.EATL	;go into search for a
	TXO	F,F.NEWL	; new line
	JRST	GETLN2
;
;	Here we move the characters of the next line into a scratch
;	buffer for processing by BUFLIN
;
NXTBYT:	PUSHJ	P,GETC	;get next character from PTY
	 POPJ	P,		;requires another PTY buffer
DEPC:	SOSL	LINCNT		;don't overwrite LINBUF			[M2]
	IDPB	T1,T2		;deposit in scratch buffer
	CAIE	T1,LF		;was this a line-feed?
	JRST	NXTBYT		;no, go back for more
	PUSHJ	P,BUFLIN	;process this complete line from the PTY
	TXO	F,F.NEWL	;go into search mode
	JRST	GETLN2		;start processing next line
;
;
;
GETC:	TXNE	F,F.FLSH	;are we ignoring this buffer?
	POPJ	P,		;yes
	SOSG	INCNT		;another character in this PTY buffer?
	POPJ	P,		;no, take non-skip return
	ILDB	T1,INPTR	;get next character
	JRST	CPOPJ1		;return with it
	SUBTTL	Check Priority of Line Output On PTY
;
;	This routine examines the current line output on the PTY and
;	checks to see if it should be returned to the COBOL program.
;
;		Call:
;			PUSHJ	P,PRICHK
;			 error return	;discard this line
;			normal return	;return this line
;
;		Inputs:
;			T1 contains first character of current line
;
;		AC's modified: T3
;
;	Here we see if the first character of this line is in the
;	character priority table (?,[, etc.)
;
PRICHK:	HRLZI	T3,-PRISIZ	;get number of entries in PRITAB
TABEXM:	CAMN	T1,PRITAB(T3)	;does char match this table entry?
	JRST	FOUND		;yes
	AOBJN	T3,TABEXM	;no, examine next table entry
	SETO	T3,		;this line has no priority
;
;	Here we see if the priority of this line allows it to replace
;	the current "most important" line.
;
FOUND:	HRRZS	T3		;get rid of left-half counter
	CAMG	T3,CURPRI	;is this greater than priority of curr line?
	POPJ	P,		;no, discard this line
	MOVEM	T3,CURPRI	;save priority of new line
	PJRST	CPOPJ1		;take normal return
	SUBTTL	Generate ASCII Error Message
;
;	This routine looks up the text error message associated with an error
;	number and moves it to the return-line buffer of the COBOL program.
;	This tells the COBOL program of an error internal to PTYCCL itself.
;
;		Call:
;			PUSHJ	P,ERRMSG
;			normal return
;
;		Inputs:
;			T1 contains an error code (0-n)
;
;		AC's modified: P4
;
ERRMSG:	MOVE	P4,MSGPTR(T1)		;get byte pointer word for error text
	PUSHJ	P,BUFLIN		;install PTYCCL msg in return-buffer
	POPJ	P,			;return
SUBTTL Login or Logout a subjob
;
; ROUTINE: LOGINO checks the flag word to see if bit mask
;	   LOGIO is set.  If it is, then the ascii command
;	   to login a subjob is passed to OUTPTY if not the
;	   the logout command is passed.
;
; Ac's modified: T1
;
; CALL:	TLZ	F,(LOGIO)		;Log the subjob off the PTY
;	TLO	F,(LOGIO)		;Log the subjob on the PTY
;	PUSHJ	P,LOGINO		;Go process a login/out command
;	 error	return			;Tell user it failed
;	normal	return			; Made it

LOGINO: TLNN	F,(LOGIO)		;Check if logging in or out

	JRST	[	MOVEI	T1,LGOCMD	;Set for logout
			JRST	LOG01	]	;continue with logic

	MOVEI	T1,LGNCMD		;Set for login
	PUSHJ	P,CMDMOV		;Go output the LOGIN command
	PUSHJ	P,GETPPN		;Get controlling jobs PPN
	PUSHJ	P,GETCHG		;Get the controlling jobs charge number
	MOVEI	T1,LGNCM1		;Point to remainder of command
LOG01:	PUSHJ	P,CMDMOV		;Move the command to the PTY I/O buffer
	PUSHJ	P,OUTPTY		;Go issue the monitor command
	POPJ	P,			;Error return
	TXO	F,F.FLSH!F.PLIN		;Flush the PTY output buffer
	PUSHJ	P,GETBUF		;Eat PTY output till at monitor mode
	 jfcl				;***error handling?
	TXZ	F,F.FLSH		;Done flushing the buffer
LOG02:	HLRZ	T1,FILBLK		;Get the channel number of the PTY
	JOBSTS	T1,			;Get the status of the job on the PTY
	 POPJ	P,			;Should never happen -ERROR-
	TLNN	F,(LOGIO)		;See if the job is logging in

	JRST	[	TLNE	T1,(JB.ULI)	;See if job logged out
			 POPJ	P,		;Error job didn't log out
			PJRST	CPOPJ1	]	;All done

	TLNN	T1,(JB.ULI)		;see if job is logged in
	 POPJ	P,			;Job didn't get logged in
	PJRST	CPOPJ1			;All done good return
SUBTTL Examine or take the output buffer from PTY
;
; ROUTINE: INPTY get from the PTY a tty buffer at a time
;	   and passes it to the controling jobs memory
;	   for its own pleasure
;
; Ac's modified: T1
;
; CALL:	PUSHJ P,INPTY		;Get a buffer from the PTY
;	 error	return		;bad input from PTY
;	normal	return		;Back with data in buffer

INPTY:	HRRI	T1,.FOINP	;Get fuction code for FILOP
	HRRM	T1,FILBLK	;Set for output to the PTY
	MOVE	T1,[1,,FILBLK]	;Length and pointer to argument list
	FILOP.	T1,		;Get some output from the PTY
	 POPJ	P,		;Return to caller and check status
	PJRST	CPOPJ1		;Good exit with buffer full

SUBTTL Deposit command from calling program to PTY
;
; ROUTINE: OUTPTY will pass  buffer with the monitor
;	   command to the PTY, thus issuing the command
;	   for the COBOL program.
;
; Ac's mofified: C, T2
;
; CALL:	PUSHJ	P,OUTPTY		;Dump the commad in the PTYs input buffer
;	 error	return			;Check the status 
;	normal	return			;Return with command in PTY command buffer

OUTPTY:	MOVEI	C,33			;Terminate with an <ESC>
	PUSHJ	P,PTYCHR		;Send the <ESC>
OUTPY1:	HRRI	T2,.FOOUT		;Get fuction code for FILOP
	HRRM	T2,FILBLK		;Set for output to the PTY
	MOVE	T2,[1,,FILBLK]		;Length and pointer to argument list
	FILOP.	T2,			;Get some output from the PTY
;
; BECAUSE OF MONITOR BUG do the following

	TXNN	T2,IO.ERR		;Check for device error
	PJRST	CPOPJ1			;Good return
	POPJ	P,			;Error, bad return

SUBTTL Move an ASCIZ string into the PTY command buffer
;
; ROUTINE: CMDMOV moves an ASCIZ command string into the PTY
;	   command buffer, without issuing the command.
;
; Ac's mofified: T1, C
;
; CALL:	MOVEI	T1,[ASCIZ string address]
;	PUSHJ	P,CMDMOV		;Move the message
;	always 	return			;Return with messaged moved
;
;
CMDMOV:	HRLI	T1,(POINT 7,0)		;Set up byte pointer
CMDMV1:	ILDB	C,T1			;Get one character from command
	JUMPE	C,CPOPJ			;Check for a NULL and return
	PUSHJ	P,PTYCHR		;Move the character in CHR to the PTY
	JRST	CMDMV1			;Go move another character to buffer
SUBTTL Deposit  a character into the PTY (output) CMD buffer
;
; ROUTINE: PTYCHR moves  one character into the PTY  command 
;	   buffer.  If the buffer is full, the routine calls
;	   the OUTPY1 routine to pass the full buffer to the
;	   PTY, returns and moves the pending character into
;	   the   PTY  buffer  and  returns,  else  moves the
;	   character in the buffers and returns.
;
; Ac's mofified: none
;
; CALL:	with character in ac C
;
;	PUSHJ	P,PTYCHR		;Put the character into the PTY buffer
;	always	return			;Return with character in PTY buffer

 
PTYCHR:	SOSGE	OUTCNT			;Check for more room in PTY I/O buffer
	PUSHJ	P,DMPBUF		;Go dump the buffer at the PTY
	IDPB	C,OUTPTR		;Move the command to the CMDBUF
	POPJ	P,			;Return to calling routine
DMPBUF:	PUSHJ	P,OUTPY1		;Send tthe buffer to the PTY
	 JFCL				;Some random error
	POPJ	P,			;Return as normal


SUBTTL Subroutines and misc.
;
; ROUTINE: CPOPJ1 add 1 to the stack to cause 
;	   a routine to do a skip return

CPOPJ1:	AOS	(P)			;Add to stack for a skip return
CPOPJ:	POPJ	P,			;Return to controlling routine

SUBTTL Get and convert the Controlling jobs PPN
;
; ROUTINE: GETPPN Gets the controlling jobs P,PN converts it to
;	   ascii and puts it in the PTY output buffer
;
; Ac's modified: T1
;
; CALL: PUSHJ	P,GETPPN		;Get the PPN of the controling job
;	Always	return			;Should never fail

GETPPN:	GETPPN	T1,			;Get the controlling PPN
	 JFCL				;Make Bill Meier happy
	PUSH	P,T1			;Save the P,PN on the stack
	HLRZ	T1,T1			;Get the Project
	PUSHJ	P,OCTOUT		;Go send It to the PTY buffer
	MOVEI	C,","			;Get the comma
	PUSHJ	P,PTYCHR		;Store it in the PTY I/O buffer
	POP	P,T1			;Restore the P,PN
	HRRZ	T1,T1			;Get the Programmer number
	PUSHJ	P,OCTOUT		;Go send It to the PTY buffer
	POPJ	P,			;Return with PPN converted and moved
;
; ROUTINE: GETBUF eats all usless output from the PTY and loops or SLEEPS
;	   till PTY is at monitor mode.
;
; Ac's modified: T1
;
; CALL:	PUSHJ	P,GETBUF	;Eat till full or monitor mode
;	 error	return
;	normal return

GETBUF:	MOVE	T1,[HB.RPT!HB.RWJ+<10*1000>];Set for PTY status change
	HIBER	T1,			;snore
	JFCL				;Don't do anything on failure
	PUSHJ	P,INPTY			;Get response from the program
	POPJ	P,			;Error
	PUSHJ	P,GETLIN		;Pass message back to controlling job
	HLRZ	T1,FILBLK		;Get the extended channel
	JOBSTS	T1,			;See what the job is doing
	JFCL				;Should never fail
	TXNN	T1,JB.UOA		;Check for more output from PTY
	TXNN	T1,JB.UDI		;Check to see if at monitor level
	JRST	EATMOR			;Yes, go get a buffer full
	JRST	EATDN1			;go exit routine
EATMOR:	PUSHJ	P,INPTY			;Get the first buffer full of nothing
	POPJ	P,			;return through the error loop
	JRST	GETBUF			;Go get another buffer
EATDN1:	PUSHJ	P,INPTY			;Get the first buffer full of nothing
	POPJ	P,			;return through the error loop
	PJRST	CPOPJ1			;Good return at monitor mode

SUBTTL OCTAL and DECIMAL conversion routines to ASCII
;
; Convert binary octal to OCTAL ASCII or DECIMAL ASCII
;
;	Inputs: T1 has the number to be converted
;		1 number at a time returned in C
;	Trashed locations: T1, C and T3
;
DECOUT:	SKIPA	T3,[DECIMA]		;Set up radix for decimal conversion
OCTOUT:	MOVEI	T3,OCTAL		;Set up radix for octal conversion
COMON1:	IDIV	T1,T3			;get the number in T1+1
	PUSH	P,T1+1			;Save number on stack
	SKIPE	T1			;Done computing the number?
	PUSHJ	P,COMON1		;No, compute the next number
;
COMON2:	POP	P,C			;Get the first number
	ADDI	C,"0"			;Make the number ascii
	PJRST	PTYCHR			;Put character in PTY output buffer
;
;
;
; Get the CHARGE number from the Monitor
;	If charge number = 0, then return
; Else move charge message to the PTY cmd
;  buffer, convert charge number from
;  SIXBIT to ASCII and move to CMD buffer and return
;
; Ac's modified: T1
;
; CALL:	PUSHJ	P,GETCHG		;Get and convert charge number (if one)
;	always	return			;Back to caller

GETCHG:	HRROI	T1,.GTCNO		;Get the charge number of the controlling job
	GETTAB	T1,			;Go get it from TOPS10
	 SETZ	T1,			;If it fails, no  /CHARGE: switch used
	JUMPE	T1,CPOPJ		;See if no charge
	PUSH	P,T1			;Save the SIXBIT charge number
	MOVEI	T1,[ASCIZ"/CHARGE:"]	;Set up the CHARGE switch
	PUSHJ	P,CMDMOV		;Move the switch the PTY I/O buffer
	POP	P,T1			;Get the charge number of the stack
	PUSHJ	P,SIXASC		;Convert to ASCII and put in PTY buffer
	POPJ	P,			;Return
SUBTTL SIXBIT to ASCII conversion routine
;
; ROUTINE: SIXASC is a SIXBIT to ASCII conversion
;
; INPUTS: T1 contains the SIXBIT word
; OUTPUTS: ASCII character in C
;
; TRASHED ACCS: C, T3 & T4

SIXASC:	MOVE	T3,[POINT 6,T1]		;Make a SIXBIT byte pointer
	MOVSI	T4,-6			;Max number in T1
SIXCVT:	ILDB	C,T3			;Get the SIXBIT characters
	ADDI	C," "-' '		;Make the number ASCII
	PUSHJ	P,PTYCHR		;Send the character to the PTY buffer
	AOBJN	T4,SIXCVT		;Loop til all characters are converte
	POPJ	P,			;Leave with conversion in PTY buffer
SUBTTL Get the size of the PTY I/O buffers
;
;
; Routine: GETSIZ get the I/O buffer size of the appropriate
;	   device in the OPEN block and returns the size in 
;	   PTYSIZ
;
;	   On a good return it skips
;
; Acs used: T1 and T2. Memory locations used, PTYSIZ

GETSIZ:	MOVEI	T1,FILBLK+1		;Set pointer to OPEN block
	DEVSIZ	T1,			;Get the # and size of PTY buffers
	 POPJ	P,			;Return to the ERROR handler
	HLRZ	T2,T1			;Get the number of buffers in T2
	HRLI	T1,0			;We just want the # of words in buffer
	IMUL	T1,T2			;Amount of CORE needed in PTY I/O
	LSH	T1,1			;Double for Input and Output buffers
	MOVEM	T1,PTYSIZ		;Save the size for later use
	PJRST	CPOPJ1			;Give a good return
SUBTTL 2 routines: one to get CORE, and one to give it back
;
; Routine: GETCOR get the amount of core needed by any device from
;	   the OTS. On a good return you get a skip.
;
; Ac's used: T2, X

GETCOR:	MOVE	T2,.JBFF		;Get the first free
	MOVEM	T2,FRECOR		;And save for CORE deallocation
	MOVEI	T2,.JBFF		;Get the address for storage
	MOVEM	T2,ARG1			;Set in the CALL list
	MOVEI	T2,GOT			;Function code for getting CORE
	MOVEM	T2,FCTCOD		;set the function
	MOVEI	T2,PTYSIZ		;Get the CORE amount needed
	MOVEM	T2,ARG2			;Move it to the argument block
	MOVEI	X,ARGBLK		;Set pointer to the arg list
	PUSHJ	P,FUNCT.		;go get the CORE
	 SKIPN	STATWD			;Skip if error occured
	PJRST	CPOPJ1			;Got it!, return w/addr in FRECOR
	 PJRST	CPOPJ			;Return with error



;
; Routine: CORBAK returns the core allocated through the above call
;	   through the OTS.  Skip on a good return
;
; Ac's used: T2, X

CORBAK:	MOVEI	T2,ROT			;Get the function for returning CORE
	MOVEM	T2,FCTCOD		;Set it in the argument block
	MOVEI	T2,PTYSIZ		;Get the size to be returned
	MOVEM	T2,ARG2			;Set it in the argument block
	MOVEI	T2,FRECOR		;Get the address of the 'free' core
	MOVEM	T2,ARG1			;Set it in the argument block
	MOVEI	X,ARGBLK		;set the pointer to the arg list
	PUSHJ	P,FUNCT.		;Go give the CORE back
	 SKIPN	STATWD			;Skip if error occured
	PJRST	CPOPJ1			;Got it!, return w/addr in FRECOR
	 PJRST	CPOPJ			;Return with error

	
	LIT
	END