.title "K83SCRN.ASM Kaypro '83 screen driver 11/8/86" .sbttl "Copyright (c) 1986 Plu*Perfect Systems" .remark \== Source code for CDL/TDL Z80 assembler (AZM.COM). ; production by: AZM k83scrn ZLINK *k83.com=k83scrn.rel */locate .prog.=3f80; *q ZSID k83.com m3f80 4500 100 ^C SAVE 5 k83scrn.drv ==\ ; revision history: ; ; v 1.1 no scroll on line 24 in cut ; (changes probably too long to include in '84 driver) ; v 1.0 id imbedded in string, 9/8/86 debug = 0 .ifg DEBUG, [ bios =\ 'Base of bios = ?' ] .remark \=== The first sections of code are generic (except for some terminal equates); beginning at 'STMRKS' it is terminal-specific. Particular features of Kaypro '83 code: 1. The video ram is accessed by bank switching. Active code, including stack must be >= 4000h, and interrupts disabled. 2. There's no return-cursor function. We read the screen, send a test character, and find the byte that changed. 3. There's no reverse video, but we create a BLINK attribute to "hilite" the cut region by setting bit 7 of the video-ram character. 4. Cursor-movement sequences are all single-byte control characters. note: If UNDERSCORE is found at cursor, we convert it to SPACE on screen restore. This isn't good if cursor is sitting on a real underscore. ===\ .ifg DEBUG, [ codloc = 100h .phex .psym .pabs consta = bios +06h conin = bios +09h conout = bios +0ch ] ; [ .prel .ident SCRK83 consta = 0 conin = 0 conout = 0 outch = 0 puts = 0 bwrch = 0 bflush = 0 ] .xlist .xsym .sall ; ; ascii equates ; NUL = 00h BELL = 07h BS = 08h CR = 0dh LF = 0ah ESC = 1bh SPACE = 20h DEL = 7fh ; ; CUT command characters ; HOME = 'H' ;home the cursor LOHOME = 'h' MARK = 'X' ;set a mark LOMARK = 'x' PASTE = 'P'-'@' ;paste region at cursor CANCEL = 'C'-'@' ;cancel cut command ; ; ; TERMINAL-SPECIFIC EQUATES ; ; kaypro cursor controls ; LEFT = 08H RIGHT = 'L'-'@' UP = 'K'-'@' DOWN = 0AH ; LEFT8 = 82h ;kaypro raw keypad arrow values... RIGHT8 = 83h UP8 = 80h DOWN8 = 81h ; HOMEC = 1eh ;home cursor ; ; Kaypro '83 screen parameters ; NCOLS = 80 NROWS = 24 NROW24 = 24 ;# rows excluding status line ; SCRSIZ = NCOLS*NROWS ; ; loglin = 128 ;length of logical screen line vidram = 3000h ;base of video ram bitprt = 1ch ; controller port ; .remark \=== Kaypro '83 video ram is laid out as: 24 80-char rows each row begins 128 bytes after the previous one 3000: row 0 3080: row 1 ... ===\ ;========================= .ifg DEBUG, [ .loc codloc ] ; [ .loc .PROG. ] ; ;------------------------------------------------------------ ; ; id sector - nul-terminated string - at 3f80h ; sdid: .ascii "Kaypro '83 driver v 1.1" db 0 ;NUL terminator idlen = . - sdid ds 80h-idlen ;total of 80h bytes ; START: ; ; ; Start of Screen Module. Assemble to run at 4000h. ; ;***** MODULE ENTRY HEADER ; ; EXTERNAL ADDRESSES, supplied by loader ; jjcons: jmp consta ;bios constat jjconi: jmp conin ;bios conin jjouta: jmp outch ;A to conout, preserving bc,de,hl jjputs: jmp puts ;hl-string to conout, NUL/bit-7 term. ; preserving bc,de,hl jjbrdc: jmp 0000 ;buffered read char from cut-swp jjbwrc: jmp bwrch ;buffered write char to cut-swp jjbflu: jmp bflush ;flush (write) buffer ; ; INTERNAL ENTRY POINTS ; savscr: jmp savpag ;save screen resscr: jmp respag ;restore saved screen lastnb: jmp lstnbl ;last non-blank char in rows 1-24 dmpchr: jmp retnch ;return next screen char dmpcur: jmp retncu ;return buffer cursor dmpatt: jmp retnat ;return next screen attribute setmrk: jmp stmrks ;set region marks, move cursor cutrg: jmp docut ;cut region pastrg: jmp dopast ;paste region ininpd: jmp ininot ;initialize notepad putnpd: jmp putnch ;put char to notepad ; ;======================================== ; generic ; ININOT: ; ; Initiate Notepad - clear screen, print banner. ; lxi h,Zbanner jr jjputs ; ;======================================== ; generic ; PUTNCH: ; ; Put char in A to notepad (screen) ; Convert CR to CRLF, DEL to rubout. ; cpi CR lxi h,Zcrlf ;convert CR to CR,LF jrz jjputs cpi DEL lxi h,Zrub jrz jjputs jr jjouta ;======================================== ; generic ; RETNCU: ; ; Return buffer cursor as row/col. ; ; ret: D = binary row, E= binary col ; L = ascii row, H = ascii col (for shld ...) ; lhld bcursor ; ; Convert offset to col/row. ; exit: D = binary row, E = binary col ; H = ascii col, L = ascii row <-- NOTE ORDER ; off2cr: mvi b,0 ;convert to row,col lxi d,-NCOLS ..1: dad d jrnc ..2 inr b ;row count++ jr ..1 ..2: lxi d,NCOLS dad d mov a,l ;col mov e,a ;binary col in E mov d,b ;binary row in D adi SPACE ; + bias mov h,a ;H = ascii col mov a,b ;row adi SPACE ; +bias mov l,a ;L = ascii row ret ; ;======================================== ; generic ; DOPASTE: ; ; Paste the last-cut region onto active screen at the current cursor. ; ; 1. Get previously-cut region from external routine ; 2. Send chars to screen, avoiding boundary overflows. ; ; 'savpag' not needed if terminal supports 'send cursor address' ; call savpag ;get current screen, ;in order to find cursor mvi b,4 ;read 4 data bytes ..0: push b call jjbrdc pop b djnz ..0 ; mov b,a ;4th byte is # rows push b call crs2hl ;current cursor's row/col to hl pop b ; ; loop over rows ; ..rowlp:push b push h mov e,l ;e = col no. push d call stcrshl ;set cursor at h,l ..collp:call jjbrdc ;read char from cut-swp cpi CR jrz ..rend mov c,a ;save char pop d ;check for off screen mov a,e cpi NCOLS inr e push d ;row/col to stack cc sendc ;to conout, unless off edge jr ..collp ; ..rend: pop d ;clear row/col pop h pop b inr h ;bump row mov a,h ;check for off bottom of screen cpi NROWS jrnc ..xit djnz ..rowlp ..xit: xra a ret ; ;======================================== ; generic ; DOCUT: ; ; Cut rectangular region defined by keypresses. ; 1. Parse keypresses to move cursor and mark corners. ; Highlight region as cursor is moved. ; 2. Send the marked region, row-wise to external routine. ; Append CR after each row. ; ; Data structure is: ; size (word) ; # columns (byte) ; # rows (byte) ; row 1 ; CR ; row 2 ; CR ; .... ; .ifg DEBUG, [ ;if debugging, put output in cutbuf lxi h,cutbuf ;set ptr shld dbgptr ] ; xra a sta mrkcnt ;init for next time ; ; ; set ctcols = # cols, ctrows = # rows ; (assumes mark2 is SE of mark1) ; corners:lded mark1 lhld mark2 mov a,h ;# rows = 1 + mark2row -mark1row inr a sub d mov h,a mov a,l ;# cols = 1 + mark2col -mark1col inr a sub e mov l,a shld ctcols ; ; cut rectangle [mark1...mark2] & copy to buffer ; append CR at end of each row ; xchg push h ;mark1 call wrpara ;write parameters pop h ;mark1 call rc2off ;convert to scr addr lda ctrows ;get # rows mov b,a ; ; write the cut region to external buffer ; ..rowlp:push b ;(+1 push h ;(+2 lxi d,buf ;fetch from screen buffer dad d ; ; write 1 row of cut region to external buffer ; lda ctcols mov b,a ;b = # cols ; ; write 1 row of cut region to external buffer ; lda ctcols mov b,a ;b = # cols ; ; buffered write B chars at hl, ascii only ; ..bwrt: push b push h mov a,m cpi DEL jrnc ..mksp cpi SPACE ;convert graphics jrnc ..1 ..mksp: mvi a,SPACE ; to space ..1: mov c,a call jjbwrch pop h pop b inx h djnz ..bwrt ; mvi c,CR ;append CR to each row call jjbwrch ; pop h ;(+1 pop b ;(+0 lxi d,NCOLS ;bump to next row dad d djnz ..rowlp ; and loop jmp jjbflu ;flush the write buffer ; ; ; write parameters: size, # cols, # rows to swp file ; de = ctcols ; wrpara: mov b,d ;# rows mvi d,0 inr e ;+1 for CR lxi h,0 ;accum. ..0: dad d djnz ..0 call bwhl ;write word lhld ctcols ;now #cols, # rows ; bwhl: push h mov c,l call jjbwrch pop h mov c,h jmp jjbwrch ; ;======================================== ; generic ; LSTNBL: ; ; Find last non-blank line (1-24 only) in current scr buffer. ; Graphics and 8-bit characters are considered blanks. ; If B=0ff, save screen first. ; ; ret: H=row, L=col of last non-blank char in rows 1-24 ; inr b cz savpag lxi b,NROW24*100h + NCOLS ;b=# rows, c=# cols lxi d,buf lxi h,0 ..lp: ldax d cpi SPACE+1 ;don't count cntl chars or SPACE jrc ..1 cpi DEL ; or DEL or graphics 8-bit jrnc ..1 shld savrc ..1: inx d inr l dcr c jrnz ..lp ;loop over cols inr h mov l,c ;0 mvi c,NCOLS djnz ..lp ;loop over rows savrc = .+1 lxi h,0000 ;hl = last non-blank ret ;---------------------------------------- ; xring: mvi c,BELL ; ; send C to screen, exit Z, no CY ; sendc: mov a,c ; send A to screen, exit Z, no CY ; (this will scroll, however!) ; send: call jjouta xra a ;Z, no CY ret ;======================================== ; ; end of generic code ; ;======================================== ; specific ; STMRKS: ; ; Move cursor and set marks. Return CY clear until exit. ; ; 1. move cursor, until: ; 2. 'X' = set 1st mark ; turn on hiliting, set mark, keep cursor at mark ; 3. move cursor right/down only ; 4. 'X' = set 2nd mark ; turn off hiliting, set 2nd mark ; exit CY (done) ; 5. cntl-C = CANCEL. ; turn off hilighting, set CY, exit ; ; cpi CANCEL jrz abort cpi LEFT jz goleft cpi LEFT8 jz golef8 cpi UP jz goup cpi UP8 jz goup8 cpi RIGHT jz gort cpi RIGHT8 jz gort8 cpi DOWN jz godn cpi DOWN8 jz godn8 cpi HOME jrz gohome cpi LOHOME jrz gohome cpi CR jrz ..mrk cpi MARK jrz ..mrk cpi LOMARK jrz ..mrk xra a ;no action ret ..mrk: lxi h,mrkcnt ;if no mark yet set mov a,m ora a mvi m,1 jrz mk1 ;..set mark1 call mk2 ;else set mark2 mrkxit: xra a sta mrkcnt ;init for next time stc ;CY = all done ret ; abort: call normal ;restore normal video mvi a,CANCEL jr mrkxit ; ;------------------------------------------- ; ; set 1st mark, turn on rev. video, don't move cursor ; mk1: call crs2hl shld mark1 shld mark2 shld curcol ;L->curcol,H->currow ;; ;;kaypro '83 doesn't have attributes, omit: ;; push h ;; call reverse ;reverse video on (dummy routine) ; ;; pop h ;mark1 ; ; Blink the marked char. Cursor may itself be off, or solid. ; mvi a,1 ;blink 1 char sta colct sta rowct jmp showro ; ; set 2nd mark, restore normal video, set CY ; mk2: call normal ;dummy - restore normal video stc ;CY = all done ret ; ;-------------------------------------------- ; ; bump row/col var that tracks actual cursor ; if mark not yet, send cntl char ; ret NZ if mark is set ; inrsnd: inr m ;next row/col call anymrk cz sendc ; ; nz if a mark has been set ; anymrk: lda mrkcnt ora a ret ; ; for H19, etc. that use ESC sequences, ; change these routines to send ESC, then the byte. ; gohome: mvi c,HOMEC ;convert to video driver's cntl char call anymrk ;if mark set, jnz xring ;..error mov h,a ;set row=col=0 mov l,a shld bincol jjsndc: jmp sendc ; ; cursor left and cursor up: ; send if not at top or left margin ; golef8: mvi a,LEFT ;convert to 7-bit char ; goleft: lxi h,bincol ;ck for col ==0 ; zck: mov c,a ;save char in c call anymrk rnz cmp m ;ck col/row == 0 jz xring ;..error dcr m ;dcr col/row jr jjsndc ; goup8: mvi a,UP ;7-bit code goup: lxi h,binrow ;ck for top row and send jr zck ; ; cursor right and cursor down: ; if mark is not set, move cursor ; if mark is set, expand region and highlight ; keep track of cursor location in both cases ; don't move if it would scroll ; ; move cursor right ; gort8: mvi a,RIGHT ;convert to 7-bit code ; gort: mov c,a ;save in c lxi h,bincol mvi a,NCOLS-2 cmp m jc xring call inrsnd ;bump col & send if mrk not set rz ;rtn if mark not yet set ; ; hilite marked column ; gort1: lxi h,mark2 inr m ;bump 2nd mark-row lxi h,curcol ;bump col inr m mov l,m lda mark1+1 ;top row mov h,a ;h=row, l=col for col to hilite rowct = .+1 mvi b,00 ; ; loop over each row in cut region ; ..rlp: push b push h ;save binary row/col mvi a,1 ;display 1 char in each row call showhi pop h pop b inr h ;next row djnz ..rlp lxi h,colct ;prepare to bump col cnt & exit jr inrmbs ; ; move cursor down ; godn8: mvi a,DOWN ;7bit code godn: mov c,a ;save char lxi h,binrow ;ck if already on bottom row mvi a,NROWS-2 cmp m jc xring call inrsnd ;bump row & send rz ;rtn if mark not yet set ; ; hilite marked row ; godn1: lxi h,mark2+1 ;row inr m ;bump 2nd mark-col lxi h,currow ;bump row inr m mov h,m lda mark1 ;left col mov l,a ;h=row, l=col for row to hilite call showro ;display 1 cut row lxi h,rowct ;bump row cnt inrmbs: inr m ; and exit ret ; ; .remark \== For Kaypro '83, write directly to screen, in order to set blink attribute. if down: set cur at next row, left col send partial row rowcnt++ BS (back up 1) if right: set cur at toprow, next col send partial column colcnt++ ==\ ; ; enter: H = binary row, L= binary col ; showro: colct = .+1 mvi a,00 ; ; Fetch A chars at H=binary row, L=binary col from buffer. ; Put chars to screen, setting BLINK attribute. ; showhi: push psw call stvptr ;set video ram ptr call rc2off lxi d,buf ;fetch from screen buffer dad d pop psw ;#chars mov b,a ..lp: mov a,m ;fetch char from buffer cpi SPACE jrnz ..set7 mvi a,7fh ;make displayable 'DEL' char ..set7: set 7,a ;set blink bit mov c,a push h call putv ;put to screen pop h inx h djnz ..lp ora a ;clear CY ret ; ;======================================== ; specific ; RETNCH: ; ; Return next screen char from buffer. ; ; enter: ; d = row, e = col ; b = FF ==> read screen ; c = FF ==> set bufptr ; exit: ; A = char, CY set if good ; DE -> row,col of next char, HL -> buf of next char ; CY clear if out of range ; ; This routine can be called to get successive chars from ; buffer as long as caller preserves hl,de and sets b=c=0. ; xra a call stdump rnc mov a,m ;get char inx h ;bump bufptr ret ; ;======================================== ; specific ; RETNAT: ; ; Return next screen attribute from buffer. ; THIS IS A NUL FUNCTION for Kaypro '83. ; ; enter: ; d = row, e = col ; b = FF ==> read screen ; c = FF ==> set bufptr ; exit: ; A = attr, CY set if good ; DE -> row,col of next char, HL -> buf of next char ; CY clear if out of range ; xra a ;clear CY ret ; ;-------------------- ; ; ret: NC if out of range ; else hl-> buffer char ; stdump: inr b jrnz ..0 push b ;b == 0ff -> read screen push d push h ;$$$ missing in k84 !!! call savpag pop h pop d pop b ..0: inr c jrnz ..4 ; ; enter: D = row, E = col ; set: hl -> buffer address, cy set, preserve de ; ret: CY clear if error (off screen) ; ;conv: mov a,d ;c == 0ff -> set bufptr cpi NROWS jrnc ..bad mov a,e cpi NCOLS jrc ..ok ..bad: xra a ;out of range , ret NC ret ..ok: lxi h,buf mov a,d lxi b,NCOLS ;row*(cols per row) inr a ..lp: dcr a jrz ..2 dad b jr ..lp ..2: mvi d,0 ;+ col # dad d ; ..4: inx d ;bump col mov a,e cpi NCOLS rc mvi e,0 ;end of row, set col = 0 inr d ;and bump row mov a,d cpi NROWS ret ;NC if out of range ; ; Set video-ram pointer. ; enter: H=binary row, L=binary col ; set vptr = row*128 + col, preserves all ; stvptr: push b push d push h mov b,h mov c,l lxi h,0 lxi d,128 inr b jr ..bot ..lp: dad d ;row*128 ..bot: djnz ..lp dad b ; + col (b=0) lxi b,vidram dad b shld vptr pop h pop d pop b ret ; ; Initialize for screen save/restore ; enter: A=0 to save(read) screen ; A=NZ to restore (write) screen ; iscr: sta putflg ;0=save, 0ff=restore itop: lxi h,buf ;init buf ptr shld cptr lxi h,vidram ;int video ram ptr shld vptr ret vptr: dw 0 ;ptr to video ram char ; ;======================================== ; specific ; SAVPAG: ; ; Save screen to buffer. ; xra a ;initialize for reading screen call iscr call doscr ;save screen first call crs2off ;THEN find screen cursor shld bcursor ;and save it call off2cr sded bincol ;save binary col/row ret ; ;-------------------- ; doscr: lxi b,SCRSIZ ..0: push b call vch ;r/w char pop b inx d ;bump ptr USED?? dcx b mov a,b ora c jrnz ..0 ret ; ;======================================== ; specific ; RESPAG: ; ; Restore saved screen from buffer. ; ; Note: this sequence is necessary to be sure that the ; char in the hardware cursor register isn't written back ; to video ram after the new character has been put there. lhld bcursor ;set the new cursor position FIRST push h call stcrs mvi a,0ffh ;initialize for writing screen call iscr call doscr ;put buffer to screen pop h ;get cursor offset push h lxi d,buf ;get char at the cursor dad d mov a,m call jjouta ;send it via conout pop h ;reset the cursor ; ; Set cursor on screen by direct cursor addressing. ; enter: HL = cursor offset relative to 0000 ; stcrs: call off2cr ;convert from offset to ascii col/row stcoro: shld colrow ;put ascii col/row into string lxi h,Zcurs ;send set-cursor string jmp jjputs ; ; Set cursor on screen. ; enter: H=binary row, L = binary col ; stcrshl:call rc2off jr stcrs ; ;-------------------- ; ; CONVERSION ROUTINES ; ; Get current cursor position to H=binary row, L=binary col ; crs2hl: call crs2off ;get cursor by re-read of screen call off2cr ;returns binary in de xchg ret ; ; convert H=binary row, L=binary col to hl= offset ; (hl = row*NCOLS + col) ; uses bc,de,hl ; ; note fix from 'convhl' in k84 version !! ; rc2off: mov b,h ;b=row mov c,l ;c=col lxi h,0 inr b lxi d,NCOLS jr ..bot ..0: dad d ;rows*NCOLS ..bot: djnz ..0 dad b ;+ col ret ; ; ; Get current screen cursor. ; ret: HL= binary offset from 0000. ; ; (Screen must already be saved into buffer). ; Send a test char via conout. Read screen and find mismatch. ; T1CHAR = 07Eh T2CHAR = 07Dh crs2off: lxi h,0 ;init duplicate count FIRST shld dupcnt ; ; Send a test char to the screen. If the testchar happens to be the ; char at the cursor, bump dupcnt and repeat the loop. Sending ; the char again puts it at cursor+1. Repeat until there's a mismatch. ; By testing the final screen char, we ensure a mismatch will be found. ; ..nxtc: lda buf+SCRSIZ-1 ;set test char so it is != last char ani 7Fh ;kill cursor bit cpi T1CHAR ; on screen mvi a,T1CHAR jrnz ..1 mvi a,T2CHAR ..1: sta tstchr ;send test char to screen at cursor call jjouta ; call itop lxi b,SCRSIZ ..lp: push b lhld vptr shld orighl call getv ;get screen char to C lhld cptr ;compare to buffer char mov a,m sta origc shld origbf sub c ;hi bit has been killed inx h shld cptr pop b jrz ..same adi (7Fh-SPACE) ;check for space converted to blink-DEL jrnz ..fnd ..same: dcx b mov a,b ora c jrnz ..lp ; ; have a duplicate of testchar at current cursor lhld dupcnt inx h shld dupcnt jr ..nxtc ; ; cursor found by mismatch of buffer char, testchar ; ..fnd: lxi h,SCRSIZ ;offset = scrsize-countleft ora a dsbc b lded dupcnt ;adjust for any duplicates ora a dsbc d ;count - dupcnt ..ok: push h ;save offset to cursor loc. origc = .+1 mvi a,00 ;restore original char res 7,a cpi '_' ;in case we picked up the cursor jrnz ..2 ; at a space, put it back to space mvi a,SPACE ;(not foolproof) ..2: mov c,a origbf = .+1 lxi h,0000 ;and correct buffer value too mov m,a orighl = .+1 lxi h,0000 ;to screen call putvhl pop h push h call stcrs ;put cursor back on screen pop h ret ;hl =cursor offset from 0000 ; tstchr: db 0 ;test char to find cursor dupcnt: dw 0 ;# of duplicates of test char at cursor ; ;-------------------- ; ; putflg = 0: read 1 char from screen, put into buffer ; putflg = NZ: get 1 char from buffer, write to screen ; ret: c = char, if putflg != 0 ; uses A, HL ; vch: lda putflg ora a jrnz ..put ; ..get: call getv ;get from video ram lhld cptr ;put into buffer mov m,c inx h shld cptr ret ; ..put: lhld cptr ;get char from buffer mov c,m ; to C res 7,c ;kill any cursor bit inx h shld cptr ; putv: lhld vptr putvhl: in bitprt ;get port byte ori 80h ;set for bank 1 di ;prevent interruption out bitprt ;switch to bank 1 mov m,c ;put char in C into video ram putv1: ani 7fh ;switch bank 0 back in out bitprt ei ; ; Set pointer to next video ram char, adjusting for gap ; at end of each line. ; ..bmpv: inx h mov a,l cpi 80 jrz ..adj cpi 128+80 jrnz ..sh ..adj: adi 128-80 mov l,a jrnc ..sh inr h ..sh: shld vptr ret ; getv: lhld vptr in bitprt ;get port byte ori 80h ;set for bank 1 di ;prevent interruption out bitprt ;switch to bank 1 mov c,m ;get char from video ram res 7,c ;kill blinking jr putv1 ; ;****************************************** ; ; DATA AREA ; putflg: db 0 ;NZ to restore(put) screen from buf cptr: dw 0 ;char ptr ; ; cut-region data ; ctcols:db 0 ;# cols in cut region (excl. CR), A PAIR ctrows:db 0 ;# rows ; ; mark-region data ; mrkcnt: db 0 curcol: db 0 ;a pair currow: db 0 mark1: dw 0 ;binary row,col of upperleft mark mark2: dw 0 ;lower right mark bincol: db 0 ;a pair binrow: db 0 ; Zrub: db BS,SPACE,BS+80H ;rub-out previous char ; ;**************************************** ; ; TERMINAL-SPECIFIC data ; ; dummy routines - no attrributes for Kaypro '83 ; normal: reverse: RET ; ; Kaypro '83 video strings ; Zcurs: .ascii [1bh]'=' ;set cursor to colrow: db SPACE,SPACE ; row,col - modified in-line db NUL ;must have following NUL ; .ifg DEBUG, [ Zclr: db 1Ah,NUL ;kaypro ] ; ;================================ ; ; JOTPAD BANNER - just 2 lines' worth ; ; 1. Clear screen. ; 2. Remind user of usage, to extent space is available. ; The editing keys are those supported by the terminal itself. ; Zbanner: db 1ah ;clear screen KAYPRO-SPECIFIC ; .ascii 'JOT: = exit, ^Paste' db CR,LF .ascii '^X = del. rest of line, ESC E = ins. line, ' ;43 .ascii 'ESC R = del. line' ;17 ; ; NO ROOM FOR THIS ! ; if turborom--> ;.ascii 'Cntl-A = insert char. Cntl-B = delete char. ' ; Zcrlf: db CR,LF+80h ; .slist .list codlen = .-start ;length of code .rlist ; ;++++++++++++++++++++++++++++++ .remark \== Debugging stragegy: Assemble screendriver at 100h. Load with Z80 debugger. Clear ram buffers. Set breakpoints as needed. Call these test routines and inspect buffers. ==\ .ifg DEBUG, [ dbg0 = . ; ; these emulate the external BGii routines ; using ram buffers for debugging ; bwrch: push h lhld dbgptr ;put to debug cut buffer mov m,c inx h shld dbgptr pop h ret ; bflush: ret ; ;bios display-a-string ; nul/8-bit terminated string at hl ; preserves bc,de,hl ; puts: push h ;save hl, outch save bc,de ..0: mov a,m rlc srlr a ;shift right logical (register) A inx h jrz ..1 push psw call outch pop psw jrnc ..0 ..1: pop h ret ; ; char in A to conout, preserve bc,de,hl ; outch: push b push d push h mov c,a call conout pop h pop d pop b ret ; ; Various routines for debugging in ram. ; TSTACK = 05000h ;test stack, above bank-switching tdump: lxi b,0ffffh ;fetch scr, set ptr lxi d,0 ;from row 0,col 0 call dmpchr ; tdump2: lxi b,0 call dmpchr ; tdump3: lxi d,100h + 0 lxi b,00ffh call dmpchr ; tdump4: lxi d,3000h ;out of range test lxi b,00ffh call dmpchr rst 7 ; ; clear: lxi h,Zclr ;clear screen call jjputs rst 7 ; flood: lxi h,Zflood ;write to screen call jjputs rst 7 Zflood: .ascii '=======TESTING=======' db 0 ; tsave: lxi sp,TSTACK ;save screen call savscr rst 7 trest: lxi sp,TSTACK ;restore screen call resscr rst 7 tmark: lxi sp,TSTACK ;set a mark call savscr call sttop ;so debugger doesn't scroll screen ..0: call conin call setmrk jnc ..0 ; rst 7 nop ; tcut: lxi h,cutbuf ;clear buffer mvi m,0 lxi d,cutbuf+1 lxi b,2*80h ldir call cutrg ;cut region call setbot ;put cursor out of way rst 7 ; place cursor nerar bottom or top ; setbot: lxi h,100h*(20h+18) +20h jr sttop1 sttop: lxi h,2020h sttop1: shld colrow lxi h,Zcurs ;send set-cursor string jmp jjputs ; dbgptr: dw 0 .slist .list dbglen = . - dbg0 .rlist ] ;++++++++++++++++++++++++++++++ ; .list ; SCREEN BUFFER STRUCTURE ; ; The rest of the 4K block is available ; for the screen image and other data. xbreq = 2 + NROWS*NCOLS ; .ifg DEBUG, [ ; ; put buffer on even byte ( for attributes) bstart = start + 800h ;make some room ] ; [ ; put buffer at end of 4K area, to just fit bstart = (start + 400h) + (3*400h-xbreq) short = start+codlen-bstart xfree = - short .ifg (short), [ .prntx '[07]Code overflows buffer!' ] ] ; ; addresses: ; bcursor = bstart ;cursor location in saved screen buf = bcursor+2 ;start of screen buffer ; ;buffer uses (24 lines x 80 chars) ; bufend = buf + NROWS*NCOLS ; .ifg DEBUG, [ ; ; put cutbuffer in ram for debugging ; datcut = bstart+10h+3*400h cutbuf = datcut ] .xlist .end jjcons