; -*- mode: Fundamental; tab-width: 8; indent-tabs-mode: 1; -*- TITLE BOOTCRT 80 column card driver INCLUDE BOOTCONF.INC IFT CRT80 .Z80 ASEG ; ;Modified 23/9/86 to declare CRT and ECRT externals ;Old 8080 nmemonics changed in places ; ; WJB - Added further comments ; ; ********************** ; * * ; * CRT OUTPUT HANDLER * ; * * ; ********************** DISP EQU 20H ADRLO EQU 10H+DISP ; I/O port for video RAM low address - Accessing this port initiates read / write ADRHI EQU 11H+DISP ; I/O port for video RAM ligh address ASCD EQU 12H+DISP ; I/O port for character data ATRD EQU 13H+DISP ; I/O port for attribute data CRTCA EQU 18H+DISP ; 6845 register select port CRTCD EQU 19H+DISP ; 6845 data port XMAX EQU 80 ; Number of columns on screen YMAX EQU 24 ; Number of rows on screen ESC EQU 27 ; Escape character ORG 100H+0F400H-0E000H ; CRT:: ; .PHASE 0F400H VSTK EQU $+600H ; Entry point for processing charaters. Character is stored in C register. CRTOUT: PUSH AF ; Save registers PUSH BC PUSH DE PUSH HL LD HL,EXIT PUSH HL ; SETUP RETURN ADDRESS ; The following jump is modified (by routine FRIGIT) to point to the processing ; required for the next character in a control or escape sequence DB 0C3H ; JMP OP-CODE FRIG: DW INITL ; HANDLER STATUS STORAGE ASCR: DB ' ' ; Character fetched by ESC R ATRR: DB 2 ; Attribute fetched by ESC R SCRFLG: DB 1 ; Scroll (255) / Page flag (0) PRATR: DB 2 ; Attribute for printed characters NPATR: DB 2 ; Attribute for non printed characters WRMSK: DB 11100000B ; WRITE TO ASC & ATR SA: DW 0 ; Address in video RAM of top of screen XLOC: DB 0 ; Column position (zero based) YLOC: DB 0 ; Row position (zero based) ; Jump table for processing escape codes CTAB: DW DUMMY ; ^@ DW DOTDO ; ^A DW VCTDO ; ^B DW CXYDO ; ^C DW BKGSET ; ^D DW EOLDO ; ^E DW ATRSET ; ^F DW BELDO ; ^G DW BSDO ; ^H DW TABDO ; ^I DW LFDO ; ^J DW UPDO ; ^K DW CLRDO ; ^L DW CRDO ; ^M DW BLSET ; ^N DW BLOFF ; ^O DW COLSET ; ^P DW COLSET ; ^Q DW COLSET ; ^R DW COLSET ; ^S DW COLSET ; ^T DW COLSET ; ^U DW COLSET ; ^V DW COLSET ; ^W DW INITLZ ; ^X DW FWDDO ; ^Y DW HMEDO ; ^Z DW ESCDO ; ^[ DW SCRSET ; ^\ DW PGESET ; ^] DW CSSET ; ^^ DW CSOFF ; ^_ ; NEXT 11 BYTES WILL BE USED FOR TEMP STORAGE TEMP: ; This routine is called once on receipt of the very first character ; to set up the display. ; As noted, this routine may subsequently be overwritten for scratch storage. INITL: PUSH BC ; Save character CALL CLRDO ; Clear screen POP BC LD HL,CRTGO ; Set default handling for next character LD (FRIG),HL ; DETERMINE CHARACTER TYPE ; This is the default entry point, for printable characters and the ; start of control and escape sequences. CRTGO: LD A,C ; Test 3 msb of character, and jump if zero (control code) AND 11100000B JR Z,CNTRL ; PRINTABLE CHARACTER ; The first subroutine call is modified by escape sequences to call one of three routines: ; DUMMY - Do nothing - standard characters ; ALTMAP - Set high bit - alternate characters ; GRPMAP - Map to special graphics characters FRIG1: CALL DUMMY ; Apply character maping CALL GETCUR ; Get video RAM address of current cursor position LD A,(PRATR) ; Printing character attributes CALL WRITE ; Write character and attribute to video RAM CALL FWDDO ; Advance cursor position RET ; RESTORE REGESTERS ; This routine is called to exit processing of current character EXIT: CALL XYCALC ; Calculate video RAM address from (XPOS) and (YPOS) CALL SETCUR ; Set cursor address in 6845 chip POP HL ; Restore registers POP DE POP BC POP AF RET ; CONTROL CODE ; Look up address of processing routine for current control character in CTAB, and jump to it CNTRL: LD HL,CTAB LD D,0 LD A,C ADD A,C LD E,A ADD HL,DE LD A,(HL) INC HL LD H,(HL) LD L,A JP (HL) ; CONTROL CODE HANDLERS ; === Escape Ctrl+[ 0x1B ESCDO: CALL FRIGIT ; Get next character LD A,C ; Test for less than space (0x20) CP ' ' JR C,NORMAL ; If so, drop the ESC and this character AND 11111B ; Take 5 lsb ADD A,A LD HL,ESCTAB ; Use this to look up address in ESCTAB LD E,A LD D,0 ADD HL,DE LD A,(HL) INC HL LD H,(HL) LD L,A JP (HL) ; And jump to it ; === Set cursor position Ctrl+C 0x03 CXYDO: CALL FRIGIT ; Get next character LD A,C ; x = ( m - 32 ) & 0x7F SUB 32 AND 7FH CP XMAX ; If 0 <= x < 80, set (XLOC) JR NC,CXSKIP LD (XLOC),A CXSKIP: CALL FRIGIT ; Get next character LD A,C ; y = ( n - 32 ) & 0x7F SUB 32 AND 7FH CP YMAX ; If 0 <= y < 24, set (YLOC) JR NC,CYSKIP LD (YLOC),A CYSKIP: ; Reset handling of next character to default NORMAL: LD HL,CRTGO LD (FRIG),HL RET ; This routine esentially acts as get the next character. ; It pops the return address of the call (address of the instruction following the call) ; and then sets the destination of the jump in routine CRTOUT to that address. ; It then falls through to the next address on the stack, which is the EXIT routine. FRIGIT: POP HL LD (FRIG),HL RET ; === Set background colour Ctrl+D 0x04 BKGSET: CALL FRIGIT ; Get next character LD A,C ; Extract 3 lsb AND 111B .8080 RLC ; Shift them up 3 bits RLC RLC .Z80 LD C,A ; Copy them into bits 5-3 of (PRATR) LD A,(PRATR) AND 11000111B OR C LD (PRATR),A LD A,(NPATR) ; And (NPATR) AND 11000111B OR C LD (NPATR),A JP NORMAL ; Reset default character handling ; === Set attributes Ctrl+F 0x06 ATRSET: CALL FRIGIT ; Get next character LD A,C ; Copy character into (PRATR) and(NPATR) LD (PRATR),A LD (NPATR),A JP NORMAL ; Reset default character handling ; === Plot a point Ctrl+A 0x01 DOTDO: CALL FRIGIT ; Get next character LD A,C ; x = m - 32 SUB 32 LD (TEMP),A CALL FRIGIT ; Get next character LD A,C ; y = n - 32 SUB 32 LD H,A ; H=Y LD A,(TEMP) LD L,A ; L=X CALL PLOTD ; Plot point JP NORMAL ; Reset default character handling ; === Draw a line Ctrl+B 0x01 VCTDO: CALL FRIGIT ; Get next character LD A,C ; x1 = m1 - 32 SUB 32 LD (TEMP+0),A CALL FRIGIT ; Get next character LD A,C ; y1 = n1 - 32 SUB 32 LD (TEMP+1),A CALL FRIGIT ; Get next character LD A,C ; x2 = m2 - 32 SUB 32 LD (TEMP+2),A CALL FRIGIT ; Get next character LD A,C ; y2 = n2 - 32 SUB 32 LD C,A CALL PLOTV ; draw line JP NORMAL ; Reset default character handling ; HANDLERS NOT REQUIRING PERAMETERS ; === Reset display Ctrl+X 0x19 INITLZ: LD A,255 ; Scroll mode LD HL,SCRFLG LD (HL),255 INC HL ; (PRATR) = Green on Black LD (HL),2 INC HL ; (NPATR) = Green on Black LD (HL),2 INC HL ; (WRMSK) = 0xE0 - Write both LD (HL),11100000B CALL CSSET ; Cursor on CALL CRDO ; Carriage return CALL LFDO ; Line feed JP ESTD ; Select standard characters ; === Blink on Ctrl+N 0x0E BLSET: LD A,(PRATR) ; Set blink bit (bit 6) in (PRATR) only OR 01000000B LD (PRATR),A RET ; === Blink off Ctrl+O 0x0F BLOFF: LD A,(PRATR) ; Clear blink bit (bit 6) in (PRATR) only AND 10111111B LD (PRATR),A RET ; === Cursor on Ctrl+^ 0x1E CSSET: LD A,10 ; Write 0x60 to 6845 register 10 OUT (CRTCA),A LD A,01100000B OUT (CRTCD),A RET ; === Cursor off Ctrl+_ 0x1F CSOFF: LD A,10 ; Write 0x20 to 6845 register 10 OUT (CRTCA),A LD A,00100000B OUT (CRTCD),A RET ; === Scroll mode Ctrl+\ 0x1C SCRSET: LD A,255 ; Write 255 to (SCRFLG) LD (SCRFLG),A RET ; === Page mode Ctrl+] 0x1D PGESET: XOR A ; Write 0 to (SCRFLG) LD (SCRFLG),A RET ; === Set foreground colour. (PRATR) only Ctrl+P to Ctrl+W 0x10 to 0x17 COLSET: LD A,C ; Get 3 lsb AND 111B LD C,A LD A,(PRATR) ; Copy into bits 0-2 of (PRATR) AND 11111000B OR C LD (PRATR),A RET ; === Carriage return Ctrl+L 0x0D CRDO: XOR A ; Set (XLOC) to zero LD (XLOC),A DUMMY: RET ; === Line feed Ctrl+J 0x0A LFDO: LD A,(YLOC) ; Test for (YLOC) = 23 CP YMAX-1 JR Z,LFS ; Jump if so INC A ; Otherwise increment (YLOC) and exit PAGEM: LD (YLOC),A RET LFS: LD A,(SCRFLG) ; Test for page mode OR A JR Z,PAGEM ; If so set (YLOC) to zero CALL SCRUP ; Otherwise scroll screen one line CALL ERLN ; Clear bottom line RET ; === Cursor forward Ctrl+Y 0x19 FWDDO: LD A,(XLOC) ; Test for (XLOC) = 79 CP XMAX-1 JR Z,FWDL ; Jump if so INC A ; Otherwise increment (XLOC) and exit LD (XLOC),A RET FWDL: XOR A ; Reset (XLOC) to zero LD (XLOC),A JR LFDO ; Do a line feed ; === Bell - Repeat last video RAM read / write ??? Ctrl+G 0x07 BELDO: IN A,(ADRLO) RET ; === Backspace Ctrl+H 0x08 BSDO: LD A,(XLOC) ; Test for (XLOC) zero OR A JR Z,BSU ; Jump if so DEC A ; Otherwise decrement (XLOC) and exit LD (XLOC),A RET BSU: LD A,XMAX-1 ; Set (XLOC) to 79 LD (XLOC),A LD A,(YLOC) ; Test for (YLOC) zero OR A JR Z,BSS ; Jump if so DEC A ; Otherwise decrement (YLOC) and exit LD (YLOC),A RET BSS: XOR A ; Reset (XLOC) to zero - cursor is at top of screen LD (XLOC),A RET ; === Tab Ctrl+I 0x09 TABDO: LD A,(XLOC) ; Set 3 lsb of (XLOC) - Advances 0-7 characters OR 111B LD (XLOC),A JR FWDDO ; Advance one more character (with line feed if necessary) ; === Cursor up Ctrl+K 0x0B UPDO: LD A,(YLOC) ; If (YLOC) > 0, decrement it by one OR A JR Z,UPS DEC A LD (YLOC),A RET UPS: RET ; === Clear screen Ctrl+L 0x0C CLRDO: CALL CLRSCN ; Fill screen with space character and non-printing attribute LD HL,0 ; Set top of screen to top of video memory CALL SETSA ; === Home Ctrl+Z 0x1A HMEDO: XOR A ; Zero (XLOX) and (YLOC) LD (XLOC),A LD (YLOC),A RET ; Blank line ERLN: LD A,(XLOC) ; Save (XLOC) PUSH AF XOR A ; Zero (XLOC) LD (XLOC),A CALL EOLDO ; Blank line POP AF ; Restore (XLOC) LD (XLOC),A RET ; === Erase to end of line Ctrl+E 0x05 EOLDO: CALL XYCALC ; Calculate video RAM address from (XPOS) and (YPOS) LD A,(XLOC) ; B = (XLOC) LD B,A JP ERASE1 ; Blank ; UTILITIES ; Mapping for special graphics characters ; 0x00 - 0x3F Unchanged ; 0x40 - 0x5F Mapped to 0x00 - 0x1F ; 0x60 - 0x7F Mapped to 0x80 - 0x9F ; 0x80 - 0xBF Mapped to 0x00 - 0x40 ; 0xC0 - 0xEF Mapped to 0x00 - 0x1F ; 0xE0 - 0xFF Mapped to 0x80 - 0x9F GRPMAP: LD A,C ; Clear bit 7 AND 7FH LD C,A ; Exit if bit 6 is zero AND 01000000B RET Z LD A,C ; Get bit 5 AND 00100000B .8080 RLC ; Shift it up to bit 7 RLC .Z80 OR C ; And add it back to the character AND 10011111B ; Clear bits 5 and 6 LD C,A RET ; Mapping for alternate alpha characters ALTMAP: LD A,C ; Set bit 7 OR 10000000B LD C,A RET ; Select a bit ; If the character is an ASCII "0", then return with A = 0 and zero flag set ; Otherwise take 3 lsb: If zero, return A = 0x80, zero flag clear ; Otherwise return A = 1 << ( C & 0x07 - 1 ), zero flag clear ; ; This was obviously intended that ASCII "1" to "8" should be used to select bits (lsb to msb) ; But it gives a non-zero mask for all characters other than "0". ; In particular 0x00 selects msb rather than no bits. GETMSK: LD A,C ; Test for ASCII "0" CP '0' JR NZ,GETBIT ; Jump if not XOR A ; Zero A and set zero flag RET GETBIT: DEC A ; Change 1-8 to 0-7 AND 111B ; Extract 3 lsb LD C,A CALL NCALC ; A = 1 << C OR A ; Clear zero flag RET ; Get top of screen address from 6845 GETCUR: LD A,14 ; H = read from register 14 OUT (CRTCA),A IN A,(CRTCD) LD H,A LD A,15 ; L = Read from register 15 OUT (CRTCA),A IN A,(CRTCD) LD L,A RET ; Calculate address in video RAM from (XLOC) and (YLOC) coordinates XYCALC: LD A,(XLOC) ; D = (XLOC), E = (YLOC) LD D,A LD A,(YLOC) ; ASSUMES XMAX OF 80 LD E,A CALC1: PUSH BC LD A,E ADD A,A ADD A,A ADD A,E LD L,A ; L = 5 * E LD H,0 ADD HL,HL ADD HL,HL ADD HL,HL ADD HL,HL ; HL = 80 * E LD B,H LD C,L LD HL,(SA) ADD HL,BC ; HL = (SA) + 80 * E LD A,D ; A = D POP BC CALC2: LD D,0 LD E,A ADD HL,DE LD A,H AND 00111111B LD H,A ; HL = ( HL + A ) & 0x3FFF RET .8080 PLOT: MOV L,D ; LD L, D ; L = x MOV H,E ; LD H, E ; H = y PLOTD: MOV A,L ; LD A, L STC ; SCF CMC ; CCF RAR ; RRA ; A = x/2, CF = x mod 2 MOV D,A ; LD D, A ; XA - Column to plot (in D) MVI A,0 ; LD A, 0 RAL ; RLA MOV C,A ; LD C, A ; C = x mod 2 MOV A,H ; LD A, H ANI 11B ; AND 11B RLC ; RLCA ; A = 2 * ( y mod 4 ) ORA C ; OR C MOV C,A ; LD C, A ; N - Bit to plot MOV A,H ; LD A, H RRC ; RRCA RRC ; RRCA ANI 00111111B ; AND 00111111B ; A = y / 4 CPI YMAX ; CP YMAX ; Exit if below bottom of screen RNC ; RET NC MOV E,A ; LD E, A ; YA - Row to plot (in E) MOV A,D ; LD A, D ; Exit if column is to right of screen CPI XMAX ; CP XMAX RNC ; RET NC CALL NCALC ; CALL NCALC ; A = 1 << C MOV C,A ; LD C, A CALL CALC1 ; CALL CALC1 ; Calculate video RAM address from position in DE MOV A,H ; LD A, H ; Set high address for video read ANI 111B ; AND 111B MOV H,A ; LD H, A OUT ADRHI ; OUT (ADRHI), A MOV A,L ; LD A, L ; Set low address and perform read OUT ADRLO ; OUT (ADRLO), A IN ATRD ; IN A, (ATRD) ; Get attributes MOV E,A ; LD E, A ANI 10000000B ; AND 10000000B ; Test for graphics mode IN ASCD ; IN A, (ASCD) ; Get character .Z80 JR NZ,ORWR ; Zero character if not in graphics mode XOR A ORWR: LD B,A ; Save character in B LD A,(NPATR) ; Get non-printing attributes PUSH AF AND 111B JR Z,ERSD ; Jump if Black foreground POP AF OR 10000000B ; Set graphics mode bit OUT (ATRD),A ; Output attribute LD A,B ; Set new pixel in character OR C ORWR1: OUT (ASCD),A ; Output character LD A,(WRMSK) ; Output high address for write with mask bits OR H OUT (ADRHI),A LD A,L ; Output low address and perform write OUT (ADRLO),A RET ERSD: POP AF LD A,E ; Get existing character attribute OR 10000000B ; Set graphics mode bit OUT (ATRD),A ; Output attributes LD A,C .8080 CMA ; CPL ; Clear the plot bit ANA B ; AND B .Z80 JR ORWR1 ; Unplot the point .8080 PLOTV: LXI H,0 ; LD HL, 0 ; Save existing stack pointer DAD SP ; ADD HL, SP SHLD TEMP+8 ; LD (TEMP+8), HL LXI SP,VSTK ; LD SP, VSTK ; Set new stack STKSKP: LXI H,TEMP ; LD HL, TEMP MOV D,M ; LD D, (HL) ; D = x1 INX H ; INC HL MOV E,M ; LD E, (HL) ; E = y1 INX H ; INC HL MOV H,M ; LD H, (HL) ; H = x2 MOV L,C ; LD L, C ; L = y2 VECT: LXI B,0 ; LD BC, 0 ; Push marker for end of line PUSH B ; PUSH BC MOV A,D ; LD A, D ; Compare x1 & x2 CMP H ; CP H .Z80 JR C,NOXG ; Jump if x2 > x1 JR NZ,XG ; Jump if x2 < x1 LD A,E ; Compare y1 & y2 CP L JR C,NOXG ; Jump if y2 > y1 .8080 XG: XCHG ; EX DE, HL ; Swap if necessary so x2 > x1 or x2 = x1 and y2 > y1 NOXG: MOV B,H ; LD B, H MOV C,L ; LD C, L LXI H,INRAL ; LD HL, INRAL ; Modify later instruction MVI M,03CH ; LD (HL), 03CH ; (INR A) - This if y2 > y1 MOV A,E ; LD A, E CMP C ; CP C .Z80 JR C, LOOP .8080 MVI M,00CH ; LD (HL), 00CH ; (INR C) - This if y2 <= y1 LOOP: MOV A,D ; LD A, D CMP B ; CP B .Z80 JR Z, EQX ; Jump if x2 = x1 .8080 PUSH B ; PUSH BC ; Push (x2, y2) ADD B ; ADD A, B ; A = x1 + x2 RAR ; RRA MOV B,A ; LD B, A ; B = ( x1 + x2 ) / 2 INR A ; INC A MOV H,A ; LD H, A ; H = ( x1 + x2 ) / 2 + 1 = x3 MOV A,E ; LD A, E CMP C ; CP C .Z80 JR Z, EQY ; Jump if y1 = y2 .8080 NEQY: ADD C ; ADD A, C ; A = y1 + y2 RAR ; RRA MOV C,A ; LD C, A ; C = ( y1 + y2 ) / 2 INRAL: INR A ; INC A ; This code modified to be either INC A or INC C EQY: MOV L,A ; LD L, A ; L = ( y1 + y2 ) / 2 + ( 0 or 1 ) = y3 PUSH H ; PUSH HL ; Push (x3, y3) .Z80 JR LOOP .8080 EQX: MOV A,E ; LD A, E CMP C ; CP C .Z80 JR Z, EQXY ; Jump if both points the same .8080 PUSH B ; PUSH BC ; Push (x2, y2) MOV H,D ; LD H, D .Z80 JR NEQY .8080 EQXY: CALL PLOT ; CALL PLOT ; Plot point (x1, y1) POP D ; POP DE ; Pop (x1, y1) MOV A,D ; LD A, D ORA E ; OR E .Z80 JR Z, PLEXIT ; Exit if marker (0, 0) .8080 POP B ; POP BC ; Pop (x2, y2) .Z80 JR LOOP .8080 PLEXIT: LHLD TEMP+8 ; LD HL, (TEMP+8) ; Restore stack pointer SPHL ; LD SP, HL RET ; A = 1 << C NCALC: INR C ; INC C MVI A,1 ; LD A, 1 NCALCL: DCR C ; DEC c RZ ; RET Z RLC ; RLCA .Z80 JR NCALCL ; Set 6845 cursor address to HL SETCUR: LD A,14 ; H to register 14 OUT (CRTCA),A LD A,H OUT (CRTCD),A LD A,15 ; L to register 15 OUT (CRTCA),A LD A,L OUT (CRTCD),A RET ; Scroll up SCRUP: LD HL,(SA) ; HL = (SA) + 80 LD A,XMAX CALL CALC2 ; Set top of screen to HL SETSA: LD A,12 ; Write H to 6845 register 12 OUT (CRTCA),A LD A,H OUT (CRTCD),A LD A,13 ; Write L to 6845 register 13 OUT (CRTCA),A LD A,L OUT (CRTCD),A LD (SA),HL ; Store in (SA) RET ; Clear screen. Writes 2K spaces with non-printing attributes to video RAM CLRSCN: LD HL,0 LD C,' ' CLRLP: LD A,(NPATR) CALL WRITE INC HL LD A,H CP 1000B JR NZ,CLRLP RET ; Writes 80 - B spaces and non-printing attributes to video RAM starting at HL ERASE1: LD A,256-XMAX ; B = B - 80 ADD A,B LD B,A ; SET UP BYTE COUNT LD A,' ' ; Set space OUT (ASCD),A LD A,(NPATR) ; And non-printing character OUT (ATRD),A LD A,(WRMSK) ; Write mask LD D,A ERLP0: LD A,H ; High address AND 00000111B OR D OUT (ADRHI),A ERLP1: LD A,L ; Low address and to write OUT (ADRLO),A INC B ; Count characters and exit if done RET Z INC L ; Increment low address JR NZ,ERLP1 INC H ; Increment high address if necessary JR ERLP0 ; Write character in C and attribute in A to video RAM at (HL) ; Taking account of write enable bits in (WRMSK) WRITE: OUT (ATRD),A ; Output attributes LD A,C OUT (ASCD),A ; Output character LD A,(WRMSK) ; Combine (WRMSK) with high address LD D,A LD A,H AND 00000111B OR D OUT (ADRHI),A ; Output high address LD A,L OUT (ADRLO),A ; Output low address. Do write. RET ; ESCAPE SEQUENCE LOOK-UP TABLE ESCTAB: DW NORMAL ; @ DW EALT ; A DW EBOTH ; B DW ESCRL ; C DW EPGE ; D DW ECSON ; E DW ECSOFF ; F DW EGRPH ; G DW NORMAL ; H DW EIBLLN ; I DW EDCSLN ; J DW NORMAL ; K DW NORMAL ; L DW NORMAL ; M DW ENPATR ; N DW NORMAL ; O DW EPRATR ; P DW NORMAL ; Q DW EREAD ; R DW ESTD ; S DW ESIPR ; T DW ESINP ; U DW ESIBT ; V DW EWRMS ; W DW CNTSIM ; X DW NORMAL ; Y DW NORMAL ; Z DW NORMAL ; [ DW NORMAL ; \ DW NORMAL ; ] DW NORMAL ; ^ DW NORMAL ; _ ; ESCAPE SEQUENCE HANDLERS ; === Select standard character set Esc "S" ; Sets character mapping call to DUMMY ESTD: LD HL,DUMMY LD (FRIG1+1),HL JP NORMAL ; Reset default character handling ; === Select alternate character set Esc "A" ; Sets character mapping call to ALTMAP EALT: LD HL,ALTMAP LD (FRIG1+1),HL JP NORMAL ; Reset default character handling ; === Select special graphics character set Esc "G" ; Sets character mapping call to GRPMAP EGRPH: LD HL,GRPMAP LD (FRIG1+1),HL JP NORMAL ; Reset default character handling ; === Simulate a control character Esc "X" CNTSIM: CALL FRIGIT ; Get next character LD A,C ; Get 5 lsb of character AND 11111B LD C,A CALL NORMAL ; Reset default character handling JP CNTRL ; Process control character ; === Set scroll mode Esc "C" ESCRL: CALL SCRSET ; Set scroll mode JP NORMAL ; Reset default character handling ; === Set page mode Esc "D" EPGE: CALL PGESET ; Set page mode JP NORMAL ; Reset default character handling ; === Cursor on Esc "E" ECSON: CALL CSSET ; Cursor on JP NORMAL ; Reset default character handling ; === Cursor off Esc "F" ECSOFF: CALL CSOFF ; Cursor off JP NORMAL ; Reset default character handling ; === Set attributes for printable characters Esc "T" ESIPR: CALL FRIGIT ; Get next character LD A,C LD (PRATR),A ; Save to (PRATR) JP NORMAL ; Reset default character handling ; === Set attributes for non-printable characters Esc "U" ESINP: CALL FRIGIT ; Get next character LD A,C LD (NPATR),A ; Save to (NPATR) JP NORMAL ; Reset default character handling ; === Set attributes for printable and non-printable characters Esc "V" ESIBT: CALL FRIGIT ; Get next character LD A,C LD (NPATR),A ; Save to (NPATR) LD (PRATR),A ; And to (PRATR) JP NORMAL ; Reset default character handling ; === Delete the current line Esc "J" EDCSLN: LD A,(XLOC) ; Save (XPOS) PUSH AF XOR A ; Zero (XPOS) LD (XLOC),A CALL XYCALC ; Calculate video RAM address from (XPOS) and (YPOS) EX DE,HL ; DE = Start of current line LD HL,XMAX ADD HL,DE ; HL = Start of next line LD A,(YLOC) LD B,A ; B = Current line number SHFTUP: LD A,B ; Test for last line CP YMAX-1 JR Z,SHUPOK ; Jump if so INC B ; Count line CALL TRXMAX ; Copy line up JR SHFTUP SHUPOK: EX DE,HL ; Blank last line LD B,0 CALL ERASE1 ; Write spaces POP AF ; Restore (XLOC) LD (XLOC),A JP NORMAL ; Reset default character handling ; === Insert a blank line at cursor position Esc "J" EIBLLN: LD HL,(SA) ; Calculate start of lines LD DE,XMAX*(YMAX-2) ADD HL,DE EX DE,HL ; DE = Line 22 LD HL,XMAX ADD HL,DE ; HL = Line 23 EX DE,HL ; DE = Line 23, HL = Line 22 LD B,YMAX-1 ; B = Line to move LD A,(YLOC) LD C,A ; C = Line containing cursor SHFTDN: LD A,B ; Test for done CP C JR Z,SHDNOK ; Jump if so DEC B ; Count line CALL TRXMAX ; Copy line up PUSH BC ; Reset addresses to one line higher LD BC,-2*XMAX ADD HL,BC EX DE,HL ADD HL,BC EX DE,HL POP BC JR SHFTDN ; Repeat SHDNOK: EX DE,HL ; Blank the line containing the cursor LD B,0 CALL ERASE1 JP NORMAL ; Reset default character handling ; Copy a line of video data from HL to DE, taking account of write mask TRXMAX: PUSH BC LD A,(WRMSK) LD B,A ; B = (WRMSK) LD C,XMAX ; C = Counter TRLP: LD A,H ; Set high address and read mode AND 111B OUT (ADRHI),A LD A,L ; Set low address and do read OUT (ADRLO),A IN A,(ASCD) ; Copy character from input to output port OUT (ASCD),A IN A,(ATRD) ; And attribute OUT (ATRD),A LD A,D ; Set high address for write mode and enable bits AND 111B OR B OUT (ADRHI),A LD A,E ; Set low address and do write OUT (ADRLO),A INC DE ; Increment addresses INC HL DEC C ; Count characters JR NZ,TRLP POP BC RET ; === Read character and attribute at current cursor location Esc "R" EREAD: CALL XYCALC ; Calculate video RAM address from (XPOS) and (YPOS) LD A,H ; Set high address and read mode OUT (ADRHI),A LD A,L ; Set low address and do read OUT (ADRLO),A IN A,(ASCD) ; Copy character to (ASCD) LD (ASCR),A IN A,(ATRD) ; Copy attribute to (ATRD) LD (ATRR),A JP NORMAL ; Reset default character handling ; === Set write enable bits Esc "W" ; ASCII "0" - Enable character and attribute writes ; ASCII "1" - Enable only character writes ; ASCII "2" - Enable only attribute writes ; All other characters have no other effect EWRMS: CALL FRIGIT ; Get next character LD A,C LD C,11100000B ; Enable both CP '0' ; Jump if "0" JR Z,SWRM LD C,11000000B ; Enable character CP '1' ; Jump if "1" JR Z,SWRM LD C,10100000B ; Enable attribute CP '2' ; Jump (do nothing) if not "2" JP NZ,NORMAL SWRM: LD A,C ; Set write mask LD (WRMSK),A JP NORMAL ; Reset default character handling ; === Set printing attribute bit Esc "P" ; If data byte (m) is ASCII "0" clear printing character attrbute ; Otherwise set bit ( m - 1 ) & 0x07 of printing character attribute EPRATR: CALL FRIGIT ; Get next character CALL GETMSK ; Convert to mask JR Z,SETPR ; Jump if zero LD C,A ; Set selected bit LD A,(PRATR) OR C SETPR: LD (PRATR),A ; Store result JP NORMAL ; Reset default character handling ; === Set non printing attribute bit Esc "N" ; If data byte (m) is ASCII "0" clear non-printing character attrbute ; Otherwise set bit ( m - 1 ) & 0x07 of non-printing character attribute ENPATR: CALL FRIGIT ; Get next character CALL GETMSK ; Convert to mask JR Z,SETNP ; Jump if zero LD C,A ; Set selected bit ENPA1: LD A,(NPATR) OR C SETNP: LD (NPATR),A ; Store result JP NORMAL ; Reset default character handling ; === Set bit in both attributes Esc "B" ; If data byte (m) is ASCII "0" clear both attrbutes ; Otherwise set bit ( m - 1 ) & 0x07 in each attribute EBOTH: CALL FRIGIT ; Get next character CALL GETMSK ; Convert to mask JR NZ, SETB ; Jump if not zero LD (PRATR),A ; Clear both attributes JR SETNP SETB: LD C,A ; Set bit in (PRATR) LD A,(PRATR) OR C LD (PRATR),A ; And in (NPATR) JR ENPA1 ; END OF ESCAPE SEQUENCE HANDLERS ; .DEPHASE ECRT:: ENDIF ; CRT80 ; ; ; END