home *** CD-ROM | disk | FTP | other *** search
- %title "NNANSI Terminal Driver Main Module"
- %pagesize 60, 132
- %noconds
- ;--- nnansi.asm ----------------------------------------------------------
- ; New, New ANSI terminal driver.
- ; Optimized for speed in the case of multi-character write requests.
- ; (C) 1986 Daniel Kegel, Pasadena, CA
- ; May be distributed for educational and personal use only
- ; The following files make up the driver:
- ; nnansi.asm - all DOS function handlers except init
- ; nnansi_d.asm - Compilation options
- ; nnansi_p.asm - parameter parser for ANSI escape sequences
- ; nnansi_f.asm - ANSI command handlers
- ; nnansi_i.asm - init DOS function handler
- ;
- ; Daniel Kegel, Bellevue, Washington & Pasadena, California
- ; Revision history:
- ; 5 july 85: brought up non-ANSI portion except forgot backspace
- ; 6 july 85: split off ANSI stuff into other files, added backspace
- ; 11 july 85: fixed horrible bug in getchar; changed dosfns to subroutines
- ; 12 july 85: fixed some scrolling bugs, began adding compaq flag
- ; 9 aug 85: added cursor position reporting
- ; 10 aug 85: added output character translation
- ; 11 aug 85: added keyboard redefinition, some EGA 80x43 support
- ; 10 sept 85: Tandy 2000 support via compaq flag (finding refresh buffer)
- ; 30 Jan 86: removed Tandy 2000 stuff, added graphics mode support
- ; 12 feb 86: added int 29h handler, added PUSHA/POPA, added direct beep,
- ; direct cursor positioning, takeover of BIOS write_tty,
- ; noticed & squashed 2 related bugs in tab expansion
- ; 13 feb 86: Squashed them again, harder
- ; 24 feb 86: There is a bug in the timing code used by the BEEP routine.
- ; If the addition of the beep period to the
- ; BIOS low timer word results in an overflow, the beep will be
- ; supressed. Also made code compatible eith earlier versions
- ; of assembler.
-
- ; Tom Almy, Tualatin, Oregon (toma@tekgvs.labs.tek.com) modified the NANSI
- ; version ; 2.2 code for use in EGA/VGA environments only:
- ; 8 Jan 89: Additional compilation options
- ; Scrolling via reprogramming display start (*MUCH* faster)
- ; INT29 updates display directly if not control character.
- ; Various cleanups
- ; Nov 89: Some bug fixes, customization for various cards enhanced
- ; display modes, better handling of graphic cursor, graphic
- ; characters in 16 color modes are drawn by NNANSI rather
- ; than BIOS (much faster).
- ; Sept 90: Color backgrounds and XOR mode (as BLINK) in 16 color graphic
- ; modes. VGA has 43 or 50 line modes (instead of producing 50
- ; (when 43 selected). FAST mode can be toggled via escape
- ; sequences. Lots of code clean up. Some old options incorporated
- ; (extra ANSI sequences) or deleted (output conversion).
- ; The fast graphic draw routine has been speeded up, since it
- ; was slower than some BIOSes (!). The BIOS TTY call has been
- ; redirected to the INT29 routine which has some efficiency
- ; speedups; this also saved code space.
-
- ;------------------------------------------------------------------------
-
- include nnansi_d.asm ; definitions
-
- ; from nnansi_f.asm
- extrn f_escape:near, f_in_escape:near
-
- ; from nnansi_i.asm
- extrn dosfn0:near
-
- ; to nnansi_p.asm
- public f_loopdone
- public f_not_ansi
- public f_ansi_exit
- public in_num
-
- ; to both nnansi_p.asm and nnansi_f.asm
- public cur_x, cur_y, max_x, cur_attrib
-
- ; to nnansi_f.asm
- public xy_to_regs, get_blank_attrib
- public wrap_flag
- public cur_parm_ptr
- public cur_coords, saved_coords, max_y
- public escvector, string_term
- public cpr_esc, cprseq
- public video_mode
- if key_redef
- public lookup
- endif
- public gmode_flag
- public gcursor
- public set_gmode
- public fmode
- public rev_flag
- public move_back
-
- ; to nnansi_i.asm
- public req_ptr, break_handler
- public int_29
- public new_vid_bios, old_vid_bios
-
- ; to all modules
- public param_buffer, param_end
- if key_redef
- public redef_end
- endif
-
- ;--- push_all, pop_all ------------------------------------------------
- ; Save/restore all user registers.
- IF cheap_pc
- push_all macro
- push ax
- push bx
- push cx
- push dx
- push bp
- push si
- push di
- endm
- ELSE
- push_all macro
- pusha
- endm
- ENDIF
-
- IF cheap_pc
- pop_all macro
- pop di
- pop si
- pop bp
- pop dx
- pop cx
- pop bx
- pop ax
- endm
- ELSE
- pop_all macro
- popa
- endm
- ENDIF
-
- call_video macro ; call original video interrupt
- pushf ; push flags
- call dword ptr cs:old_vid_bios
- endm
-
- draw_gcursor macro ; draw graphic cursor
- if quick_char
- mov ax, 8f16h
- call quick_graph
- else
- mov ax, 0916h ; draw cursor at location
- mov bx, 8fh
- mov cx, 1
- call_video
- endif
- endm
-
-
- keybuf struc ; Used in getchar
- len dw ?
- adr dw ?
- keybuf ends
-
-
- ABS40 segment at 40h
- org 1ah
- buffer_head dw ? ; Used in 'flush input buffer' dos call.
- buffer_tail dw ?
-
- org 49h
- crt_mode db ?
- crt_cols dw ?
- crt_len dw ?
- crt_start dw ?
- cursor_posn dw 8 dup (?)
- cursor_mode dw ?
- active_page db ?
- addr_6845 dw ?
- crt_mode_set db ? ; = 7 only if monochrome display adaptor
- crt_palette db ?
- org 6ch
- timer_low dw ? ; low word of time-of-day counter (18.2 hz)
- org 84h
- ega_rows db ? ; #rows-1 on display
- ega_points dw ? ; bytes per character
-
- ABS40 ends
-
- page
-
- CODE segment word public 'CODE'
- assume cs:CODE, ds:CODE
-
- ; Device Driver Header
-
- org 0
-
- dd -1 ; next device
- dw 8013h ; attributes
- dw strategy ; request header pointer entry
- dw interrupt ; request entry point
- db 'CON' ; device name (8 char)
- db 5 dup (20h) ; ... and 5 blanks)
-
- ; Identification- in case somebody TYPEs the assembled driver
- db 27,'[2J'
- db "NNANSI.SYS EGA/VGA"
- ife cheap_pc
- db "(80286)"
- else
- db "(80x86)"
- endif
- db 13, 10
- db 'by Tom Almy based on code (C) Daniel Kegel, Pasadena, CA 1986.'
- db 13, 10, 26
-
- even
- ;----- variable area --------------------
- org $-38 ; overlay id string with uninitialized data
- req_ptr label dword
- req_off dw ?
- req_seg dw ?
- f_cptr_seg dw ? ; part of fastout write buffer pointer
- cur_parm_ptr dw ? ; last byte of parm area now used
- old_vid_bios dd ? ; pointer to old video bios routine
- saved_coords dw ? ; holds XY after a SCP escape sequence
- temp_val dw ? ; just a temporary
- param_buffer dw ? ; address of first byte free for new params
- param_end dw ? ; address of end of free area
- if key_redef
- redef_end dw ? ; address of end of redefinition area
- endif
- no_c_flag db ? ; there is no graphic cursor on the screen.
- max_y db ? ; lines-1
- max_cur_x label word ; used to get both max & cur at once
- max_x db ? ; line width (79 for 80x25 modes)
- cur_coords label word
- cur_x db ? ; cursor position (0 = left edge)
- cur_y db ? ; (0 = top edge)
- video_mode db ? ; ROM BIOS video mode (2=BW, 3=color, etc)
- string_term db ? ; either escape or double quote
- in_num db ? ; true if between a digit and a semi in parse
- int_29_buf db ? ; character buffer for int 29 calls
- fnkeybuf db ? ; holds second byte of fn key codes
- cpr_buf db 8 dup (?), '['
- cpr_esc db 1bh ; descending buffer for cpr function
-
- even ; this should be redundant, if I did it right
-
- ; following four keybufs hold information about input
- ; Storage order determines priority- since the characters making up a function
- ; key code must never be separated (say, by a Control-Break), they have the
- ; highest priority, and so on. Keyboard keys (except ctrl-break) have the
- ; lowest priority.
-
- fnkey keybuf <0, fnkeybuf> ; fn key string (0 followed by scan code)
- cprseq keybuf <0> ; CPR string (ESC [ y;x R)
- brkkey keybuf <0, brkkeybuf> ; ^C
- if key_redef
- xlatseq keybuf <0> ; keyboard reassignment string
- endif
-
- escvector dw 0 ; state vector of ESCape sequencor
- brkkeybuf db 3 ; control C
- wrap_flag db 1 ; 0 = no wrap past line end
- cur_attrib db 7 ; current char attributes
- gmode_flag db 0 ; true if in graphics mode
- gcursor db initgc ; true if graphic cursor enabled
- fmode db initfast ; in fast mode?
- rev_flag db 0 ; non-zero if in reverse video
-
- port_6845 equ 3d4h
- page
- ;------ xy_to_regs --------------------------------------------
- ; on entry: x in cur_x, y in cur_y
- ; on exit: dx = chars left on line, di = address
- ; Alters ax, bx.
- xy_to_regs proc near
- ; Find number of chars 'till end of line, keep in DX
- mov ax, max_cur_x
- mov bx, ax ; save max_x & cur_x for next block
- xor ah, ah ; ax = max_x
- xchg dx, ax
- mov al, bh
- xor ah, ah ; ax = cur_x
- sub dx, ax
- inc dx ; dx is # of chars till EOL
- ; Calculate DI = current address in text buffer
- mov al, bl ; al = max_x
- inc al
- mul cur_y
- add al, bh ; al += cur_x
- adc ah, 0 ; AX is # of chars into buffer
- add ax, ax
- xchg di, ax ; DI is now offset of cursor.
-
- push ds
- mov ax, ABS40
- mov ds, ax
- assume ds:ABS40
- add di, crt_start ; crt offset
- ; the offset could be non-zero because
- ; of video pages or fast scrolling.
- pop ds
- assume ds:nothing
- ret
- xy_to_regs endp
-
- page
- ;------- dos_fn_tab -------------
- ; This table is used in "interrupt" to call the routine that handles
- ; the requested function.
-
- max_cmd equ 12
- dos_fn_tab:
- dw dosfn0, nopcmd, nopcmd, badcmd, dosfn4, dosfn5, dosfn6
- dw dosfn7, dosfn8, dosfn8, nopcmd, nopcmd
-
- ;------- strategy ----------------------------------------------------
- ; DOS calls strategy with a request which is to be executed later.
- ; Strategy just saves the request.
-
- strategy proc far
- mov cs:req_off,BX
- mov cs:req_seg,ES
- ret
- strategy endp
-
- ;------ interrupt -----------------------------------------------------
- ; This is where the request handed us during "strategy" is
- ; actually carried out.
- ; Calls one of 12 subroutines depending on the function requested.
- ; Each subroutine returns with exit status in AX.
-
- interrupt proc far
-
- sti
- push_all ; preserve caller's registers
- push ds
- push es
-
-
- ; Read requested function information into registers
- lds bx,cs:req_ptr
- xor ah,ah ; clear upper part of ax
- mov al,ds:[BX+02h] ; al = function code
- ;
- ; The next instruction blows up MASM 1.0 but who cares!!
- ;
- les si,[BX+0Eh] ; ES:SI = input/output buffer addr
- mov cx,[BX+12h] ; cx = input/output byte count
-
- cmp al, max_cmd
- ja unk_command ; too big, exit with error code
-
- xchg bx, ax
- shl bx, 1 ; form index to table of words
- mov ax, cs
- mov ds, ax
- call word ptr dos_fn_tab[bx]
- int_done:
- lds bx,cs:req_ptr ; report status
- or ax, 100h ; (always set done bit upon exit)
- mov [bx+03],ax
-
- pop ES ; restore caller's registers
- pop DS
- pop_all
- ret ; return to DOS.
-
- unk_command:
- call badcmd
- jmp int_done
-
- interrupt endp
- page
- ;----- BIOS break handler -----------------------------------------
- ; Called by BIOS when Control-Break is hit (vector was set up in Init).
- ; Simply notes that a break was hit. Flag is checked during input calls.
-
- break_handler proc
- mov cs:brkkey.len, 1
- iret
- break_handler endp
-
- page
-
- ;------ badcmd -------------------------------------------------------
- ; Invalid function request by DOS.
- badcmd proc near
- mov ax, 813h ; return "Error: invalid cmd"
- ret
- badcmd endp
-
-
- ;------ nopcmd -------------------------------------------------------
- ; Unimplemented or dummy function request by DOS.
- nopcmd proc near
- xor ax, ax ; No error, not busy.
- ret
- nopcmd endp
-
- ;------- dos function #4 ----------------------------------------
- ; Reads CX characters from the keyboard, places them in buffer at
- ; ES:SI.
- dosfn4 proc near
- jcxz dos4done
- mov di, si
- dos4lp: push cx
- call getchar
- pop cx
- stosb
- loop dos4lp
- dos4done:
- xor ax, ax ; No error, not busy.
- ret
- dosfn4 endp
-
- ;-------- dos function #5: non-destructive input, no wait ------
- ; One-character lookahead into the keyboard buffer.
- ; If no characters in buffer, return BUSY; otherwise, get value of first
- ; character of buffer, stuff into request header, return DONE.
- dosfn5 proc near
- call peekchar
- jz dos5_busy
-
- lds bx,req_ptr
- mov [bx+0Dh], al
- xor ax, ax ; No error, not busy.
- jmp short dos5_exit
- dos5_busy:
- MOV ax, 200h ; No error, busy.
- dos5_exit:
- ret
-
- dosfn5 endp
-
- ;-------- dos function #6: input status --------------------------
- ; Returns "busy" if no characters waiting to be read.
- dosfn6 proc near
- call peekchar
- mov ax, 200h ; No error, busy.
- jz dos6_exit
- xor ax, ax ; No error, not busy.
- dos6_exit:
- ret
- dosfn6 endp
-
- ;-------- dos function #7: flush input buffer --------------------
- ; Clears the IBM keyboard input buffer. Since it is a circular
- ; queue, we can do this without knowing the beginning and end
- ; of the buffer; all we need to do is set the tail of the queue
- ; equal to the head (as if we had read the entire queue contents).
- ; Also resets all the device driver's stuffahead buffers.
- dosfn7 proc near
- xor ax, ax
- mov fnkey.len, ax ; Reset the stuffahead buffers.
- mov cprseq.len, ax
- mov brkkey.len, ax
- if key_redef
- mov xlatseq.len, ax
- endif
-
- mov ax, ABS40
- mov es, ax
- mov ax, es:buffer_head ; clear queue by making the tail
- mov es:buffer_tail, ax ; equal to the head
-
- xor ax, ax ; no error, not busy.
- ret
- dosfn7 endp
-
- page
- ;--- new_vid_bios -------------------------------------------
- ; new_vid_bios takes the set cursor, get display mode, change mode, and
- ; get mode calls.
-
- ; If bios_write_tty defined, new_vid_bios replaces the write_tty call.
- ; This gives BIOS ANSI capability.
- ; However, it takes away the escape character.
- ; If this is not desired, just tell init to not take over the vector.
- ;
- ; All other calls get sent to the old video bios.
-
- JUMPS ; clarify branches -- TASM V2.0 recommended
-
- new_vid_bios proc
- STI
- IF bios_write_tty
- cmp ah, 14
- jz nvb_write_tty
- ENDIF
- cmp Ah, 02h ; set cursor position command?
- jz nvb_setcursor
- cmp Ah,0 ; change mode command?
- jz nvb_smode
- cmp cs:fmode,0 ; slow mode?
- jz new_vid_pass ; then pass it on
- cmp Ah, 0Fh ; get display mode command?
- jz nvb_display
- cmp Ah, 06h ; clear screen command?
- jz nvb_scroll
- cmp Ah, 07h ; alternative cls command?
- jz nvb_scroll
- new_vid_pass:
- jmp dword ptr cs:old_vid_bios
- IF bios_write_tty
- IF 1 ; Does INT 29 now!
- ; WRITE TTY SUBCOMMAND
- nvb_write_tty:
- push cx ; save register
- mov cl, cs:cur_attrib
- ; If in graphics mode, BL is new color
- cmp cs:gmode_flag, 0
- jz nvb_wt_text
-
- mov cs:cur_attrib, bl ; ja?
- nvb_wt_text:
- int 29h
- mov cs:cur_attrib, cl
- pop cx
- iret
- ELSE
- ; WRITE TTY SUBCOMMAND
- nvb_write_tty:
- ; sti
- push ds
- push cs
- pop ds ; establish adressability
- assume ds:CODE
- push es
- push_all
- mov cl, cur_attrib
- ; If in graphics mode, BL is new color
- cmp gmode_flag, 0
- jz nvb_wt_text
-
- mov cur_attrib, bl ; ja?
- nvb_wt_text:
- push cx
-
- mov cx, 1
- mov bx, cs
- mov es, bx
- mov si, offset int_29_buf
- mov byte ptr es:[si], al
- call dosfn8
-
- pop cx
- mov cs:cur_attrib, cl ; restore color
- pop_all
- pop es
- pop ds
- assume ds:nothing
- iret
- ENDIF
- ENDIF
-
- ; GET DISPLAY MODE SUBCOMMAND
- nvb_display:
- cmp cs:gmode_flag,0 ; Graphic mode?
- jnz new_vid_pass
- push ds
- push dx
- mov dx, ABS40
- mov ds, dx
- assume ds:ABS40
- cmp crt_start,0 ; At start of mem?
- jz nvb_pass
- call move_back
- jmp nvb_pass
-
- ; SCROLL DISPLAY SUBCOMMAND
- nvb_scroll:
- push ds
- push dx
- mov dx, ABS40
- mov ds, dx
- assume ds:ABS40
- mov cs:no_c_flag, 1 ; if graphic, don't draw cursor afterwards
- cmp cs:gmode_flag,0 ; graphic mode?
- jnz nvb_pass
- cmp crt_start,0 ; not at start of mem
- jz nvb_pass
- cmp al, 0 ; scroll, not erase
- jne nvb_pass
- or cx, cx ; not entire screen?
- jne nvb_pass
- pop dx
- push dx
- inc dl
- cmp dl, byte ptr crt_cols ; same question, max columns
- ja nvb_pass ; >size is full screen, though
- cmp dh, ega_rows ; same question, max rows
- ja nvb_pass ; >size is full screen, though
- push ax ; erase is easier since we dont move screen
- xor ax,ax
- mov crt_start,0 ; reset offsets
- mov dx,port_6845
- mov al,0ch
- out dx,ax
- inc al
- out dx,ax
- pop ax
- ; jmp nvb_pass ; jump is redundant
-
- nvb_pass:
- pop dx
- assume ds:nothing
- pop ds
- jmp dword ptr cs:old_vid_bios ; now doit
-
- ; SET CURSOR SUBCOMMAND
- nvb_setcursor:
- push ds
- push dx
- mov dx, ABS40
- mov ds,dx
- assume ds:ABS40
- cmp cs:gmode_flag,0 ; Alpha mode?
- je nvb_pass
- cmp cs:no_c_flag, 0 ; inhibited cursor?
- jnz nvb_pass ; then keep inhibited
- cmp cs:gcursor, 0 ; no cursor?
- jz nvb_pass ; then don't want one now!
- push_all
- draw_gcursor
- pop_all
- assume ds:nothing
- pop dx ; restore registers
- pop ds
- call_video ; original int 10h
- push_all
- draw_gcursor ; redraw the cursor
- pop_all
- iret ; return from interrupt
-
- ; SET DISPLAY MODE SUBCOMMAND
- nvb_smode:
- call_video
- push_all
- push ds
- mov dx, ABS40
- mov ds, dx
- assume ds:ABS40
- mov al, crt_mode ; get mode and check for being graphic
- call set_gmode
- mov cs:no_c_flag, al ; if graphic, then no cursor is on screen.
- pop ds
- assume ds:nothing
- pop_all
- iret
- NOJUMPS
- new_vid_bios endp
- page
-
- ;------ int_29 ----------------------------------------------
- ; Int 29 handles DOS quick-access putchar.
- ; Last device loaded with attribute bit 4 set gets accessed for
- ; single-character writes via int 29h instead of via interrupt.
- ; Must preserve all registers.
- ; Installed as int 29h by dosfn0 (init).
-
- int_29 proc near
- sti
- push ds
- push es
- push_all
- if fast29
- cmp al, 20h ; control char?
- jb slow_way
- cmp cs:escvector, 0 ; middle of an escape sequence?
- jnz slow_way
- mov dx, ABS40
- mov ds, dx ; set addressability
- assume ds:ABS40
- mov cx, word ptr crt_mode ; mode in cl, columns in ch
- cmp cl, 3 ; graphics mode?
- ja slow_way
- xor bx, bx ; get cursor position
- mov bl, active_page
- add bx, bx
- mov dx, cursor_posn[bx] ; dh has y, dl has x
- inc dl ; point to next location
- cmp dl, ch ; at edge?
- jnb slow_way
- ; we can go with it!
- mov cursor_posn[bx], dx ; update pointer
- xchg ax, bx
- mov al, dh
- mul ch ; ax has line offset
- add al, dl
- adc ah, 0 ; total offset
- mov cx, bx
- mov bx, ax ; cl has character, bx offset
-
- mov ax, crt_start
- shr ax, 1
- add bx, ax ; corrected cursor offset, either
- ; because of fast scroll or
- ; page<>0
-
- mov dx, port_6845 ; update cursor location
- mov al,0eh ; more effective to write two bytes at a time
- mov ah,bh
- out dx,ax
- inc al
- mov ah,bl
- out dx,ax
-
- mov al, cl ; get back character
-
- dec bx
- add bx, bx ; byte offset
- mov dx, 0b800h ; address screen
- mov ds, dx
- assume ds:nothing
- mov ah, cs:cur_attrib
- mov ds:[bx], ax ; write character
- jmp short int_fin
- endif
- slow_way:
- mov cx, 1
- mov bx, cs
- mov es, bx
- mov si, offset int_29_buf
- mov byte ptr es:[si], al
- call dosfn8
- int_fin:
- pop_all
- pop es
- pop ds
- iret
- int_29 endp
-
-
- page
- ;------ dosfn8 -------------------------------------------------------
- ; Handles writes to the device (with or without verify).
- ; Called with
- ; CX = number of bytes to write
- ; ES:SI = transfer buffer
- ; DS = CS, so we can access local variables. NOT ANY MORE
-
- dosfn8 proc near
-
- mov cs:f_cptr_seg, es ; save segment of char ptr
-
- ; 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,word ptr crt_mode ; al = crt mode; ah = # of columns
- mov cs:video_mode, al
- dec ah ; ah = max column
- mov cs:max_x, ah
-
- ; Save graphics mode flag
- call set_gmode
-
- mov al, ega_rows ; number of display rows
- mov cs:max_y, al ; set maxy value
-
- ; Find current cursor coordinates.
-
- mov al, active_page
- cbw
- add ax, ax
- xchg bx, ax
- mov ax, cursor_posn[bx]
- mov cs:cur_coords, ax
-
- ; Find video buffer segment address; adjust it
- ; so the offset is zero; return in AX.
-
- mov ax, 0B800H ; this gets corrected in xy_to_regs
- ; if we are not screen 0
- push cs
- pop ds
- assume ds:CODE
- mov es, ax
- call xy_to_regs ; Set DX, DI according to cur_coords.
-
- ; | If in graphics mode, clear old pseudocursor
-
- cmp gmode_flag, 0
- jz d8_no_cp
- cmp no_c_flag, 0 ; cursor not previously drawn?
- mov no_c_flag, 0 ; (reset flag, will be drawn from now on)
- jnz d8_no_cp ; not drawn -- don't clear
- cmp gcursor, 0 ; don't clear if cursor is off, either
- jz d8_no_cp
- push cx
- push dx
- push di
- draw_gcursor
- pop di
- pop dx
- pop cx
-
- d8_no_cp:
-
- mov ah, cur_attrib
- mov ds, f_cptr_seg ; get segment of char ptr
- assume ds:nothing
- cld ; make sure we'll increment
-
- ; The Inner Loop: 12+4+4+11+14+2+19= 66 cycles/loop
- ; on 8088; at 4.77 MHz, that gives 16.1 microseconds/loop.
- ; At that speed, it takes 32 milliseconds to fill a screen.
-
- ; Get a character, put it on the screen, repeat 'til end of line
- ; or no more characters.
- jcxz f_loopdone ; if count = 0, we're already done.
- cmp cs:escvector, 0 ; If in middle of an escape sequence,
- jz f_tloop
- jmp f_in_escape ; jump to escape sequence handler.
-
- f_tloop:; | If in graphics mode, jump to alternate loop
- ; | What a massive kludge! A better approach would have been
- ; | to collect characters for a "write n chars" routine
- ; | which would handle both text and graphics modes.
- cmp cs:gmode_flag,0
- jz f_t_cloop
- jmp f_g_cloop
-
- f_t_cloop:
- LODSB ; get char! (al = ds:[si++])
- cmp al, 28 ; is it a control char?
- jb f_control ; maybe...
- f_t_nctl:
- STOSW ; Put Char! (es:[di++] = ax)
- dec dx ; count down to end of line
- loopnz f_t_cloop ; and go back for more.
- jz f_t_at_eol ; at end of line, maybe do a crlf.
- jmp short f_loopdone ; finished execution
-
- f_looploop:
- f_ansi_exit: ; in case we switched into
- loopnz f_tloop ; a graphics mode
- jnz f_loopdone
- f_t_at_eol:
- jmp f_at_eol
-
- f_loopdone:
-
- ;--------- All done with write request -----------
- ; DI is cursor address, cursor position in cur_y, dl
-
- assume ds:ABS40
- mov ax, ABS40
- mov ds, ax
-
- ; Set cursor position in low memory.
-
- mov al,active_page
- cbw
- add ax,ax
- xchg bx,ax
- mov al, cs:max_x
- inc al
- sub al, dl
- mov ah, cs:cur_y
- mov cursor_posn[bx],ax
-
- cmp cs:gmode_flag,0
- jnz pseudocursor ; In graphics mode, there is
- ; a pseudo cursor to draw.
-
- ; Write directly to 6845 cursor address register.
- mov bx, di
- shr bx, 1 ; convert word index to byte index
-
- mov dx, port_6845 ; works with or without no-mono
-
- mov al,0eh ; more effective to write two bytes at a time
- mov ah,bh
- out dx,ax
- inc al
- mov ah,bl
- out dx,ax
-
-
- ; Return to DOS.
- xor ax, ax ; No error, not busy.
- ret
-
- pseudocursor:
- cmp cs:gcursor, 0 ; graphics cursor off?
- jz nopseudo
- mov cs:no_c_flag,0 ; there is a cursor now!
- draw_gcursor
- nopseudo:
- xor ax, ax
- ret
-
- ;---- handle control characters ----
- ; Note: cur_x is not kept updated in memory, but can be
- ; computed from max_x and dx.
- ; Cur_y is kept updated in memory.
- f_escapex: ; far jump
- jmp f_escape
-
- f_control:
- cmp al, 27 ; Is it an escape?
- jz f_escapex
- cmp al, 13 ; carriage return?
- jz f_cr
- cmp al, 10 ; line feed?
- jz f_lf
- cmp al, 8 ; backspace?
- jz f_bs
- cmp al, 9 ; tab?
- jz f_tab
- cmp al, 7 ; bell
- jz f_bell
- jmp f_nctl ; then it is not a control char.
-
- f_bell: ;----- Handle bell ----------------------
- ; Use BIOS to do the beep. DX is not changed, as bell is nonprinting.
- call beep
- or al, al ; clear z
- jmp f_looploop ; Let main loop decrement cx.
-
- f_bs: ;----- Handle backspace -----------------
- ; Moves cursor back one space without erasing. No wraparound.
- cmp dl, cs:max_x ; wrap around to previous line?
- ja fbs_wrap ; yep; disallow it.
- dec di ; back up one char & attrib,
- dec di
- inc dx ; and note one more char left on line.
- fbs_wrap:
- jmp f_looploop
-
- f_cr: ;----- Handle carriage return -----------
- ; di -= cur_x<<1; set di= address of start of line
- ; dx=max_x+1; set bx= chars left in line
- mov al, cs:max_x
- inc al
- sub al, dl ; Get cur_x into ax.
- mov ah, 0
- sub di, ax
- sub di, ax
- mov dl, cs:max_x ; Full line ahead of us.
- inc dx
- mov ah, cs:cur_attrib ; restore current attribute
- or al, 1 ; clear z
- jmp f_looploop ; and let main loop decrement cx
-
- f_at_eol:
- ;----- Handle overrunning right end of screen -------
- ; cx++; compensate for double loop
- ; if (!wrap_flag) { dx++; di-=2; }
- ; else do_crlf;
- inc cx
- test cs:wrap_flag, 1
- jnz feol_wrap
- dec di
- dec di
- inc dx
- jmp f_looploop
- feol_wrap:
- ; dx=max_x+1; set bx= chars left in line
- ; di -= 2*(max_x+1);
- ; do_lf
- mov dl, cs:max_x
- inc dx
- sub di, dx
- sub di, dx
- ; fall thru to line feed routine
-
- f_lf: ;----- Handle line feed -----------------
- ; if (cur_y >= max_y) scroll; scroll screen up if needed
- ; else { cur_y++; di += max_x<<1; else increment Y
-
- mov al, cs:max_y
- cmp cs:cur_y, al
- jb flf_noscroll
- call scroll_up ; preserves bx,cx,dx,si,di
- jmp short flf_done
- flf_noscroll:
- inc cs:cur_y
- mov al, cs:max_x
- mov ah, 0
- inc ax
- add ax, ax
- add di, ax
- flf_done:
- mov ah, cs:cur_attrib ; restore current attribute
- or al, 1 ; clear z
- jmp f_looploop ; and let main loop decrement cx
-
- f_tab: ;----- Handle tab expansion -------------
- ; Get cur_x into al.
- mov al, cs:max_x
- inc al
- sub al, dl
- ; Calculate number of spaces to output.
- push cx ; save cx
- mov ch, 0
- mov cl, al ; get zero based x coordinate
- and cl, 7
- neg cl
- add cl, 8 ; 0 -> 8, 1 -> 8, ... 7 -> 1
- sub dx, cx ; update chars-to-eol, maybe set z
- pushf ; || save Z for main loop
- ; ah is still current attribute. Move CX spaces to the screen.
- mov al, ' '
- cmp cs:gmode_flag,0
- jnz f_tab_putc
-
- REP STOSW
- popf ; || restore Z flag for main loop test
- pop cx ; restore cx
- jmp f_looploop ; Let main loop decrement cx.
-
- ;--------------- graphics mode support -----------------------
-
- ;---- Alternate main loop for graphics mode ----
- f_g_cloop:
- LODSB ; get char! (al = ds:[si++])
- cmp al, 28 ; is it a control char?
- jb f_g_control ; maybe...
- f_g_nctl:
- call putchar
- dec dx ; count down to end of line
- loopnz f_g_cloop ; and go back for more.
- jz f_at_eol ; at end of line; maybe do a crlf.
- jmp f_loopdone
-
- f_g_control: jmp f_control
-
- ; Tabs in graphic mode
- f_tab_putc: ; graphics mode- call putc to put the char
- add dx, cx ; move back to start of tab
- f_tp_lp:
- call putchar
- dec dx ; go to next cursor position
- loop f_tp_lp
- popf ; Z set if wrapped around EOL
- pop cx
- jmp f_looploop
-
- ;---- Where to go when a character turns out not to be special
- f_nctl:
- f_not_ansi:
- cmp cs:gmode_flag,0
- jnz f_g_nctl
- jmp f_t_nctl ; text mode
-
- page
- ;---- putchar ------------------------------------------------
- ; Writes char AL, attribute AH to screen at (max_x+1-dl), cur_y.
- ; On entry, registers set up as per xy_to_regs.
- ; Preserves all registers.
- putchar proc near
- push dx
- push cx
- push bx
- push ax
- ; 1. Set cursor position.
- mov al, cs:max_x
- inc al
- sub al, dl
- mov cs:cur_x, al
- mov dx, cs:cur_coords ; get X & Y into DX
- push ds
- mov ax, 40h
- mov ds, ax
- assume ds:ABS40
- mov cursor_posn,dx
- pop ds
- assume ds:nothing
- xor bx, bx ; choose dpy page 0
- mov ah, 2 ; chose "Set Cursor Position"
- call_video
- ; 2. Write char & attribute.
- IF quick_char
- pop ax
- push ax ; character and attribute
- call quick_graph
- ELSE
- mov cx, 1
- pop ax ; get char in AL
- push ax
- mov bl, ah ; attribute in BL
- mov bh, 0
- mov ah, 9
- call_video
- ENDIF
- pop ax
- pop bx
- pop cx
- pop dx
- ret
- putchar endp
- page
- IF quick_char
- quick_graph proc near
- ; this code has been reworked for much greater speed.
-
- ; ah= mode, al= char, ax,bx,cx,dx destroyed
- gmode_test yesQuick
-
- mov bl,ah
- xor bh,bh
- mov cx, 1
- mov ah, 9
- call_video ; do it the old way
- ret
-
- yesQuick:
- push ds
- mov bx, 40h
- mov ds, bx
- assume ds:ABS40 ; address abs segment
- push es
- push bp
- push si
- push di ; save some registers
- push ax ; save char and mode
-
- mov ax, crt_cols
- mov cx, ega_points ; pixel rows in character
- mov bp, ax ; save number of columns=#bytes
- mul byte ptr (cursor_posn+1)
- mul cx ; (ignore upper product in DX)
- add al, byte ptr (cursor_posn) ; y*#cols*#rows + x
- adc ah, 0 ; take care of carry
- mov si, ax ; save address in si
- xor ax, ax
- mov es, ax ; absolute zero
- les di, es: dword ptr (43h * 4) ; contents of vector 43h
- pop ax
- push ax ; get char and mode
- mul cl ; offset to character in table
- add di,ax ; di has character bit pattern start
- mov ax, 0a000h ; address of display segment
- mov ds, ax
- assume ds:nothing
-
- ; to recap: cx=#rows, bp=#columns, ds:si=display address, es:di=character addr
- mov dx, 3ceh
- mov ax, 0a05h
- out dx,ax ; set write mode 2, read mode 1
-
- mov ax, 7 ; set color dontcare register to zero
- out dx,ax
-
- pop bx ; character mode in bh
- IF gbackground
- mov bl,bh ; extract background color
- IF cheap_pc
- shr bl,1
- shr bl,1
- shr bl,1
- shr bl,1
- ELSE
- shr bl,4
- ENDIF
- or bh, bh
- jns overMode
- mov ax, 1803h ; exor mode
- out dx,ax
-
- and bx, 0f07h ; xor=blink bit
- ELSE
- or bh, bh
- jns overMode
- mov ax, 1803h ; exor mode
- out dx,ax
-
- and bx, 7f00h ; mask off xor bit
- ENDIF
- mov al, 8 ; bit mask register
- out dx, al
- inc dx
- chLoop:
- mov al, es:[di] ; get pixel pattern
- out dx, al
- and [si],bh ; update foreground
- not al
- out dx, al ; and background
- and [si],bl
- inc di
- add si, bp ; go to next character byte and line
- loop chLoop
-
- joinret:
- dec dx
- mov ax, 0ff08h ; bit mask
- out dx, ax
- mov ax, 5 ; mode register
- out dx, ax
- mov al, 3 ; (ah is zero)
- out dx, ax
- mov ax, 0f07h
- out dx, ax
-
- pop di
- pop si
- pop bp
- pop es
- pop ds
- ret
-
- overMode:
- IF gbackground
- and bx, 0f07h ; xor=blink bit
- ELSE
- and bx, 7f00h ; mask off xor bit
- ENDIF
- mov al, 8 ; bit mask register
- out dx, al
- inc dx
- ; we need to load the internal buffer with a solid
- ; background. By writing a solid background and then
- ; reading it back, we can do the job.
- mov al, 0ffh ; force set background
- out dx, al
- mov [si], bl
- mov al, [si] ; read reset pattern
- chLoop2:
- mov al, es:[di] ; get pixel pattern
- out dx, al
- mov [si],bh ; update foreground
- inc di
- add si, bp ; go to next character byte and line
- loop chLoop2
- jmp joinret
-
- quick_graph endp
- ENDIF
-
-
- ;--------------- end of graphics mode support --------------------
-
- dosfn8 endp
- page
- ;--- get_blank_attrib ------------------------------------------------
- ; Determine new attribute and character for a new blank region.
- ; Use current attribute, just disallow blink and underline.
- ; (Pretty strange way to do it. Might want to disallow rev vid, too.)
- ; Returns result in AH, preserves all other registers.
- get_blank_attrib proc near
- IF gbackground
- cmp cs:gmode_flag,0
- jz get_attrib ; if alpha mode
- gmode_test get_attribg ; or good graphic mode, get attrib
- xor ah,ah
- ret
- get_attribg:
- mov ah, cs:cur_attrib ; must do different technique
- IF cheap_pc
- shr ah,1 ; color must be shifted into position
- shr ah,1
- shr ah,1
- shr ah,1
- ELSE
- shr ah,4
- ENDIF
- and ah,07
- ret
- get_attrib:
- mov ah, cs:cur_attrib ; the attribute
- and ah, 7fh ; but disallowing blink
- ret
- ELSE
- mov ah, 0 ; 0 is background if graphics mode
- cmp cs:gmode_flag,0
- jnz gb_aok
-
- mov ah, cs:cur_attrib
- and ah, 7fh ; disallow blink
- gb_aok: ret
- ENDIF
- get_blank_attrib endp
-
- page
- ;---- scroll_up ---------------------------------------------------
- ; Scroll screen up- preserves ax, bx, cx, dx, si, di, ds, es.
- ; Moves screen up 1 line, fills the last line with blanks.
- ; Attribute of blanks is the current attribute sans blink and underline.
-
- scroll_up proc near
- push_all
-
- cmp cs:gmode_flag,0
- jz scroll_char
- jmp scroll_graphic
- scroll_char:
- push es
- push ds ; save all!
- mov ax, ABS40 ; address low mem via ds
- mov ds, ax
- mov ax, 0b800h ; address display via es
- mov es, ax
- assume ds:ABS40
- cmp cs:fmode,0 ; see if in fast mode
- jz slow_scroll_up
- xor ax,ax ; calc addresses
- mov al, cs:max_x
- inc ax
- mov cx, ax ; save (word) count for fill
- mov bx, ax ; and save byte count
- shl bx, 1 ; byte count
- mov cs:temp_val, bx
- mul cs:max_y ; address offset of last line (words)
- shl ax, 1 ; address offset in bytes
- mov di, ax
-
- mov ax, crt_start ; start of display
- add ax, bx ; add line size in bytes
- add di, ax ; di is now address of new last line
- cmp di, 7fffh - 264 ; is there room here?
- ja no_room_here
-
- mov crt_start, ax
- shr ax, 1 ; make into word offset
- mov bx, ax ; and put into 6845
- mov dx, port_6845
- mov al, 0ch
- out dx, ax
- inc al
- mov ah, bl
- out dx, ax
-
- mov ah, cs:cur_attrib
- and ah, 7fh ; disallow blink
- mov al, 20h ; blank
- rep stosw ; clear line
-
- assume ds:nothing
- pop ds
- pop es
- pop_all
-
- add di, cs:temp_val
- ret
-
- no_room_here:
- pop ds ; restore registers
- pop es
- pop_all
- call move_back ; go to buffer start
- sub di, cs:temp_val
- jmp scroll_up ; try again
-
- slow_scroll_up:
- assume ds:ABS40
- mov di, crt_start ; offset of display (because of
- ; different page)
- mov ds, ax ; ds is now display
- assume ds:nothing
- xor ax,ax ; calc addresses
- mov al, cs:max_x
- inc ax
- mov bx, ax ; save (word) count
- shl ax, 1 ; byte count
- mov si, ax ; start address is second line
- add si, di ; adjust start address by any offset
- mov ax, bx
- mul cs:max_y ; number of words to move
- mov cx, ax
- rep movsw ; move them!
- mov cx, bx ; words to clear
- mov ah, cs:cur_attrib
- and ah, 7fh ; disallow blink
- mov al, 20h ; blank
- rep stosw ; clear line
- pop ds
- pop es
- pop_all
- ret
-
- scroll_graphic:
-
- gmode_test scrOurself
- mov bh, 0
- mov al, 1 ; AL is number of lines to scroll.
- mov ah, 6 ; BIOS: scroll up
- xor cx, cx
- mov dl, cs:max_x ; lower-rite-x
- mov dh, cs:max_y ; lower-rite-y (zero based)
- call_video ; call BIOS to scroll a rectangle.
-
- scrret:
- pop_all
- ret
-
- scrOurself: ; try scrolling screen ourself!
- push es
- push ds
-
- mov dx, 3ceh ; set write mode 1
- mov ax, 105h
- out dx, ax
-
- mov ax, 40h ; address abs40 segment
- mov ds, ax
- assume ds:ABS40
- mov ax, crt_cols ; calculate length of line in bytes
- mul byte ptr ega_points
- mov si, ax ; source of move
- xor dx,dx
- mov dl, ega_rows
- mul dx ; number of bytes to move
- mov cx, ax
- mov ax, si ; save bytes in line for later
-
- mov bx, 0a000h ; address display
- mov ds, bx
- mov es, bx
-
- xor di, di ; destination of move
- rep movsb ; scroll
-
- mov cx, ax ; bytes in line = bytes to clear
-
- mov dx, 3ceh
- mov ax, 05h ; return to write mode 0
- out dx, ax
-
- IF gbackground
- mov ah, cs:cur_attrib
- IF cheap_pc
- shr ah,1
- shr ah,1
- shr ah,1
- shr ah,1
- ELSE
- shr ah,4
- ENDIF
- and ah,07 ; background color
- mov al,0
- out dx,ax ; set color to write
-
- mov ax,0f01h ; set mask
- out dx,ax
-
- rep stosb ; clear the line
-
- mov ax,0001 ; reset mask
- out dx,ax
- ELSE
- xor ax, ax
- rep stosb ; clear the line
- ENDIF
-
- pop ds ; restore registers and return
- pop es
- jmp scrret
-
- scroll_up endp
- page
- ;-----move_back --------------------------------------------
- ; This routine moves the display to offset zero.
- ; alters:
- ; cs:temp_val = original crt_start value
- ; crt_start = 0
- ; controller reset properly
- move_back proc near
- push ds
- push es
- push_all
- mov ax, ABS40
- mov ds, ax
-
- assume ds:ABS40
- mov al, ega_rows
- inc al
- mul byte ptr crt_cols ; words to move
- mov cx, ax
- mov si, crt_start
- mov cs:temp_val, si ; save this value
- xor di, di
- mov crt_start, di
- mov bx, cursor_posn ; y in bh, x in bl
- mov al, byte ptr crt_cols
- mul bh
- add al, bl
- adc ah, 0
- xchg bx, ax ; save cursor position in bx
-
- mov ax, 0B800h
- mov es, ax
- mov ds, ax
-
- mov dx, cx
- add dx, cx ; see if overlapping
- cmp dx, si
- ja slow_move
- join_move:
- cld
- rep movsw ; move data
-
- mov dx, port_6845
- mov al, 0ch ; reset offset
- xor ah,ah
- out dx, ax
- inc al
- out dx, ax
- inc al
- mov ah, bh
- out dx, ax
- inc al
- mov ah, bl
- out dx, ax
- ; sti
- assume ds:nothing
- pop_all
- pop es
- pop ds
- ret
-
- slow_move: ; we gotta move to another spot first
- push cx ; save length
- dec dx ; length-2
- dec dx
- add si, dx ; point to end
- mov di, 7FFEh ; safe location -- as safe as we can get
- std
- rep movsw ; move from far end in case of overlap
- ; (may happen on large displays)
- mov dx, port_6845
- mov si, di ; source becomes destination
- inc si ; take care of last decrement
- inc si
- mov cx, si
- shr cx, 1 ; word offset to start of new area
- mov al, 0Ch ; display at this new location
- mov ah, ch
- out dx, ax
- inc al
- mov ah, cl
- out dx, ax
- pop cx ; reset all registers
- xor di, di ; destination is zero
- jmp join_move ; NOW move to destination
-
- move_back endp
- page
- if key_redef
- ;---- lookup -----------------------------------------------
- ; Called by getchar, peekchar, and key to see if a given key has
- ; been redefined.
- ; Sets AH to zero if AL is not zero (i.e. if AX is not a function key).
- ; Returns with Z cleared if no redefinition; otherwise,
- ; Z is set, SI points to redefinition string, CX is its length.
- ; Preseves AL, all but CX and SI.
- ; Redefinition table organization:
- ; Strings are stored in reversed order, first char last.
- ; The word following the string is the character to be replaced;
- ; the next word is the length of the string sans header.
- ; param_end points to the last byte used by the parameter buffer;
- ; redef_end points to the last word used by the redef table.
-
- lookup proc near
- mov si, redef_end ; Start at end of table, move down.
- or al, al
- jz lu_lp
- mov ah, 0 ; clear extraneous scan code
- lu_lp: cmp si, param_end
- jbe lu_notfound ; If below redef table, exit.
- mov cx, [si]
- cmp ax, [si-2] ; are you my mommy?
- jz lu_gotit
- sub si, 4
- sub si, cx ; point to next header
- jmp lu_lp
- lu_notfound:
- or si, si ; clear Z
- jmp short lu_exit
- lu_gotit:
- sub si, 2
- sub si, cx ; point to lowest char in memory
- cmp al, al ; set Z
- lu_exit:
- ret
- lookup endp
- endif
- page
- ;---- searchbuf --------------------------------------------
- ; Called by getchar and peekchar to see if any characters are
- ; waiting to be gotten from sources other than BIOS.
- ; Returns with Z set if no chars found, BX=keybuf & SI=keybuf.len otherwise.
- searchbuf proc near
- ; Search the stuffahead buffers.
- if key_redef
- mov cx, 4 ; number of buffers to check for chars
- else
- mov cx, 3
- endif
- mov bx, offset fnkey - 4
- sbloop: add bx, 4 ; point to next buffer record
- mov si, [bx].len
- or si, si ; empty?
- loopz sbloop ; if so, loop.
- ret
- searchbuf endp
- page
- ;---- getchar -----------------------------------------------
- ; Returns AL = next char.
- ; Trashes AX, BX, CX, BP, SI.
- getchar proc near
- gc_searchbuf:
- ; See if any chars are waiting in stuffahead buffers.
- call searchbuf
- jz gc_trykbd ; No chars? Try the keyboard.
- ; A nonempty buffer was found.
- dec [bx].len
- dec si
- mov bp, [bx].adr ; get pointer to string
- mov al, byte ptr ds:[bp][si]; get the char
- ; Recognize function key sequences, move them to highest priority
- ; queue.
- sub si, 1 ; set carry if si=0
- jc gc_nofnkey ; no chars left -> nothing to protect.
- cmp bx, offset fnkey
- jz gc_nofnkey ; already highest priority -> done.
- or al, al
- jnz gc_nofnkey ; nonzero first byte -> not fnkey.
- ; Found a function key; move it to highest priority queue.
- dec [bx].len
- mov ah, byte ptr ds:[bp][si]; gec [bx].len
- mov ah, byte ptr ds:[bp][si]; get the second byte of fn key code
- gc_fnkey:
- mov fnkey.len, 1
- mov fnkeybuf, ah ; save it.
- gc_nofnkey:
- ; Valid char in AL. Return with it.
- jmp short gcdone
-
- gc_trykbd:
- ; Actually get a character from the keyboard.
- mov ah, 0
- int 16h ; BIOS returns with char in AX
- ; If it's Ctrl-break, it has already been taken care of.
- or ax, ax
- jz gc_trykbd
-
- if key_redef
- ; Look in the reassignment table to see if it needs translation.
- call lookup ; Z=found; CX=length; SI=ptr
- jnz gc_noredef
- ; Okay; set up the reassignment, and run thru the translation code.
- mov xlatseq.len, cx
- mov xlatseq.adr, si
- jmp gc_searchbuf
- endif
- gc_noredef:
- ; Is it a function key?
- cmp al, 0
- jz gc_fnkey ; yep- special treatment.
- gcdone: ret ; with character in AL.
-
- getchar endp
- page
- ;---- peekchar -----------------------------------------------
- ; Returns Z if no character ready, AL=char otherwise.
- ; Trashes AX, BX, CX, BP, SI.
- peekchar proc near
- call searchbuf
- jz pc_trykbd ; No chars? Try the keyboard.
- ; A nonempty buffer was found.
- dec si
- mov bp, [bx].adr ; get pointer to string
- mov al, byte ptr ds:[bp][si]; get the char
- ; Valid char from buffer in AL. Return with it.
- jmp short pcdone
- pc_trykbd:
- ; Actually peek at the keyboard.
- mov ah, 1
- int 16h ; BIOS returns with char in AX
- jz pcexit
- ; If it's control-break, it's already been taken care of.
- or ax, ax
- jnz pc_notbrk
- mov ah, 0
- int 16h ; so get rid of it!
- jmp short pc_trykbd
- pc_notbrk:
- if key_redef
- ; Look in the reassignment table to see if it needs translation.
- call lookup ; Z=found; CX=length; SI=ptr
- jnz pcdone ; Nope; just return the char.
- ; Okay; get the first code to be returned.
- add si, cx
- mov al, [si-1]
- endif
- pcdone: or ah, 1 ; NZ; char ready!
- pcexit: ret ; with character in AL, Z true if no char waiting.
- peekchar endp
- page
- ;----- set_gmode ------------------------------------------------
- ; Set gmode_flag based on mode byte in register al
- set_gmode proc near
- gmode_code ; a macro in nnansi_d.asm
- ret
- set_gmode endp
-
-
- ;---- beep ------------------------------------------------------
- ; Beep speaker; period given by beep_div, duration by beep_len.
- ; Preserves all registers.
-
- beep_div equ 1300 ; fairly close to IBM beep
- beep_len equ 3 ; 3/18 sec- shorter than IBM
-
- beep proc near
- push_all
-
- mov al, 10110110b ; select 8253
- mov dx, 43h ; control port address
- out dx, al
- dec dx ; timer 2 address
- mov ax, beep_div
- jmp $+2
- out dx, al ; low byte of divisor
- xchg ah, al
- jmp $+2
- out dx, al ; high byte of divisor
- mov dx, 61h
- jmp $+2
- in al, dx ; get current value of control bits
- push ax
- or al, 3
- jmp $+2
- out dx, al ; turn speaker on
-
- ; Wait for desired duration by monitoring time-of-day 18 Hz clock
- push es
- mov ax, ABS40
- mov es, ax
- assume es:ABS40
- mov bx, timer_low
- mov cx, -1
- beeplp: mov ax, timer_low
- sub ax, bx
- cmp ax, beep_len
- jg beepover
- loop beeplp
- beepover:
- pop es
- assume es:CODE
-
- ; Turn off speaker
- pop ax
- and al, not 3 ; turn speaker off
- out dx, al
- pop_all
- ret
- beep endp
- CODE ends
-
- end ; of nansi.asm
-
-