.MCALL .MODULE .MODULE RTTFW,VERSION=18,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. ; ; Author: David Fingerhut November 1984 ; ;++ ; REVISION HISTORY: ; Person Date Modification ; Deb S. 28-JAN-87 Re_enabled frame/done interrupt to fix problem ; of cursor permanently disappearing after GIDIS ; is started up. (REV001) ;-- .MCALL .RDBBK,.WDBBK,.RDBDF,.CRAW,.EXIT,.PRINT .MCALL .LOOKUP,.READW,.CRRG,.CLOSE,.ELRG,.ELAW .MCALL .TRPSET,.SPFUN,.GVAL,.POKE,.WRITW,.GTJB .MCALL .ENTER,.GTIM .SBTTL Video Hardware Parameters ; ; Pointers to video hardware registers. ; ; The initialization code locates the video hardware and modifies these ; values as necessary. ; .PSECT BKBA01 GBL,D,RW BAIDR:: .WORD 174400 ; 0 Identification register BARAR:: .WORD 174402 ; 2 ROM address register BACSR:: .WORD 174404 ; 4 CSR BAP1C:: .WORD 174406 ; 6 Plane-1 control register BAOPC:: .WORD 174410 ; 10 Option-plane control register (2 and 3) BACMP:: .WORD 174412 ; 12 Color map register BASCL:: .WORD 174414 ; 14 Scroll register BAX:: .WORD 174416 ; 16 Horizontal position register BAY:: .WORD 174420 ; 20 Vertical position register BACNT:: .WORD 174422 ; 22 Count register (decrements) BAPAT:: .WORD 174424 ; 24 Pattern register BAMBR:: .WORD 174426 ; 26 Memory base register NUMREG = 12. ; Number of Registers BACSRH::.WORD 174405 ; 4 High byte of control/status register BACSRL::.WORD 174404 ; 4 Low byte of control/status register ; CONSTANTS RMON == 54 ; Base of RMON JSW == 44 ; JSW VIRT$ == 2000 ; Virtual bit in JSW GETVEC == 436 ; Offset from RMON to $GTVEC routine S.SUFF = 412 ; Offset from RMON to handler suffix S.CNF1 = 300 ; Offset from RMON to config word 1 HWFPU$ = 100 ; CONFIG1 bit for FP11 float point hardware S.CNF2 = 370 ; Offset from RMON to config word 2 C2.PRO = 20000 ; Bit in CONFIG2 for PRO series SYSGEN = 372 ; Offset from RMON to sysgen features word P1EXT = 432 ; PAR1 externalization routine STASK$ = 40000 ; System job support VID380 == 50 ; Video ID for 380 VID350 == 1002 ; Video ID for 350 VID38E == 10050 ; Video ID for 380 with EBO CSOME == 2000 ; Color map enable bit CSSPL = 20000 ; Multi plane bit TRMMOD == 0 ; Offset into CONTEXT of terminal mode TMCMON == 1 ; Offset into TERMOD of color terminal bit BMPHSZ == 10000 ; Physical size of bitmap ALCHAN = 0 ; Channel for ALPH00 INT480 = 4 ; 480 interlace bit in CSR AL$TOT = 6 ; Offset into FNT of total size word UISAR0 = 177640 ; User instruction area 0 UISDR0 = 177600 ; User PDR 0 UISAR4 = 177650 ; User instruction area 4 UISDR4 = 177610 ; User PDR 4 F.LOCK = 200 ; Turn off text mode F.UNLK = 201 ; Turn on text mode F.STRT = 357 ; Get CSR for video and turn on GIDIS F.WAIT = 356 ; Get a GIDIS command string from PI F.STOP = 355 ; Turn off GIDIS F.READ = 370 ; User READ request (read report from GIDIS) F.WRIT = 371 ; User WRITE request (send command to GIDIS) .SBTTL PURE AREA DBLK:: .RAD50 /DK / .RAD50 /BOLD / .RAD50 /GID/ ALPBLK: .RAD50 /SY / .RAD50 /ALPH00/ .RAD50 /FNT/ lsblk: .rad50 /LS / .RAD50 / / PIDEV: .RAD50 /PI / .RAD50 / / XMSUFF: .RAD50 / X/ ; XM monitor suffix BITMAP: .ASCIZ /BITMAP/ IOPAGE: .ASCIZ /IOPAGE/ .SBTTL IMPURE AREA ONEPLN::.BYTE 0 ; One-plane configuration (vs. multi-plane) BASE: .BYTE 0 ; Context byte .EVEN BMVSHI::.WORD 240. ; Visible height of bitmap BOOTIM::.WORD 0 ; Clear boot time flag. $DSW:: .WORD 0 ; Fake directive status word CONTXT::.WORD BASE IOAREA: .BLKW 6 ; AREA for all EMT calls BUF:: .BLKW 256. BLKNUM: .WORD 0 REPBUF: .BLKW 32. ;Intermediate storage for report buffer FLAGWD::.WORD 0 ;Miscellaneous flag word FL.380 == 1 ;Running on a 380 ALPSIZ: .WORD 0 ;Size of default font in words FONTSZ::.WORD 0 ;Size of default font ORG1: .WORD 0 ;Storage area for user par ORG2: .WORD 0 ;Storage area for user par APRFNG == 6 ; APR for Default alphabet APRADR == 140000 ; Address of APRFNG APRIFC == 5 ; APR for mapping to bitmap APRIOP == 7 ; APR for IOPAGE RFNBLK: .RDBBK 0,RS.GBL!RS.CGR!RS.EXI,NAME=ALPH00 ;RDB for default font RDBMAP::.RDBBK 0,RS.GBL,NAME=BITMAP ;RDB for BITMAP RDBIOP: .RDBBK 0,RS.GBL,NAME=IOPAGE ;RDB for IOPAGE WDFNTG::.WDBBK APRFNG,72.,0,0,72.,WS.MAP ;WDB for default font WDBMPP: .WDBBK APRIFC,200,,,,WS.MAP ;WDB for BITMAP WDBIOP: .WDBBK APRIOP,0,,,,WS.MAP ;WDB for IOPAGE WFNBLK: .WDBBK APRFNG,1,0,0,0,WS.MAP ;WDB for user fonts .SBTTL Error messages ;+ ; Error messages ;- ERRGID: .ASCII /?GIDIS-/ ;Prefix string LEVERR: .ASCII /X-/<200> ;Level string .EVEN ERRARE::.BYTE 0 ;Error code .BYTE 0 ;ASCII character level .WORD ERRGID ;-> prefix string .WORD LEVERR ;-> level byte .WORD MSGTAB ;-> message table .WORD 0 ;-> filename .WORD FINISH ;-> abort exit MSGLST MSGTAB ERRMSG ATT ERRMSG FPU ERRMSG JOB ERRMSG PRO ERRMSG XMR ; ; The following messages are in module ULB033 ; ;ERRMSG CIU ;ERRMSG CNO ;ERRMSG DVF ;ERRMSG DFL ;ERRMSG FER ;ERRMSG FCP ;ERRMSG FNF ;ERRMSG ILD ;ERRMSG INE ;ERRMSG NOM ;ERRMSG OPE ;ERRMSG OFF ;ERRMSG OFP ;ERRMSG SYS ;ERRMSG EOF .EVEN MSGEND .ASECT .=JSW .WORD VIRT$ .SBTTL Jump Vectors .PSECT BKBA00 GBL,I,RO $RISOM::JMP @#RISOMP ; Reset output map to initial state INTCHK::JMP @#$INTCK ; Interrupt check REPGDS::JMP @#$RPGDS ; Report from GIDIS $MPGDS::JMP @#MPGDS ; Map to GIDIS data segments MPBMPP::JMP @#$MPBMP ; Map a bitmap page $MPIFC::RETURN ; Map to interface common (not needed) PRANY:: RETURN ; Print screen (graphic mode) (not supported) PRGDS:: RETURN ; Print screen (GIDIS entry) (not supported) START:: MOV #STACK,SP ;Setup the stack in high memory .GTIM #IOAREA,#BUF ;Get time .GVAL #IOAREA,#S.CNF2 ;Get config word 2 in R0 BIT #,R0 ;Running on a PRO series? BNE 5$ ;Branch if so MOV #PRO,R1 BR 40$ ; -F-GIDIS must be run on a PROFESSIONAL series processor 5$: .GTJB #IOAREA,#BUF ;Get job number BCC 8$ ;Branch if no error MOV #FE.SYS,R1 BR 40$ ; -F-System error 8$: .GVAL #IOAREA,#S.CNF1 ;Get config word 1 in R0 BIT #,R0 ;Float point present? BNE 10$ ;Branch if so MOV #FPU,R1 BR 40$ ; -F-Floating point microcode required 10$: .GVAL #IOAREA,#SYSGEN ;R0 = sysgen features word MOV #2,R1 ;If no system job support, jobnum must be 2 BIT #STASK$,R0 ;System job support? BEQ 20$ ;Branch if not MOV #16,R1 ;If system job support, jobnum must be 16 20$: CMP BUF,R1 ;Is job number correct? BEQ 30$ MOV #JOB,R1 BR 40$ ; -F-GIDIS must be run as a foreground job 30$: .GVAL #IOAREA,#S.SUFF ;R0 = handler suffix CMP XMSUFF,R0 ;Is this XM? BEQ 50$ ;Branch if so MOV #XMR,R1 40$: .ERR #ERRARE,R1,RETURN=NO,LEVEL=F ; -F-Extended memory monitor required for GIDIS.SAV 50$: CALL DEFONT ;Read in default FONT CALL ATTACH ;Attach to BITMAP and IOPAGE ; CALL OPENLS .LOOKUP #IOAREA,#0,#PIDEV BCC 80$ ;Branch if no error 60$: MOV #FE.SYS,R1 70$: .ERR #ERRARE,R1,LEVEL=F,RETURN=NO ; -F-System Error 80$: CALL VIDREG ;Set the video registers BIC #40100,@BACSR ;disable end of frame/done interrupts BIT #INT480,@BACSR ;Is 480 interlace on? BEQ 90$ ;Branch if not MOV #480.,BMVSHI ;Set 480 mode on 90$: CLRB ONEPLN ;Assume multi-plane MOV CONTXT,R0 ;R0 -> context byte BISB ,(R0) ;Set color bit BIT #CSSPL,@BACSR ;Using single plane? BEQ 100$ ;Branch if not COMB ONEPLN ;Indicate single plane BISB ,(R0) ;Clear color bit 100$: ;++REV001 ;Forget to re_enable frame/done interrupts and BIS #40100,@BACSR ; the cursor goes kaputski !! for keeps !!! ;--END REV001 .SPFUN #IOAREA,#0,#F.LOCK,#0,#0,#0,#0 ;Lock text mode BCS 112$ CALL NEW.GI 110$: .SPFUN #IOAREA,#0,#F.UNLK,#0,#0,#0,#0 ;Unlock text mode BCS 112$ 111$: .SPFUN #IOAREA,#0,#F.WAIT,#BUF,#0,#0,#0 ;Wait for a command BCC 120$ ;Branch if no error 112$: .ERR #ERRARE,#FE.SYS,RETURN=NO,LEVEL=F ; -F-System error 120$: MOV BUF+2,R5 ;R5 = wordcount BGE 125$ ;Branch if not CALL GID.SYNC ;Re-synchronize to command mode CALL ALPH.E ;Detach all user defined regions BR 111$ ;Get next command 125$: CMP BUF,#F.READ ;Is this a read BNE 130$ ;Branch if not CALL REPORT ;Send back a report BR 111$ ;Get next command 130$: MOV @#UISAR0+,-(SP) ;Save original mapping MOV @#UISDR0+,-(SP) MOV BUF+6,@#UISAR0+ ;Input buffer PAR1 value MOV #77406,@#UISDR0+ ; MOV BUF+4,R2 ;R2 = Input buffer virtual address ADD #*20000,R2 MOV #USRBUF,R4 ;R4 = buffer for user's commands 131$: MOV (R2)+,(R4)+ ;copy the user's commands into high memory SOB R5,131$ MOV (SP)+,@#UISDR0+ ;Restore original mapping MOV (SP)+,@#UISAR0+ MOV BUF+2,R2 ;R2 = wordcount ASL R2 ;R2 = bytecount MOV #USRBUF,R1 ;R1 -> command to execute .SPFUN #IOAREA,#0,#F.LOCK,#0,#0,#0,#0 ;Lock text mode BCS 112$ CALL GID.PR ;Execute the command BR 110$ ;Wait for next command .SBTTL DEFONT - Read in default font ;+ ; DEFONT Read in the default font ;- DEFONT:: .LOOKUP #IOAREA,#0,#ALPBLK ;Look for default font file BCC 20$ ;Branch if no error MOV #FE.FNF,R1 10$: .ERR #ERRARE,R1,LEVEL=F,RETURN=NO,FILE=#ALPBLK ; -F-File not found ALPH00.FNT 20$: .READW #IOAREA,#0,#BUF,#256.,#1 ;Get first block BCC 30$ ;Branch if no error MOV #FE.INE,R1 BR 10$ ; -F-Input error ALPH00.FNT 30$: MOV #BUF,R1 ;R1 -> first block of font MOV #RFNBLK,R2 ;R2 -> RDB ADD #AL$TOT,R1 MOV @R1,R0 ;Number of bytes in font ASR R0 ;Make it a word count MOV R0,ALPSIZ ;Save it ADD #100,R0 ;Round up to next higher 32. word unit ASR R0 ;Divide by 2 ASR R0 ;By 4 ASR R0 ;By 8 ASR R0 ;16 ASR R0 ;32 MOV R0,R.GSIZ(R2) ;Move in the length MOV R0,FONTSZ ;Save fontsize .CRRG #IOAREA,#RFNBLK ;Create the global region BCC 40$ ;Branch if no error MOV #FE.NOM,R1 BR 50$ ; -F-Insufficient memory 40$: MOV #WFNBLK,R3 ;R3 -> window block MOV R.GID(R2),W.NRID(R3) ;Move in the ID MOV FONTSZ,W.NSIZ(R3) ;Move in the size .CRAW #IOAREA,#WFNBLK ;Create a window and map to it BCC 60$ ;Branch if no error MOV #FE.SYS,R1 50$: .ERR #ERRARE,R1,LEVEL=F,RETURN=NO ; -F-System error 60$: .READW #IOAREA,#0,#APRADR,ALPSIZ,#1 ;Read entire font BCC 70$ ;Branch if no error MOV #FE.INE,R1 BR 10$ ; -F- Input error ALPH00.FNT 70$: .CLOSE #0 .ELAW #IOAREA,#WFNBLK ;Unmap window BCC 80$ ;Branch if no error MOV #FE.SYS,R1 BR 50$ ; -F-System error 80$: .ELRG #IOAREA,#RFNBLK BCC 90$ ;Branch if no error MOV #FE.SYS,R1 BR 50$ 90$: RETURN .SBTTL ATTACH Attach to bitmap and to IOPAGE ;+ ; ATTACH Attach to bitmap and to iopage ;- ATTACH:: .CRRG #IOAREA,#RDBMAP ;Attach to bitmap BCC 20$ ;Branch if no error MOV #BITMAP,R1 10$: .ERR #ERRARE,#ATT,LEVEL=F,RETURN=NO,ASCII=R1 ; -F-Error attaching to global region: BITMAP 20$: .CRRG #IOAREA,#RDBIOP ;Attach to IOPAGE BCC 30$ ;Branch if no error MOV #IOPAGE,R1 BR 10$ ; -F-Error attaching to global region: IOPAGE 30$: MOV #WDBIOP,R3 ;R3 -> IOPAGE WDB MOV #RDBIOP,R2 ;R2 -> IOPAGE RDB MOV R.GID(R2),W.NRID(R3) ;Move in the region id MOV R.GSIZ(R2),W.NSIZ(R3) ;Move in the size of the region .CRAW #IOAREA,#WDBIOP ;Map to the I/O page BCC 40$ ;Branch if no error .ERR #ERRARE,#FE.SYS,LEVEL=F,RETURN=NO ; -F-System Error 40$: RETURN .SBTTL VIDREG Set the video registers ;+ ; VIDREG Set the video hardware registers ; ; Registers changed: R0 R1 R2 ;- VIDREG:: .SPFUN #IOAREA,#0,#F.STRT,#BUF,#0,#0,#0 BCC 5$ ;Branch if no error .ERR #ERRARE,#FE.SYS,RETURN=NO,LEVEL=F ; -F-System error 5$: MOV BUF,R0 ;R0 = register address MOV #NUMREG,R2 ;R2 = number of registers to set MOV #BAIDR,R1 ;R1 -> Register to set 10$: MOV R0,(R1)+ ;Move in the register ADD #2,R0 ;Next value SOB R2,10$ ;Do all registers MOV BACSR,BACSRL ;Set low byte of CSR MOV BACSR,BACSRH INC BACSRH ;Set high byte RETURN $INTCK:: CLR R0 ;Say no interrupts (for now) RETURN .SBTTL $RPGDS - Report GIDIS-Mode Information ;+ ; Return a byte string containing GIDIS-mode information to the user ; (through PI). This routine saves the string in REPBUF so that when ; a read is done (SPFUN 370), REPBUF can be copied to the user's buffer. ; ; 2(SP) size of byte string (in words) ; 4(SP) -> byte string ; ; CALL $RPGDS ; ; Registers changed: R0,R1,R2 ;- $RPGDS:: MOV R0,-(SP) MOV R1,-(SP) MOV R2,-(SP) MOV #REPBUF,R2 ; R2 -> report buffer MOV 10(SP),R0 ; R0 = number of words to save BEQ 20$ ; Branch if no report to save ASL R0 ; R0 = number of bytes to save MOV 12(SP),R1 ; R1 -> string CMP #64.,R0 ; More than 64 bytes? BGE 10$ ; Branch if not MOV #32.,R0 ; Make it 64 10$: MOVB (R1)+,(R2)+ ; Move a byte SOB R0,10$ ; Next byte 20$: MOV (SP)+,R2 MOV (SP)+,R1 MOV (SP)+,R0 RETURN .SBTTL REPORT - Send a report back to user ;+ ; REPORT ; Copy the report buffer (REPBUF) into the users area. ; ; Input: R1 -> user's command buffer ; R2 = number of bytes to copy ; ; Registers changed: R0,R1,R2 ;- REPORT: MOV BUF+4,R1 ADD #60000,R1 .POKE #IOAREA,#UISAR4,BUF+6 MOV R0,ORG1 ;Save original value .POKE #IOAREA,#UISDR4,#77406 MOV R0,ORG2 MOV BUF+2,R2 ;R2 = bytecount of command MOV #REPBUF,R0 ;R0 -> report buffer TST R2 ;Does user want any bytes copied? BEQ 90$ ;Branch if not 10$: MOVB (R0)+,(R1)+ ;Move a byte SOB R2,10$ ;Copy as many bytes as requested 90$: .POKE #IOAREA,#UISDR4,ORG2 .POKE #IOAREA,#UISAR4,ORG1 RETURN .SBTTL MPGDS - Map GIDIS Related Data Regions ;+ ; Create and map windows for GIDIS related data regions. ; ; Regions mapped are: ; Default (VDFNTS) or created (unnamed) font region. ; ; CALL MPGDS ; The error code (converted to RSX) is put into $DSW. ;- .ENABL LSB .EVEN MPGDS:: MOV #1,$DSW ; Assume success TST WDFNTG+W.NRID ; Is the region ID zero BEQ 10$ ; Yes -- no region to map to .CRAW #IOAREA,#WDFNTG ; Create and map GIDIS font window BCC 20$ ; Branch if no error CALL CRERR ; Set $DSW depending on CRAW error 10$: CLC ; Unconditionally indicate success 20$: RTS PC ; Return (with C-bit) .DSABL LSB .SBTTL CREER - Convert RT error code for .CRAW and .CRRG to RSX error code. ;+ ; Input: Location 52 contains the RT error code ; Output: The RSX error code is put in $DSW. ;- CRAWE: .WORD -124 ;0 .WORD -125 ;1 .WORD -126 ;2 .WORD -6 ;3 .WORD -124 ;4 .WORD 0 ;5 (not used) .WORD -1 ;6 .WORD -2 ;7 .WORD -3 ;10 CRERR:: CLR R0 BISB @#52,R0 ; R0 = Error code ASL R0 ; Make it a byte offset MOV CRAWE(R0),$DSW ; Move in the RSX error equivalent RETURN .SBTTL $MPBMP - Map to an 8kb Page of the Bitmap ;+ ; Map an 8kb page of the bitmap starting at a specified offset into ; the bitmap. If less than 8kb remains in the bitmap, map the size ; remaining. ; ; Note that in order to access the bitmap directly, hardware registers ; in the video controller must be manipulated to control which plane(s) ; appear on the bus. It is not sufficient to merely call this subroutine ; to map the bitmap into the virtual address space of the task. ; ; R0 offset within bitmap region (in 64-byte blocks) ; ; CALL $MPBMP ; ; If the CRAW$ fails, the firmware crashes. ;- $MPBMP:: MOV R0,-(SP) ; Save R0 MOV R1,-(SP) ; And R1 MOV #WDBMPP,R1 ; R1 -> window definition block MOV R0,W.NOFF(R1) ; Specify offset of window in region MOV RDBMAP+R.GID,W.NRID(R1) ; Move region ID into window def block CLR W.NLEN(R1) ; Want to map as much as possible .CRAW #IOAREA,R1 ; Map the window BCC 10$ ; Branch if no error .EXIT 10$: MOV (SP)+,R1 ; Restore R1 MOV (SP)+,R0 ; Restore R0 RTS PC .SBTTL RISOMP - Reset Output Map to Initial State ;+ ; Reset the output map to its initial state. ; ; If using a one-plane configuration, nothing is done except to ; guarantee that the output map is not enabled. ; ; If using a multi-plane configuration, the values written to the output ; map depend on the type of monitor being used (color vs. monochrome). ; If not boot time, the output map is then enabled. ; ; R5 -> current context ; BOOTIM boot-time-initialization flag ; ONEPLN one-plane-configuration flag ; TRMMOD(R5) terminal mode settings (monitor type info) ; ; CALL RISOMP ; ; @BACMP color map initialized as appropriate ; @BACSR color map enabled/disabled as appropriate ;- RISOMP:: MOV R1,-(SP) ; Save regs MOV R2,-(SP) 1$: TST @BACSRL BPL 1$ TSTB ONEPLN ; Using a one-plane configuration BEQ 10$ ; No BIC #CSOME,@BACSR ; Disable use of output map BR 50$ 10$: ; TSTB TMCMON+TRMMOD(R5) ; Using a color monitor ; BEQ 20$ ; No -- using a monochrome monitor ;For now, assume that if it's a multi-plane configuration, then it's ; a color monitor MOV #OMPCLR,R1 ; Point to initial values for color BR 30$ 20$: MOV #OMPMNO,R1 ; Point to initial values for monochrome 30$: MOV #7*400,R2 ; Initialize loop counter/entry number 40$: CLRB R2 ; Remove previous output map value BISB (R1)+,R2 ; Insert new output map value MOV R2,@BACMP ; Set output map value SUB #400,R2 ; Decrement loop counter/entry number BHIS 40$ ; Do remaining entries BIS #CSOME,@BACSR ; Enable the output map 50$: MOV (SP)+,R2 ; Restore regs MOV (SP)+,R1 RETURN ; MACRO to initialize table of output map values. ; ; OMPBEG .MACRO OMPBEG .BYTE 0,0,0,0,0,0,0,0 .T = . .ENDM OMPBEG ; MACRO to define a value for an output map entry. ; ; OMPENT ,,, .MACRO OMPENT ENTRY,RED=0,GREEN=0,BLUE=0 .SAVE . = .T - .BYTE ++ .RESTORE .ENDM OMPENT .SAVE .PSECT DATA ; Table of initial output map values for use with a color monitor. ; ; The values were chosen to be consistent with the VT125. OMPCLR: OMPBEG OMPENT 0 RED=0 GREEN=0 BLUE=0 ; Black OMPENT 2 RED=7 GREEN=2 BLUE=2 ; Red OMPENT 4 RED=2 GREEN=2 BLUE=6 ; Blue OMPENT 6 RED=2 GREEN=7 BLUE=2 ; Green OMPENT 1 RED=6 GREEN=6 BLUE=6 ; White OMPENT 3 RED=6 GREEN=6 BLUE=6 ; White OMPENT 5 RED=6 GREEN=6 BLUE=6 ; White OMPENT 7 RED=6 GREEN=6 BLUE=6 ; White ; Table of initial output map values for use with a monochrome monitor. ; ; The values were chosen to be consistent with the VT125. OMPMNO: OMPBEG OMPENT 0 ; Black OMPENT 2 GREEN=4 ; Light gray OMPENT 4 GREEN=2 ; Dark gray OMPENT 6 GREEN=6 ; White OMPENT 1 GREEN=6 ; White OMPENT 3 GREEN=6 ; White OMPENT 5 GREEN=6 ; White OMPENT 7 GREEN=6 ; White .RESTORE FINISH:: .EXIT .END