.TITLE TTYDRV terminal driver .IDENT /04.05/ ; ; This is a hardware independent terminal driver for the Grumpf system. ; ; Individual hardware drivers can register terminals (terminal lines, actually) ; with the system and use system routines to enqueue characters read from the ; terminal or dequeue characters to be sent to the terminal. ; ; Programs can use this driver through the I/O system, routines to read, write ; and control the terminal are provided, as well as mandatory open and close ; routines. ; ; layout of terminal structure: ; ... device structure as required by the I/O system, NAME and TYPE ; are always "TTY", NUM is counted up ; T$NUM the terminal number is stored a second time inside the terminal ; structure so that it can be accessed without knowledge of the ; device structure ; K$ENBL hardware driver routine to enable keyboard interrupts ; K$DSBL hardware driver routine to disable keyboard interrupts ; P$ENBL hardware driver routine to enable printer interrupts ; P$DSBL hardware driver routine to disable printer interrupts ; T$PUTC terminal driver routine used by the hardware driver to input ; characters read from the terminal into the system ; T$GETC terminal driver routine used by the hardware driver to read ; characters from the system to be output on the terminal ; T$ACNT count of active asynchronous writes to the terminal (not used) ; T$BCNT count of character buffers in use by this terminal ; T$OCNT count of "OPEN" calls to the terminal ; T$OWNR owner of the terminal (first job to OPEN it) ; T$MODE mode flags of the terminal ; O$CCNT count of characters in the output character buffer list ; O$HEAD pointer to next character to be sent in the output character ; buffer list ; O$TAIL pointer to last character appended to the output character ; buffer list ; O$LIST pointer to O$CCNT, for use as argument to GETC and PUTC ; P$BACK backup of P$ENBL, used while in XOFF mode ; I$TAHD remaining size of typeahead part of input character buffer list ; I$CCNT count of characters in the input character buffer list ; I$HEAD pointer to next character to be read from the input character ; buffer list ; I$TAIL pointer to last character appended to the input character ; buffer list ; I$LIST pointer to I$CCNT, for use as argument to GETC and PUTC ; O$OOBB out-of-band output buffer, can hold a single character to be ; sent to the terminal out-of-band ; ; T$MODE mode flags: ; T$ECHO input characteres are echoed in line input mode (they are never ; in character input mode, regardless of the state of this bit) ; T$DELM the terminal can backspace and erase the last typed character ; T$LINE use line input mode, which means that more than one character ; can be read with a single call to READ ; T$COOK enables cooked line mode, which means that BS and DEL are ; processed and that a CR terminates input and returns control to ; the caller (in raw line mode, control is returned when the ; specified number of characters was read) ; T$EXCL exclusive mode, writes to a terminal in this mode are forbidden ; for anyone but the owner of the terminal ; T$WAIT the owner is $WAITing for characters to be input, so do a $DONE ; after characters are received ; T$BITS mask for user-settable bits of T$MODE ; T$SIZE mask for size part of T$MODE, if this part is nonzero on it ; will be used as the new size of the typeahead input buffer ; ; system calls: ; $TTYREG fill terminal structure and register device with I/O system. ; The argument to this call is a terminal structure with K$ENBL, ; K$DSBL, P$ENBL, P$DSBL and D$INFO correctly set. ; ; other macros: ; .TTY reserves space for a terminal structure and stores K$ENBL, ; K$DSBL, P$ENBL and P$DSBL at the correct offsets ; ; I/O functions: ; READ reads a character or a line from the terminal. In line mode, ; the number of read characters is returned in R0, in character ; mode the character read is returned in R0. ; WRITE writes a buffer to the terminal ; OPEN is unimplemented ; CLOSE closes the I/O channel connected to the terminal. If the owner ; closes, no more input will be allowed. ; SEEK is unimplemented ; BSIZE returns the current remaining size of the typeahead input ; buffer ; MODE set mode flags in T$MODE and the size of the typeahead input ; buffer ; ; interface to hardware drivers: ; K$ENBL, K$DSBL, P$ENBL and P$DSBL will be called with the address of ; the terminal structure as single argument. ; T$PUTC and T$GETC have to be called with the address of the terminal ; structure as argument, T$PUTC needs the character to be input ; as second argument. ; ; The terminal driver itself implements XON/XOFF handling for output. On ; reception of a XOFF, P$ENBL and T$GETC will be cut short to stop output of ; characters until a XON is received, which will restore P$ENBL and T$GETC. ; ; 09-AUG-2005 H. Rosenfeld fixed bugs .TTY macro ; 04-JUN-2005 H. Rosenfeld fixed PSW restoration in READ ; 28-MAY-2005 H. Rosenfeld in cooked line mode, abort reading on Ctrl-C ; and return error, don't echo CR in line mode ; 27-MAY-2005 H. Rosenfeld return error codes in R0 ; 17-MAY-2005 H. Rosenfeld removed usage of OCTAL and RADENC to create ; the device number, added routine MAKNUM for ; this purpose ; 11-MAY-2005 H. Rosenfeld ; .LIST ME .NLIST CND .ENABL REG .LIBRARY /CALL.SML/ .LIBRARY /SYSCLL.SML/ .LIBRARY /JOBCTL.SML/ .LIBRARY /IOSYS.SML/ .LIBRARY /MEMORY.SML/ .MCALL .CALL,.ENTRY,.RETRN,.IMAGE .MCALL $SYS,$REGSYS,$WAIT,$DONE,$TERM,$EXIT,$CURJOB .MCALL .DEVCTL,.IOSYS,.IOFUNC,.IOERR,.IOCLR,.IOHND,.IOTAB .MCALL $IODONE,$IOREQ .MCALL $READ,$WRIT .MCALL $P$INIT,$P$ALLO,$P$FREE,$P$ERR .MCALL $M$ALLO .MACRO .TTYMOD T$ECHO=100000 T$DELM=040000 T$LINE=020000 T$COOK=010000 T$EXCL=004000 T$WAIT=000200 T$BITS=177400 T$SIZE=000177 .ENDM .MACRO .TTYCTL T$NUM=SIZE$D+0 K$ENBL=SIZE$D+2 K$DSBL=SIZE$D+4 P$ENBL=SIZE$D+6 P$DSBL=SIZE$D+10 T$PUTC=SIZE$D+12 T$GETC=SIZE$D+14 T$ACNT=SIZE$D+16 T$BCNT=SIZE$D+20 T$OCNT=SIZE$D+22 T$OWNR=SIZE$D+24 T$MODE=SIZE$D+26 O$CCNT=SIZE$D+30 O$HEAD=SIZE$D+32 O$TAIL=SIZE$D+34 O$LIST=SIZE$D+36 P$BACK=SIZE$D+40 I$TAHD=SIZE$D+42 I$CCNT=SIZE$D+44 I$HEAD=SIZE$D+46 I$TAIL=SIZE$D+50 I$LIST=SIZE$D+52 O$OOBB=SIZE$D+54 SIZE$T=SIZE$D+56 .ENDM .MACRO .TTY KENBL,KDSBL,PENBL,PDSBL .WORD .WORD KENBL .WORD KDSBL .WORD PENBL .WORD PDSBL .BLKW </2> .ENDM .MACRO .FREE BUF MOV FRELST,@BUF ;; append FRELST to buffer MOV BUF,FRELST ;; make buffer new head of FRELST .ENDM .MACRO .ALLO BUF ?EMPT ?NEMPT MOV FRELST,BUF ;; get head of FRELST BEQ EMPT ;; abort if empty MOV @BUF,FRELST ;; make next buffer new head of FRELST CLR @BUF ;; clear forward link of buffer CLC ;; no error BR NEMPT EMPT: SEC ;; indicate error NEMPT: .ENDM .MACRO .APPND BUF,LIST BIC #17,LIST ;; get pointer to next buffer MOV BUF,@LIST ;; next buffer will be BUF MOV @LIST,LIST ;; advance LIST to BUF INC LIST ;; increment character pointer .ENDM .DEVCTL .IOSYS .IOFUNC .IOERR .TTYMOD .TTYCTL NTTY=4 NBUF=10 B$CCNT=0 B$HEAD=2 B$TAIL=4 C$XOFF=23 C$XON=21 C$CR=15 C$DEL=177 C$BS=10 C$SPC=40 C$BEL=7 C$BACK=134 C$CC=3 .IMAGE TTYDRV .CSECT ; driver initialization ; allocate partition for character buffers, register TTYREG system call, ; initialize character buffers TTYDRV: MOV #TTYTAB,R0 MOV #NTTY,R1 1$: CLR (R0)+ ; clear TTYTAB SOB R1,1$ $M$ALLO #0,#<*>*20,#^RUSR,#^RTTY,#^RBUF ; allocate a partition for character buffers BCC 3$ ; continue if no error $EXIT ; exit otherwise 3$: MOV R0,R4 ; save partition address for reuse $REGSYS #^RTTY,#^RREG,#TTYREG,#340 MOV R4,R0 ADD #17,R0 BIC #17,R0 ; align it to buffer size CLR (R0) ; no next buffer MOV R0,FRELST ; make it head of FRELST MOV #*NBUF,R1 2$: ADD #20,R0 .FREE R0 ; free rest of the partition into FRELST SOB R1,2$ $TERM ; terminate ; TTYREG, register terminal device ; input: pointer to terminal structure ; output: terminal structure is filled with valid data, registered as device ; return: carry as returned from device registration .MACRO $TTYREG TTY $SYS #^RTTY,#^RREG,TTY .ENDM TTYREG: .ENTRY MOV #TTYTAB,R0 MOV #NTTY,R1 1$: TST (R0)+ ; search for free entry in TTYTAB BEQ 2$ ; found one, use it SOB R1,1$ SEC ; no free entries, indicate error .RETRN 2$: MOV 6(R5),-(R0) ; save pointer to device in TTYTAB MOV R0,R4 SUB #TTYTAB,R0 ASR R0 ; calculate TTY number JSR PC,MAKNUM ; convert to RAD50 MOV R0,R3 ; save for reuse MOV (R4),R4 ; get device structure MOV #^RTTY,D$TYPE(R4) ; this device is a TTY MOV #^RTTY,D$NAME(R4) ; which is also named TTY MOV R3,D$NUM(R4) ; and has a number MOV #IOREQ,D$IORQ(R4) ; use our I/O handler MOV R3,T$NUM(R4) ; save the number again MOV #TTYOPN,D$OPEN(R4) ; use our OPEN routine CLR T$OWNR(R4) ; no owner yet CLR T$ACNT(R4) ; no asynchronous writes yet MOV #NBUF+4,T$BCNT(R4) ; no buffers used CLR T$OCNT(R4) ; zero open count CLR O$CCNT(R4) ; no characters for output CLR O$HEAD(R4) ; no buffer list CLR O$TAIL(R4) MOV R4,O$LIST(R4) ; create pointer to buffer list ADD #O$CCNT,O$LIST(R4) CLR I$CCNT(R4) ; no characters for input CLR I$HEAD(R4) ; no buffer list CLR I$TAIL(R4) MOV R4,I$LIST(R4) ; create pointer to buffer list ADD #I$CCNT,I$LIST(R4) MOV #52,I$TAHD(R4) ; initial type-ahead size CLR O$OOBB(R4) ; no out-of-band data MOV #T$ECHO!T$LINE!T$COOK,T$MODE(R4) ; initially cooked line mode with echo MOV #TTYPUT,T$PUTC(R4) ; save pointer to input routine MOV #TTYGET,T$GETC(R4) ; save pointer to output routine MOV P$ENBL(R4),P$BACK(R4) ; save P$ENBL backup .IOCLR #IORQP ; clear I/O request packet $WRIT #IORQP,#SIZE$D,R4 ; register device 3$: .RETRN ; error status by WRIT ; MAKNUM is a helper routine for TTYREG. It will convert the value in R0 ; to RAD50 representation, leaving the result in R0. The registers R1 and R2 ; are changed. MAKNUM: MOV R0,R1 ; prepare for division MOV #3,R2 ; 3 characters 1$: CLR R0 ; prepare for division DIV #10,R0 ; R0 undecoded, R1 decoded ADD #36,R1 ; convert to RAD50 MOV R1,-(SP) ; store character MOV R0,R1 ; continue with undecoded part SOB R2,1$ MOV #3,R2 ; 3 characters CLR R0 CLR R1 2$: MUL #50,R1 ; shift by one RAD50 character MOVB (SP)+,R0 ; get character from stack ADD R0,R1 ; add character to RAD50 word SOB R2,2$ MOV R1,R0 RTS PC ; TTYOPN, driver open routine ; input: pointer to device structure ; output: terminal owner is set if clear, open count increased, keyboard ; interrupt is enabled ; return: carry cleared, ; R0 pointer to device structure TTYOPN: .ENTRY MOV 6(R5),R4 ; first argument: device TST T$OWNR(R4) ; already an owner? BNE 1$ ; yea, skip setting of owner $CURJOB ; get current job MOV R0,T$OWNR(R4) ; make it the new owner .CALL @K$ENBL(R4),R4 ; enable keyboard interrupts 1$: INC T$OCNT(R4) ; increment open count MOV R4,R0 ; pointer to device structure is to be used ; as argument to I/O requests CLC ; no error .RETRN ; TTYPUT, put a character ; input: pointer to device structure, character ; output: character is put into input buffer list, XON/XOFF is interpreted, ; BEL is sent if buffer is full, $DONE for terminal if anyone waiting ; return: none TTYPUT: .ENTRY MOV 6(R5),R4 ; first argument: device TST T$OCNT(R4) ; device opened? BEQ 3$ ; no, return MOV 10(R5),R3 ; second argument: character CMPB #C$XOFF,R3 ; is it XOFF? BEQ 1$ ; yea, switch off output CMPB #C$XON,R3 ; is it XON? BEQ 2$ ; yea, switch on output MOV I$LIST(R4),R2 ; get input buffer list CMP B$CCNT(R2),I$TAHD(R4) ; type-ahead exhausted? BLO 4$ ; nay, input character MOVB #C$BEL,O$OOBB(R4) ; yea, beep .CALL @P$ENBL(R4),R4 ; enable printer interrupt .RETRN 4$: .CALL PUTC,R4,R2,R3 ; input character (device, list, char) BCC 5$ ; no error, continue MOVB #7,O$OOBB(R4) ; buffer was full, beep .CALL @P$ENBL(R4),R4 ; enable printer interrupt 5$: BIT #T$WAIT,T$MODE(R4) ; anyone waiting for characters? BEQ 3$ ; nay, skip do not wake up BIC #T$WAIT,T$MODE(R4) ; clear wait bit $DONE #^RTTY,T$NUM(R4) ; wake up anyone waiting 3$: .RETRN 1$: .CALL @P$DSBL(R4),R4 ; disable printer interrupt MOV #GENERR,T$GETC(R4) ; replace output routine MOV #GENERR,P$ENBL(R4) ; replace interrupt enable routine .RETRN 2$: MOV #TTYGET,T$GETC(R4) ; restore output routine MOV P$BACK(R4),P$ENBL(R4) ; restore interrupt enable routine .CALL @P$ENBL(R4),R4 ; enable printer interrupt .RETRN ; TTYGET, get a character ; input: pointer to device structure ; output: character is removed from buffer ; return: carry from GETC call or cleared if out-of-band data is returned ; R0 character from buffer TTYGET: .ENTRY MOV 6(R5),R4 ; argument: device MOV O$OOBB(R4),R0 ; get out-of-band data BNE 1$ ; out-of-band data valid, use it .CALL GETC,R4,O$LIST(R4) ; otherwise, get character from buffer .RETRN 1$: CLR O$OOBB(R4) ; clear out-of-band buffer CLC ; no error .RETRN ; PUTC, put character in list ; input: pointer to device structure, pointer to buffer list, character ; output: character is put into list ; return: carry set on error, clear otherwise PUTC: .ENTRY MFPS -(SP) MTPS #340 ; we do not want to be interrupted MOV 6(R5),R2 ; first argument: device MOV 10(R5),R4 ; second argument: buffer list TST B$HEAD(R4) ; is there a buffer in the list? BNE 4$ ; yea, use it TST T$BCNT(R2) ; check buffers left to use BEQ 3$ ; none, error .ALLO B$HEAD(R4) ; get new buffer BCS 3$ ; allocation failed, error DEC T$BCNT(R2) ; one less buffer available now INC B$HEAD(R4) ; adjust HEAD pointer MOV B$HEAD(R4),B$TAIL(R4) ; this will also be new TAIL INC B$HEAD(R4) ; advance HEAD pointer to first char CLR B$CCNT(R4) ; no characters yet BR 1$ ; done here 4$: MOV B$TAIL(R4),R0 ; get TAIL pointer BIC #177760,R0 CMP #17,R0 ; is this buffer full? BNE 1$ ; nay, insert character TST T$BCNT(R2) ; still buffers left? BEQ 3$ ; nay, error .ALLO R0 ; get new buffer BCC 2$ ; continue if no error 3$: MTPS (SP)+ SEC ; indicate error .RETRN 2$: DEC T$BCNT(R2) ; one less buffer available .APPND R0,B$TAIL(R4) ; append this buffer 1$: INC B$TAIL(R4) ; increment TAIL pointer INC B$CCNT(R4) ; increment character count MOVB 12(R5),@B$TAIL(R4) ; store character from argument MTPS (SP)+ CLC ; no error .RETRN ; GETC, get character from list ; input: pointer to device structure, pointer to buffer list ; output: character removed from buffer ; return: carry set on error, cleared otherwise ; R0 character from buffer GETC: .ENTRY MFPS -(SP) MTPS #340 ; we do not want to be interrupted MOV 6(R5),R2 ; first argument: device MOV 10(R5),R4 ; second argument: buffer list TST B$CCNT(R4) ; any characters in buffer? BNE 1$ ; yea, get one MTPS (SP)+ SEC ; indicate error .RETRN 1$: MOVB @B$HEAD(R4),R3 ; get character from HEAD pointer DEC B$CCNT(R4) ; decrement character count MOV B$HEAD(R4),R0 ; get head pointer BIC #177760,R0 CMP #17,R0 ; buffer empty? BNE 2$ ; nay, finish BIC #17,B$HEAD(R4) ; get pointer to next buffer MOV @B$HEAD(R4),R0 ; unlink the buffer .FREE B$HEAD(R4) ; and return it to FRELST INC T$BCNT(R2) ; one more buffer available MOV R0,-(SP) ; save new HEAD buffer $DONE #^RTTY,#^RBUF ; wake up anyone waiting for buffers MOV (SP)+,B$HEAD(R4); restore new HEAD buffer BEQ 3$ ; skip adjusting if zero INC B$HEAD(R4) ; adjust HEAD pointer 2$: INC B$HEAD(R4) ; advance HEAD pointer to next character 3$: MOV R3,R0 ; return character MTPS (SP)+ CLC ; no error .RETRN ; READ, I/O read function ; input: buffer address and size, pointer to device structure ; output: characters read in buffer ; return: carry set on error, clear otherwise ; R0 number of characters read READ: .ENTRY MOV 6(R5),R4 ; first argument: I/O request packet CMP #4,IO$SIZ(R4) ; READ should have a size of 4 BEQ 2$ ; continue if equal 1$: MOV #IO$INV,R0 ; invalid request SEC ; indicate error .RETRN 2$: MOV 10(R5),R3 ; second argument: device structure $CURJOB ; get current job CMP R0,T$OWNR(R3) ; is it the owner? BNE 1$ ; nay, error CLR R2 ; clear character count 3$: MFPS -(SP) MTPS #340 ; we do not want to be interrupted .CALL GETC,R3,I$LIST(R3) ; get character BCC 4$ ; continue if no error BIS #T$WAIT,T$MODE(R3) ; set wait flag $WAIT #^RTTY,T$NUM(R3) ; and wait for this terminal MTPS (SP)+ BR 3$ 4$: MTPS (SP)+ BIT #T$LINE,T$MODE(R3) ; are we in line mode? BNE 5$ ; yea, do line mode processing ; nay, return character in R0 CLC ; no error .RETRN 5$: MOV IO$DAT+2(R4),R1 ; get buffer pointer BIT #T$COOK,T$MODE(R3) ; cooked mode? BEQ 10$ ; nay, skip special processing CMPB #C$CC,R0 ; Ctrl-C? BEQ 1$ ; abort with error CMPB #C$CR,R0 ; carriage return? BNE 13$ JMP 12$ ; yea, end reading 13$: CMPB #C$BS,R0 ; backspace? BEQ 6$ ; yea, do delete CMPB #C$DEL,R0 ; delete? BEQ 6$ ; yea, do delete 10$: CMP R2,IO$DAT(R4) ; buffer full? BHIS 8$ ; yea, beep 11$: MOVB R0,(R1)+ ; store character INC R2 ; increment character count MOV R1,IO$DAT+2(R4) ; save buffer pointer BIT #T$COOK,T$MODE(R3) ; cooked mode? BNE 14$ ; yea, do echo CMP R2,IO$DAT(R4) ; buffer full? BHIS 9$ ; yea, end reading 14$: BIT #T$ECHO,T$MODE(R3) ; echo on? BEQ 3$ ; nay, skip echo .CALL PUTC,R3,O$LIST(R3),R0 ; echo character .CALL @P$ENBL(R3),R3 ; enable printer interrupt BR 3$ ; read on 6$: TST R2 ; characters in buffer? BEQ 8$ ; nay, beep DEC R2 ; decrement character count DEC R1 ; rewind buffer pointer MOV R1,IO$DAT+2(R4) ; store buffer pointer BIT #T$ECHO,T$MODE(R3) ; echo on? BEQ 3$ ; nay, skip echoing delete BIT #T$DELM,T$MODE(R3) ; special delete mode? BNE 7$ ; yea, erase character .CALL PUTC,R3,O$LIST(R3),#C$BACK ; no, print backslash .CALL @P$ENBL(R3),R3 ; enable printer interrupt JMP 3$ ; read on 7$: .CALL PUTC,R3,O$LIST(R3),#C$BS ; backspace cursor .CALL PUTC,R3,O$LIST(R3),#C$SPC ; overwrite character .CALL PUTC,R3,O$LIST(R3),#C$BS ; backspace cursor .CALL @P$ENBL(R3),R3 ; enable printer interrupt JMP 3$ ; read on 8$: .CALL PUTC,R3,O$LIST(R3),#C$BEL ; make some noise .CALL @P$ENBL(R3),R3 ; enable printer interrupt JMP 3$ ; read on 9$: BIT #T$ECHO,T$MODE(R3) ; echo on? BEQ 12$ ; nay, finish .CALL PUTC,R3,O$LIST(R3),R0 ; echo character .CALL @P$ENBL(R3),R3 ; enable printer interrupt 12$: MOV R2,R0 ; return character count CLC ; no error .RETRN ; WRITE, I/O write function ; input: buffer address and size, pointer to device structure ; output: buffer contents written to device ; return: carry set on error, clear otherwise ; R0 number of bytes written WRITE: .ENTRY MOV 6(R5),R4 ; first argument: I/O request packet CMP #4,IO$SIZ(R4) ; WRIT should be of size 4 BEQ 2$ ; continue if it is 1$: MOV #IO$INV,R0 ; illegal request SEC ; indicate error .RETRN 2$: MOV 10(R5),R3 ; second argument: device structure $CURJOB ; get current job CMP R0,T$OWNR(R3) ; is it the owner? BEQ 3$ ; yea, continue writing BIT #T$EXCL,T$MODE(R3) ; exclusive mode? BNE 1$ ; yea, error 3$: MOV IO$DAT(R4),-(SP) ; save byte count BEQ 9$ ; zero byte count means we're done 4$: TST T$ACNT(R3) ; any asynchronous writes in progress? BEQ 5$ ; nay, continue writing $WAIT #^RTTY,T$NUM(R3) ; yea, wait for this terminal BR 4$ ; try again 5$: MOV IO$DAT+2(R4),R2 ; get buffer pointer 6$: MOVB (R2),R0 ; get character from buffer .CALL PUTC,R3,O$LIST(R3),R0 ; print character BCC 7$ ; continue if no error .CALL @P$ENBL(R3),R3 ; otherwise enable printer interrupt $WAIT #^RTTY,#^RBUF ; and wait for buffer BR 6$ ; then try again 7$: BIT #7,IO$DAT(R4) ; 7 characters print? BNE 8$ ; nay, continue .CALL @P$ENBL(R3),R3 ; yea, enable printer interrupt 8$: INC R2 ; increment buffer pointer DEC IO$DAT(R4) ; decrement byte count BNE 6$ ; repeat if not done .CALL @P$ENBL(R3),R3 ; enable printer interrupt 9$: MOV (SP)+,R0 ; return original byte count CLC ; no error .RETRN ; MODE, I/O mode function ; input: new mode word, pointer to device structure ; output: mode word into T$MODE if owner of device ; return: carry set on error, clear otherwise MODE: .ENTRY MOV 6(R5),R4 ; first argument: I/O request packet CMP #2,IO$SIZ(R4) ; MODE should be of size 2 BEQ 2$ ; continue if it is 1$: MOV #IO$INV,R0 ; invalid request SEC ; indicate error .RETRN 2$: MOV 10(R5),R3 ; second argument: device structure $CURJOB ; get current job CMP R0,T$OWNR(R3) ; is it the owner? BNE 1$ ; nay, error MOV IO$DAT(R4),R0 ; get new MODE word BIT #T$SIZE,R0 ; new type-ahead size given? BEQ 3$ ; nay, skip MOV #T$SIZE,R1 COM R1 BIC R1,R0 ; leave only new type-ahead size MOV R0,I$TAHD(R3) ; set new type-ahead size MOV IO$DAT(R4),R0 ; restore new MODE word BIC #T$SIZE,R0 ; mask out type-ahead size 3$: MOV #T$BITS,R1 COM R1 BIC R1,R0 ; leave only settable flags MFPS -(SP) MTPS #340 ; we do not want to be interrupted BIC #T$BITS,T$MODE(R3) ; clear all flags XOR R0,T$MODE(R3) ; set new flags MTPS (SP)+ CLC ; no error .RETRN ; BSIZE, I/O bsize function ; input: pointer to device structure ; output: none ; return: carry set on error, clear otherwise ; R0 size of type-ahead buffer BSIZE: .ENTRY MOV 6(R5),R4 ; first argument: I/O request packet CMP #2,IO$SIZ(R4) ; BSIZ should be of size 2 BEQ 2$ ; continue if it is 1$: MOV #IO$INV,R0 ; invalid request SEC ; indicate error .RETRN 2$: MOV 10(R5),R3 ; second argument: device structure MOV I$TAHD(R3),R0 ; return type-ahead size CLC ; no error .RETRN ; CLOSE, I/O close routine ; input: pointer to device structure ; output: input buffer list freed ; return: carry set on error, clear otherwise CLOSE: .ENTRY MOV 6(R5),R4 ; first argument: I/O request packet CMP #2,IO$SIZ(R4) ; CLOS should be of size 2 BEQ 2$ ; continue if it is 1$: MOV #IO$INV,R0 ; invalid request SEC ; indicate error .RETRN 2$: MOV 10(R5),R3 ; second argument: device structure $CURJOB ; get current job CMP R0,T$OWNR(R3) ; is it the owner? BNE 5$ ; if not, do not discard input .CALL @K$DSBL(R3),R3 ; disable keyboard interrupt CLR I$CCNT(R3) ; clear input character count 3$: BIC #17,I$HEAD(R3) ; convert HEAD pointer to buffer pointer BEQ 4$ ; get out if no buffer MOV @I$HEAD(R3),R1 ; save next buffer .FREE I$HEAD(R3) ; free buffer MOV R1,I$HEAD(R3) ; repeat with next buffer BNE 3$ 4$: CLR I$TAIL(R3) ; clear TAIL pointer 5$: DEC T$OCNT(R3) ; decrement open count BNE 8$ ; if still opened, we're done 6$: TST T$ACNT(R3) ; any asynchronous writes in progress? BEQ 7$ ; nay, done .CALL @P$ENBL(R3),R3 ; enable printer interrupt $WAIT #^RTTY,T$NUM(R3) ; wait for this terminal BR 6$ ; try again 7$: .CALL @P$ENBL(R3),R3 ; enable printer interrupt 8$: $IODONE R4 ; clear I/O channel CLC ; no error .RETRN OPEN: ; no open routine GENERR: SEC RTS R5 IOREQ: .IOHND .PSECT DATA .IOTAB READ,WRITE,GENERR,OPEN,CLOSE,BSIZE,MODE TTYTAB::.BLKW NTTY FRELST::.BLKW 1 IORQP: .BLKW 5 .END TTYDRV