.MCALL .MODULE .MODULE PIOVR,VERSION=24,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 REVISION HISTORY ; ;023 Came with 5.6 sources ; ;024 7-Oct-1998 Tim Shoppa Y2K support for PRO TOY clock ; .SBTTL INSTALLATION OVERLAY ;+ ; In order to get RT to run on the PRO, PI and the bootstrap each have a hook ; list containing locations that have to be modified and values to be stored ; at these locations. PI's hook list is at PITBL and BSTRAP's hook list is ; at BSTTBL. At PI installation time, both of these tables are placed in ; BSTRAP's BUFFB buffer along with the PI installation code which actually ; does the hooking specified by the hook lists. ; ; Hook lists are made up of a series of hook tables followed by a zero word ; as the terminator. ; ; Hook tables are identified by an id #. The hook code matches up a hook ; table in BSTRAP with the table in PI that has the same id #. One of ; the corresponding hook tables is a list of locations to be hooked; the ; other is a list of values to put in these hook locations. There is a ; mode bit in each table which indicates which table of a pair is the ; location list and which table is the value list. The mode bits in both ; of a pair of corresponding tables are always identical. A mode bit of 0 ; means that BSTRAP's table contains the location to hook and PI's table ; contains the value to use, while a mode bit of 1 means that PI's table ; contains the location to hook and BSTRAP's table contains the value to use. ; ; Each hook table also contains a word count. The word count tells how many ; hook locations or values that table contains. The word count may be between ; 1 and 16., inclusive. ; ; Each hook table also contains an abs/rel bit map. Each bit in the bit map ; indicates whether the corresponding hook location or hook value in that ; hook table is absolute or is relative. A bit of 0 indicates that the ; location or value is absolute; a 1 indicates that the location or value ; is relative. The bits are assigned from right to left; that is, bit 0 ; of the abs/rel word is used for the first hook item, bit 1 is used for the ; second, and so on. Hook items that are relative need to be relocated by ; the code performing the hooking, while hook items which are absolute need ; no such relocation. ; ; ; The format of the tables is the same for both: ; ; .BYTE Word count - this is the number of words in this table ; .BYTE 200*mode + id # (mode is 1 bit, id # is 7 bits) ; .WORD ABS/REL bit map ; .WORD Hook item 1 ; .WORD Hook item 2 ; | (The # of hook items (n) is the specified ; | by the value of the word count above.) ; .WORD Hook item n ; ; ; Note: Both BSTRAP's hook list and PI's hook list must have their hook ; tables arranged in ascending order of their table id numbers. ; (Only the 7-bit id # is used for ordering; the mode bit is ignored ; for ordering purposes.) ; ; ; PIHK13 is an unused hook here and in PI. It is unused because ; of the restriction that you cannot build a PRO system with powerfail ; messages (PWF$L = 1). PIHK13 would be used if PWF$L = 1. ; It is included here for completeness only. It must remain commented ; out. ; ; PIHK13 corresponds to hook HKPC13 in BSTRAP and RMONFB. HKPC13 is ; also commented out in BSTRAP. Because of the PI design, if PIHK13 ; is unused, HKPC13 must also be unused. ; ; BSTRAP can be modified to conditionalize HKPC13 for PWF$L. But ; PI is shipped prebuilt, and there is no way to modify it. ; ;- .PSECT INSOVR PITBL:: .BYTE 3. .BYTE 1. .WORD ^B111 ;ABS/REL bit map .WORD PICLOK .WORD KBDBUF .WORD KBOUT .BYTE 3. .BYTE 200+2. .WORD ^B111 .WORD JLKINT .WORD CTTIIN .WORD JSAV30 .BYTE 10. .BYTE 3. .WORD ^B1010101010 ;ABS/REL bit map CALL @#PIHK03 CALL @#PIHK04 CALL @#PIHK05 CALL @#PIHK07 JMP @#TTIIN1 .BYTE 2. .BYTE 4. .WORD ^B10 ;ABS/REL bit map MOV @#KBDBUF,-(SP) .BYTE 2. .BYTE 5. .WORD ^B10 ;ABS/REL bit map MOV @#KBDBUF,R0 .BYTE 4. .BYTE 6. .WORD ^B1010 ;ABS/REL bit map CALL @#PIHK01 CALL @#PIHK02 .BYTE 14. .BYTE 7. .WORD ^B10101010101010 ;ABS/REL bit map CALL @#PIHK06 JMP @#TTIIN1 ; CALL @#ERRHK CALL @#PIHK10 CALL @#TTOEN1 CALL @#PIHK12 ; The next word must remain commented out ; CALL @#PIHK13 CALL @#NULHK CALL @#PCHHK1 .WORD 0. PISIZE == . - PITBL / 2 .ASSUME PISIZE LE 128. BSTTBL== PITBL + 256. .SBTTL INIT - Second PI overlay - initialize the hardware ;+ ;INIT ;This routine initializes the registers and sets up the appropriate pointers ;for gathering characters and the font tables. This code is executed only ;once. So it better be right. ; ;This overlay is read in after OVRINS, although it is physically located ;before OVRINS. ;- .ENABL LSB . = PITBL+BLK ;Position to a block boundary INIT:: BIS R5,VIDON ;Make code to enable video interrupts MOV VD$SLT(R3),R5 ;Get controller register for slot ADD R5,$VDCSR(R3) ;Fix up pointer to video CSR 1$: TST VD$CSR(R5) ;Transfer done? BPL 1$ ;Branch until done BIC #,VD$CSR(R5) ;Ensure that 240 and 480 ;interlace is off .IF NE MMG$T ;If XM MOV #1000,R1 ;Assume PRO350 without EBO (bitmap chuck size) BIT #VDEBO$,VD$CSR(R5) ;Is EBO present? BNE 2$ ;Branch if not MOV #3000,R1 ;PRO350 with EBO (bitmap chunk size) 2$: .IFTF ;NE MMG$T MFPT ;Move from processor type CMPB R0,# ;J11? (i.e. PRO380?) BNE 3$ ;Branch if not MOV SP,PRO380(R3) ;Indidate that system is PRO380 .IFT ;NE MMG$T ASL R1 ;PRO380 has twice as much bitmap memory .IFTF ;NE MMG$T 3$: .IFT ;NE MMG$T MOV (SP)+,R0 ;Get next free RCB MOV R1,(R0)+ ;Store bitmap size in the RCB. MOV #170000,(R0)+ ;Now put the address in the RCB. MOV #140,(R0)+ ;Put in the status MOV #<^RBIT>,(R0)+ ;And store the name MOV #<^RMAP>,@R0 ; of the RCB owner MOV #,WDCHNK(R3) ;# of 32 word chunks 1 printable row MOV #,PXLRAD(R3) ;Address of line to move MOV #,PXLLPC(R3) ;# of words in line to move (LOOP ;COUNT) .ENDC ;NE MMG$T MOV #,CHRHIG(R3) ;Set Character height to 12 MOV #<177400>,SCLMSK(R3) ;Set def bit mask for scrolling reg value MOV #<256.>,MLISL(R3) ;Set memory lgth in scan lines for 240 mode MOV #<256.->,SCRNBD(R3) ;Y coordinate of next to last display row MOV #,BOTROW(R3) ;Set BOTROW to bottom of screen MOV #<*CHRTMP>,BOTLIN(R3) ;Set BOTLIN to last ROW of ;screen MOV BOTLIN(R3),SCRBOT(R3) MOV #<<*CHRTMP>+CHRTMP>,SCNLIN(R3) MOV #,ROWWRD(R3) ;Get # of words in a scan line MOV #170,VD$MBR(R5) ;Set bitmap start at 17000000 MOV #VDSNP$,VD$P1C(R5) ;Set pattern - plane 1 operation BIT #,VD$CSR(R5) ;Is extended bitmap option present? BNE 4$ ;Branch if not MOV #,VD$OPC(R5) ;Same for option planes BIS #,VD$CSR(R5) ;Enable color map MOV SS$BG(R3),VD$CMP(R5) ;Setup background color MOV SS$FG(R3),VD$CMP(R5) ;Setup foreground color 4$: CALL CLRSCR(R3) ;Clear the screen BIT #,VD$CSR(R5) ;Is extended bitmap option present? BNE 5$ ;Branch if not CLR VD$OPC(R5) ;No-operation control for option planes 2 & 3 5$: TSTB D$SCNM(R3) ;Dark or reverse screen? BEQ 6$ ;Branch if dark COM CLRPAT(R3) ;Set clear pattern to -1 for light 6$: CALL CLRSCR(R3) ;Clear the screen MOV R3,R0 ADD #ESCBUF,R0 ;Get pointer to ESCAPE sequence parameter buf. MOV R0,EBPTR(R3) ;And store it ADD #MAXPAR,R0 ;Set up pointer to end of buffer MOV R0,EBPTRE(R3) ;Store the PIC MOV R0,DEFBUF(R3) ;Address is also start of default flag buffer BIS #,VD$CSR(R5) ;Enable end of frame interrupt ; in video CSR BIC #,VD$CSR(R5) ;Disable transfer done interrupt ; in video CSR VIDON = . + 2 ;Contents are OR'ed with video slot # above MOV #30,@#173206 ;Turn on end of frame interrupt MOV VIDON,@#173212 ;Turn on transfer done interrupt MOV #173500,R5 ;R5 -> keyboard registers 7$: BIT #KBTRD$,KB$STA(R5) ;Is keyboard transmitter ready? BEQ 7$ ;Branch if not MOVB #KLEDOF,@R5 ;Send turn LED off command 8$: BIT #KBTRD$,KB$STA(R5) ;Is keyboard transmitter ready? BEQ 8$ ;Branch if not MOVB #,@R5 ;Clear all LEDs O.GOOD: CLC ;Allow PI to be installed RETURN ;Return to BSTRAP .DSABL LSB .ASSUME .-INIT LE 2*BLK ;Overlay must be at most 2 blocks .SBTTL OVRINS - First PI overlay ;+ ; R0 -- work register ; R1 -- work register ; R2 -- block number of PI(X).SYS ; R3 -- PIBASE value ; R4 -- RMON base ; R5 -- video slot number ;- . = INIT+<2*BLK> ;Position to a block boundary .ENABL LSB OVRINS:: MOV R1,(PC)+ ;Save start address of BUFFB BUFFBA: .WORD 0 MOV R2,(PC)+ PIBLK: .WORD 0 ;Start block of PI(X).SYS MOV R5,(PC)+ ; SLOTNO: .WORD 0 ;Video slot number ASH #7,R5 ;Compute video ADD #174000,R5 ; slot address MOV R5,VD$SLT(R3) ; and store in pointer in PI MOV @#JRMON,R4 ; point to RMON .IF NE MMG$T ADD R2,ORDBLK ; add in offset to PIX file MOV MEMPTR(R4),R0 ; get offset to memory tables **GVAL** ADD R4,R0 ; get real address MOV CORPTX(R0),R5 ; get offset to extended ALLOC **PEEK** ADD R4,R5 ; and real address 1$: CMP #-1,(R5)+ ; look for end of free list **PEEK** BNE 1$ ; loop until found ; R5 now points to handler RCBs 2$: ; look for an empty one CMP #-1,@R5 ; end of list? **PEEK** BEQ O.BAD ; yes, failure TST @R5 ; empty? **PEEK** BEQ 3$ ; yes, got one to use ADD #10.,R5 ; point to next BR 2$ ; keep trying 3$: MOV P1EXT(R4),R0 ; get address of P1EXT routine **GVAL** MOV (PC)+,R2 ; area needed PIXSIZ:: .WORD PIXTOP-PIXBAS+KTGRAN-1/KTGRAN ; amount to allocate MOV R3,-(SP) ; save R3 CALL XALLOC(R0) ; call routine to allocate it MOV (SP)+,R3 ; restore R3 BCS O.BAD ; failed .ASSUME R.BSIZ EQ 0 MOV R2,(R5)+ ; build RCB (put in size) **POKE** .ASSUME R.BADD EQ R.BSIZ+2 MOV R1,(R5)+ ; put address in RCB **POKE** MOV R1,P1VD(R3) ; save ext. mem. addr. for MAPX MOV R1,P1KBD(R3) ADD #,P1KBD(R3) ;Get ext. mem. addr. ; of PIK for MAPKBD .ASSUME R.BID EQ R.BADD+2 MOV #100100,(R5)+ ; put status in RCB **POKE** MOV (PC)+,(R5)+ ; put name in RCB **POKE** .RAD50 /PI / ; our Rad50 name MOV (PC)+,(R5)+ ; ... **POKE** .RAD50 /$ / MOV R5,(PC)+ ; save addres of next free RCB NXTRCB: .WORD 0 MOV @#PS,OLDPS ; save the PSW **IOPAGE** BIC #CMKERN,@#PS ; set current mode to Kernel **IOPAGE** PUSH @#KISDR1 ; save current mapping **IOPAGE** PUSH @#KISAR1 ; registers **IOPAGE** MOV R1,@#KISAR1 ; map to PIV extended region **IOPAGE** MOV #AP$ACF,@#KISDR1 ; ... **IOPAGE** .ADDR #OREAD,R0 ; address of read request block **PIC** .READC CODE=NOSET ; read into extended memory ; really a .READW BCS UNMAP0 ; failed ... kill install .ENDC ;NE MMG$T .ADDR #RELRM,R0 ; R0 -> RMON $REL list 4$: MOV (R0)+,R1 ; get next $REL list entry BEQ 5$ ; done this list ADD R3,R1 ; real address to relocate ADD R4,@R1 ; relocate using JRMon as base BR 4$ ; and do next .IF NE MMG$T ;If XM UNMAP0: POP @#KISAR1 ; restore mapping **IOPAGE** POP @#KISDR1 ; **IOPAGE** MOV OLDPS,@#PS ; restore psw **IOPAGE** .ENDC ;NE MMG$T O.BAD: SEC ;Don't allow PI to be installed RETURN 5$: .IF NE MMG$T .ADDR #RELRMV,R0 ; R0 -> RMONV $REL list 6$: MOV (R0)+,R1 ; get next $REL list entry BEQ 7$ ; done this list ADD R4,@R1 ; relocate using JRMon as base BR 6$ ; and do next 7$: .ENDC ;NE MMG$T .ADDR #RELPI,R0 ; R0 -> PI $REL list 8$: MOV (R0)+,R1 ; get next reloc list entry BEQ 9$ ; done this list ADD R3,R1 ; real address to locate ADD R3,@R1 ; relocate value in address BR 8$ ; and do next OSDTTM: .WORD .SDTTM .WORD DATE-OSDTTM ; Relocated to DATE at .SDTTM code DATE: .WORD 0 ; if problem with clock, HITIME: .WORD 0 ; initialize no date and LOTIME: .WORD 0 ; midnight 9$: .IF NE MMG$T .ADDR #RELPRV,R0 ; R0 -> PIRV $REL list 10$: MOV (R0)+,R1 ; get next reloc list entry BEQ 11$ ; done this list ADD R3,@R1 ; relocate value in address BR 10$ ; and do next 11$: .ADDR #$XMPI,R0 ; R0 -> PI and PIV $XMPTR list CALL FIXPAR ; Fill in the correct PAR values MOV P1KBD(R3),@#KISAR1 ; map to PIK extended region **IOPAGE** .ADDR #RELRMK,R0 ; R0 -> RMONK $REL list 12$: MOV (R0)+,R1 ; get next $REL list entry BEQ 13$ ; done this list ADD R4,@R1 ; relocate using JRMON as base BR 12$ ; and do next 13$: .ADDR #RELPRK,R0 ; R0 -> PIRK $REL list 14$: MOV (R0)+,R1 ; get next reloc list entry BEQ 15$ ; done this list ADD R3,@R1 ; relocate value in address BR 14$ ; and do next 15$: .ADDR #$XMPIK,R0 ; R0 -> PIK $XMPTR list CALL FIXPAR ; Fill in the correct PAR values POP @#KISAR1 ; restore mapping **IOPAGE** POP @#KISDR1 ; **IOPAGE** MOV #.-.,@#PS ; restore psw **IOPAGE** OLDPS =: .-4 ; ; if an error how to deallocate? .ENDC ;NE MMG$T YEAR: .BLKW 1 .BR MONTH MONTH: .BLKW 1 .BR DAY DAY: .BLKW 1 .BR HOUR HOUR: .BLKW 1 .BR MINUTE MINUTE: .BLKW 1 .BR SECND SECND: .BLKW 1 . = YEAR BIC #FREQ,CONFG1(R4) ;Force RT pseudo-clock to 60 Hertz TSTB @#CKCSR3 BPL 22$ 16$: TSTB @#CKCSR0 BMI 16$ .ADDR #YEAR,R0 MOV R0,R2 MOV @#CKYR,(R0)+ MOV @#CKMON,(R0)+ MOV @#CKDAY,(R0)+ MOVB @#CKHR,@R0 BMI 17$ CLR PM.OFF 17$: BIC #177600,(R0)+ MOV @#CKMIN,(R0)+ MOV @#CKSEC,(R0)+ BIT #CK.DM,@#CKCSR1 ;Is clock in BCD mode? BNE 19$ MOV #6.,R4 ;If BCD, to BCD -> Binary conversions 18$: MOV -(R0),R5 ASH #-4,R5 MUL #6,R5 SUB R5,@R0 SOB R4,18$ ; A TOY clock year in the range 72-99 implies 1900's, ; in the range 00-71 implies 2000's. 19$: MOV (R2)+,R4 ;Get year SUB #72.,R4 ;Get year relative to 1972 BPL 191$ ;Did we underflow? ;024 ADD #100.,R4 ;If so, we're in 2100's ;024 191$: MOV R4,R5 ;Now in range 0-127 ;024 BIC #^C000140,R5 ;Mask off era bits in R5 ;024 SUB R5,R4 ; (year-1972)mod32 in R4 ;024 ASL R5 ;Put the era bits in R5 ;024 SWAB R5 ; where we want them ;024 ADD R5,R4 ;R4 has era/year in RT form ;024 MOV (R2)+,R0 ;Get month ASH #5.,R0 ADD (R2)+,R0 ;Get day ASH #5,R0 ADD R4,R0 ;Get year relative to 1972 MOV R0,DATE BIT #CK.HM,@#CKCSR1 BNE 21$ SUB #12.,@R2 BEQ 20$ ADD #12.,@R2 20$: ADD #12.,@R2 PM.OFF =: .-2 21$: MOV (R2)+,R1 ;Get hours MOV #60.,R5 MUL R5,R1 ;Convert hours to minutes MOV R1,R4 ADD (R2)+,R4 ;Add in minutes MOV @R2,R1 ;Get seconds MUL R5,R1 ;Convert seconds to ticks MUL R5,R5 ;Same as a "MOV #3600.,R5" MUL R5,R4 ;Convert hours an minutes to ticks ADD R1,R5 ;Add all the ticks ADC R4 ; (Add double-word with single-word) MOV R4,HITIME MOV R5,LOTIME 22$: .ADDR #OSDTTM,R0 ADD R0,2(R0) ;Relocate ptr to DATE (Date and time block) .SDTTM CODE=NOSET ;Do a .SDTTM #OSDTTM,#DATE PICly MOV @#60,@#200 ;Copy Console Input start address to KB receiver vec MOV @#62,@#202 ;And the priority MOV @#100,@#230 ;Copy clock address to clock vector MOV @#102,@#232 ;And the priority MOV SLOTNO,R0 ;Get the slot number for the video vector ASL R0 ;Shift it over to bits 3-5 ASL R0 ASL R0 ADD #300,R0 ;Get the Interrupt A vector MOV R0,(PC)+ ;Save it VIDVEC: .WORD 0 ADD #4,R0 ;Add the offset for the Interrupt B vectors MOV @#64,(R0)+ ;Copy console output start address to ;video end-of transfer vector MOV @#66,@R0 ;And the priority MOV #173024,R1 ;R1 -> Clock CSR0 MOV #2*20!12,(R1)+ ;Set divider control and 64Hz BIS #100,(R1)+ ;Set PERIODIC INTERRUPT ENABLE ; MOV #173202,R0 ;Get Interrupt controller 1 CSR MOV #37,@#173202 ;Enable clock TST @R1 ;Prime clock to interrupt MOV #PR7,@#206 ;Priority for the KB transmitter MOV VIDVEC,R0 ;Get the video interrupt A vector MOV #VDCURS,@R0 ;Video end-of-frame interrupt vector ADD R3,(R0)+ MOV #PR7,@R0 ;Priority for it MOV VIDVEC,4(SP) ;Return the video interrupt vector to the monitor in R1 .IF NE MMG$T MOV NXTRCB,-(SP) ;Get address of next free RCB for INIT .ENDC ;NE MMG$T MOV SLOTNO,R5 ;Save SLOTNO for INIT MOV #,RDBLK ;Get relative block number of INIT overlay ADD PIBLK,RDBLK ;Add in PI(X).SYS start block number MOV BUFFBA,RDBUFF ;Buffer starts at BUFFB in BSTRAP .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 .DSABL LSB FIXPAR: 1$: MOV (R0)+,R1 ; get next reloc list entry BEQ 5$ ; done this list CMP @R1,#PI$C ; Does this pointer reference PI? BNE 2$ ; Branch if not MOV -(R1),R2 ; Get the 16-bit low memory pointer BIC #177700,@R1 ; Leave only the block word offset ADD #P1ADDR,(R1)+ ; Bias it to be a PAR1 virtual address ROL R2 ; Get the ROL R2 ; high 10 ROLB R2 ; bits of the pointer as SWAB R2 ; the PAR1 BIC #176000,R2 ; value in the MOV R2,@R1 ; low 10 bits BR 1$ ; and do the next 2$: .IF NE MMG$T CMP @R1,#PIK$C ; Does this pointer reference PIK? BNE 3$ ; Branch if not MOV P1KBD(R3),@R1 ; Store the PAR1 value for PIKBAS BR 1$ ; and do the next 3$: CMP @R1,#PIV$C ; Does this pointer reference PIV? BEQ 4$ ; Branch if OK .IFTF ;NE MMG$T JMP O.BAD ; Branch if not (invalid code) .IFT ;NE MMG$T 4$: MOV P1VD(R3),@R1 ; Store the PAR1 value for PIVBAS BR 1$ ; and do next .ENDC ;NE MMG$T 5$: RETURN RRB: .BYTE 0 ; channel number .BYTE .READ ; read request subcode RDBLK: .WORD 0 ; block number RDBUFF: .WORD 0 ; buffer is BUFFB in BSTRAP RDWCNT: .WORD 1000 ; word count = 2 blocks .WORD 0 ; wait mode .IF NE MMG$T OREAD: ORDCHN: .BYTE BOTCHN ; channel number .BYTE .READ ; request subcode ORDBLK: .WORD PIXBAS/BLK+.-. ; block number .WORD P1ADDR ; buffer is Par1 area .WORD PIXTOP-PIXBAS+1/2 ; word count .WORD 0 ; wait mode .ENDC ;NE MMG$T .ASSUME .-OVRINS LE 2*BLK ;Overlay must be at most 2 blocks .END