home *** CD-ROM | disk | FTP | other *** search
- ;
- ;Version 2.0 - 11th December 1987
- ;
- ;SUPERVDU.SYS (IBM) Version 2.1
- ;
- ;This program may be freely copied and altered subject only to a credit for
- ;the author remaining in the source.
- ;
- ;(C) M. F. Winiberg, 5 Parc Villas, Newlyn, Penzance, Cornwall TR18 5EA
- ;
- ;A terminal device, designed to replace ANSI.SYS as distributed by IBM et al,
- ;this software contains both ANSI (corrected and extended from IBMs) and VT52
- ;terminal support. In addition, interfaces to a Marconi Trackerball or
- ;Microsoft serial mouse are included.
- ;
- ;06/01/87
- ;
- ;Spurious VT52 codes are now ignored, not echoed - makes things designed for
- ;ACT machines run more smoothly!
- ;
- ;26/04/87
- ;
- ;Colour selection via sgr ansi command now uses high intensity colours - this
- ;gives a brighter display on EGA cards or where CGA with intensity is
- ;available
- ;
- ;04/09/87
- ;
- ;Maximum column/row addresses extended to 132 by 66 to allow for 132 column
- ;EGA cards etc
- ;
- ;11/12/87
- ;
- ;Mouse and Trackerball support made optional via an equate.
- ;
- ;Maximum column/row addresses reset by finding current display mode
- ;with int 10H, ah = 0fH and then looking up the screen sizes in
- ;a table. The 132 column modes etc produced by the ATI VIP and
- ;EGA WONDER cards are also included.
- ;
- ;14/12/87
- ;
- ;The above (11/12) mod didn't work because the VIP ROM BIOS does not
- ;return the exepcted info - it always returns mode 3 for the high res modes!
- ;
- ;I have now added some extra controls that allow the user to set the resolution
- ;of the display by sending pseudo ansi sequences.
- ;
- ;
- codeseg SEGMENT PARA PUBLIC
- ASSUME CS:codeseg,DS:codeseg,ES:codeseg
- ;
- true EQU 0FFFFH
- false EQU 0
- ;
- ; Set the next equate to true if you want the mouse/trackerball code
- ; included.
- ;
- tracker EQU false
- ;
- rkadr EQU 6CH
- CR EQU 0DH
- LF EQU 0AH
- ;
- ;Version definitions
- ;
- ;
- MAJOR EQU '2'
- MINOR EQU '1'
- ;
- BUFFER_HEAD EQU 041AH ; IBM ROM keyboard variable
- ;
- ; Maximum length of buffer used to store key definitions and incoming
- ; parameter data.
- ;
- max_pbuf EQU 500
- ;
- org 0
- ;
- ; CONSOLE DEVICE HEADER
- ;
- condev DW 0ffffh
- DW 0ffffh
- DW 8013h
- DW strategy
- DW entry
- DB 'CON '
- ;
- ;device command switch table
- ;
- contbl DW con$init
- DW exit
- DW exit
- DW cmderr
- DW con$read
- DW con$rdnd
- DW exit
- DW con$flsh
- DW con$writ
- DW con$writ
- DW exit
- DW exit
- ;
- ;VT52 command lookup table
- ;
- ;
- vt52_tab LABEL BYTE
- ;
- db '('
- dw bright ; high intensity foreground
- db ')'
- dw dim ; normal intensity
- db 'A'
- dw cuu ; cursor up
- db 'B'
- dw vcud ; cursor down
- db 'C'
- dw cuf ; cursor forward
- db 'D'
- dw cub ; cursor back
- db 'E'
- dw vcls ; clear top 24 lines only - leave cursor
- db 'H'
- dw cuh ; cursor position
- db 'J'
- dw ved ; erase display
- db 'K'
- dw el ; erase line
- db 'Y'
- dw vcup ; cursor position
- db 'j'
- dw scp ; save cursor position
- db 'k'
- dw rcp ; restore cursor position
- db 'p'
- dw revon ; reverse video on
- db 'q'
- dw revoff ; reverse video off
- db 'y'
- dw vrm ; reset mode
- db 'x'
- dw vsm ; set mode
- db 00
- ;
- ;ANSI sequence command lookup table
- ;
- cmdtab DB 'A'
- DW cuu
- DB 'B'
- DW cud
- DB 'C'
- DW cuf
- DB 'D'
- DW cub
- DB 'H'
- DW cup
- DB 'J'
- DW ed
- DB 'K'
- DW el
- DB 'R'
- DW cpr
- DB 'f'
- DW cup
- DB 'h'
- DW sm
- DB 'l'
- DW rm
- DB 'm'
- DW sgr
- DB 'n'
- DW dsr
- DB 'p'
- DW kkr
- DB 's'
- DW scp
- DB 'u'
- DW rcp
- ;
- if tracker
- ;
- ;input device controls - not ANSI!
- ;
- DB '['
- DW devon
- DB ']'
- DW devoff
- ;
- endif
- ;
- ; Screen resolution setting control - not ansi
- ;
- DB '#'
- DW set_res
- ;
- DB 0 ; end of table
- ;
- ptrsav DW 0
- ptrsav2 DW 0
- ;
- ;
- ;Note - reversed order so word fetches get row,col into rH,rL
- ;
- win_col DB 24 ; physical start of window
- win_row DB 17
- win_col_max DB 79 ; maximum size of window
- win_row_max DB 24
- ;
- strategy PROC FAR
- ;
- mov cs:ptrsav,bx
- mov cs:ptrsav2,es
- ret
- ;
- strategy ENDP
-
- entry:
- push si
- push ax
- push cx
- push dx
- push di
- push bp
- push ds
- push es
- push bx
- lds bx,cs:DWORD PTR ptrsav
- mov cx,18[bx]
- mov al,2[bx]
- cbw
- mov si,OFFSET contbl ; 12h
- add si,ax
- add si,ax
- cmp al,0bh ; Number of entries in table
- ja cmderr
- les di,DWORD PTR 14[bx]
- push cs
- pop ds
- jmp WORD PTR [si]
-
- bus$exit:
- mov ah,3
- jmp SHORT err1
-
- cmderr:
- mov al,3
- mov ah,81h
- jmp SHORT err1
-
- exitp PROC FAR
- ;
- exit:
- mov ah,1
- err1:
- lds bx,cs:DWORD PTR ptrsav
- mov 3[bx],ax
- pop bx
- pop es
- pop ds
- pop bp
- pop di
- pop dx
- pop cx
- pop ax
- pop si
- ret
- ;
- exitp ENDP
- ;
- break:
- mov cs:altah,3
- intret:
- iret
-
- ;
- ;NOTE - we must keep a separate idea of our cursor position in case the ROM is
- ;called to alter it without our knowledge, also if we use the same ones, they
- ;risk causing double scrolling because of double updating of the row values.
- ;
- ;See note dated 16/05/86 above - to avoid the problem of programs that cursor
- ;address via the ROM but then continue via the OS - tricky one - calls to the
- ;rom routines to cursor address also alter our local copy!
- ;
- chrout:
- cmp al,CR
- jnz trylf
- mov col,0
- jmp setit
-
- trylf:
- cmp al,LF
- jz islf
- cmp al,7
- jnz tryback
- ;
- ;BEEPS
- ;
- torom:
- mov bx,WORD PTR attr
- and bl,7
- mov ah,0eh
- int 10h
- ret5:
- ret
-
- tryback:
- cmp al,8
- jnz outchr
- cmp col,0
- jz ret5
- dec col
- jmp SHORT setit
-
- outchr:
- mov bx,WORD PTR attr
- mov cx,1
- mov ah,9
- int 10h
- inc col
- mov al,win_col_max ; applies in all cases regardless
- cmp col,al
- jbe setit
- cmp wrap,0
- jz outchr1
- dec col
- ret
-
- outchr1:
- mov col,0
- islf:
- inc row
- mov al,win_row_max
- cmp row,al
- jbe setit
- mov row,al
- call scroll
- setit:
- mov dh,row
- mov dl,col
- mov bh,dis_page
- mov ah,2
- int 10h
- ret
- scroll:
- mov ax,601H ; scroll up one line
- xor cx,cx ; top left is 0,0
- mov bh,attr
- mov dx,WORD PTR win_col_max ; bottom right
- int 10H ; scroll it
- ret
-
- ; mov al,0ah
- ; jmp torom
-
- con$read:
- jcxz con$exit
- con$loop:
- push cx
- call chrin
- pop cx
- stosb
- loop con$loop
- con$exit:
- jmp exit
-
- chrin:
- xor ax,ax
- xchg al,altah
- or al,al
- jnz keyret
- no_key:
- cmp bufcnt,0
- jnz read_buf ; get chars from buffer
- ;
- if tracker
- ;
- xor ax,ax ; get next key from input device
- call inp_key
- jz no_inpk ; none found
- jmp SHORT lkup
- no_inpk:
- ;
- endif
- ;
- xor ah,ah ; see if key available
- int 16h
- lkup:
- call lookup ; see if a key definition to be used
- jnz no_def
- dec cx ; cx has length of definition
- dec cx
- inc bx
- inc bx
- or al,al ; if extended key, need to skip a byte
- jnz ord_key ; in the definition.
- dec cx
- inc bx
- ord_key:
- mov bufcnt,cl
- mov bufpos,bx
- call read_buf
- no_def:
- or ax,ax
- jz no_key
- or al,al
- jnz keyret
- mov altah,ah ; save station code?
- keyret:
- ret
-
- read_buf:
- mov bx,bufpos
- mov ax,[bx]
- dec bufcnt
- inc bx
- or al,al
- jnz key_ord ; special keys are words not bytes
- inc bx
- dec bufcnt
- key_ord:
- mov bufpos,bx
- ret
-
- ;
- ;Keyboard key reassignment lookup.
- ;
- ;This routine looks through a linked list of key redefinitions to see if the
- ;current key has to be translated.
- ;
- ;On entry:
- ;
- ; AX - has key code as returned by ROM BIOS
- ;
- ;On exit:
- ;
- ; Z flag unset if no definition found
- ;
- ; Z flag set if definition found,
- ; BX points to start of definition data made up as follows:
- ;
- ; length of entry byte
- ; BIOS key code byte ( or word for extended keys)
- ; New definition bytes to make up length
- ;
- ; CX has length of entry
- ;
- lookup:
- mov bx,OFFSET keybuf
- look_2:
- mov cl,[bx] ; get definition length
- xor ch,ch
- or cx,cx
- jz no_trans ; no defn - cannot translate
- or al,al
- jnz not_ext
- cmp ax,1[bx] ; extended key stored as word
- jmp SHORT is_key
-
- not_ext:
- cmp al,1[bx] ; ordinary - this is key val
- is_key: jz found_key
- add bx,cx ; point to next defn
- jmp SHORT look_2 ; keep looking
-
- no_trans:
- or bx,bx ; set flags
- found_key:
- ret
-
- con$rdnd:
- mov al,altah
- or al,al
- jnz rdexit
- cmp bufcnt,0
- jz rd1
- mov bx,bufpos
- mov al,[bx]
- jmp SHORT rdexit
-
- rd1:
- ;
- if tracker
- ;
- mov ah,1 ; any keys waiting in input device
- call inp_key
- jz chk_kbd ; no - check the system keyboard
- jmp SHORT kkr_chk ; otherwise go translate if reqd
- ;
- endif
- ;
- chk_kbd:
- mov ah,1 ; non-des read
- int 16h
- jz con_mt ; nothing there
- or ax,ax
- jnz kkr_chk ; check key value in case kkr in force
- mov ah,0 ; remove any null chars from the buffer
- int 16h
- jmp SHORT con$rdnd
-
- kkr_chk:
- call lookup
- jnz rdexit
- mov al,2[bx]
- cmp BYTE PTR 1[bx],0 ; true if extended key definition
- jnz rdexit
- mov al,3[bx] ; first byte of defn
- rdexit:
- lds bx,DWORD PTR ptrsav
- mov 13[bx],al ; pass back to caller
- exvec:
- jmp exit
-
- con_mt:
- jmp bus$exit
-
- con$flsh:
- ;
- if tracker
- ;
- mov ah,2 ; clear pending input dev keys
- call inp_key
- ;
- endif
- ;
- mov altah,0
- mov bufcnt,0 ; clear internal buffer
- push ds
- xor bp,bp
- mov ds,bp
- mov bp,BUFFER_HEAD ; IBM keyboard buffer
- mov ds:WORD PTR [bp],1eh ; clear IBM ROM keyboard buffer
- mov ds:WORD PTR 2[bp],1eh
- pop ds
- jmp SHORT exvec
- ;
- if tracker
- ;
- ;inp_key
- ;
- ;function that manipulates the keystrokes generated by an input device (eg
- ;mouse) in a way similar to the ROM BIOS kbd handler.
- ;
- ;On entry:
- ;
- ; AH 0 Fetch next key from device - return with null if none
- ; AH 1 return Z if no keys waiting, NZ if there are some
- ; AH 2 clear any pending key returns
- ;
- ;On exit:
- ;
- ; AX has key value where relevant
- ; Z flag set if no key available
- ;
- ; In addition, this function attempts to return movement keys in a sensible
- ;fashion so that diagonal movements come out naturally, not as x,y steps.
- ;
- inp_key PROC NEAR
- ;
- push ax ; save passed command while we scan
- mov al,devflg ; if device off, then do nothing
- or al,al
- jnz dev_active
- jmp no_butt
- dev_active:
- call device ; the device
- push ax ; save any button info
- mov ax,bx
- add ax,xrem ; get any current x remainder
- cwd
- idiv speed ; divide by the selected speed
- mov xrem,dx ; keep any remainder for next time
- mov bx,ax
- or bx,bx ; set flags
- jz no_inpx
- jns inp_px
- neg bx
- mov ax,4B00H ; (left) station code
- jmp SHORT inp_xset
- inp_px:
- mov ax,4D00H ; (right)
- inp_xset:
- push cx
- mov cx,bx
- px_lp:
- call add_inp ; add ax to the buffer if pos
- loop px_lp
- pop cx
- no_inpx:
- mov ax,cx
- add ax,yrem ; get any y remainder
- cwd
- idiv speed
- mov yrem,dx ; keep this remainder
- mov cx,ax
- or cx,cx
- jz no_inpy
- jns inp_py
- neg cx
- mov ax,5000H ; (down) station code
- jmp SHORT inp_yset
- inp_py:
- mov ax,4800H ; (up)
- inp_yset:
- call add_inp ; add ax to the buffer if pos
- loop inp_yset
- no_inpy:
- pop ax
- or al,al ; any buttons?
- jz no_butt
- mov di,6800H ; ALT-F1 (we use F1-8)
- mov cx,8 ; 8 bits to examine
- butt_lp:
- ror al,1 ; see if button down
- jnc butt_up ; no, so don't add to buffer
- push ax
- mov ax,di ; get key value
- call add_inp
- pop ax
- butt_up:
- add di,100H ; move to next F key value
- loop butt_lp
- no_butt:
- pop ax ; get back passed command
- cmp ah,2
- jz inp_clr ; clear any pending data
- cmp ah,1 ; read any waiting key
- jz inp_ndrd
- or ah,ah
- jz inp_rd ; read next value
- clr_ex:
- xor ax,ax
- ret ; otherwise give up
- ;
- inp_clr:
- xor ax,ax
- mov in_rd,ax ; reset read pointer into buffer
- mov in_wr,ax ; reset write pointer
- mov in_cnt,ax ; reset current char count
- jmp SHORT clr_ex
- ;
- inp_ndrd: ; return any pending value
- mov ax,in_cnt ; any in buffer
- or ax,ax
- jz clr_ex ; no - give up
- mov bx,OFFSET inp_buf
- mov si,in_rd
- mov ax,[bx+si] ; get key value without moving pointer
- or ax,ax ; set flags
- ret
- ;
- inp_rd:
- mov ax,in_cnt
- or ax,ax
- jz clr_ex ; none in, so give up
- mov bx,OFFSET inp_buf
- mov si,in_rd ; current offset into buffer
- mov ax,[bx+si] ; get current key
- dec WORD PTR in_cnt ; knock one off contents
- add si,2
- cmp si,256 ; see if we have wrapped around
- jb no_rdwp
- xor si,si ; reset to beginning of buffer
- no_rdwp:
- mov in_rd,si
- or ax,ax
- ret ; return char to kbd routine
- ;
- inp_key ENDP
- ;
- ;
- ;add_inp adds AX to the circular buffer
- ;
- add_inp PROC NEAR
- ;
- push bx
- push dx
- push si
- mov dx,in_cnt ; see if any room
- cmp dx,256
- jae no_add
- mov bx,OFFSET inp_buf
- mov si,in_wr ; get current write position
- mov [bx+si],ax ; store key value
- inc WORD PTR in_cnt
- add si,2
- cmp si,256
- jb no_wrwp
- xor si,si ; wrap back to beginning of buffer
- no_wrwp:
- mov in_wr,si
- no_add:
- pop si
- pop dx
- pop bx
- ret
- ;
- add_inp ENDP
- ;
- ;
- endif
- ;
- ;
- con$writ:
- or cx,cx
- jnz get_lp
- jmp exvec
- get_lp:
- mov al,es:[di]
- inc di
- call outc
- loop get_lp
- jmp exvec
-
- cout:
- sti
- push ds
- push cs
- pop ds
- call outc
- pop ds
- iret
-
- ;
- outc:
- push ax
- push bx
- push cx
- push dx
- push si
- push di
- push es
- push bp
- push ax
- push bx
- push cx
- push dx
- mov cx,ds ; IBM rom as ROM BIOS seems to cause
- mov dx,40H ; problems
- mov ds,dx ; point to ROM BIOS data area
- mov bl,ds:BYTE PTR 62H ; find current active display page
- xor bh,bh
- mov dx,80[bx] ; get current cursor pos
- mov ds,cx
- mov WORD PTR cs:col,dx
- pop dx
- pop cx
- pop bx
- pop ax
- call video
- pop bp
- pop es
- pop di
- pop si
- pop dx
- pop cx
- pop bx
- pop ax
- ret
-
- video:
- mov si,OFFSET state ; Starts by jumping to s1
- jmp WORD PTR [si]
-
- ansi_chk:
- cmp al,'['
- jz ansi_comes
- ;
- ;Now check for VT52 codes
- ;
- mov bx,OFFSET vt52_tab - 3
- vs7a:
- add bx,3
- cmp BYTE PTR [bx],0
- jnz vs7b
- jmp s1a ; was no_cmd, but I now want to ignore
- vs7b:
- cmp BYTE PTR [bx],al
- jnz vs7a
- mov cx,1 ; only one thing to do for all VT52s
- jmp WORD PTR 1[bx]
- ;
- ansi_comes:
- mov state,OFFSET scan_params
- xor bx,bx
- mov WORD PTR delim,bx
- jmp SHORT t_p_buff
-
- scan_params:
- cmp al,';' ; separator
- jnz chk_dig
- nxt_pbyte:
- inc parm_len ; ensure at least 1
- t_p_buff: ; terminate current param area end
- call np_byte
- xor ax,ax
- mov [bx],ax
- ret
-
- chk_dig:
- cmp al,'0' ; 30h
- jb chk_delim
- cmp al,'9' ; 39h
- ja chk_delim
- call np_byte
- sub al,'0' ; 30h
- xchg al,[bx]
- mov ah,0ah
- mul ah
- add [bx],al
- ret
-
- chk_delim:
- cmp al,'=' ; These are lead-in/separators used
- jz sep_fnd ; by some commands
- cmp al,'?'
- jz sep_fnd
- cmp al,'"' ; String delimiter for kkr
- jz str_fnd
- cmp al,27h ; ' - alternate string delimiter
- jnz scan_cmd
- str_fnd:
- mov state,OFFSET read_parm
- mov delim,al
- sep_fnd:
- ret
-
- read_parm:
- cmp al,delim
- jnz still_str ; still receiving a string
- dec parm_len
- mov state,OFFSET scan_params
- ret
-
- still_str:
- call np_byte
- mov [bx],al
- mov state,OFFSET read_parm ; 398h
- jmp SHORT nxt_pbyte
-
- scan_cmd:
- mov bx,OFFSET cmdtab - 3
- scmd_2:
- add bx,3
- cmp BYTE PTR [bx],0
- jz no_cmd
- cmp [bx],al
- jnz scmd_2
- mov ax,1[bx]
- mov bx,OFFSET keybuf
- inc bx
- add bx,kbuf_end
- mov dl,[bx] ; get first parameter (should always be
- xor dh,dh ; a number
- mov cx,dx
- or cx,cx
- jnz gotoit
- inc cx ; set default of 1 for param 1 value
- gotoit:
- jmp ax
-
- s1:
- cmp al,1bh
- jnz no_cmd
- mov state,OFFSET ansi_chk
- ret
-
- no_cmd:
- call chrout ; print char if not in table
- s1a:
- mov state,OFFSET s1
- ret
-
- movcur:
- cmp [bx],ah
- jz setcur
- add [bx],al
- loop movcur
- setcur:
- mov dh,row
- mov dl,col
- mov bh,dis_page
- mov ah,2
- int 10h
- jmp SHORT s1a
-
- cuh:
- mov WORD PTR col,0
- jmp SHORT setcur
-
- cup:
- mov al,win_row_max
- inc al
- cmp cl,al ; Check ROW is in range (parm 1)
- jbe cup2
- jmp setcur ; no - reset cursor to previous value
- cup2:
- mov al,win_col_max
- inc al
- mov ch,1[bx] ; get column (parm 2)
- or ch,ch
- jz zer_col
- dec ch
- zer_col:
- cmp al,ch ; limit it to current max value
- ja col_ok
- mov ch,al
- col_ok:
- xchg cl,ch ; get into correct place for writing
- dec ch ; row is always at least 1
- mov WORD PTR col,cx ; enter new value and then set it
- jmp setcur
-
- vcup:
- mov state,OFFSET vcup1
- ret
- vcup1:
- sub al,32
- mov BYTE PTR rowtemp,al
- mov state,OFFSET vcup2
- ret
- vcup2:
- sub al,32
- mov BYTE PTR col,al
- mov al,BYTE PTR rowtemp
- mov BYTE PTR row,al
- jmp setcur
-
- ;
- ;reverse video is done like this so that it works the way you would expect
- ;on a colour display, ie it swaps background and foreground as far as possible.
- ;
- ;NOTE- for MVD11 reverse video is obtained by writing ASCII + 128 byte, thus
- ;we need to select the method depending on the current display selected.
- ;
- ;
- revon:
- mov BYTE PTR revflg,80H
- jmp SHORT set_rev
-
- revoff:
- mov BYTE PTR revflg,0
-
- set_rev:
- mov al,attr
- and al,77H
- mov cl,4 ; swap the attribute settings
- ror al,cl
- and BYTE PTR attr,88H ; keep B and I as before
- or BYTE PTR attr,al
- jmp s1a
-
- bright:
- or BYTE PTR attr,08H ; set intensity bit
- jmp s1a
-
- dim:
- and BYTE PTR attr,0F7H ; remove intensity bit
- jmp s1a
-
- cuf:
- mov ah,win_col_max
- mov al,1
- cuf1:
- mov bx,OFFSET col
- jmp movcur
-
- cub:
- mov ax,0FFH
- jmp SHORT cuf1
-
- cuu:
- mov ax,0FFH
- cuu1:
- mov bx,OFFSET row
- jmp movcur
-
- cud:
- mov ah,win_row_max
- mov al,1
- jmp SHORT cuu1
-
- scp:
- mov ax,word ptr col
- mov savcr,ax
- jmp setcur
-
- rcp:
- mov ax,savcr
- mov WORD PTR col,ax
- jmp setcur
-
- vcud: mov ah,win_col_max
- mov al,1
- jmp SHORT cuu1
-
- sgr:
- xor cx,cx
- xchg cl,BYTE PTR parm_len
- call np_byte
- inc cx
- att_loop:
- mov al,[bx] ; get an attribute command from param
- push bx ; area
- mov bx,OFFSET att_tab ; look it up in the table
- att_next:
- mov ah,[bx]
- add bx,3
- cmp ah,0ffh ; end of table ?
- jz att_done
- cmp ah,al ; found requested attribute?
- jnz att_next ; no, look at next entry in table
- mov ax,-2[bx] ; yes, get mask and bits needed to
- and attr,al ; establish the attribute requested
- or attr,ah
- att_done:
- pop bx
- inc bx
- loop att_loop
- jmp setcur
-
- ved:
- mov al,win_row_max ; last line is special in VT52
- dec al
- cmp BYTE PTR row,al
- jb ved_j
- jmp vel1
- ved_j: ; BLOODY INTEL!
- mov dh,al
- ;
- ;Clear to end of screen - because of way ROM BIOS works, we must clear
- ;the current line from cursor to end, and clear the remainder of the screen
- ;window at full width
- ;
- ved2:
- mov cx,WORD PTR col
- inc ch ; up row to clear remainder
- xor cl,cl
- mov dl,win_col_max
- mov bh,attr
- mov ax,600H
- int 10H ; clear it
- jmp SHORT el ; now erase to end of current line
-
- vcls: ; clear whole display, leave cursor
- xor cx,cx ; and line 25
- mov dh,win_row_max
- dec dh
- jmp SHORT erase
-
- ed:
- xor cl,cl ; examine the passed param (if any)
- xchg cl,BYTE PTR parm_len
- call np_byte
- mov al,[bx] ; get it
- or al,al ; 0 - clear from cursor to end of screen
- mov dh,win_row_max
- jz ved2
- cmp al,2
- jz clr
- mov dx,WORD PTR col
- xor cx,cx ; al = 1 clear up to cursor
- dec dh ; do area above cursor line
- mov dl,win_col_max
- mov bh,attr
- mov ax,600H
- int 10H
- mov dx,WORD PTR col ; now clear up to cursor
- mov ch,dh
- xor cl,cl
- jmp SHORT erase2
- clr:
- xor cx,cx ; clear the lot!
- mov WORD PTR col,cx
- erase:
- mov dl,win_col_max
- erase2:
- mov bh,attr
- mov ax,600h
- int 10h
- jmp setcur
-
- vel1:
- mov BYTE PTR col,0
-
- el:
- mov cx,word ptr col
- el2:
- mov dh,ch
- jmp SHORT erase
-
- byte_to_dec:
- mov dl,0ah
- inc al
- xor ah,ah
- div dl
- add ax,3030h
- ret
-
- dsr:
- mov al,row
- call byte_to_dec
- mov rowval,ax
- mov al,col
- call byte_to_dec
- mov colval,ax
- mov bufcnt,9
- mov bufpos,OFFSET cprbuf
- cpr:
- jmp s1a
-
- vrm:
- mov state,OFFSET vrm1
- ret
-
- vrm1:
- xor cx,cx
- mov ch,24
- jmp SHORT el2
-
- rm:
- mov cl,1
- jmp SHORT setmode
-
- vsm:
- mov state,OFFSET s1a
- ret
- sm:
- xor cx,cx
- setmode:
- mov al,dl
- cmp al,7
- ja cpr
- jb set_it
- mov wrap,cl
- jmp SHORT cpr
-
- set_it:
- mov ah,0
- int 10h
- jmp SHORT cpr
-
- ;
- if tracker
- ;
- ;
- ;devon - enable (in software) the input device - also init the buffers etc
- ;
- devon:
- mov speed,cx ; first param (def 1) sets speed
- mov ax,2
- call inp_key ; clear any pending keys
- mov ax,io_port ; if Z then cannot use device
- or ax,ax
- jz not_on
- mov BYTE PTR devflg,1 ; tell console device is active
- call devinit ; tell device to init
- not_on:
- jmp setcur
- ;
- ;
- ;devoff - disable input device, hence freeing any ports etc it was using
- ;
- devoff:
- mov BYTE PTR devflg,0
- call devterm
- jmp setcur
- ;
- endif
- ;
- ; Screen resolution setting command
- ;
- set_res:
- mov ch,cl ; get rows to ch
- mov cl,1[bx] ; and columns to cl
- dec cl ; adjust to max address
- dec ch
- mov WORD PTR win_col_max,cx ; set it
- jmp setcur
- ;
- ;Keyboard Key Reassignment
- ;
- kkr:
- xor dx,dx
- xchg dl,BYTE PTR parm_len
- inc dx
- inc dx
- call np_byte ; bx points to start of param area
- mov ax,[bx] ; get key value required
- call lookup ; is it already defined?
- jnz isn_defd ; no
- mov di,bx ; yes - remove existing definition
- sub kbuf_end,cx ; cx has length of definition
- mov bufcnt,0
- mov si,di ; di points to start of defn
- add si,cx ; si to end
- add cx,OFFSET enk_buf
- sub cx,si ; shift rest of table up
- cld
- push es
- push cs
- pop es
- rep movsb
- pop es
- isn_defd:
- call np_byte
- cmp BYTE PTR [bx],0 ; extended key?
- jnz kk_nsp
- cmp dl,4 ; minimum length for a definition
- jb is_room
- jmp SHORT kk_isdef
- kk_nsp:
- cmp dl,3 ; minimum length for a definition
- jb is_room ; no - just terminate table here
- kk_isdef:
- mov -1[bx],dl
- add kbuf_end,dx
- add bx,dx ; point to new end to key table
- cmp kbuf_end,max_pbuf - 8 ; leave some room for more commands
- jb is_room
- sub bx,dx ; no room in buffer - give up
- sub ds:WORD PTR kbuf_end,dx
- is_room:
- mov BYTE PTR -1[bx],0 ; make last byte in table a 0
- mov state,OFFSET s1
- ret
-
- ;
- ;This routine returns the address in BX of the next byte to be used for storing
- ;incoming parameters (including strings) to be used by the ANSI commands
- ;
- ;This data is stored on the end of the keyboard translate buffer.
- ;
- np_byte:
- mov bx,ds:kbuf_end
- inc bx
- add bx,parm_len
- cmp bx,max_pbuf
- jb pbuf_ok
- dec parm_len
- jmp SHORT np_byte
-
- pbuf_ok:
- add bx,OFFSET keybuf ; 555h
- ret
- ;
- if tracker
- ;
- ;
- ;device hooks temporarily set here
- ;
- device:
- jmp mouse ; filled in when device loaded
- devinit:
- jmp minit
- devterm:
- jmp mterm
- ;
- ;space for device code
- ;
- db 512 DUP (0C3H) ; ret instructions!
- ;
- ;General purpose button, loop counters for use by device
- ;
- ;
- last_b DB 0
- key DB 0
- count DW 0
- ;
- ;
- ;input device data area.
- ;
- ;Here I implement a circular (FIFO) buffer to hold the data returned by the
- ;input device. Only the untranslated keycodes are stored.
- ;
- ;
- in_rd DW 0 ; current read key value
- in_wr DW 0 ; next location to store key
- in_cnt DW 0 ; number of entries in buffer
- inp_buf DW 256 DUP (0) ; buffer 256 keys at a time
- devflg DB 0 ; flags that input device is enabled
- speed DW 1 ; divisor to control device speed
- xrem DW 0 ; remainders carried over to next
- yrem DW 0 ; call of device
- io_chan DW 0 ; set to 0 for COM1
- io_port DW 0 ; contains I/O address base for driver
- ; the last two are set by INIT
- ;
- endif
- ;
- ;
- ;
- ;Data used by the device driver - some of this is position dependant
- ;so be very careful when adding/deleting new bits!
- ;
- text_ok DB 0 ; set by init
- keys_ok DB 0 ; set by init
- ibm_cur DW 0
- ibm_atr DW 0
- rowtemp DB 0
- revflg DB 0
- wrap DB 0
- kbuf_end DW 4
- state DW s1
- mode DB 3
- col DB 0
- row DB 0
- savcr DW 0
- delim DB 0
- parm_len DW 0 ; length of parameter area in buffer
- bufcnt DB 0
- bufpos DW keybuf ; location to get next key value from!
- cprbuf DB 1bh,'['
- rowval DW 3030h
- DB ';'
- colval DW 3030h
- DB 'R',0dh
- altah DB 0
- attr DB 7
- dis_page DB 0
- base DW 0b800h
- scr_seg DW 0
- ;
- ;Table used by SGR for modifying the current attributes associated with
- ;characters written to the screen.
- ;
- ;Made up as follows:
- ;
- ; attr cmd val mask attribute bits to be set
- ;
- ;
- att_tab LABEL BYTE
-
- DB 0, 0, 7
- DB 1, 0FFH, 8
- DB 4, 0F8H, 1
- DB 5, 0FFH, 80H
- DB 7, 0F8H, 70H
- DB 8, 88H, 0
- DB 1EH, 0F8H, 0
- DB 1FH, 0F8H, 4+8 ; Use high intensity colours -
- DB 20H, 0F8H, 2+8 ; looks better on EGA etc
- DB 21H, 0F8H, 6+8
- DB 22H, 0F8H, 1+8
- DB 23H, 0F8H, 5+8
- DB 24H, 0F8H, 3+8
- DB 25H, 0F8H, 7+8
- DB 28H, 8FH, 0
- DB 29H, 8FH, 40H
- DB 2AH, 8FH, 20H
- DB 2BH, 8FH, 60H
- DB 2CH, 8FH, 10H
- DB 2DH, 8FH, 50H
- DB 2EH, 8FH, 30H
- DB 2FH, 8FH, 70H
- DB 0FFH
- ;
- ;
- keybuf DB 4, 0, 72h, 10h ; Print screen key
- DB (max_pbuf - 4) DUP (0)
- enk_buf LABEL BYTE
- ;
- ;init code can be thrown away after use
- ;
- con$init:
- ;
- sti
- int 11H ; equipment check
- and al,30H ; get display info
- cmp al,30H ; Z if BW card
- jz con$crt
- mov ax,3 ; set 80 x 25 colour mode
- int 10H
- jmp SHORT con$set
- con$crt:
- mov ax,7 ; set CRT mode
- int 10H
- con$set:
- mov WORD PTR col,0
- xor ax,ax ; IBM window always set to 0,0
- mov WORD PTR win_col,ax
- mov WORD PTR col,ax
- ;
- if tracker
- ;
- ;
- ;set up the required input device driver code
- ;
- lds bx,cs:DWORD PTR ptrsav ; examine the invocation line
- lds si,DWORD PTR 18[bx] ; get pointer to string
- ;
- ;first find the end of the line
- ;
- scloop:
- mov al,[si]
- cmp al,0DH ; Carriage Return
- jz en_lin ; found the end
- cmp al,0AH ; might be a line feed
- jz en_lin
- inc si
- jmp SHORT scloop
- en_lin: ; line end is guaranteed!
- ;
- ;now go back until we find a char - should be a digit!
- ;
- b1_lp:
- dec si
- cmp BYTE PTR [si],' ' ; ignore any trailing spaces
- jz b1_lp
- ;
- cmp BYTE PTR [si],'0'
- jb no_dig
- cmp BYTE PTR [si],'9'
- ja no_dig
- mov al,[si] ; get the digit - 0 or 1?
- sub al,'1'
- and ax,1 ; force into range 0 - 1
- mov cs:io_chan,ax ; save for later setup
- ;
- ;now go back until we hit another character
- ;
- b2_lp:
- dec si
- cmp BYTE PTR [si],' '
- jz b2_lp
- no_dig:
- ;
- ;now we fetch the two characters that should indicate the device to use
- ;
- dec si
- mov ax,[si] ; get the chars
- and ax,5f5fH ; force into upper case
- cmp ax,'SM' ; intel reverses word bytes
- jnz st_tb ; not mouse, so set trackball
- ;
- ;serial mouse setup
- ;
- mov ax,40H ; point to PC data area
- mov ds,ax
- mov bx,cs:io_chan
- add bx,bx ; point into RS232_BASE
- mov ax,[bx]
- push cs
- pop ds
- mov io_port,ax ; set up device data area
- or ax,ax ; Z if port not available
- jz no_com
- mov ax,OFFSET ld_ok ; set up display messages
- jmp SHORT dev_mst
- no_com:
- mov ax,OFFSET ld_bad
- dev_mst:
- mov dv_ms2,ax
- or bx,bx ; which port?
- jnz dev_2
- mov ax,OFFSET c1_mess
- jmp SHORT dev_ms2
- dev_2:
- mov ax,OFFSET c2_mess
- dev_ms2:
- mov dv_ms3,ax
- mov ax,OFFSET sm_mess ; and actual device name
- mov dv_ms1,ax
- mov cx,(OFFSET sm_end) - (OFFSET sm_start)
- mov di,OFFSET device
- mov si,OFFSET sm_start
- jmp ld_dev
- ;
- ;come here if trackerball is to be used!
- ;
- st_tb:
- mov ax,40H ; point to PC data area
- mov ds,ax
- mov bx,cs:io_chan
- add bx,bx ; point into PRINTER_BASE
- add bx,8 ; offset to PRINTER_BASE
- mov ax,[bx]
- push cs
- pop ds
- mov io_port,ax ; set up device data area
- or ax,ax ; Z if port not available
- jz no_lst
- mov ax,OFFSET ld_ok
- jmp SHORT dev_tb
- no_lst:
- mov ax,OFFSET ld_bad
- dev_tb:
- mov dv_ms2,ax
- test WORD PTR io_chan,0FFFH
- jnz p_dev2
- mov ax,OFFSET p1_mess
- jmp SHORT dev_tb2
- p_dev2:
- mov ax,OFFSET p2_mess
- dev_tb2:
- mov dv_ms3,ax
- mov ax,OFFSET mb_mess
- mov dv_ms1,ax
- mov cx,(OFFSET tb_end) - (OFFSET tb_start)
- mov si,OFFSET tb_start
- mov di,OFFSET device
- ld_dev:
- push cs
- pop es
- cld
- rep movsb
- ;
- endif
- ;
- setbrk:
- xor bx,bx
- mov ds,bx
- mov bx,6ch ; set up MSDOS int vectors
- mov WORD PTR [bx],OFFSET break
- mov 2[bx],cs
- mov bx,0a4h ; 29 - conout
- mov WORD PTR [bx],OFFSET cout
- mov 2[bx],cs
- push dx
- push cs
- pop ds
- mov dx,OFFSET signon
- mov ah,9
- int 21H
- ;
- if tracker
- ;
- mov dx,dv_ms1
- mov ah,9
- int 21H
- mov dx,dv_ms2
- mov ah,9
- int 21H
- mov dx,dv_ms3
- mov ah,9
- int 21H
- ;
- endif
- ;
- pop dx
- sti
- lds bx,cs:DWORD PTR ptrsav
- mov WORD PTR 14[bx],OFFSET con$init ; yes
- mov 16[bx],cs
- jmp exit
- ;
- signon DB 27,'[2J'
- DB 27,'[1;20H',27,'p'
- DB ' '
- DB 27,'[2;20H'
- DB ' CHARTER SOFTWARE LTD '
- DB 27,'[3;20H'
- DB ' '
- DB 27,'q',27,'[5;17H'
- DB 'ANSI/VT52 Terminal V 2.1: 12th DEC 1987'
- DB 27,'[7;17H'
- DB ' For PC, XT, AT and compatibles only'
- DB 27,'[8;17H'
- DB '$'
- ;
- if tracker
- ;
- ;
- mb_mess DB 'RB2 Trackerball $'
- sm_mess DB 'Microsoft Mouse $'
- ;
- ld_ok DB 'installed, using $'
- ld_bad DB 27,'punable to access',27,'q $'
- ;
- c1_mess DB 'COM1',13,10,10,'$'
- c2_mess DB 'COM2',13,10,10,'$'
- p1_mess DB 'LPT1',13,10,10,'$'
- p2_mess DB 'LPT2',13,10,10,'$'
- ;
- dv_ms1 DW 0
- dv_ms2 DW 0
- dv_ms3 DW 0
- ;
- ;
- sm_start:
- ;
- ;Hooks into device code
- ;
- jmp mouse
- jmp minit
- jmp mterm
- ;
- ;Simple interface to the Microsoft Serial Mouse, via the IBM ROM BIOS RS232
- ;controls. This returns data to the caller using a method that can be adapted
- ;to other input devices:
- ;
- ;When called it returns:
- ;
- ; AL - 8 bits set to 0 or 1 depending on the state of buttons
- ; 1 - 8 (bits 0 - 7). A one indicated the button is down
- ;
- ; BX - Count of x steps received
- ; CX - Count of y steps received
- ;
- ;
- mouse PROC NEAR
- ;
- xor bx,bx ; prepare return registers
- xor cx,cx
- call status ; get COM1 status
- and al,1 ; any bytes waiting
- jnz got_one
- jmp no_mouse ; nothing received, go back to caller
- got_one:
- call c1_dat ; read a byte
- test al,40H ; true if this is start of the sequence
- jnz rd_mouse ; yes, get the mouse data
- jmp no_mouse
- rd_mouse:
- push ax ; save for later
- call c1_dat ; two more chars should be coming
- mov bl,al ; x movement
- call c1_dat
- mov cl,al ; y
- ;
- ;now see which buttons are pressed - give the left one priority
- ;
- pop dx ; get first byte into dl
- mov al,dl ; take copy to check for button release
- and dl,30H ; don't xor it if none there, else we
- jz not_lst ; will get the last one pressed again!
- xor dl,last_b ; previous button settings
- not_lst:
- mov last_b,al ; save for next time
- xor dh,dh ; keep button byte in here
- test dl,20H ; true if left button (1)
- jz no_left
- or dh,1 ; set first button bit
- no_left:
- test dl,10H ; right button (3): tball compatability
- jz no_right
- or dh,4
- no_right:
- mov dl,al ; get original flag byte back
- test dl,03H ; negative x movement
- jz xv_ok
- mov ax,40H ; numbers are 7 bit twos complement
- sub ax,bx
- xor bx,bx
- sub bx,ax ; make into a 16 bit twos comp number
- xv_ok:
- test dl,0CH ; negative y (= + y in cartesian terms)
- jz yv_pos
- mov ax,40H
- sub ax,cx
- jmp SHORT yv_ok
- yv_pos:
- xor ax,ax
- sub ax,cx
- yv_ok:
- mov cx,ax
- mov al,dh
- xor ah,ah
- jmp SHORT all_done
- no_mouse:
- xor ax,ax
- all_done:
- ret
- ;
- status PROC NEAR
- ;
- mov dx,io_port ; read COM? status
- add dx,5
- in al,dx
- ret
- ;
- status ENDP
- ;
- c1_dat PROC NEAR
- ;
- push cx ; time out if nothing received
- xor cx,cx ; to avoid lockup
- wt_dat:
- dec cx
- jcxz no_dat
- call status ; call it a few times to give
- call status ; reasonable loop
- call status
- call status
- and al,1
- jz wt_dat
- mov dx,io_port ; COM? data
- in al,dx
- jmp SHORT dat_in
- no_dat:
- xor ax,ax
- dat_in:
- pop cx
- ret
- ;
- c1_dat ENDP
- ;
- mouse ENDP
- ;
- minit PROC NEAR
- ;
- ;
- ;Set COM1 baud rate etc for the mouse
- ;
- mov ax,82H ; 1200 baud, 7 bits, 1 stop, no parity
- mov dx,io_chan ; contains 0 for COM1, 1 for COM2
- int 14H
- ;
- ;mouse needs RTS and DTR on, so we have to program those directly using data
- ;from the ROM BIOS area
- ;
- push ds
- push dx
- mov dx,40H ; IBM data segment
- mov ds,dx
- mov dx,cs:io_port ; word holding port address selected
- or dx,dx ; Z if no serial card there
- jz m_nogo
- add dx,4 ; point to modem control register
- mov al,3 ; enable RTS and CTS
- out dx,al
- m_nogo:
- pop dx
- pop ds
- ret
- ;
- minit ENDP
- ;
- mterm PROC NEAR
- ;
- ret ; restore any initial host state
- ;
- mterm ENDP
- ;
- sm_end:
- ;
- tb_start:
- ;
- ;Hooks into trackerball driver
- ;
- jmp tball
- jmp tbinit
- jmp tbterm
- ;
- ;
- ;It is possible to use all the status I/O lines on the IBM standard printer
- ;port as inputs, by setting them all to 0 and then just reading them back.
- ;
- ;This allows us to obtain the seven lines needed to poll the trackerball.
- ;
- ;The connections and ports are as follows:
- ;
- ; Port Pin Signal Trackball signal Port bit
- ;
- ; 1 /strobe X1 3BE/37A 0
- ; 14 /AutoFeed X2 3BE/37A 1
- ; 16* /init Y1 3BE/37A 2
- ; 17 /select Y2 3BE/37A 3
- ; 15* /error L 3BD/379 3
- ; 13* select M 3BD/379 4
- ; 12* P.End R 3BD/379 5
- ;
- ; The pins marked * are presented in the read port in the same sense as the
- ; actual signals, the others are inverted, hence these bits need to be turned
- ; around as necessary to get the actual data.
- ;
- ;
- ;
- ;This function takes no parameters and returns no value, it simply
- ;programs the IBM status lines to be a inputs
- ;
- tbinit PROC NEAR
- ;
- ;NOTE other pins are already inputs
- mov dx,io_port ;assume mono/printer adapter for now
- add dx,2
- mov al,04H ;set all pins as inputs (16 is not inverted)
- out dx,al
- ret
- ;
- tbinit ENDP
- ;
- ;
- ;Restore the parallel port to normal use
- ;
- tbterm PROC NEAR
- ;
- mov dx,io_port ;reset port to power up defaults
- add dx,2
- mov al,0BH
- out dx,al
- ret
- ;
- tbterm ENDP
- ;
- ;
- ;This routine performs two functions, it first scans the trackerball keys.
- ;If any are pressed, it waits for them to be released and then returns with
- ;the pattern (active high). The trackerball itself is then examined, the
- ;program determines the direction of rotation and returns this as an x,y
- ;movement. The speed sensing used in the direct driver is not used here,
- ;otherwise a quick spin might produce 256 movement codes in one go!
- ;
- ;Returns the same data as the mouse driver above
- ;
- tball PROC NEAR
- ;
- timval equ 020H
- ;
- ;
- xor si,si
- xor di,di
- xor bx,bx ;clear ball directions
- retry:
- or si,si ;any movement yet recorded?
- jz tst_di
- jmp goback ;yes!
- tst_di:
- or di,di
- jnz goback
- nokeys:
- mov dx,io_port ;input port address
- inc dx
- in al,dx ;get current settings
- and al,38H
- xor al,38H ;non - zero if any keys pressed
- mov cl,3
- shr al,cl ;get into correct bit positions
- or al,al ;see if any pressed
- mov dl,al
- jz non_pr ;don't xor with last val if none pressed
- xor dl,last_b ;make code wait for release on next passes
- non_pr:
- mov last_b,al ;save value
- mov key,dl ;save button value for end
- balls: ;scan tracker ball
- ;
- mov dx,io_port
- inc dx
- inc dx
- in al,dx ;fetch ball status
- xor al,0BH ;get all bits into the same sense (see above)
- and al,5 ;examine x1 and y1
- mov ah,al ;save current x1 and y1
- mov count,timval ;used to give time for a transition to occur
- ballp:
- dec count
- jz goback ;fed up with waiting
- in al,dx
- xor al,0BH
- mov cl,al ;save result
- and al,5
- cmp ah,al ;wait for a transition
- jz ballp
- ;
- ;we have now scanned a transition, so we can find out the direction the ball
- ;was moving in from the quadrature square waves
- ;
- xor al,ah ;zero if both same
- push ax ;save for later
- and al,1 ;check x1 first
- jz testy1 ;no change in x1
- test cl,1 ;low to high transition on x1?
- jz xhtol ;no
- test cl,2 ;if x2 high we are moving left
- jnz xleft1
- xleft2:
- inc si
- jmp SHORT testy1
- xhtol:
- test cl,2 ;if x2 high we are moving right
- jnz xleft2
- xleft1:
- dec si
- testy1:
- pop ax
- and al,4 ;see if y1 changed
- jz goback
- test cl,4 ;low to high transition on y1?
- jz yhtol ;no
- test cl,8 ;if y2 high we are moving up
- jz yup2
- yup1:
- inc di
- jmp SHORT goback
- yhtol:
- test cl,8 ;if y2 high we are going down
- jz yup1
- yup2:
- dec di
- goback: ;something somewhere may have been read
- mov bx,si ;x movement
- mov cx,di ;y
- mov al,key ;get buttons
- xor ah,ah
- ret
- ;
- ;
- tball ENDP
- ;
- ;
- tb_end:
- ;
- ;
- endif
- ;
- ;
- codeseg ENDS
- END
- ;
-