.TITLE MO V04.6 .IDENT /V04.6/ .enabl lc ; Updated 4-May-83 ; SPECIAL MODEM DRIVER FOR EXEC, A SMART TERMINAL PROGRAM ; Note: To use this driver under TSX+, you must create a ; driver for both RT-11 and TSX+, as TSX+ requries that all ; of it's handlers be known (installed) to RT-11. For RT-11 ; systems without memory management, set MMG$T=0. For RT-11 ; with memory management or TSX+ systems, set MMG$T=1. .IIF NDF MMG$T, MMG$T = 0 ;18-BIT I/O ; Change these values to correspond to the I/O board you are using MOADR = 176560 ;Modem serial I/O address MOVEC = 360 ;Modem serial I/O vector ; This handler is intended to be used with a smart terminal ; program called EXEC. It allows communications with a remote ; system at high baud rates, although the highest baud rate it ; has been tested at is 1200 baud. ; Created by: Robert Walraven ; Applied Science ; University of California, Davis 95616 ; (916) 752-0360 ; Modified by: Chuck Sadoian ; 821 Newton Drive ; Dinuba, Calif 93618 ; 209-591-2631 (work) .SBTTL MACRO DEFINITIONS .MACRO ADDR ADDRESS,REG MOV PC,REG ADD #ADDRESS-.,REG .ENDM .SBTTL PREAMBLE SECTION ; Declare symbols PR7 = 340 ;Priority 7 KISAR6 = 172354 ;Address of kernal PAR6 SI = 17 ;Shift into protocol CTRLS = 23 ;Xoff character CTRLQ = 21 ;Xon character EXEFLG = 40 ;Executive mode enabled bit HDERR = 1 ;Hard error bit .MCALL .DRDEF .DRDEF MO,375,HNDLR$!SPFUN$,0,MOADR,MOVEC .QELDF .SBTTL REGISTER DEFINITIONS MR$CSR == MO$CSR ;READ CONTROL REGISTER MR$VEC == MO$VEC ;READ VECTOR MRB == MR$CSR+2 ;READ DATA BUFFER MW$VEC == MR$VEC+4 ;WRITE VECTOR MW$CSR == MRB+2 ;WRITE CONTROL REGISTER MWB == MW$CSR+2 ;WRITE DATA BUFFER .SBTTL SPECIAL FUNCTION VALUES RD$ON = 377 ;Turn read interrupt on, set DTR RD$OF = 376 ;Turn read interrupt off, clear DTR IN$OFF = 375 ;Turn only the reader interrupts off WRT$Q = 374 ;Write in progress query BA$UD = 373 ;Set baud rate BR$K = 372 ;Send a break to the remote TST$CAR = 371 ;Test for modem carrier .SBTTL HEADER SECTION .DRBEG MO .SBTTL I/O INITIATION SECTION START: MOV MOCQE,R4 ;R4 points to CQE MOVB Q$FUNC(R4),R5 ;Pick up special function BNE SPFUN ;Branch if it is special MOV Q$WCNT(R4),R5 ;Get word count ASL R5 ;Make word count a byte count BCS MW ;If negative, WRITE BCC MOERR ;A read request if illegal JMP MOFIN ;Seeks complete immediately WAIT: RTS PC ; This section handles .WRITE requests MW: TST WRITFL ;Write already in progress? BNE WAIT ; If so, return immediately INC WRITFL ;Turn write flag on ASL Q$WCNT(R4) ;Make word count a byte count MOV Q$WCNT(R4),WCOUNT ;Save byte count ADDR WRTBUF,R5 ;R5 = address of WRTBUF MOV R5,WRTPTR ;Store it in WRTPTR MOV #WLEN,R3 ;R3 = Length of write buffer .IF EQ MMG$T ;If no memory management ADD #Q$WCNT,R4 ;Point to word count 50$: TST (R4) ;More chars to output? BEQ 60$ ; Branch if not INC (R4) ;Dec byte count (It's negative) MOVB @-(R4),(R5)+ ;Move char to internal buffer INC (R4)+ ;Bump pointer .IFF ;If memory management 50$: TST Q$WCNT(R4) ;More chars to output? BEQ 60$ ; Branch if not INC Q$WCNT(R4) ;Dec byte count (It's negative) JSR PC,@$GTBYT ;Get byte from user MOVB (SP)+,(R5)+ ;Put in internal buffer .ENDC DEC R3 ;Dec buffer count BNE 50$ ;Branch if still room MOV #WLEN,WCOUNT ;Else shorten count and go NEG WCOUNT ;After negating count 60$: TSTB -(R5) ;Was the last char zero? BNE 70$ ;Branch if not INC WCOUNT ;Else back up one char 70$: BIS #100,@#MW$CSR ;Enable interrupt FINISH: JMP MOFIN ;Clear queue element ;Here on hard errors MOERR: BIS #HDERR,@-(R4) ;Set hard error bit CLR @#MW$CSR ;Clear write interrupts CLR @#MR$CSR ;Clear read interrupts BR FINISH ; This section handles the SPECIAL FUNCTION requests SPFUN: CMPB R5,#RD$ON ;Turn on special read mode? BNE 10$ ;Branch if no MOV @#MR$VEC,SAVE1 ;Save contents of read interrupt vector MOV @#MR$VEC+2,SAVE2;Save read priority MOV @#MW$VEC,SAVE3 ;Save contents of write interrupt vector MOV @#MW$VEC+2,SAVE4;Save write priority ADDR MOINT,R3 ;Get address of read interrupt service MOV R3,@#MR$VEC ;and deposit in interrupt vector MOV #PR7,@#MR$VEC+2 ;Set priority at level 7 ADDR MWINT,R3 ;Get address of write interrupt service MOV R3,@#MW$VEC ;and deposit in interrupt vector MOV #PR7,@#MW$VEC+2 ;Set priority at level 7 MOV Q$BUFF(R4),POINT;Get pointer to user program MOV POINT,R3 ;Get start of header address in kernal space MOV R3,ADDR ;copy into ADDR ADD #12.,ADDR ;set ADDR to point to data buffer .IF NE MMG$T ;If memory management on MOV Q$PAR(R4),PARVAL ;Save user PAR6 value .ENDC MOV #102,@#MR$CSR ;Enable read interrupts, set DTR BR FINISH ;Clean up XON/XOFF stuff 10$: CMPB R5,#RD$OF ;Turn off special read mode? BNE 20$ ;Branch if no CLR @#MR$CSR ;Disable read interrupts, clear DTR JSR PC,VECTOR ;Restore original contents of vectors BR FINISH ;Return to user 20$: CMPB R5,#WRT$Q ;Write in progress query? BNE 30$ ;Branch if not .IF EQ MMG$T ;If memory management off MOVB WRITFL,@Q$BUFF(R4) ;Return write status flag .IFF ;If memory management on MOVB WRITFL,-(SP) ;Put flag on stack JSR PC,@$PTBYT ;Move it to user buffer .IFTF BR FINISH ;Return to user 30$: CMPB R5,#BA$UD ;Set baud rate? BNE 50$ ;Branch if not CLR R5 .IFT MOVB @Q$BUFF(R4),R5 ;Get baud rate .IFF JSR PC,@$GTBYT ;Get baud rate MOVB (SP)+,R5 ;under memory management .ENDC SWAB R5 ;Put baud rate in high byte 40$: BIS R5,@#MW$CSR ;Set the DLV11E BR FINISH 50$: CMPB R5,#BR$K ;Send a break? BEQ BREAK ;Yes, send it CMPB R5,#IN$OFF ;Turn interrupts off? BNE 60$ ;No BIC #100,@#MR$CSR ;Clear interrupts only JSR PC,VECTOR ;Restore original contents of vector BR FINISH 60$: CMPB R5,#TST$CAR ;Test for modem carrier? BNE MOERR ;No, return error JSR PC,CHECK BR FINISH BREAK: MOV #-1.,R5 ;Set counter BIS #1,@#MW$CSR ;Set break bit 10$: SOB R5,10$ ;Wait a bit BIC #1,@#MW$CSR ;Clear break bit BR FINISH ; This routine restores the contents of the modem interrupt vectors VECTOR: MOV SAVE1,@#MR$VEC ;Restore original contents of MOV SAVE2,@#MR$VEC+2;interrupt vectors MOV SAVE3,@#MW$VEC MOV SAVE4,@#MW$VEC+2 RTS PC ; This routine checks to see if a carrier is present on the DLV11E CHECK: BIT #10000,@#MR$CSR ;Carrier detected? BEQ 2$ ;No BIS #1,SPFLAG ;Set carrier bit in SPFUN flag BR 4$ ;and pass it to EXEC 2$: BIC #1,SPFLAG ;Clear carrier bit in SPFUN flag 4$: ADD #10.,Q$BUFF(R4) ;Point to SPFUN status flag in EXEC .IF EQ MMG$T ;If no memory management MOV SPFLAG,@Q$BUFF(R4) ;Set SPFUN status flag SUB #10.,Q$BUFF(R4) ;Point Q$BUFF back to RSIZE .IFF ;If memory management on MOV SPFLAG,-(SP) ;Put status on stack JSR PC,@$PTWRD ;and call the putword routine SUB #12.,Q$BUFF(R4) ;Point Q$BUFF back to RSIZE .ENDC BIT #1,SPFLAG ;Check to see how we should exit BNE 6$ TST (PC)+ ;Set carry to indicate carrier on 6$: SEC ;Clear carry to indicate carrier off RTS PC .SBTTL INTERRUPT SERVICE SECTION ;WRITE-READ VECTOR TABLE .DRVTB MO,MR$VEC,MOINT .DRVTB ,MW$VEC,MWINT ;WRITE INTERRUPT SERVICE .DRAST MW,4,MOABRT 10$: TST WCOUNT ;More chars to output? BEQ MWDONE ;If not, branch INC WCOUNT ;Dec byte count (it is negative) MOV WRTPTR,R4 ;Point to next char INC WRTPTR ;Increment pointer MOVB (R4),@#MWB ;Write the character RTS PC MWDONE: CLR @#MW$CSR ;Disable interrupts CLR WRITFL ;Clear write flag RTS PC ; READ INTERRUPT SERVICE .DRAST MO,4,MOABRT .IF NE MMG$T ;If memory managament on MOV @#KISAR6,-(SP) ;Save PAR6 MOV PARVAL,@#KISAR6 ;Map to user buffer .IFTF MOV POINT,R5 ;Get pointer to EXEC ADD #6,R5 ;Point to CSSTAT MOVB @#MRB,R4 ;Get character MOVB R4,TEMP ;Save 8 bit character BICB #200,R4 ;Strip parity BIT #EXEFLG,(R5) ;Executive mode enabled? BNE 12$ ;Yes, skip checks CMPB R4,#SI ;Protocol mode? BNE 6$ ;No, skip this BIS #EXEFLG,(R5)+ ;Else set protocol flag BR 2$ 6$: CMPB R4,#CTRLS ;Control-S? BNE 8$ ;No, skip INC (R5) ;Set pause flag BR 2$ 8$: CMPB R4,#CTRLQ ;Control Q? BNE 12$ ;No, pass character to ring buffer CLR (R5) ;Else clear pause flag BR 2$ 12$: MOVB TEMP,@ADDR ;Put character in ring buffer INC ADDR ;Bump address pointer (ADDR) MOV POINT,R5 ;Get start of header again TST (R5)+ ;bump to BCOUNT INC (R5)+ ;Increment BCOUNT, point to CNT DEC (R5) ;Dec ring buffer character count (CNT) BNE 2$ ;End of buffer? MOV POINT,R4 ;Yes, get pointer to EXEC again MOV (R4),(R5) ;Reset counter (CNT) to buffer size MOV R4,ADDR ;Put start of header in ADDR ADD #12.,ADDR ;Point ADDR to start of ring buffer 2$: .IFT ;If memory management on MOV (SP)+,@#KISAR6 ;Restore PAR6 .ENDC RTS PC MOABRT: CLR @#MW$CSR ;Turn off interrupts CLR @#MR$CSR CLR WRITFL ;Clear write flag JSR PC,VECTOR ;Restore interrupt vectors RTS PC .SBTTL DATA STORAGE SAVE1: .WORD 0 ;Area to save interrupt vector contents SAVE2: .WORD 0 SAVE3: .WORD 0 SAVE4: .WORD 0 PARVAL: .WORD 0 ;User PAR6 value POINT: .WORD 0 ;Pointer to EXEC ring buffer size ADDR: .WORD 0 ;Pointer to ring buffer TEMP: .WORD 0 ;Temporary character storage SPFLAG: .WORD 0 ;SPFUN status flag WRITFL: 0 ;Write in progress flag WCOUNT: 0 ;-(# of bytes to write) WRTPTR: 0 ;Pointer to next byte to write WRTBUF: .BLKB 256. ;Write buffer WBFEND: WLEN = WBFEND-WRTBUF .SBTTL I/O COMPLETION SECTION MOFIN: .DRFIN MO ;GO TO I/O COMPLETION .DREND MO .END