.MCALL .MODULE .MODULE PI,VERSION=23,COMMENT= ; Copyright (c) 1998 by Mentec, Inc., Nashua, NH. ; All rights reserved ; ; This software is furnished under a license for use only on a ; single computer system and may be copied only with the ; inclusion of the above copyright notice. This software, or ; any other copies thereof, may not be provided or otherwise ; made available to any other person except for use on such ; system and to one who agrees to these license terms. Title ; to and ownership of the software shall at all times remain ; in Mentec, Inc. ; ; The information in this document is subject to change without ; notice and should not be construed as a commitment by Digital ; Equipment Corporation, or Mentec, Inc. ; ; Digital and Mentec assume no responsibility for the use or ; reliability of its software on equipment which is not supplied ; by Digital or Mentec, and listed in the Software Product ; Description. .SBTTL INSTALLATION CODE ;+ ; PI is installed via the system handler offset by the bootstrap on ; Professional 300 Series (PC) computers only. It is a resident handler ; that resides above RMON but below the system handler in low memory. There ; is a special protocol that the bootstrap and the PI installation code ; use to properly install PI and to hook RMON to support the PC. ; ; Bootstrap loads PI into memory immediately after it loads the system handler ; but before loading the monitor. This is done by reading in the first ; block of the PI handler into the bootstrap's internal buffer (BUFFB), ; determining the handler's size, and then reading the handler into ; low memory immediately below the system device. The bootstrap then ; loads and relocates the monitor. After it is done with this, it reads a ; special PC hook list from a bootstrap overlay into BUFFB+1400 and reads ; the PI installation code into BUFFB. The PI installation code then loads ; a special PC hook list from a PI overlay into BUFFB+1000. PI then hooks ; the monitor according to the specification of the hook lists. ; ; The following registers need to be set up for PIINST by BSTRAP: ; ; R0 contains the block number of PI(X).SYS on SY: ; R1 contains the top of low memory (normally 160000 (octal)) ; R3 contains the entry point of PI in low memory (it hasn't ; had the monitor's load relocation bias (R4) added in yet) ; R4 contains the load relocation bias for the monitor ;- .DRINS PI BR O.BAD ;PI cannot be installed as regular handler PIINST: MOV R0,(PC)+ ;Get PIBLK: .WORD 0 ; block number of PI handler on SY: MOV R0,RDBLK ;Get block number of PI handler on SY: ; ADD R4,R3 ;Compute PI SUB #PISTRT+6,R3 ; relocation bias .ADDR #1000,R0 ;Compute BUFFB + 1000 buffer pointer PICly MOV R0,RDBUFF ; and store it in RRB ADD #,RDBLK ;Compute overlay block number on SY: .ADDR #RRB,R0 ;Compute address of read request block PICly .READC CODE=NOSET ;Read PI relocation table into ; BSTRAP buffer (really a .READW) BCS O.BAD ;Can't install PI because of read error MOV RDBUFF,R0 ;Get pointer to PI relocation table 1$: .ADDR #1$,@SP,PUSH ;Put start of loop address on stack CALL GETWRD ;Get id and count word MOV (SP)+,R5 ; from BSTTBL BEQ DOREL ;If = 0, we are done hooking CMP (R0)+,R5 ;Does first table agree with second table? BNE NOTYET ;Skip past rest of this PITBL entry TST R5 ;If > 0, leave as BSTTBL=loc, PITBL=val BPL 2$ ;If < 0, change to CALL FLIP ; BSTTBL=val, PITBL=loc 2$: CALL GETWRD ;Get address relocation MOV (SP)+,R1 ; indicator word MOV (R0)+,R2 ;Get value relocation indicator word 3$: CALL GETWRD ;Get address to hook ROR R1 ;Is this address absolute? BCC 4$ ;Branch if yes ADD R4,@SP ;Else relocate address 4$: MOV (R0)+,-(SP) ;Get value to hook location with ROR R2 ;Is this value absolute? BCC 5$ ;Branch if yes ADD R3,@SP ;Relocate value 5$: MOV (SP)+,@(SP)+ ;Hook the location with the value DECB R5 ;Any more hooks in this segment? BNE 3$ ;Yes, continue hooking RETURN ;If we called FLIP then call FLIP back; and ; go see if there is another segment to hook O.BADX: TST (SP)+ ;Pop stack, set carry, and return O.BAD: SEC RETURN .ASSUME . LE 400 ;Must not overlay SET table . = 400 .WORD 0 ;No SET options for PI NOTYET: MOV -(R0),R2 ;Get PI table id/count word BEQ O.BADX ;Don't install if there isn't a PI table MOVB R2,R2 ;Isolate count byte ASL R2 ;Change word offset to byte offset CMP (R2)+,(R2)+ ;Skip the id/count and rel/abs flag words ADD R2,R0 ;Skip over this PI table but SUB R2,...OFF ; leave pointer at current BSTRAP table RETURN DOREL: .ADDR #VIDIDS,R0 ;R0 -> video id # list 1$: MOV (R0)+,@SP ;@SP = next video id # to try BEQ O.BADX ;Don't install if we couldn't find video CALL $GTSLT(R3) ;Get video slot # in @SP BCS 1$ ;Branch if $GTSLT failed MOV (SP)+,R5 ;Get video option slot number CMP #,#<2*BLK> ;Do not install PI unless code BHI O.BAD ; and $REL tables fit in 2 blocks MOV #,RDBLK ;Get relative block number of $REL overlay MOV PIBLK,R2 ;Get block number to start of PI(X).SYS in R2 ADD R2,RDBLK ;Make block number absolute SUB #BLK,RDBUFF ;Buffer starts at BUFFB in BSTRAP and we MOV #BLK,RDWCNT ; read 2 blocks .ADDR #RRB,R0 ;Compute address of read request block PICly MOV RDBUFF,R1 ;Get address to JMP to after overlay read JMP RDOVR(R3) ;Call overlay read routine in resident PI GETWRD: MOV @SP,-(SP) ;Push return address on stack 1 level deeper ...OFF = . + 2 MOV BSTTBL-PITBL(R0),2(SP) RETURN FLIP: CALL 1$ CALL @(SP)+ 1$: MOV R3,R2 ;Switch R3 MOV R4,R3 ; and R4 MOV R2,R4 ; relocation biases ADD ...OFF,R0 ;R0 -> corresponding entry in other table NEG ...OFF ;Adjust offset to point to entry in this table RETURN RRB: .BYTE 0 ; channel number .BYTE .READ ; read request subcode RDBLK: .WORD 0 ; block number RDBUFF: .WORD 0 ; buffer is BUFFB + 1000 in BSTRAP RDWCNT: .WORD PISIZE ; word count .WORD 0 ; wait mode VIDIDS: ;Video ID table .WORD $VD350 ;PRO 350 ID (1002) .WORD $VD380 ;PRO 380 ID (50) .WORD 10000!$VD380 ;PRO 380 ID (with EBO) .WORD $IVIS ;IVIS ID .WORD 0 .ASSUME . LE 1000 ;Installation code must fit in block 0 .SBTTL HANDLER ENTRY POINT PIBASE ==: 0 .DRBEG PI ;+ ; $GTVEC, $GTCSR, and $GTSLT each have a fixed entry point for BSTRAP's ; benefit. So don't change the following 4 BR and .BR lines!!!! ;- .ENABL LSB BR PIREQ ;Go do PI request BR $GTVEC ;Go to $GTVEC routine BR $GTCSR ;Go do $GTCSR routine .BR $GTSLT ;Go do $GTSLT routine ;+ ; $GTSLT - Returns option slot number of a PRO3xx device ; ; Input: @SP = hardware device id # ; ; Calling sequence: ; ; CALL $GTSLT ; ; Output: @SP = slot number if C=0 ; = random (device does not exist) if C=1 ;- $GTSLT::CALL GTSLT ;We need an extra word on the stack RETURN ;Return ;+ ; $GTCSR - Returns the CSR for PRO3xx device in an option slot ; ; Input: @SP = hardware device id # ; ; Calling sequence: ; ; MOV @#SYSPTR,Rn ; CALL @GETCSR(Rn) ; ; Output: @SP = CSR (device base memory address) if C=0 ; = random (device does not exist) if C=1 ;- $GTCSR::CALL GTSLT BCS 1$ SWAB 2(SP) ASR 2(SP) ADD #PC$CSR,2(SP) ;Compute CSR and clear carry 1$: RETURN ;+ ; $GTVEC - Returns vector A for PRO3xx device in an option slot ; ; Input: @SP = hardware device id # ; ; Calling sequence: ; ; MOV @#SYSPTR,Rn ; CALL @GETVEC(Rn) ; ; Output: @SP = vector A if C=0 ; = random (device does not exist) if C=1 ;- $GTVEC::CALL GTSLT BCS 2$ ASL 2(SP) ASL 2(SP) ASL 2(SP) ADD #PC$VEC,2(SP) ;Calculate base vector and clear carry 2$: RETURN GTSLT: .ADDR #PIEND,R0,PUSH ;Point to option slot device id table MOV R0,-(SP) 3$: CMP @R0,#-1 SEC BEQ 4$ CMP (R0)+,8.(SP) BNE 3$ SUB @SP,R0 ;Calculate which entry in table matched ASR R0 ;Convert byte to word offset and clear carry DEC R0 ;*C* 4$: MOV R0,8.(SP) ;*C* MOV (SP)+,R0 ;*C* Pop start of table address from stack MOV (SP)+,R0 ;*C* Restore R0 RETURN .SBTTL ABORT ENTRY POINT PIINT == . + 2 .IF EQ MMG$T RETURN .IFF ;EQ MMG$T CALL MAPKBD ;Map PAR 1 to PIK region CALLR @#ABORT $REL .-2 ABORT PIK .ENDC ;EQ MMG$T PIREQ: .IF NE MMG$T CALL MAPKBD ;Map PAR 1 to PIK region .IFTF ;NE MMG$T CALL @#SPFUN ;Call SPFUN code $REL .-2 SPFUN PIK .IFT ;NE MMG$T DRFIN:: TST (SP)+ ;Get rid of MAPKBD coroutine address MOV (SP)+,@#KISAR1 ;Restore PAR1 mapping .IFTF ;NE MMG$T .DRFIN PI .IFT ;NE MMG$T $DECTCE:: CALL MAPVD ;Map video code ;;; CALL STPCUR ;;; CALLR DECTCE ;Call cursor routine and restore mapping .ENDC ;NE MMG$T PI$VER::.ASCIZ /506/ .EVEN RDOVR:: .READC CODE=NOSET ;Read PI $REL overlay into BUFFB ; BSTRAP buffer (really a .READW) ; R0 is already set up by PIINST BCS 7$ ;If error reading overlay, don't install PI JMP @R1 ;Execute the PI $REL overlay code .IF NE MMG$T ;If XM MAPVD:: MOV @SP,-(SP) ;Push return address deeper on stack MOV @#KISAR1,2(SP) ;Save current kernel PAR1 mapping MOV #.-.,@#KISAR1 ;Map kernel PAR1 to extended memory region P1VD ==: .-4 ;Value to use for PAR1 BR 5$ MAPKBD::MOV @SP,-(SP) ;Push return address deeper on stack MOV @#KISAR1,2(SP) ;Save current kernel PAR1 mapping MOV #.-.,@#KISAR1 ;Map kernel PAR1 to extended memory region P1KBD ==: .-4 ;Value to use for PAR1 5$: CALL @(SP)+ ;Call caller back as a coroutine MOV (SP)+,@#KISAR1 ;Restore kernel PAR1 RETURN ;Return to caller's caller .ENDC ;MMG$T 6$: MOV #16.,PCTIK ;;;Re-initialize PC tick counter RTI ;;;Drop this tick on the floor PICLOK::TST @#173030 ;;;Prime clock to interrupt on next tick DEC (PC)+ ;;;Count off tick PCTIK: .WORD 16. BEQ 6$ ;;;Drop every 16th tick LKINT = 0 JLKINT == . + 2 JMP @#LKINT ;;;Go do normal RT clock tick processing ; JLKINT is hooked with LKINT from RMON PIHK06::ADD #2,@SP ;Skip 1 word unused instruction PIHK01::TST @#173500 MOV #31,@#173202 ;Enable input interrupts 7$: RETURN ERRHK: ADD #14,@SP BR BUFMT PIHK02::ADD #14,@SP ;Skip 4 words of unused instructions BR 8$ PIHK04:: TTOEN1::ADD #2,@SP ;Enable the console output interrupts 8$: MFPS -(SP) ;Save the PS BIS #PR7,@#PS ;Set the priority to 7 so we won't be interrupted MOV SP,(PC)+ ;Tell VDCURS routine that buffer is not empty VDFLAG:: .WORD 0 ;0 = buffer empty, non-0 = buffer not empty BIT #VDDIE$,@(PC)+ ;Is end-of-transfer interrupt enabled $VDCSR:: .WORD VD$CSR ;This is relocated by PI installation ; code to point to the video CSR BNE 10$ ;Branch if yes TST PRIO0 ;Has video said to leave it alone? BNE 9$ ;Yes, so don't turn on interrupts yet BIS #VDDIE$,@$VDCSR ;Generate an end-of-transfer interrupt BR 10$ 9$: MOV #100000,REENAB ;Tell video to turn on interrupts when it ; is ready for them 10$: MTPS (SP)+ ;Restore the PS RETURN PIHK05:: PIHK10:: PIHK12::ADD #2,@SP PIHK03:: BUFMT: MFPS -(SP) ;Save the PS BIS #PR7,@#PS ;Set the priority to 7 so we won't be interrupted CLR VDFLAG ;Tell VDCURS routine that buffer is empty CLR REENAB ;Tell video not to turn on end-of- ; transfer interrupts when it is ; exiting the critical region BIC #VDDIE$,@$VDCSR ;Turn off end-of-transfer interrupts MTPS (SP)+ ;Restore the PS RETURN PIHK07::MOVB R0,VIDBUF ;Put char in pseudo-transmitter buffer BR OUTCHR ;Tell video firmware to do its thing PIHK13::MOVB (R1)+,VIDBUF ;Put char in pseudo-transmitter buffer BR OUTCHR ;Tell video firmware to do its thing NULHK:: CLRB VIDBUF ;Put null in pseudo-transmitter buffer BR OUTCHR ;Call video firmware and it will return PCHHK1::MOVB -(R4),(PC)+ ;Put char in pseudo-transmitter buffer VIDBUF:: .WORD 0 ;Pseudo-transmitter buffer OUTCHR: CALL PUTCHR ;Call video routine to output character TSTB VIDBUF ;Caller needs Z-bit set correctly RETURN .DSABL LSB JSAV30 ==: . + 2 SAVE30::JMP @#SAVE30 ;This is hooked to point to RMON SAVE30 .END