home *** CD-ROM | disk | FTP | other *** search
- page 58,132
- ;----- zavt_f.asm ---------------------------------------------
- ; Zephyr Avatar terminal driver.
- ; Copyright (C) 1989-1990, Luns Tee, Toronto ON.
- ; Based on original code for ZANSI by Thomas Hanlin III, Alexandria VA.
- ; and original code for NANSI by Daniel Kegel, Pasadena CA.
- ;------------------------------------------------------------------------
- ; Each routine is called with the following register usage:
- ; AX = max(1, value of first parameter)
- ; Z flag is set if first parameter is zero.
- ; CX = number of paramters
- ; SI = offset of second parameter from CS
- ; DS = CS
- ; ES:DI points to the current location on the memory-mapped screen.
- ; DX is number of characters remaining on the current screen line.
- ; The control routine is free to trash AX, BX, CX, SI, and DS.
- ; It must preserve ES, and can alter DX and DI if it wants to move the
- ; cursor.
- ;
- ; Revisions
- ;----------------------------------------------------------------
- ; Luns Tee, Toronto Ontario
- ;
- ; 19 Dec 1988: Replaced 43 line code with code to set max_y to current
- ; length of screen
- ;
- ; 8 Mar 1989: Moved code to set max_y to ZANSI.ASM where code to
- ; set max_x is
- ;
- ; 24 Mar 1989: Added pseudo cursor switching a la NANSI24. SM 45
- ; enables, RM 45 disables.
- ;
- ; 23 Aug 1989: Now variable length output from DSR - 1 to 3 digits
- ; rather than a rigid two as before
- ;
- ; 28 Aug 1989: Added support for unimplemented EID and EIL functions
- ; and added blitz versions to be used in text mode -
- ; faster, but as functions are infrequently used, not
- ; significant
- ;
- ; 17 Sep 1989: Added SGR2 as bold off conforming to DOS "standard"
- ; and let DSR respond only to 6n
- ;----------------------------------------------------------------
- include zavt_d.asm ; get equates
-
- ; To zavt_p.asm
- public ansi_fn_table
-
- ; From zavt.asm
- extrn pseudo_flag:byte, wrap_flag:byte
- extrn gmode_flag:byte
- extrn port_6845:word
- extrn cur_coords:word, saved_coords:word
- extrn cur_x:byte, max_x:byte
- extrn cur_y:byte, max_y:byte
- extrn max_coords:word
- extrn cur_attrib:byte
- extrn xy_to_regs:near
- extrn get_blank_attrib:near
- extrn cpr_esc:byte, cpr_buf:byte, cprseq:keybuf
- extrn video_mode:byte
- extrn screen_len:word
- extrn cur_page:byte, video_off:word
-
- if xlate
- public key_init
-
- extrn lookup:near
- extrn param_end:word, redef_end:abs
- extrn param_buffer:abs
- extrn xlatseq:keybuf
- else
- extrn param_end:abs
- endif
-
- code segment byte public 'CODE'
- assume cs:code, ds:code
-
- ;----- byteout ---------------------------------------------------
- ; Converts al to a decimal ASCII string (in 0..255),
- ; stores it at ES:DI++. Returns DI pointing at byte after last digit.
- ; Destroys BX.
-
- byteout proc near
- aam ; ones in al, tens in ah
- mov bx,ax ; " " bl, " " bh
- mov al,ah ; tens in al
- aam ; hundreds in ah
- or ah,ah ; <99?
- jz tens ; if so, drop first digit
- xchg al,ah ; put hundreds in al, tens in ah
- add al,30h ; "0" base
- stosb ; store it
- mov al,bl ; restore ones
- ; and make sure we print both remaining
- twodigit:
- xchg al,ah ; tens in al, ones in ah
- add ax,3030h ; "00" base
- stosw ; store them
- ret
-
- tens: mov ax,bx ; ones in al, tens in ah
- or ah,ah ; <9?
- jnz twodigit ; skip another digit
- onedigit:
- add al,30h ; "0" base
- stosb ; store it
- ret
- byteout endp
-
- ;----- ansi_fn_table -----------------------------------
- ; Table of offsets of terminal control subroutines in order of
- ; the character that invokes them, @..Z, a..z. Exactly 53 entries.
- ; All the subroutines are defined below in this module.
- ansi_fn_table label word
- dw ic, cup, cdn, cfw, cbk ; @, A, B, C, D
- dw nul, nul, nul, hvp, nul ; E, F, G, H, I
- dw eid, eil, il, d_l, nul ; J, K, L, M, N
- dw nul, dc, nul, nul, nul ; O, P, Q, R, S
- dw nul, nul, nul, nul, nul ; T, U, V, W, X
- dw nul, nul ; Y, Z
- dw nul, nul, nul, nul, nul ; a, b, c, d, e
- dw hvp, nul, sm, nul, nul ; f, g, h, i, j
- dw nul, rm, sgr, dsr, nul ; k, l, m, n, o
- dw key, nul, nul, scp, nul ; p, q, r, s, t
- dw rcp, nul, nul, nul, nul ; u, v, w, x, y
- dw nul ; z
-
- ;-------- Color table -----------------------------------------
- ; Used in "set graphics rendition"
- colors equ 23 ; number of colors in table
- color_table:
- db 0, 000h,07h ; all attribs off; normal.
- db 1, 0ffh,08h ; bold
- db 2, 0f7h,00h ; bold off
- db 4, 0f8h,01h ; underline
- db 5, 0ffh,80h ; blink
- db 7, 0f8h,70h ; reverse
- db 8, 088h,00h ; invisible
-
- db 30,0f8h,00h ; black foreground
- db 31,0f8h,04h ; red
- db 32,0f8h,02h ; green
- db 33,0f8h,06h ; yellow
- db 34,0f8h,01h ; blue
- db 35,0f8h,05h ; magenta
- db 36,0f8h,03h ; cyan
- db 37,0f8h,07h ; white
-
- db 40,08fh,00h ; black background
- db 41,08fh,40h ; red
- db 42,08fh,20h ; green
- db 43,08fh,60h ; yellow
- db 44,08fh,10h ; blue
- db 45,08fh,50h ; magenta
- db 46,08fh,30h ; cyan
- db 47,08fh,70h ; white
-
- ansi_functions proc near ; set return type to NEAR
-
- ;----- Cursor Motion -----------------------------------------------
-
- ;-- cursor to y,x
- hvp: dec ax ; Convert to zero-based coordinates.
- mov cur_y,al
- ; Get second parameter, if it is there, and set X with it.
- mov al,ah
- cmp cx,2 ; was there a second parameter?
- jb hvp_xok
- lodsb ; yes.
- cmp al,1
- adc al,ah
- dec ax ; convert to zero-based coordinates.
- hvp_xok:mov cur_x,al
-
- ; Clip to maximum coordinates.
- hvp_set:
- mov ax, max_coords ; ah = x, al = y
- dec ah
- cmp ah, cur_x
- jae hvp_sxok
- mov cur_x, ah
- hvp_sxok:
- cmp al, cur_y
- ja hvp_syok
- mov cur_y, al
- hvp_syok:
- ; Set values of DX and DI accordingly.
- call xy_to_regs
-
- ret
-
- ;-- cursor forward --
- cfw: add cur_x, al
- jmp hvp_set
-
- ;-- cursor back -----
- cbk: sub cur_x, al
- jae hvp_set
- mov cur_x, ah
- jmp hvp_set
-
- ;-- cursor down -----
- cdn: add cur_y, al
- jmp hvp_set
-
- ;-- cursor up -------
- cup: sub cur_y, al
- jae hvp_set
- mov cur_y, ah
- jmp hvp_set
-
- ;-- save cursor position --------------------------------------
- scp: mov ax, cur_coords
- mov saved_coords, ax
- ret
-
- ;-- restore cursor position -----------------------------------
- rcp: mov ax, saved_coords
- mov cur_coords, ax
- jmp hvp_set ; Clip in case we have switched video modes.
-
- ;-- set graphics rendition ------------------------------------
- ; Modifies the color in which new characters are written.
-
- sgr: dec si ; get back pointer to first parameter
- cmp cx,1 ; Did he give any parameters?
- adc cl,ah ; no parameters, so fake
- ; one with the default value.
-
- sgr_loop: ; Handles each parameter
- lodsb ; al = next parameter
- push cx
- mov cx,colors
- mov bx,offset color_table - 3
- sgr_search:
- add bx,3
- cmp al,[bx]
- loopne sgr_search ; until match found or done
- jne sgr_loopx
-
- ; If parameter named a known color, set the current color variable.
- mov bx,1[bx]
- mov al,cur_attrib
- and al,bl
- or al,bh
- mov cur_attrib,al
- sgr_loopx:
- pop cx
- loop sgr_loop ; until no more parameters.
- ret
-
- ;-- Insert / Delete Characters ----------------------------
- ; AL is number of characters to insert or delete. AH=0
- ; Preserves DX, DI; does not move cursor.
-
- ic: dec ah ; 1 => swap dest & source below
-
- dc: ; AL = number of chars to ins or del (guarenteed nonzero).
- ; Limit him to # of chars left on line.
- cmp al,dl
- jbe dc_cok
- mov al,dl
- dc_cok:
- mov cl,al ; CX gets # of chars to ins/del
- mov ch,dh ; make it a word
- mov bp,cx ; BP gets # of columns to clear.
-
- ; Set up source = destination + cx*2, count = dx - cx
- mov si,di
- add si,cx
- add si,cx
- neg cl
- add cl,dl ; CX = # of words to transfer
-
- ; If this is an insert, then flip transfer around in both ways.
- or ah,ah
- jz DC_CH_DO
- xchg di,si ; source <-> dest
- std ; up <-> down
- mov ax,cx ; make move over same range
- dec ax
- shl ax, 1 ; AX=dist from 1st to last byte.
- add di,ax ; Start transfer at high end of block
- add si,ax ; instead of low end.
- DC_CH_DO:
- cmp cs:gmode_flag,ch
- jnz gmode_idc ; if in graphics mode, leave
-
- push es
- pop ds
- rep movsw ; Move those characters.
- push cs
- pop ds
-
- mov cx,bp ; fetch chars to blank
- blankit:
- call get_blank_attrib; get attribute in ah
- mov al," " ; and space in al
- rep stosw ; blank out region
- cld ; clear direction flag before continuing
- call xy_to_regs ; and restore DI,DX
- gmode_idc:
- ret
-
- ;== erase in line ================================================
- eil: dec si
- lodsb ; get the real parameter
- if direct_scroll
- cmp gmode_flag,ah
- jnz eil_slow
-
- ;--- fast_eil ------------
- cmp al,1
- jbe fast_eil_partscreen; 2K - erase whole line
- std ; work backwards
- mov ch,ah
- mov cl,max_x ; max_x characters
- mov ax,dx ; ax now chars to eol
- dec ax ; less one
- shl ax,1 ; bytes to eol
- add di,ax ; start from end of line
- jmp short blankit
-
- fast_eil_partscreen:
- jb fast_to_eol ; 1K - erase to cursor
- std ; work backwards
- mov cl,cur_x ; cur_x spaces backwards
- inc cx ; include character under cursor
- jmp short blankit
-
- fast_to_eol: ; 0K - erase from cursor
- mov cx,dx
- jmp short blankit
- endif
-
- ;---- bios_eil -----------
- eil_slow:
- push dx ; save count to eol
- mov cl,ah ; left margin
- mov ch,cur_y ; set row pointer for
- mov dh,ch ; both corners of scroll region
- mov dl,max_x ; right margin
- dec dx
-
- cmp al,1 ; 2K - whole line?
- ja scrollem ; yes, blank it
- jb eil_from_cursor ; 1K - erase up to cursor
- mov dl,cur_x ; point right side at cursor
- jmp short scrollem ; and blank it
-
- eil_from_cursor:
- mov cl,cur_x ; set left corner of scroll region
- jmp short scrollem ; to cursor location and blank
-
- ;== erase in display ========================================================
- eid: dec si
- lodsb ; get the real parameter
- if direct_scroll
- cmp gmode_flag,ah
- jnz eid_slow
-
- ;--- fast_eid ------------
- cmp al,1 ; 2J - clear screen and home cursor
- jbe fast_partscreen
- mov cur_coords,0 ; home the cursor
- call xy_to_regs ; set up DI and DX accordingly
- mov cx,screen_len ; get size of screen in CX
- shr cx,1 ; make it a word count
- jmp short blankit
-
- fast_partscreen:
- jb fast_from_cursor; 1J - erase screen up to cursor
- std ; work backwards
- mov cx,di ; get pointer to word on screen
- sub cx,video_off ; and subtract start of screen
- shr cx,1 ; to get count in words of area
- inc cx ; to clear
- jmp short blankit ; then clear it
-
- fast_from_cursor:
- mov cx,video_off ; get start of screen
- add cx,screen_len ; point to end of screen
- sub cx,di ; and subtract pointer from it
- shr cx,1 ; to get count in words
- jmp short blankit ; then blank
- endif
-
- ;--- slow_eid ------------
- eid_slow:
- push dx ; preserve count to eol
- mov dx,max_coords ; point to bottom right
- xchg dl,dh ; corner (make adjustments
- dec dx ; for column being 1 based
- cmp al,1
- jbe eid_partscreen ; 2J clear screen
- xor cx,cx ; point to top right corner
- mov cur_coords,cx ; put cursor there
- pop dx ; trash saved count to eol
- call xy_to_regs ; (doesn't modify CX)
- push dx ; use new one instead
- mov dh,max_y
-
- scrollem:
- call get_blank_attrib ; get attribute
- mov bh,ah ; in bh
- mov ax,600h ; blank the screen
- int 10h
- noscroll:
- pop dx ; restore count to eol
- ret
-
- eid_partscreen:
- call eil_slow ; blank what there is of the current line
- xor cx,cx ; point to upper left corner
- cmp byte ptr [si-1],cl
- jz eid_from_cursor ; 1K
- mov dh,cur_y ; make line above current line bottom of
- jmp short check_overlap ; scroll region (dec dh later)
-
- eid_from_cursor:
- mov ch,cur_y ; 0K - line below current line
- inc ch ; top of scroll region
- inc dh ; lower bottom for check
- check_overlap:
- cmp ch,dh ; overlap?
- jz noscroll ; then don't scroll
- dec dh ; else restore bottom
- jmp scrollem ; and scroll region
-
- ;-- device status report --------------------------------
- ; Stuffs an escape, a left bracket, current Y, semicolon, current X,
- ; a capital R, and a carriage return into input stream.
- ; The coordinates are 1 to 3 decimal digits each.
-
- dsr: cmp al,6 ; must be 6n
- jnz dsr_out
- push di
- push es
- mov ax,cs
- mov es,ax
- mov di,offset cpr_buf
- mov al,cur_y
- inc ax ; convert to one-based coords
- call byteout ; row
- mov al,';'
- stosb
- mov al,cur_x
- inc ax ; convert to one-based coords
- call byteout ; column
- mov ax,13*256+'R' ; R ANSI function 'Cursor Position Report'
- stosw
- mov ax,di
- dec ax
- mov word ptr cprseq.adr, ax ; save pointer to last char in string
- sub ax,offset cpr_esc ; di is # of characters in string
- mov word ptr cprseq.len,ax ; pass info to the getchar routine
- pop es
- pop di
- dsr_out:
- ret
-
- ;---- Delete/Insert Lines -------------------------------
- ; AL is number of lines to delete/insert. AH=0
- ; Preserves DX, DI; does not move cursor.
-
- d_l: ; Delete lines.
- dec ah ; BIOS: scroll up
-
- il: ; Insert lines.
- add ah, 7 ; BIOS: scroll down
-
- il_open:
- ; Whether inserting or deleting, limit him to (max_y - cur_y) lines;
- ; if above that, we're just clearing; set AL=0 so BIOS doesn't burp.
- mov bh, max_y
- sub bh, cur_y
- cmp al, bh
- jbe il_ok ; DRK 9/4...
- mov al,dh ; he tried to move too far
- il_ok:
- push ax
- call get_blank_attrib
- mov bh, ah ; color to use on new blank areas
- pop ax ; AL is number of lines to scroll.
-
- mov cl,dh ; upper-left-x of data to scroll
- mov ch, cur_y ; upper-left-y of data to scroll
- push dx
- mov dx, max_coords ; lower-right-x
- xchg dh, dl ; lower-right-y (zero based)
- dec dx
- int 10h ; call BIOS to scroll a rectangle.
- pop dx
- ;fall through to a way back
-
- ;----- nul ---------------------------------------------
- ; No-action ansi sequence; called when unknown command given.
- nul: ret ; done.
-
- ;---- set / reset mode ---------------------------------------
- ; Sets graphics/text mode; also sets/resets "no wrap at eol" mode.
-
- sm: dec ah ; set
-
- rm: mov bx, offset wrap_flag
- cmp al, 7 ; Wrap/nowrap?
- jz sm_flag
- mov bx, offset pseudo_flag
- cmp al, 45 ; Graphics cursor or not?
- jz sm_flag
-
- ;--- Set Video Mode ---
- ; It must be a video mode. Call BIOS.
-
- dec si
- lodsb ; in case mode chosen is zero
- mov ah,dh ; "set video mode"
- int 10h
-
- ; Read the BIOS buffer address/cursor position variables.
- mov ax,abs40
- mov ds,ax
- assume ds:abs40
-
- ; Find current video mode and screen size.
- mov ax, crt_len
- mov cs:screen_len, ax
-
- mov ax,word ptr crt_mode ; al = crt mode; ah = # of columns
- mov cs:max_x, ah
-
- mov bx,0B800h ; segment for colour card
- cbw
- cmp al,4
- jb text_mode
- mov bh,0B8h ; but if not colour text, it's mono
- cmp al,7
- jz text_mode
- dec ah
- text_mode:
- mov es,bx
- mov word ptr cs:video_mode,ax
-
- mov al, crt_rows
- mov cs:max_y,al
-
- ; Find current cursor page.
- mov al,active_page
- mov cs:cur_page,al
-
- ; Find video buffer segment address; adjust so ofs is 0; return in AX.
- mov ax,crt_start
- mov cs:video_off,ax
- mov ax,addr_6845 ; 6845 address
-
- push cs
- pop ds
- assume ds:code
-
- mov port_6845,ax
-
- mov cur_coords,0
- call xy_to_regs
- ret
-
- ;--- Set or reset simple flag ---
- sm_flag:
- mov [bx], ah
- ret
-
- ;-- keyboard reassignment -------------------------------------------
- ; Key reassignment buffer is between param_end and redef_end+2, exclusive.
- ; When it shrinks or grows, param_end is moved.
- ; Format of an entry is as follows:
- ; highest address -> length:word (may be 0)
- ; key to replace:word (either hi or low byte is zero)
- ; .
- ; . new key value, "length" bytes long
- ; .
- ; lowest address -> next entry, or free space.
- ; If no arguments are given, keyboard is reset to default condition.
- ; Otherwise, first parameter (or first two, if first is zero) defines
- ; the key whose value is to be changed, and the following parameters
- ; define the key's new, possibly zero-length, value.
-
- if xlate
- key:
- ; Is this a reset?
- or cx, cx
- jz key_init
- ; Get the first (or first two) parameters
- cld
- dec si
- mov ax,[si] ; get two params
- dec cx ; first param isn't in string
- add si,cx ; point si to end of string
-
- or al, al ; Is it a function key?
- jnz key_notfnkey
-
- or cx,cx ; It's a function key
- jz key_init; if only a zero passed, take it as a reset
- dec cx
- key_notfnkey:
-
- ; Key to redefine now in AX. If it's already redefined,
- ; lookup will set Z, point SI to redef string, set CX to its length.
- push di
- push es
- push cx
- push si
-
- std ; moving up, must move from top down
- push ds
- pop es ; string move must have ES=DS
- call lookup ; rets Z if redefined...
- jnz key_newkey
-
- ; It's already defined. Erase its old definition- i.e., move
- ; region param_end+1..SI-CX upwards CX+4 bytes, add CX+4 to param_end.
-
- sub si,cx
- mov di,si
- add cx,4
- add param_end,cx
- add di,cx
-
- ; adjust the xlatseq pointer
- mov bx, xlatseq.adr
- cmp bx, di ; in area above deleted entry
- ja del_def ; so nothing to do
- add xlatseq.adr, cx ; else move pointer upwards
- cmp bx, si ; was it the deleted entry?
- jb del_def
- mov xlatseq.len, 0 ; if so, null the sequence
- del_def:
- rep movsb
- key_newkey:
- ; Key not redefined. See if there's enough room to redefine it.
- pop si ; get back pointer to redef string
- pop cx ; get back number of bytes in redef string
- mov di, param_end ; hi byte of new redef record, hi byte of len
- sub di, 3 ; low byte of new redef index
- mov bx, di
- sub bx, 17 ; better be at least 16 bytes room
- cmp bx, si
- jb key_popem ; nope- forget it.
- ; Nothing in the way now!
- mov [di+2], cx ; save length field
- stosw
- inc di ; adjust for descending pointer
- rep movsb ; copyit
- mov param_end, di ; save adr of new hi byte of free area
- key_popem:
- pop es
- pop di
- cld
- ret
-
- key_init:
- ; Build the default redefinition table:
- ; control-printscreen -> control-P
- push es
-
- push ds
- pop es
-
- std
- mov di, redef_end
- mov ax, 1
- stosw
- mov ax, 7200h ; control-printscreen
- stosw
- inc di
- mov al, 16 ; control P
- stosb
- mov param_end, di ; save new bottom of redef table
- pop es
- cld
- ret
-
- else
- key equ offset nul
- endif
-
- ansi_functions endp ; end dummy procedure block
-
-
- code ends
- end
-