[comp.binaries.ibm.pc] nansi.sys part 2 of 2

tes@whuts.UUCP (07/04/87)

[This part is all sources, alas.  See part 1 for the reason.  ++bsa]

# This is a shell archive.  Remove anything before this line,
# then unpack it by saving it in a file and typing "sh file".
#
# Wrapped by sally!nather on Thu Jul 17 13:13:38 CDT 1986
# Contents:  nansi.asm nansi_d.asm nansi_f.asm nansi_i.asm nansi_p.asm
 
echo x - nansi.asm
sed 's/^@//' > "nansi.asm" <<'@//E*O*F nansi.asm//'
; 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:
;	nansi.asm   - all DOS function handlers except init
;	nansi_p.asm - parameter parser for ANSI escape sequences
;	nansi_f.asm - ANSI command handlers
;	nansi_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.
;------------------------------------------------------------------------

	include nansi_d.asm	; definitions

	; from nansi_f.asm
	extrn	f_escape:near, f_in_escape:near

	; from nansi_p.asm
	extrn	param_end:word, redef_end:word

	; from nansi_i.asm
	extrn	dosfn0:near

	; to nansi_p.asm
	public	f_loopdone
	public	f_not_ansi
	public	f_ansi_exit

	; to both nansi_p.asm and nansi_f.asm
	public	cur_x, cur_y, max_x, cur_attrib

	; to nansi_f.asm
	public	xy_to_regs, get_blank_attrib
	public	port_6845
	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
	public	lookup
	public	in_g_mode

	; to nansi_i.asm
	public	req_ptr, break_handler
	public	int_29
	if	takeBIOS
	public	new_vid_bios, old_vid_bios
	endif

	; to all modules
	public	xlate_tab_ptr

;--- seg_cs is the CS: override prefix
; (assembler forgets cs: on second "xlat dummy_cs_byte")
seg_cs	macro
	db	2eh
	endm

;--- push_all, pop_all ------------------------------------------------
; Save/restore all user registers.
push_all	macro
	if	is_8088
	push	ax
	push	bx
	push	cx
	push	dx
	push	bp
	push	si
	push	di
	else
	pusha
	endif
	endm

pop_all macro
	if	is_8088
	pop	di
	pop	si
	pop	bp
	pop	dx
	pop	cx
	pop	bx
	pop	ax
	else
	popa
	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)

ABS40	ends

	page

CODE	segment byte 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	"Nansi.sys v2.2"
	ife	is_8088
	db	"(80286)"
	endif
	db	': New ANSI driver (C) Daniel Kegel, Pasadena, CA 1986'
	db	13, 10, 26


;----- variable area --------------------
req_ptr label	dword
req_off dw	?
req_seg dw	?

wrap_flag	db	1	; 0 = no wrap past line end
escvector	dw	0	; state vector of ESCape sequencor
video_mode	db	3	; ROM BIOS video mode (2=BW, 3=color)
max_y		db	24
max_cur_x	label	word	; used to get both max & cur at once
max_x		db	79	; line width (79 for 80x25 modes)
cur_coords	label	word
cur_x		db	0	; cursor position (0 = left edge)
cur_y		db	0	;		  (0 = top edge)
saved_coords	dw	?	; holds XY after a SCP escape sequence
string_term	db	0	; either escape or double quote
cur_attrib	db	7	; current char attributes
cur_page	db	0	; current display page
video_seg	dw	?	; segment of video card
f_cptr_seg	dw	?	; part of fastout write buffer pointer
cur_parm_ptr	dw	?	; last byte of parm area now used
port_6845	dw	?	; port address of 6845 card
xlate_tab_ptr	dw	?	; pointer to output translation table
		if	takeBIOS
old_vid_bios	dd	?	; pointer to old video bios routine
		endif

brkkeybuf	db	3	; control C
fnkeybuf	db	?	; holds second byte of fn key codes
cpr_buf		db	8 dup (?), '['
cpr_esc		db	1bh	; descending buffer for cpr function

; 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
xlatseq keybuf	<0>		; keyboard reassignment string

;------ 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
	mov	ah, 0			; ax = max_x
	xchg	dx, ax
	mov	al, bh
	mov	ah, 0			; 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.
	ret
xy_to_regs	endp


;------- 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
	mov	al,[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

;----- 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
	mov	xlatseq.len, ax

	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
	if	takeBIOS
;--- new_vid_bios -------------------------------------------
; New_vid_bios simply replaces the write_tty call.
; All other calls get sent to the old video bios.
; 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.

new_vid_bios	proc
	cmp	ah, 14
	jz	nvb_write_tty
	jmp	dword ptr cs:old_vid_bios
nvb_write_tty:
	push	cx
	mov	cl, cs:cur_attrib
	; If in graphics mode, BL is new color
	call	in_g_mode		; returns carry set if text mode
	jc	nvb_wt_text
		mov	cs:cur_attrib, bl	; ja?
nvb_wt_text:
	int	29h			; write AL
	mov	cs:cur_attrib, cl	; restore color
	pop	cx
	iret

new_vid_bios	endp
	endif

;------ 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_buf	db	?

int_29	proc	near
	sti
	push	ds
	push	es
	push_all
	mov	cx, 1
	mov	bx, cs
	mov	es, bx
	mov	ds, bx
	mov	si, offset int_29_buf
	mov	byte ptr [si], al
	call	dosfn8
	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.

dosfn8	proc	near

	mov	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

	; 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.

	; DS is abs40.
	; Find 6845 address.
	mov	ax, addr_6845
	mov	cs:port_6845, ax
	; Find video buffer address.
	MOV	AX,crt_start
	shr	ax, 1
	shr	ax, 1
	shr	ax, 1
	shr	ax, 1
	add	ah, 0B0h		; assume it's a monochrome card...
	CMP	cs:video_mode,07
	jz	d8_gots
	add	ah, 8			; but if not mode 7, it's color.
d8_gots:
	push	cs
	pop	ds
	assume	ds:code
	mov	video_seg, ax
	mov	es, ax
	call	xy_to_regs		; Set DX, DI according to cur_coords.

	; | If in graphics mode, clear old pseudocursor
	call	in_g_mode
	jc	d8_no_cp
		call	pseudocursor	; write block in xor
d8_no_cp:
	mov	bx, xlate_tab_ptr	; get pointer to translation table

	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: 4+12 +4+4 +4+4 +0+15 +4+4 +4+18 = 77 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,
	jnz	f_in_escapex		; 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.
	call	in_g_mode
	jc	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:
	seg_cs
	xlat
	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

f_looploop:
f_ansi_exit:				; in case we switched into
	loopnz	f_tloop			; a graphics mode
f_t_at_eol:
	jz	f_at_eol

f_loopdone:

	;--------- All done with write request -----------
	; DI is cursor address; cursor position in cur_y, dl.
	mov	ax, cs
	mov	ds, ax			; get our segment back
	assume	ds:code

	; Restore cur_x = max_x - dx + 1.
	mov	al, max_x
	inc	al
	sub	al, dl
	mov	cur_x, al
	; Set cursor position; cursor adr in DI; cursor pos in cur_x,cur_y
	call	set_pseudocursor
	; Return to DOS.
	xor	ax, ax			; No error, not busy.
	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_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, 9			; tab?
	jz	f_tabx
	cmp	al, 8			; backspace?
	jz	f_bs
	cmp	al, 7			; bell?
	jz	f_bell
	jmp	f_nctl			; then it is not a control char.

f_tabx: jmp	f_tab
f_escapex:
	jmp	f_escape
f_in_escapex:
	jmp	f_in_escape

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_bell: ;----- Handle bell ----------------------
	; Use BIOS to do the beep.  DX is not changed, as bell is nonprinting.
	call	beep
	or	al, al			; clear z
; old (more portable) version:
;	mov	ax, 0e07h		; "write bell to tty simulator"
;	mov	bx, 0			; "page zero, color black"
;	int	10h			; call BIOS
;	mov	ah, cs:cur_attrib	; restore current attribute
;	mov	bx, cs:xlate_tab_ptr	; restore translate table address
;	or	al, al			; al still 7; this clears Z.
	jmp	f_looploop		; Let main loop decrement cx.

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, ' '
	call	in_g_mode		; | graphics mode
	jnc	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 -----------------------

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

;---- in_g_mode -------------
; Returns Carry set if not in a graphics mode.
; Preserves all registers.

in_g_mode	proc	near
	cmp	cs:video_mode, 4
	jb	igm_stc
	cmp	cs:video_mode, 7
	jz	igm_stc
	clc
	ret
igm_stc:
	stc
	ret
in_g_mode	endp

;---- Where to go when a character turns out not to be special
f_nctl:
f_not_ansi:
	call	in_g_mode
	jnc	f_g_nctl		; graphics mode
f_jmptnctl:
	jmp	f_t_nctl		; text mode

;---- 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:
	seg_cs
	xlat
	call	putchar
	dec	dx			; count down to end of line
	loopnz	f_g_cloop		; and go back for more.
	jz	f_g_at_eol		; at end of line; maybe do a crlf.
	jmp	f_loopdone

f_g_control:	jmp	f_control
f_g_at_eol:	jmp	f_at_eol

;---- 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
	xor	bx, bx			; choose dpy page 0
	mov	ah, 2			; chose "Set Cursor Position"
	int	10h			; call ROM BIOS
	; 2. Write char & attribute.
	mov	cx, 1
	pop	ax			; get char in AL
	push	ax
	mov	bl, ah			; attribute in BL
	mov	bh, 0
	mov	ah, 9
	int	10h
	pop	ax
	pop	bx
	pop	cx
	pop	dx
	ret
putchar endp

;---- set_pseudocursor ------------
; If in graphics mode, set pseudocursor, else set real cursor.
; Destroys DS!!!!

set_pseudocursor	proc	near
	call	in_g_mode
	jnc	pseudocursor
; old (more portable, but slower) version
;	mov	dx, cur_coords		; get X & Y into DX
;	xor	bx, bx			; choose dpy page 0
;	mov	ah, 2			; chose "Set Cursor Position"
;	int	10h			; call ROM BIOS

	; Write directly to 6845 cursor address register.
	mov	bx, di
	shr	bx, 1			; convert word index to byte index

	mov	dx, port_6845
	mov	al, 0eh
	out	dx, al

	jmp	$+2
	inc	dx
	mov	al, bh
	out	dx, al

	jmp	$+2
	dec	dx
	mov	al, 0fh
	out	dx, al

	jmp	$+2
	inc	dx
	mov	al, bl
	out	dx, al

	; Set cursor position in low memory.
	assume	ds:abs40
	mov	ax, abs40
	mov	ds, ax
; Does anybody ever use anything but page zero?
;	mov	al,active_page
;	cbw
;	add	ax,ax
;	xchg	bx,ax
	mov	ax, cs:cur_coords
	mov	cursor_posn,ax
	ret

	assume	ds:code
set_pseudocursor	endp


;---- pseudocursor --------------------------------------------------
; Writes a color 15 block in XOR at the current cursor location.
; Preserves DS, ES, BX, CX, DX, SI, DI.
; Should be disableable- the pseudocursor slows down single-char
; writes by a factor of three.
pseudocursor	proc	near
	mov	ax, 8f16h	; xor, color 15, ^V (small block)
	call	putchar
	ret
pseudocursor	endp

;--------------- end of graphics mode support --------------------

dosfn8	endp

;--- 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
	mov	ah, 0
	call	in_g_mode
	jnc	gb_aok			; if graphics mode, 0 is bkgnd

	mov	ah, cs:cur_attrib
	and	ah, 7fh			; disallow blink
	cmp	cs:video_mode, 7	; monochrome?
	jnz	gb_aok
		cmp	ah, 1		; underline?
		jnz	gb_aok
		mov	ah, 7		; yep- set it to normal.
gb_aok: ret
get_blank_attrib	endp


;---- 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	ax
	push	bx
	push	cx
	push	dx

	call	get_blank_attrib
	mov	bh, ah			; color to use on new blank areas
	mov	al, 1			; AL is number of lines to scroll.
	mov	ah, 6			; BIOS: scroll up
	mov	cl, 0			; upper-left-x of data to scroll
	mov	ch, 0			; upper-left-y of data to scroll
	mov	dl, cs:max_x		; lower-rite-x
	mov	dh, cs:max_y		; lower-rite-y (zero based)
	int	10h			; call BIOS to scroll a rectangle.

	pop	dx
	pop	cx
	pop	bx
	pop	ax
	ret
scroll_up	endp

;---- 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

;---- 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.
	mov	cx, 4			; number of buffers to check for chars
	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

;---- 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]; 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

	; 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
gc_noredef:
	; Is it a function key?
	cmp	al, 0
	jz	gc_fnkey		; yep- special treatment.
gcdone: ret	; with character in AL.

getchar endp

;---- peekchar -----------------------------------------------
; Returns Z if no character ready, AL=char otherwise.
; Trashes AX, BX, CX, BP, SI.
peekchar	proc	near
pc_searchbuf:
	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:
	; 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]
pcdone: or	ah, 1			; NZ; char ready!
pcexit: ret	; with character in AL, Z true if no char waiting.
peekchar	endp

;---- beep ------------------------------------------------------
; Beep speaker; period given by beep_div, duration by beep_len.
; Preserves all registers.

beep_div	dw	1300		; fairly close to IBM beep
beep_len	dw	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, cs: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, cs: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
@//E*O*F nansi.asm//
chmod u=rw,g=r,o=r nansi.asm
 
echo x - nansi_d.asm
sed 's/^@//' > "nansi_d.asm" <<'@//E*O*F nansi_d.asm//'
; Definitions for the new ANSI driver.
; (C) 1986 Daniel Kegel
; May be distributed for educational and personal use only

takeBIOS	equ	0	; take over BIOS write_tty if true
is_8088		equ	1	; no fancy instructions if true
cls_homes_too	equ	1	; set true for ANSI.SYS compatibility

;Comment this out if running MASM 1.0

	if	is_8088
		.8086
	else
		.286c
	endif

@//E*O*F nansi_d.asm//
chmod u=rw,g=r,o=r nansi_d.asm
 
echo x - nansi_f.asm
sed 's/^@//' > "nansi_f.asm" <<'@//E*O*F nansi_f.asm//'
; The ANSI control subroutines.
; (C) 1986 Daniel Kegel, Pasadena, CA
; May be distributed for educational and personal use only
; 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:
;  19 Aug 85: Fixed horrible bug in insert/delete line.
;  26 Aug 85: Fixed simple limit-to-one-too-few-lines bug in ins/del line;
;  anyway, it inserts 24 lines when on line 2 now.  Whether it's fixed...
;  4 Sept 85: Fixed bug created on 26 Aug 85; when limiting ins/del line
;  count, we are clearing, not scrolling; fixed BIOS call to reflect this.
;  30 Jan 86: Added EGA cursor patch
;  31 Jan 86: Disabled insert/delete char in graphics modes
;	      Implemented keyboard redefinition reset
;  1 Feb 86: added video_mode and max_x test after mode set
;----------------------------------------------------------------

	include nansi_d.asm

	; To nansi_p.asm
	public	ansi_fn_table

	; From nansi.asm
	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	cur_attrib:byte, wrap_flag:byte
	extrn	xy_to_regs:near
	extrn	get_blank_attrib:near
	extrn	xlate_tab_ptr:word
	extrn	cpr_esc:byte, cprseq:word
	extrn	video_mode:byte
	extrn	lookup:near
	extrn	in_g_mode:near

	; from nansi_p.asm
	extrn	param_buffer:word	; used in keyboard programming
	extrn	param_end:word
	extrn	redef_end:word

keybuf	struc				; used in making cpr sequence
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	?
crt_palette	db	?

ABS40	ends

code	segment byte public 'CODE'
	assume cs:code, ds:code

;----- byteout ---------------------------------------------------
; Converts al to a decimal ASCII string (in 0..99),
; stores it at ES:DI++.  Returns DI pointing at byte after last digit.
; Destroys DL.

byteout proc	near
	aam
	add	ax, 3030h
	xchg	ah, al
	stosb
	xchg	ah, al
	stosb
	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, xoc		; u, v, w, x, y
	dw	nul				; z

ansi_functions	proc	near		; set return type to NEAR

;----- nul ---------------------------------------------
; No-action ansi sequence; called when unknown command given.
nul:	ret

;----- Cursor Motion -----------------------------------------------

;-- cursor to y,x
hvp:	or	al, al		; First parameter is desired Y coordinate.
	jz	hvp_yok
	dec	ax		; Convert to zero-based coordinates.
hvp_yok:mov	cur_y, al
	; Get second parameter, if it is there, and set X with it.
	xor	ax, ax
	cmp	cx, 2		; was there a second parameter?
	jb	hvp_xok
	lodsb			; yes.
	or	al, al
	jz	hvp_xok
	dec	ax		; convert to zero-based coordinates.
hvp_xok:mov	cur_x, al

	; Clip to maximum coordinates.
hvp_set:
	mov	ax, cur_coords		; al = x, ah = y
	cmp	al, max_x
	jbe	hvp_sxok
		mov	al, max_x
		mov	cur_x, al
hvp_sxok:
	cmp	ah, max_y
	jbe	hvp_syok
		mov	al, max_y
		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	cbk_ok
		mov	cur_x, 0
cbk_ok: jmp	hvp_set

;-- cursor down -----
cdn:	add	cur_y, al
	jmp	hvp_set

;-- cursor up -------
cup:	sub	cur_y, al
	jae	cup_ok
		mov	cur_y, 0
cup_ok: 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
	or	cx, cx		; Did he give any parameters?
	jnz	sgr_loop
		mov	byte ptr [si], 0	; no parameters, so fake
		inc	cx			; one with the default value.
	; For each parameter
sgr_loop:
		lodsb				; al = next parameter
		; Search color table
		push	cx
		mov	cx, colors
		mov	bx, offset color_table-3
sgr_search:
			add	bx, 3
			cmp	al, byte ptr [bx]
			loopnz	sgr_search	; until match found or done
		jnz	sgr_loopx

		; If parameter named a known color, set the current
		; color variable.
		mov	ax, [bx+1]
		and	cur_attrib, al
		or	cur_attrib, ah
sgr_loopx:
		pop	cx
		loop	sgr_loop		; until no more parameters.
	ret

;-- erase in line ----------------------------------------
; Uses BIOS to scroll away a one-line rectangle
eil:	push	dx
	mov	cx, cur_coords
	mov	dh, ch
	jmp	short scrollem

;-- erase in display -------------------------------------
; Uses BIOS to scroll away all of display
eid:	cmp	al, 2
	jnz	eid_ignore	; param must be two
	if	cls_homes_too
		mov	cur_coords, 0
		call	xy_to_regs
	endif
	push	dx
	xor	cx, cx
	mov	dh, max_y
scrollem:
	call	get_blank_attrib
	mov	bh, ah
	mov	dl, max_x
	mov	ax, 600h
	int	10h
	pop	dx
eid_ignore:
	ret

;-- 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:	push	di
	push	dx
	push	es
	mov	ax, cs
	mov	es, ax
	std			; Store string in reversed order for fun
	mov	di, offset cpr_esc - 2
	mov	al, cur_y
	inc	al		; convert to one-based coords
	call	byteout		; row
	mov	al, ';'		; ;
	stosb
	mov	al, cur_x
	inc	al		; convert to one-based coords
	call	byteout		; column
	mov	al, 'R'		; R ANSI function 'Cursor Position Report'
	stosb
	mov	al, 13
	mov	word ptr cprseq.adr, di ; save pointer to last char in string
	stosb				; send a carriage return, too
	mov	ax, offset cpr_esc
	sub	ax, di			; ax is # of characters in string
	mov	word ptr cprseq.len, ax ; pass info to the getchar routine
	cld
	pop	es
	pop	dx
	pop	di
	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.

key:
	; Is this a reset?
	or	cx, cx
	jz	key_init
	; Get the first (or first two) parameters
	cld
	dec	si	; point to first param
	dec	cx	; Assume it's a fn key, get two params
	dec	cx
	lodsw
	or	al, al	; Is it a function key?
	jz	key_fnkey
		; It's not a function key- put second param back
		inc	cx
		dec	si
key_fnkey:
	; 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-1 upwards CX+4 bytes, add CX+4 to param_end.
	add	cx, 4
	mov	bp, param_end	; save old value in bp...
	add	param_end, cx
	dec	si		; start at (SI-1)
	mov	di, si
	add	di, cx		; move to (start + CX+4)
	mov	cx, si
	sub	cx, bp		; length of region old_param_end+1..start
	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, 4		; hi byte of new data field
	mov	bx, di
	sub	bx, cx		; hi byte of remaining buffer space
	sub	bx, 16		; better be at least 16 bytes room
	cmp	bx, param_buffer
	jb	key_popem	; nope- forget it.
	; Nothing in the way now!
	mov	[di+3], cx	; save length field
	mov	[di+1], ax	; save name field
	jcxz	key_nullstring
key_saveloop:			; save data field
	movsb
	add	si, 2		; input string ascending, output descending
	loop	key_saveloop
key_nullstring:
	mov	param_end, di	; save adr of new hi byte of free area
key_popem:
	pop	es
	pop	di

key_exit:
	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
	mov	al, 16		; control P
	stosb
	mov	param_end, di	; save new bottom of redef table
	pop	es
	jmp	key_exit

;---- Delete/Insert Lines -------------------------------
; AL is number of lines to delete/insert.
; Preserves DX, DI; does not move cursor.

d_l:	; Delete lines.
	mov	ah, 6			; BIOS: scroll up
	jmp	short il_open

il:	; Insert lines.
	mov	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, 0		; 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, 0			; upper-left-x of data to scroll
	mov	ch, cur_y		; upper-left-y of data to scroll
	push	dx
	mov	dl, max_x		; lower-rite-x
	mov	dh, max_y		; lower-rite-y (zero based)
	int	10h			; call BIOS to scroll a rectangle.
	pop	dx
	ret				; done.

;-- Insert / Delete Characters ----------------------------
; AL is number of characters to insert or delete.
; Preserves DX, DI; does not move cursor.

ic:	mov	ch, 1			; 1 => swap dest & source below
	jmp	short dc_ch

dc:	mov	ch, 0

dc_ch:
	call	in_g_mode
	jnc	dc_ret			; | if in graphics mode, ignore.

	; 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:
	push	di			; DI is current address of cursor
	xchg	ax, cx			; CX gets # of chars to ins/del
	mov	bp, cx			; BP gets # of columns to clear.

	; Set up source = destination + cx*2, count = dx - cx
	mov	ch, 0			; make it a word
	mov	si, di
	add	si, cx
	add	si, cx
	neg	cl
	add	cl, dl
	mov	ch, 0			; CX = # of words to transfer
	cld				; REP increments si & di

	; If this is an insert, then flip transfer around in both ways.
	test	ah, 1
	jz	dc_noswap
		xchg	di, si		; source <-> dest
		std			; up <-> down
		mov	ax, cx		; make move over same range
		dec	ax
		add	ax, ax		; 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_noswap:
	; Move those characters.
	push	es
	pop	ds
	rep	movsw
	mov	cx, bp
	; Figure out what color to make the new blanks.
	call	get_blank_attrib
	mov	al, ' '
	; Blank out vacated region.
	rep	stosw

	; All done.
	cld				; restore normal REP state and
	pop	di			;  cursor address.
dc_ret: ret


;---- set / reset mode ---------------------------------------
; Sets graphics/text mode; also sets/resets "no wrap at eol" mode.
sm:	mov	cl, 0ffh	; set
sm_rs:
	; Is it "wrap at eol" ?
	cmp	al, 7
	jnz	sm_notwrap
		mov	wrap_flag, cl	; true = wrap at EOL
		jmp	short sm_done
sm_notwrap:
	; Is it "set highest number of screen lines available"?
	cmp	al, 43
	jnz	sm_video
		; Only valid for the Enhanced Graphics Adaptor on
		; a monochrome display or an enhanced color display.
		; Test presence of EGA by calling BIOS fn 12h.10h.
		mov	ah, 12h
		mov	bx, 0ff10h
		int	10h			; bh=0-1, bl=0-3 if EGA
		test	bx, 0FEFCH
		jnz	sm_done			; sorry, charlie
;		mov	port_6845, 3d4h
;		mov	al, video_mode
;		and	al, 7
;		cmp	al, 7			; monochrome monitor?
;		jnz	sm_colormon
;			mov	byte ptr port_6845, low(3b4h)
;sm_colormon:
		; 43 line mode only allowed in text modes, for now.
		call	in_g_mode
		jnc	sm_done

		mov	ah, 0			; "Set video mode"
		mov	al, video_mode		; Re-init current mode
		int	10h

		mov	ax,1112h		; Load 8x8 font
		mov	bl,0			; (instead of 8x14)
		int	10h

		mov	ax, 1200h		; Load new printscreen
		mov	bl, 20h
		int	10h

		mov	ah,1
		mov	cx,0707h		; (Load cursor scan lines)
		int	10h
		; | Patch; this gotten by painful observation of
		; | IBM's professional editor.	I think there's a
		; | documented bug in Video Bios's "load cursor scan line"
		; | call; try looking in latter 1985 PC Tech Journal.
		mov	dx, port_6845		; '6845' command reg
		mov	al, 10
		out	dx, al
		jmp	$+2
		inc	dx
		mov	al, 7
		out	dx, al			; set cursor start line
		; Assume that gets us 43 lines.
		mov	max_y, 42
		jmp	short sm_home
sm_video:
	; It must be a video mode.  Call BIOS.
	mov	ah, 0		; "set video mode"
	int	10h
	; Assume that gets us 25 lines.
	mov	max_y, 24
sm_home:
	; Read the BIOS buffer address/cursor position variables.
	mov	ax, abs40
	push	ds
	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
	pop	ds
	mov	video_mode, al
	dec	ah			; ah = max column
	mov	max_x, ah

	; Since cursor may end up in illegal position, it's best to
	; just go home after switching video modes.
	mov	cur_coords, 0
	call	xy_to_regs
sm_done:
	ret

rm:	mov	cl, 0		; reset
	jmp	sm_rs

;------- Output Character Translation ----------------------
; A decidedly nonstandard function, possibly useful for editing files
; intended to be printed by daisywheel printers with strange wheels.
; (The letter 'y' was chosen to conflict with the VT100 self-test command.)
; Usage: ESC [ #1;#2 y
; where #1 is the character to redefine
;	#2 is the new display value
; If only ESC [ #1 y is sent, character #1 is reset to its default value.
; If only ESC [ y is sent, the entire table is reset to the default value.
; (If only ESC [ #1; y is sent, character #1 is set to zero... sigh.)

xoc:	; Xlate output character
	mov	bx, xlate_tab_ptr
	jcxz	xoc_reset	; if no parameters, reset table to 1:1
	dec	si		; point to first parameter
	lodsw			; first parameter to AL, second to AH
	dec	cx		; is parameter count 1?
	jnz	xoc_bothparams
		mov	ah, al	; if only one param, reset that char.
xoc_bothparams:
	add	bl, al
	adc	bh, 0		; bx points to entry for char AL
	mov	byte ptr [bx], ah	; change that entry
xoc_done:
	ret

xoc_reset:
	; Fill table with default values- i.e. 0, 1, 2, ... 255.
	xor	ax, ax
xoc_loop:
	mov	byte ptr [bx], al
	inc	bx
	inc	al
	jnz	xoc_loop
	jmp	xoc_done

ansi_functions	endp	; end dummy procedure block



;-------- Color table -----------------------------------------
; Used in "set graphics rendition"
colors	equ	22			; number of colors in table
color_table:
	db	0, 000h,07h		; all attribs off; normal.
	db	1, 0ffh,08h		; bold
	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


code	ends
	end				; of nansi_f.asm

@//E*O*F nansi_f.asm//
chmod u=rw,g=r,o=r nansi_f.asm
 
echo x - nansi_i.asm
sed 's/^@//' > "nansi_i.asm" <<'@//E*O*F nansi_i.asm//'
;------ nansi_i.asm ----------------------------------------------
; Contains code only needed at initialization time.
; (C) 1986 Daniel Kegel
; May be distributed for educational and personal use only
;-----------------------------------------------------------------

	include nansi_d.asm		; definitions

	; to nansi.asm
	public	dosfn0

	; from nansi.asm
	extrn	break_handler:near
	extrn	int_29:near
	if	takeBIOS
	extrn	new_vid_bios:near
	extrn	old_vid_bios:dword
	endif
	extrn	req_ptr:dword
	extrn	xlate_tab_ptr:word

	; from nansi_p.asm
	extrn	param_buffer:word	; adr of first byte free for params
	extrn	param_end:word		; adr of last byte used for params
	extrn	redef_end:word		; adr of last used byte for redefs


code	segment byte public 'CODE'
	assume	cs:code, ds:code

;-------- dos function # 0 : init driver ---------------------
; Initializes device driver interrupts and buffers, then
; passes ending address of the device driver to DOS.
; Since this code is only used once, the buffer can be set up on top
; of it to save RAM.

dosfn0	proc	near
	; Install BIOS keyboard break handler.
	xor	ax, ax
	mov	ds, ax
	mov	bx, 6Ch
	mov	word ptr [BX],offset break_handler
	mov	[BX+02], cs
	; Install INT 29 quick putchar.
	mov	bx, 0a4h
	mov	word ptr [bx], offset int_29
	mov	[bx+2], cs
	if	takeBIOS
	; Install INT 10h video bios replacement.
	mov	bx, 40h
	mov	ax, [bx]
	mov	word ptr cs:old_vid_bios, ax
	mov	ax, [bx+2]
	mov	word ptr cs:old_vid_bios[2], ax
	mov	word ptr [bx], offset new_vid_bios
	mov	word ptr [bx+2], cs
	endif

	push	cs
	pop	ds
	push	cs
	pop	es			; es=cs so we can use stosb
	cld				; make sure stosb increments di

	; Calculate addresses of start and end of parameter/redef buffer.
	; The buffer occupies the same area of memory as this code!
	; ANSI parameters are accumulated at the lower end, and
	; keyboard redefinitions are stored at the upper end; the variable
	; param_end is the last byte used by params (changes as redefs added);
	; redef_end is the last word used by redefinitions.
	mov	di, offset dosfn0
	mov	param_buffer, di
	add	di, 512
	mov	param_end, di	; addr of last byte in free area
	inc	di

	; Build the default redefinition table:
	;	control-printscreen -> control-P
	; (Must be careful not to write over ourselves here!)
	mov	al, 16		; control P
	stosb
	mov	ax, 7200h	; control-printscreen
	stosw
	mov	ax, 1		; length field
	mov	redef_end, di	; address of last used word in table
	stosw

	; Build a 1:1 output character translation table.
	; It is 256 bytes long, starts just after the param/redef buffer,
	; and is the last thing in the initialized device driver.
	mov	xlate_tab_ptr, di
	xor	ax, ax
init_loop:
	stosb
	inc	al
	jnz	init_loop

	xor	ax, ax
	; Return ending address of this device driver.
	; Status is in AX.
	lds	si, req_ptr
	mov	word ptr [si+0Eh], di
	mov	[si+10h], cs
	; Return exit status in ax.
	ret

dosfn0	endp

code	ends
	end				; of nansi_i.asm
@//E*O*F nansi_i.asm//
chmod u=rw,g=r,o=r nansi_i.asm
 
echo x - nansi_p.asm
sed 's/^@//' > "nansi_p.asm" <<'@//E*O*F nansi_p.asm//'
; A state machine implementation of the mechanics of ANSI terminal control
; string parsing.
; (C) 1986 Daniel Kegel, Pasadena, CA
; May be distributed for educational and personal use only
;
; Entered with a jump to f_escape when driver finds an escape, or
; to f_in_escape when the last string written to this device ended in the
; middle of an escape sequence.
;
; Exits by jumping to f_ANSI_exit when an escape sequence ends, or
; to f_not_ANSI when a bad escape sequence is found, or (after saving state)
; to f_loopdone when the write ends in the middle of an escape sequence.
;
; Parameters are stored as bytes in param_buffer.  If a parameter is
; omitted, it is stored as zero.  Each character in a keyboard reassignment
; command counts as one parameter.
;
; When a complete escape sequence has been parsed, the address of the
; ANSI routine to call is found in ansi_fn_table.
;
; Register usage during parsing:
;  DS:SI points to the incoming string.
;  CX holds the length remaining in the incoming string.
;  ES:DI points to the current location on the memory-mapped screen.
;  DX is number of characters remaining on the current screen line.
;  BX points to the current paramter byte being assembled from the incoming
;  string.  (Stored in cur_parm_ptr between device driver calls, if needed.)
;
; The registers are set as follows before calling the ANSI subroutine:
;  AX = max(1, value of first parameter)
;  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 subroutine 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.
;
; Revision history:
; 7 July 85: created by DRK
;------------------------------------------------------------------------

	; From nansi.asm
	extrn	f_not_ANSI:near		; exit: abort bad ANSI cmd
	extrn	f_ANSI_exit:near	; exit: good cmd done
	extrn	f_loopdone:near		; exit: ran out of chars. State saved.
	extrn	escvector:word		; saved state: where to jump
	extrn	cur_parm_ptr:word	; saved state: where to put next param
	extrn	string_term:byte	; saved state: what ends string
	extrn	cur_x:byte, max_x:byte	; 0 <= cur_x <= max_x
	extrn	cur_attrib:byte		; current color/attribute
	extrn	xlate_tab_ptr:word

	; from nansi_f.asm
	extrn	ansi_fn_table:word	; ANSI subroutine table

	; Used in nansi.asm
	public	f_escape		; entry: found an escape
	public	f_in_escape		; entry: restore state, keep parsing

	; Used in nansi_i.asm and nansi_f.asm
	public	param_buffer, param_end, redef_end


code	segment byte public 'CODE'
	assume	cs:code

; More saved state
in_num		db	?	; true if between a digit and a semi in parse

param_buffer	dw	3000h	; address of first byte free for new params
param_end	dw	3030h	; address of end of free area
redef_end	dw	3030h	; address of end of redefinition area
		; These initialized values are only for debugging

;----- next_is -------------------------------------------------------
; Next_is is used to advance to the next state.  If there are characters
; left in the input string, we jump immediately to the new state;
; otherwise, we shut down the recognizer, and wait for the next call
; to the device driver.
next_is macro	statename
	loop	statename
	mov	ax, offset statename
	jmp	sleep
	endm

;----- sleep --------------------------------------------------------
; Remember bx and next state, then jump to device driver exit routine.
; Device driver will re-enter at f_in_escape upon next invocation
; because escvector is nonzero; parsing will then be resumed.
sleep:	mov	cs:cur_parm_ptr, bx
	mov	cs:escvector, ax
	jmp	f_loopdone

;----- f_in_escape ---------------------------------------------------
; Main loop noticed that escvector was not zero.
; Recall value of BX saved when sleep was jumped to, and jump into parser.
f_in_escape:
	mov	bx, cs:cur_parm_ptr
	jmp	word ptr cs:escvector

fbr_syntax_error_gate:		; jumped to from inside f_bracket
	jmp	syntax_error

;----- f_escape ------------------------------------------------------
; We found an escape.  Next character should be a left bracket.
f_escape:
	next_is f_bracket

;----- f_bracket -----------------------------------------------------
; Last char was an escape.  This one should be a [; if not, print it.
; Next char should begin a parameter string.
f_bracket:
	lodsb
	cmp	al, '['
	jnz	fbr_syntax_error_gate
	; Set up for getting a parameter string.
	mov	bx, cs:param_buffer
	mov	byte ptr cs:[bx], 0
	mov	cs:in_num, 0
	next_is f_get_args

;----- f_get_args ---------------------------------------------------
; Last char was a [.  If the current char is a '=' or a '?', eat it.
; In any case, proceed to f_get_param.
; This is only here to strip off the strange chars that follow [ in
; the SET/RESET MODE escape sequence.
f_get_args:
	lodsb
	cmp	al, '='
	jz	fga_ignore
	cmp	al, '?'
	jz	fga_ignore
		dec	si		; let f_get_param fetch al again
		jmp	short f_get_param
fga_ignore:
	next_is f_get_param

;----- f_get_param ---------------------------------------------------
; Last char was one of the four characters "]?=;".
; We are getting the first digit of a parameter, a quoted string,
; a ;, or a command.
f_get_param:
	lodsb
	cmp	al, '0'
	jb	fgp_may_quote
	cmp	al, '9'
	ja	fgp_may_quote
		; It's the first digit.  Initialize current parameter with it.
		sub	al, '0'
		mov	byte ptr cs:[bx], al
		mov	cs:in_num, 1	; set flag for sensing at cmd exec
		next_is f_in_param
fgp_may_quote:
	cmp	al, '"'
	jz	fgp_isquote
	cmp	al, "'"
	jnz	fgp_semi_or_cmd		; jump to code shared with f_in_param
fgp_isquote:
	mov	cs:string_term, al	; save it for end of string
	next_is f_get_string		; and read string into param_buffer

;----- f_get_string -------------------------------------
; Last character was a quote or a string element.
; Get characters until ending quote found.
f_get_string:
	lodsb
	cmp	al, cs:string_term
	jz	fgs_init_next_param
	mov	byte ptr cs:[bx], al
	cmp	bx, cs:param_end
	adc	bx, 0			; if bx<param_end bx++;
	next_is f_get_string
; Ending quote was found.
fgs_init_next_param:
	mov	byte ptr cs:[bx], 0	; initialize new parameter
	; | Eat following semicolon, if any.
	next_is f_eat_semi

;----- f_eat_semi -------------------------------------
; Last character was an ending quote.
; If this char is a semi, eat it; else unget it.
; Next state is always f_get_param.
f_eat_semi:
	lodsb
	cmp	al, ';'
	jz	fes_eaten
		inc	cx
		dec	si
fes_eaten:
	next_is f_get_param

;----- syntax_error ---------------------------------------
; A character was rejected by the state machine.  Exit to
; main loop, and print offending character.  Let main loop
; decrement CX (length of input string).
syntax_error:
	mov	cs:escvector, 0
	mov	ah, cs:cur_attrib
	mov	bx, cs:xlate_tab_ptr
	jmp	f_not_ANSI	; exit, print offending char

;------ f_in_param -------------------------------------
; Last character was a digit.
; Looking for more digits, a semicolon, or a command character.
f_in_param:
	lodsb
	cmp	al, '0'
	jb	fgp_semi_or_cmd
	cmp	al, '9'
	ja	fgp_semi_or_cmd
		; It's another digit.  Add into current parameter.
		sub	al, '0'
		xchg	byte ptr cs:[bx], al
		push	dx
		mov	dl, 10
		mul	dl
		pop	dx
		add	byte ptr cs:[bx], al
		next_is f_in_param
	; Code common to states get_param and in_param.
	; Accepts a semicolon or a command letter.
fgp_semi_or_cmd:
	cmp	al, ';'
	jnz	fgp_not_semi
		cmp	bx, cs:param_end	; prepare for next param-
		adc	bx, 0			; if bp<param_end bp++;
		; Set new param to zero, enter state f_get_param.
		mov	cs:in_num, 0		; no longer inside number
		jmp	fgs_init_next_param	; spaghetti code attack!
fgp_not_semi:
	; It must be a command letter.
	cmp	al, '@'
	jb	syntax_error
	cmp	al, 'z'
	ja	syntax_error
	cmp	al, 'Z'
	jbe	fgp_is_cmd
	cmp	al, 'a'
	jb	syntax_error
		; It's a lower-case command letter.
		; Remove hole between Z and a to save space in table.
		sub	al, 'a'-'['
fgp_is_cmd:
	; It's a command letter.  Save registers, convert letter
	; into address of routine, set up new register usage, call routine.
	push	si			; These three registers hold info
	push	cx			; having to do with the input string,
	push	ds			; which has no interest at all to the
					; control routine.

	push	cs
	pop	ds			; ds is now cs

	sub	al, '@'			; first command is @: insert chars
	cbw
	add	ax, ax
	add	ax, offset ansi_fn_table
	; ax is now pointer to command routine address in table

	mov	cx, bx
	mov	si, param_buffer	; si is now pointer to parameters
	sub	cx, si			;
	test	in_num, 1
	jz	fip_out_num
		inc	cx
fip_out_num:				; cx is now # of parameters

	xchg	ax, bx			; save pointer to routine in bx

	; Calculate cur_x from DX.
	mov	al, max_x
	inc	ax
	sub	al, dl
	mov	cur_x, al

	; Get first parameter into AX; if defaulted, set it to 1.
	mov	ah, 0
	lodsb
	or	al, al
	jnz	fgp_callem
		inc	ax
fgp_callem:
	; Finally, call the command subroutine.
	call	word ptr [bx]

	pop	ds
	pop	cx
	pop	si

	mov	ah, cs:cur_attrib	; Prepare for STOSW.
	mov	bx, cs:xlate_tab_ptr	; Prepare for translation.
	mov	cs:escvector, 0		; No longer parsing escape sequence.
	; Set flags for reentry at loopnz
	or	dx, dx			; "Any columns left on line?"
	; Re-enter at bottom of main loop.
	jmp	f_ansi_exit


code	ends
	end				; of nansi_p.asm

@//E*O*F nansi_p.asm//
chmod u=rw,g=r,o=r nansi_p.asm
 
echo Inspecting for damage in transit...
temp=/tmp/shar$$; dtemp=/tmp/.shar$$
trap "rm -f $temp $dtemp; exit" 0 1 2 3 15
cat > $temp <<\!!!
    1097    4803   27869 nansi.asm
      16      63     360 nansi_d.asm
     634    2935   16445 nansi_f.asm
     110     474    2913 nansi_i.asm
     303    1496    9308 nansi_p.asm
    2160    9771   56895 total
!!!
wc  nansi.asm nansi_d.asm nansi_f.asm nansi_i.asm nansi_p.asm | sed 's=[^ ]*/==' | diff -b $temp - >$dtemp
if [ -s $dtemp ]
then echo "Ouch [diff of wc output]:" ; cat $dtemp
else echo "No problems found."
fi
exit 0
--
  -----                    Terry Sterkel
-====----              AT&T Bell Laboratories
--------- {clyde|harvard|cbosgd|allegra|ulysses|ihnp4}!whuts!tes
  -----         [opinions are obviously only my own]