home *** CD-ROM | disk | FTP | other *** search
Text File | 1989-01-26 | 149.3 KB | 5,795 lines |
- ; PCTERM.A86
- title 'XIOS PC terminal emulator'
- pagesize 60+11
- ;********************************************************
- ;* *
- ;* XIOS SERIAL CONSOLE PC TERMINAL EMULATOR *
- ;* CDOS 386 XIOS *
- ;* *
- ;********************************************************
-
- ; modifications
- ; V3.0
- ; 26 JAN 89 -- INT 10h char write goes straight to terminal GMS
- ; 12 JAN 89 -- Set write protect on screen memory for IDLE GMS
- ; 12 Dec 88 -- block ESC printer output GMS
- ; 24 Nov 88 -- save ROS values during flush init GMS
- ; 23 Nov 88 -- allow invisble attribute GMS
- ; 22 Nov 88 -- Allow enhanced DEL_SCAN through GERMAN etc GMS
- ; 21 Nov 88 -- Calls Statline.A86 for statline related calls IJ
- ; 18 Nov 88 -- Dead key fix GMS
- ; 17 Nov 88 -- PCTerminal printers - return AH status too IJ
- ; 16 Nov 88 -- correct local NUMLOCK state on arrow keys IJ
- ; 8 Nov 88 -- map_top restores MONO+COLOR Screen/CRT ports IJ
- ; 21 Oct 88 -- allow modes 2/3, CtrlAltF10 clears lock bits IJ
- ; 10 OCT 88 -- allow CRTL/ALT dead keys GMS
- ; 5 Oct 88 -- bug fixes for beta IJ
- ; 3 Oct 88 -- int 10/9 null character check as per flush IJ
- ; 29 Sep 88 -- fix bug when mixing Dumb/PC terminals IJ
- ; 21 SEP 88 -- equates moved to PTERM.EQU GMS
- ; 21 SEP 88 -- Exception handler code moved to V386.A86 GMS
- ; 19 SEP 88 -- Get all MX's on io_switch GMS
- ; 25 AUG 88 -- Support background screen writes GMS
- ; 12 Jul 88 -- Support for Aux/Printer port on Wyse IJ
- ; 5 Jul 88 -- Ros cursor/mode support IJ
- ; 22 JUN 88 -- fix for FRENCH & GERMAN enhanced keyboards GMS
- ; 8 JUN 88 -- ctrl numpad scan code corrected GMS
- ;
- ; 11 JAN 88 -- save_equip moved to pubdata GMS
- ; 17 DEC 87 -- use PC2PORT_TABLE for port mapping JW
- ; 18 NOV 87 -- test both bits for beeper GMS
- ; 12 NOV 87 -- save ROS keyboard buffer on dispatch GMS
- ; 11 NOV 87 -- Bug fix for national enhanced keyboards GMS
- ; 10 NOV 87 -- always return 0fxh on reads from status port GMS
- ; 9 NOV 87 -- return scan code for INSERT key GMS
- ; 3 NOV 87 -- bug fix National keyboard support GMS
- ; 3 NOV 87 -- ignore CTRL NUMLOCK i.e. PAUSE key GMS
-
- nolist
- include CDOS.EQU
- include XIOS.EQU
- include PCHW.EQU
- include ASCII.EQU
- include ROSDATA.EQU
- include NAT.EQU
- include PTERM.EQU
- list
- ; These have been included:
- ; include CDOS.EQU
- ; include XIOS.EQU
- ; include PCHW.EQU
- ; include ASCII.EQU
- ; include ROSDATA.EQU
- ; include NAT.EQU
- ; include PTERM.EQU
-
-
-
- CodeMacro FLUSH_TLB
- db 0FH
- dw 0D822H ; magic "flush TLB" command
- EndM
-
- CodeMacro OP_32
- DB 66h
- EndM
-
- ; Stack frame for main pointers save area
- CON_number equ word ptr 4[bp] ; Physical/virtual console numbers
- VC_pointer equ word ptr 2[bp] ; VC_ structure pointer
- PC_pointer equ word ptr 0[bp] ; PC_ structure pointer
-
- ; System equates
- BDOS equ 224
-
- ; Local equates
-
- MAX_VIR_CONS equ NUM_VIR_CONS + (NUM_AUX_PORTS*2)
-
- IO_CONIN equ 1
- IO_CONOUT equ 2
- IO_LISTST equ 3
- IO_LIST equ 4
- IO_SWITCH equ 7
- IO_STATLINE equ 8
- PC_KBD equ 32
- PC_SHIFTS equ 33
- IO_DEVIO equ 39
-
- DELAY_COUNT equ 10 ; tick delay count (get from SETUP ?)
-
- CLNOFF equ 1000h ; offset of clean page
- IMGOFF equ 4000h ; offset of physical image
-
- CRT_FULL equ 100h * (CRT_ROWS_C - 1) + (CRT_COLS - 1)
-
- CRT_SEG equ 0B000h ; monochrome display RAM
-
- PG_ATTR equ es:byte ptr 0[di]
- PGA_DIRTY equ 40h
- PGA_RW equ 02h ; write protect bit
-
-
-
- eject
-
- CGROUP group PCTERM_CODE
- DGROUP group PCTERM_DATA
-
- PCTERM_CODE cseg
-
- public io_flush_io@, pc_point_curs@, point_vc@, point_pc1@, test_pcterm@
- public test_pcterm_printer@, print_lastchar@
- extrn flagwait@: near ; in HEADER.A86
- extrn proc_abort@:near ; in WINDOWS1.A86
- extrn sysdat$ :word
- public get_kbd_flags@ ; for KEYBOARD.A86
- extrn update_vs_cursor_from_ros@: near ; in PCVIDEO.A86
- extrn point_vs@ :near ; in WINDOWS2.A86
- extrn conout_serial_stat@ :near ; in LISTAUX.A86
-
- extrn z_sl_off@ :near ; in STATLINE.A86
- extrn z_sl_mono@ :near
- extrn z_clk_off@ :near
- extrn z_clk_on@ :near
-
- dseg
- public active_vc$
- public pc_kbd_save$
- extrn next_flag$ :byte ; in HEADER.A86
- extrn func_tbl$ :word
- extrn su_pfk_tbl$ :byte
- extrn su_mu_vs$ :byte, mu_com_type$:byte
- extrn ccb_list$ :word ; in PUBDATA.A86
- extrn save_equip$ :word, win_sized$ :byte
- extrn sl_pc_flag$ :byte
- extrn sl_crt_flag$ :byte
- extrn save_kbdata$ :word ; in KEYBOARD.A86
- extrn kbd_imhere$ :byte
- extrn switch_bits$ :byte
- extrn pfk_code_tbl$ :byte ; in CONIN.A86
- extrn pfk_scan_list$ :word
- extrn PFK_SCAN_LIST_SIZE :abs
- extrn pc2port_table$:byte ; in LISTAUX.A86
- extrn port2pc_table$:byte ; in LISTAUX.A86
-
- extrn NX_language$ :byte, NX_kbd_type$ :byte ; in NATDATA.A86
- extrn NX_natnlmode$ :byte, NX_natnlstat$ :byte
- extrn NX_dead_key$ :byte, NX_ncasetbl$ :byte
- extrn NX_n7to8tbl$ :byte, NX_n7to8chr$ :byte
- extrn NX_deadtable$: word, NX_alt_table$ :byte, NX_dead_ascii$: word
- extrn NX_alt_chars$: byte, NX_mode_table$ :byte
- extrn NX_dkeyv$ :word, NX_dkeyx$ :word
- extrn NX_last_dkey$ :word, NX_dkey_buff$ :byte
- extrn NX_nasciitable$ :word, NX_nshifttable$ :word, NX_nctrltable$ :word
- extrn NX_ctrlalt$ :word, NX_ctrlalt_shft$ :word
- extrn NX_pc_ascii$ :word, NX_pc_shift$ :word, NX_pc_ctrl$ :word
- extrn NX_pc_dead$ :word
- extrn top_screen$ :byte ; in WINDOWS3.A86
- extrn video$ :byte ; in WINDOWS1.A86
-
- eject
-
- PCTERM_CODE cseg
-
- ; Kill the Flush process if no PCTERM's SETUP
- kill_flush:
-
- sti
- mov bx,rlr$ ; terminate the running process
- and P_FLAG[bx],not (PF_KEEP + PF_TEMPKEEP)
- mov cx,P_TERM
- mov dx,0FFFFh
- call supif@ ; process is terminated
- jmps kill_flush
-
-
- supif@:
- ;------
- push es
- mov bx,.68h
- mov es,10h[bx]
- callf dword ptr .0000h
- pop es
- ret
-
-
- ; FLUSH PROCESS ENTRY - entered from flush process
- ; Entry :
- ; DL = virtual console number
- ; DS = sysdat
- ;
- io_flush_io@:
- ;------------
- cli
- mov al,0ffh
- xchg al,intercept_install
- test al,0ffh
- jnz io_flush_io1 ; been here before
- mov bx,offset func_tbl$ ; pointer to XIOS function table
- mov si,offset xios_tbl ; pointer to local entries
- mov cx,NUM_FUNCS ; number of XIOS functions to install
- setup_entries: ; install into XIOS entry table
- mov di,[si] ; get function number
- inc si ! inc si
- mov ax,cs:[bx+di] ; get original
- xchg ax,[si] ; swap
- mov cs:[bx+di],ax ; store new
- inc si ! inc si
- loop setup_entries
-
- mov di,00D4h ; dispatcher intercept
- mov 0[di],offset disp_inter
- mov 2[di],cs
-
- mov al,sl_pc_flag$
- mov ah,sl_crt_flag$
- mov save_sl_flags,ax ; save status line flags
- mov ax,PC_SEGMENT ; point at ROS data
- mov es,ax
- mov al,es:crt_mode_40 ; save some state of PC terminal
- mov save_mode,al
- mov ax,es:crt_cols_40
- mov save_cols,al
- mov ax,es:cursor_posn_40 ; save cursor position
- mov save_cursor,ax
- mov ax,es:addr_6845_40 ; save CRT controller values
- mov save_6845,ax
-
-
- io_flush_io1:
- cmp npcons$,1
- jne io_flush_io2
- jmp kill_flush ; no serial consoles
- io_flush_io2:
- push dx ; save vs
- call get_ccb ; di -> ccb
- mov dl,C_PC[di] ; logical console number
- call test_pcterm@ ; test if emulation required
- pop dx
- jnz io_flush_cont
- jmp kill_flush ; no PC emulation.. kill process
-
- io_flush_cont:
- call point_vc@
- and VC_MODE,not MATCH_BIT ; make top screen
- call point_pc ; point to PC_ structure
- mov PC_TOP_SCREEN,dl ; make us top
- push dx ; save virtual/physical console number
- push bx ; save VC_ pointer
- push si ; save PC_ pointer
- mov bp,sp
- call esc_init ; initilise escape handler
- call io_flush_init ; initialise the flush routine
-
- ; wait to be woken up
- io_flush_wait:
- push bp
- mov dx,DELAY_COUNT ; wake up 6 times a second
- mov cl,P_DELAY
- int BDOS ; Note: we run at priority 196
- pop bp
-
- mov bx,rlr$
- mov dl,P_CONS[bx] ; get Flush process VC number may have
- call point_vc@ ; been changed by IO_SWITCH.
- test VC_UPDATE,UPDATE_SL ; if so we update the status line
- je io_flush1
- and VC_UPDATE,not UPDATE_SL ; we will do the update
- pusha
- call get_ccb ; get the CCB
- mov dl,C_PC[di] ; hence the PCon number
- xor cx,cx ; normal statline call
- call fl_io_statline ; force statline update
- popa
- io_flush1:
- mov VC_pointer,bx ; save current VC-> in stack frame
- ; test if screen write occurred
- mov bx,v386_ptr$ ; get pointer to 386 specific table
- mov es,ptbl_seg ; get page table segment
- mov di,(CRT_SEG/256*4) ; get entry for screen segment
- test PG_ATTR,PGA_DIRTY ; test if screen is clean
- jz flush_cursor ; update physical cursor
- call flush_screen ; update dirty screen
- jmps io_flush_wait ; and return to sleep
-
-
- ; Update physical cursor if required
- flush_cursor:
- mov bx,VC_pointer ; BX -> VC_ screen structure
- mov si,PC_pointer ; SI -> PC_ screen structure
- call ser_mx ; output mutual exclusion
- test VC_MODE,BEL_BIT
- jz no_bel
- and VC_MODE,not BEL_BIT
- mov al,BEL ; output BELL
- call tmp_write
- no_bel:
- test VC_MODE,UPDATE_BIT ; cursor on/off mode update
- jz no_update
- and VC_MODE,not UPDATE_BIT ; reset update bit
- test VC_MODE,CURSOR_BIT
- jz update_off
- mov di,offset cur_on_seq
- call ser_write ; make sure cursor turned on
- jmps no_update
- update_off:
- mov di,offset cur_off_seq
- call ser_write ; or off
- no_update:
- mov ax,VC_CURSOR ; get virtual cursor
- call set_pcursor ; set physical cursor address
- mov PC_BUSY,0 ; release terminal
- jmp io_flush_wait ; and try again later
-
-
- ; Update the physical screen
- flush_screen:
- and PG_ATTR,not PGA_DIRTY ; mark page as clean
-
- sub si,si ; start at the beginning
- scan_for_change:
- mov cx,CRT_ROWS_P*CRT_COLS ; total screen size
- mov ax,si ; AX = offset in buffer
- shr ax,1 ; AX = character count
- sub cx,ax ; CX = characters remaining
- jbe flush_done ; everything flushed
- lea di,IMGOFF[si] ; DI = image address
- mov ax,CRT_SEG
- mov es,ax ; ES:SI -> virtual screen
- push ds
- mov ds,ax ; ES:DI -> physical image
- repe cmpsw ; skip all matching data
- pop ds
- je flush_done
- dec si ! dec si ; ES:SI -> screen buffer
- lea di,IMGOFF[si] ; ES:DI -> image buffer
- mov ax,si
- shr ax,1 ; make it character index
- mov dl,CRT_COLS
- div dl
- xchg al,ah ; AL = col, AH = row
- xchg ax,cx ; CX = cursor
- lods es:ax ; AX = character from image
- scasw ; compare with image
- je scan_for_change ; scan further if match
- mov es:0-2[di],ax ; update the image
-
- push si ; save image offset
-
- push ax
- mov si,PC_pointer ; PC_ ->
- mov bx,VC_pointer ; BX -> VC_ screen structure
- call ser_mx ; get serial semaphore
- xchg ax,cx ; AX = cursor
- call set_pcursor ; update physical cursor
- pop ax ! push ax
- call set_pattrib ; set physical attribute
- pop ax
- cmp al,' ' ; check if character large enough
- jae go_ahead ; go ahead if printable
-
- if 0 ; if 1: remap control codes to ASCII
- push bx
- mov bx,offset ctrl_xlat ; else translate to ASCII
- xlat ctrl_xlat
- pop bx
- else ; this works on the Wyse 60:
- cmp al,00 ; if zero then display a space
- jne disp_ctrl
- mov al,' '
- jmps go_ahead
- disp_ctrl:
- push ax ; convert 'xxH' to '1BH, xxH'
- mov al,ESC ; for terminal to recognize
- mov si,PC_pointer ; PC_ ->
- call tmp_write ; sequence as illegal and to
- pop ax ; display the control code.
- endif
-
- go_ahead:
- mov si,PC_pointer ; PC_ ->
- call tmp_write ; write out one character
- inc PC_CURCOL
- mov PC_BUSY,0 ; release serial semaphore
-
- pop si ; restore image offset
- jmp scan_for_change ; scan for difference
-
- flush_done:
- mov bx,v386_ptr$ ; get pointer to 386 specific table
- mov es,ptbl_seg ; get page table segment
- mov di,(CRT_SEG/256)*4 ; get entry for screen segment
- test PG_ATTR,PGA_DIRTY ; clean ?
- jz flush_ret
- jmp flush_screen ; no do it again
- flush_ret:
- ret
-
-
- eject
-
- ; INIT
- ; ----
-
- ; Initilise all data structures and buffers
- ; Entry:
- ; DL = virtual console number
- ; DH = physical console number
- ; SI = -> pc_ structure
- io_flush_init:
- ;-------------
-
- cli ; protect ourself against a dispatch
- mov al,0ffh
- xchg al,flush_install ; has flush process been installed
- test al,0ffh
- jz alloc_mem
- jmp flush_installed ; yes continue
-
- ; Allocate memory for ALL virtual images
- alloc_mem:
- mov bx,v386_ptr$ ; get pointer to 386 specific table
- mov cx,npages ; get number of pages
- mov es,mp_table
- mov si,offset mp_table_entries ; save area for memory allocs
- mov di,cx
- shl di,1 ; pointer to top of mp_table
- sub di,2 ; for backwards search
- mov al,nvcons$ ; total virtual consoles
- sub al,NUM_VIR_CONS ; less master terminal
- mov ah,npcons$ ; total physical
- dec ah ; less main console
- add al,ah
- xor ah,ah ; AX = total 4k blocks required
- mov dl,4 ; calculate number of 16k blocks
- div dl ; required
- or ah,ah ; remainder ?
- jz init1
- inc al ; extra 16k
- init1:
- mov dl,al ; DL = no. 16k blocks
-
- find_free_mem:
- sub ax,ax
- std ; scan from top of MP_TABLE
- repne scasw ; for free 16k block
- jz got_mem
- jmp no_memory ; no free mem
- got_mem:
- push di ; save current position
- push dx ! push cx ; and counts
- cld
- add di,2 ; point at free block
- mov es:word ptr[di],0ffffh ; reserve it
- shr di,1
- mov ax,16*1024 ; size of one block
- mul di
- or al,7 ; set PRESENT,U/S and R/W bits
- mov cx,4 ; store 4 4k entries
-
- save_mp_entries:
- mov [si],ax ; store ax and dx
- inc si ! inc si
- mov [si],dx
- inc si ! inc si
- add ax,4096 ; next 4k block base address
- adc dx,0
- loop save_mp_entries
-
- pop cx ! pop dx ; current counters
- pop di ; mp_table pointer
- dec dl ; number of 16k pages required
- jnz find_free_mem ; get next 16k
-
- ;
- ; install INT 10h entry
-
- sub di,di
- mov es,di
- mov ax,es:40h[di] ; take over Interrupt 10h vector
- mov int10_off,ax
- mov ax,es:42h[di]
- mov int10_seg,ax
- mov es:40h[di],offset video_int
- mov es:42h[di],cs
-
-
-
- ; INIT entry for every FLUSH process
-
- flush_installed:
-
- push ds ! pop es
- mov bx,VC_pointer ; current top screen
- lea di,VC_PAGE_SAVE ; virtual screens save area
- mov si,mp_entry_ptr ; pointer to next free 4k block
-
- lodsw ; get first part of dword address
- stosw ; and save in VC_
- xchg ax,dx
- lodsw ; second part of dword address
- stosw ; and save in VC_
- xchg ax,dx ; save same adress again for CLEAN page
- stosw
- xchg ax,dx
- stosw
-
- mov cx,si ; save current pointer for use
- ; by second VC if exists
- lodsw ; get next 4k block address
- stosw ; for physical screen image
- lodsw ; and save in VC_
- stosw
- mov mp_entry_ptr,si ; update current pointer
-
- mov dx,CON_number ; get top vc number
- xor dh,dh
- mov di,dx
- shl di,1
- mov di,ccb_list$[di] ; get CCB pointer
- mov di,C_LINK[di] ; link to next
- or di,di
- jz no_more_vc ; no more virtual consoles
-
- mov dl,C_VC[di] ; get next virtual console number
- call point_vc@ ; and VC->
- lea di,VC_PAGE_SAVE ; point to save area
-
- lodsw ; next free 4k block address
- stosw
- xchg ax,dx
- lodsw
- stosw
- xchg ax,dx
-
- stosw ; store twice for CLEAN page
- xchg ax,dx
- stosw
- mov mp_entry_ptr,si ; update pointer to free blocks
- mov si,cx ; get pointer to physical image block
- lodsw
- stosw ; and store for second VC_
- lodsw
- stosw
- ; map in second vc area to clear images
- push bx
- lea si,VC_PAGE_SAVE ; page save area for VC
- mov bx,v386_ptr$ ; get pointer to 386 specific table
- mov es,ptbl_seg ; now enable page table for us
- mov di,(CRT_SEG/100h)*4
- mov cx,2*2
- rep movsw
- add di,4*2 ; physical image offset
- mov cx,1*2
- rep movsw
-
- FLUSH_TLB ; discard TLB cache
-
- mov ax,CRT_SEG
- mov es,ax
- mov cx,2*2048 ; clear two images
- mov ax,7*256+' ' ; to all spaces
- sub di,di ;
- rep stosw
- pop bx ; get VC->
- mov VC_INSTALLED,0ffh ; and enable VC output
-
- no_more_vc:
- ; map in top screen images
- mov bx,VC_pointer ; get top screen VC_ in BX
- lea si,VC_PAGE_SAVE ; page save area for VC
- mov bx,v386_ptr$ ; get pointer to 386 specific table
- mov es,ptbl_seg ; now enable page table for us
- mov di,(CRT_SEG/100h)*4
- mov cx,2*2
- rep movsw
- add di,4*2 ; physical image offset
- mov cx,1*2
- rep movsw
-
- FLUSH_TLB ; discard TLB cache
-
-
- mov ax,CRT_SEG
- mov es,ax
- mov cx,2*2048 ; clear two images
- mov ax,7*256+' ' ; to all spaces
- sub di,di
- rep stosw
- add di,4*2048 ; point to third image
- mov cx,1*2048 ; clear physical images
- rep stosw ; and clear
-
- mov bx,v386_ptr$ ; get pointer to 386 specific table
- mov es,ptbl_seg
- mov di,(CRT_SEG/100h)*4
- and PG_ATTR,not PGA_DIRTY ; mark page as clean
-
- mov dx,CON_number
- mov active_vc$,dl ; VC number to active value
- mov sl_crt_flag$,SL_MONO_BIT ; force mono status line for terminals
- mov ax,PC_SEGMENT ; point at ROS data
- mov es,ax
- mov es:word ptr cursor_posn_40,0000 ; force cursor position
-
- mov bx,VC_pointer ; restore VC_->
- mov VC_INSTALLED,0ffh
- push bp
- mov cl,P_PRIORITY
- mov dl,196 ; lower FLUSH priority
- int BDOS
- pop bp
- sti
- mov si,PC_pointer ; restore PC_->
- call ser_mx ; get serial MX
- mov di,offset clear_seq
- call ser_write ; clear screen
- mov PC_BUSY,0 ; release MX
- call NX_init ; setup national support
- ret
-
- no_memory:
- cld
- jmp kill_flush ; not enough memory so kill flush
-
- int10_addr rd 0 ; saved INT 10h address
- int10_off rw 1 ; " offset
- int10_seg rw 1 ; " segment
-
-
-
-
- ; Initilise Escape sequence table
- ; Entry :
- ; SI = PC_ structure
- esc_init:
- push es
- push si
- push ds ! pop es
- xor ch,ch
- lea di,PC_CURPOS
- mov si,offset cpos_seq ; cursor positioning
- lodsb
- mov cl,al ; get count
- stosb ; store
- rep movsb
- pop si
- push si
- lea di,PC_ATTRIB
- mov si,offset attrib_seq ; set attribute
- lodsb
- mov cl,al ; get count
- stosb ; and store
- rep movsb ; store string
-
- pop si
- pop es
- ret
-
- eject
-
- ; XIOS Function Handlers
- ; ----------------------
-
- ; Serial Console input - XIOS function 1
- ; Entry :
- ; DL = physical console number
- fl_io_conin:
- ;-----------
- cmp dl,0 ; master console ?
- jne fl_conin_test
- conin_dumb:
- jmp io_conin
-
- fl_conin_test:
- call test_pcterm@ ; test if emulation required
- jz conin_dumb ; must be dumb terminal
-
-
- fl_conin:
- ;--------
- mov al,dl ; physical console number to AL
- call point_pc1@ ; get pointer to PC_ structure in SI
- sub al, al ; clear and test dead key buffer
- xchg al, PC_DKEY_BUFF ; see if dead key character
- test al, al ; is available
- jz test_pfk ; no, just continue
- mov ah, PC_DKEY_SCAN ; get scan code
- jmps ret_char ; return dead key char
- test_pfk:
- push dx ; DL only on entry
- mov dl,PC_TOP_SCREEN ; current foreground console
- call point_vc@ ; get the screen structure
- pop dx
-
- test VC_MODE,PCMODE_BIT ; if a DOS program...
- jnz conin_wait ; no func. keys so jump
-
- cmp VC_PFK_COUNT,0 ; if no PFKs waiting...
- je conin_wait ; then jump
-
- ; Here if there are pending function key characters:
- mov di,VC_PFK_PTR ; get the current pointer
- mov al,[di] ; get the value
- inc di
- test al,al ; if valid then jump
- jnz conin_pfk
- mov VC_PFK_COUNT,al ; else put 0 in the count
- jmps conin_wait ; and wait for a key
-
- conin_pfk:
- mov VC_PFK_PTR,di ; update the pointer
- dec VC_PFK_COUNT ; and the count
- mov ah,0 ; char is in al
- ret_char:
- ret
-
-
- conin_wait:
- ;----------
- push si ; save PC_ ->
- push dx ; save console number
- call io_conin ; get input from standard serial conin
- pop dx
- pop si
- mov bl,al ; char in AL and BL
-
- ; Test for control break
- ; ----------------------
- cmp al,PC_SCROLL_KEY ; ctrl-break scan ?
- jne conin_char
- test PC_KFLAG,CTRL_BIT
- jz conin_char
- test PC_KBD_TYPE,NX_enhanced ; is it enchanced keyboard version
- jz ctrl_brk ; no break is valid
- test PC_KFLAG3,LC_E0 ; else check if last was hidden
- jz conin_char ; no control break if not
- and PC_KFLAG3,not LC_E0
- ctrl_brk:
- mov ax,0ae03h ; cntl-c set top bit on SCAN
- jmp ci_return
-
- conin_char:
- cmp al,HIDDEN_KEY
- jne test_live
- or PC_KFLAG3,LC_E0 ; set flag
- jmp conin_wait ; and throw away
-
- test_live:
- push ds ! pop es
- mov di,offset live_tbl ; test if live key e.g. SHIFT etc.
- mov cx,live_tbl_len
- and al,7Fh
- repne scasb
- je ci_live
- jmp ci_notlive
- ci_live:
- mov cx,PC_SEGMENT ; point ES at ROS data area
- mov es,cx
-
- cmp PC_LANGUAGE,0 ;; U.S keyboard?
- je get_live
- test PC_NATNLSTAT,NX_nkbd_bit
- jz get_live
- test PC_ESHIFTLOCK,01h ; is it FRENCH/GERMAN enhanced
- jz get_live
- test PC_KFLAG,CAPSLOCK_BIT ; is CAPSLOCK already down
- jz get_live ; no let ROS have it
- cmp al,CAPSLOCK ; is it CAPSLOCK key
- jne test_eshift
- jmp live_ret ; yes.. throw it away
-
- test_eshift: ; if CAPSLOCK on and SHIFT key
- cmp al,SHFT_RIGHT ; then we must toggle CAPSLOCK off
- je tog_caps
- cmp al,SHFT_LEFT
- jne get_live
- tog_caps:
- test PC_KFLAG3,LC_E0 ; check if last was hidden
- jnz get_live ; yes not real shift
- and PC_KFLAG,not CAPSLOCK_BIT ; lets pretend it was CAPSLOCK
- jmp live_ret
-
- get_live:
- sub di,offset live_tbl+1
- mov ah,live_mask[di]
-
- cmp al,ALT ; is it toggle key
- ja toggle_key ; yes
-
- ; Live keys - SHIFT, CTRL etc
- test bl,bl
- jns ci_live_make ; skip if not break
- not ah
- and PC_KFLAG,ah ; update keyboard flag in PC_
- cmp ah,not CTRL_BIT ; ALT or CTRL
- ja test_alt_input ; no..
- test PC_KFLAG3,LC_E0 ; last char hidden
- jz not_enh ; no..
- and PC_KFLAG3,ah ; clear right ctrl and alt (alt_gr_bit)
- jmps not_enh1
- not_enh:
- sar ah,2
- and PC_KFLAG1,ah ; reset left alt and ctrl
- not_enh1:
- mov ah,al
- mov al,PC_KFLAG3 ; get right alt and ctrl
- shr al,2
- or al,PC_KFLAG1 ; put in left alt and ctrl bits
- shl al,2
- and al,ALT_BIT+CTRL_BIT
- or PC_KFLAG,al ; update real state
- mov al,ah ; recover scan code
-
- test_alt_input:
- cmp al,ALT ; if ALT BREAK
- jne not_alt_shft
- ; ALT numpad
- mov al,PC_ALT_INPUT ; check for ALT NUMPAD input
- mov ah,0
- mov PC_ALT_INPUT,ah ; zero field
- cmp al,0
- je not_alt_shft ; no ALT NUMPAD input
- call up_pc_flag ; else update ROS flags
- jmp ci_return ; and return ALT NUMPAD value
- not_alt_shft:
- jmps live_ret ; get next char input
-
- ci_live_make:
- or PC_KFLAG,ah ; update flag state in PC_
- test ah,CTRL_BIT + ALT_BIT ; ALT or CTRL ?
- jz live_ret ; no
- test PC_KFLAG3,LC_E0 ; last char hidden
- jz set_flag1 ; no..
- or PC_KFLAG3,ah ; set right ctrl and alt (alt_gr_bit)
- jmps live_ret
- set_flag1:
- shr ah,2
- or PC_KFLAG1,ah ; left ctrl and alt bits
- ci_live_done:
- jmps live_ret ; get next input char
-
-
- ; Handle toggle keys - CAPSLOCK, NUMLOCK etc
- toggle_key:
- test bl,80h
- jnz toggle_ret ; ignore break
- cmp bl,INS_SCAN ; insert key
- jne toggle1
- ; INSERT key
- test PC_KFLAG,ALT_BIT+CTRL_BIT
- jnz ci_notlive
- test PC_KFLAG,NUMLOCK_BIT
- jnz toggle_num
- test PC_KFLAG,SHFT_LEFT_BIT+SHFT_RIGHT_BIT
- jnz ci_notlive
- jmps toggle1a
- toggle_num:
- test PC_KFLAG,SHFT_LEFT_BIT+SHFT_RIGHT_BIT
- jz ci_notlive
- toggle1a:
- xor PC_KFLAG,ah ; toggle state bit
- and PC_KFLAG3,not LC_E0 ; reset hidden
- call up_pc_flag
- mov ah,bl ; scan code
- mov al,0 ; always a function key
- jmp ci_return
-
- toggle1:
- cmp bl,NUMLOCK ; numlock scan code
- jne toggle2
- test PC_KFLAG,CTRL_BIT
- jnz toggle_ret ; if CTRL NUMLOCK (i.e. PAUSE) ignore
- toggle2:
- xor PC_KFLAG,ah ; toggle state bit
- toggle_ret:
- live_ret:
- and PC_KFLAG3,not LC_E0 ; reset hidden
-
- call up_pc_flag
- jmp conin_wait
-
- up_pc_flag:
- cli ; protect against dispatch or kbd
- mov cx,word ptr PC_KFLAG ; get serial terminal flags
- cmp kbd_imhere$,0 ; in keyboard ISR ?
- jne ci_live_exit ; yes
- mov es:word ptr kb_flag_40,cx ; and store in ROS data area
- ci_live_exit:
- sti
- ret
-
-
- ; CHARACTER input
- ci_notlive:
- test PC_KFLAG3, LC_E0 ; was last hidden
- jz not_div
- cmp bl,DIV_SCAN
- jne not_div
- and PC_KFLAG3, not LC_E0 ; reset hidden flag
- jmp not_nat ; make sure we don't translate
-
- not_div:
- cmp bl,86
- ja conin_ret ; get next char
-
- ; Test for CTRL/ALT/F1 thru F5 function keys for national
- mov ah,PC_KFLAG ; get keyboard state
- and ah,CTRL_BIT or ALT_BIT ; check only those shift keys
- cmp ah,CTRL_BIT or ALT_BIT
- jne test_switch
- cmp al,F10_SCAN ; Ctl Alt F10 resets the lock bits
- jne not_lights_reset ; to get back in step with the terminal
- test PC_KFLAG,SHFT_LEFT_BIT or SHFT_RIGHT_BIT
- jz not_lights_reset ; we want shift as well (for Falcoa)
- and PC_KFLAG,not(CAPSLOCK_BIT+NUMLOCK_BIT+SCROLL_BIT)
- not_lights_reset:
- cmp al,F1_SCAN ; check if function key
- jb test_switch
- cmp al,F5_SCAN
- ja test_switch
- sub al,F1_SCAN ; make it zero based
- mov PC_NATNLMODE,al ; save current national mode
- call NX_update_mode
- jmps conin_ret ; get next char
-
- ; Test for screen switch keys
- test_switch:
- test PC_KFLAG3, LC_E0 ; was last hidden
- jnz test_alt_key
- mov ah,PC_KFLAG ; get keyboard state
- and ah,SHFT_LEFT_BIT or SHFT_RIGHT_BIT or CTRL_BIT or ALT_BIT ;;
- cmp ah,switch_bits$ ; same as keyboard switch bits
- jnz test_alt_key
- cmp al,END_SCAN ; pad 1 key
- jne test_pad2
- mov ax,0ff00h ; yes switch key
- jmps ret_switch
- test_pad2:
- cmp al,PAD2_SCAN ; pad 2 key
- jne test_alt_key
- mov ax,0ff01h
- ret_switch:
- and PC_KFLAG3, not LC_E0 ; reset hidden flag
- ret ; return switch key
-
-
- ; Test for ALT key
- test_alt_key:
- test PC_KFLAG,ALT_BIT ; test for ALT NUMPAD keys
- jz not_alt_numpad
- ; ALT numpad keys
- push ds ! pop es
- mov di,offset alt_intable
- mov cx,alt_intable_len
- repne scasb
- jne not_alt_numpad ; not ALT numpad
- sub di,offset alt_intable+1
- mov al,PC_ALT_INPUT ; get last alt char
- mov ah,10
- mul ah
- add ax,di ; add in latest entry
- mov PC_ALT_INPUT,al ; save new char
- conin_ret:
- and PC_KFLAG3, not LC_E0 ; reset hidden flag
- jmp conin_wait ; and get next char
-
- not_alt_numpad:
- mov PC_ALT_INPUT,0 ; clear ALT numpad char
- mov ah,PC_KFLAG ; get keyboard state
-
- ; the following code is supposed to take care of the case where PC Terminals
- ; are out of step with the local copy of NUMLOCK, a situation which screws up
- ; the arrow keys on extended keyboards. It is based on the observation that
- ; if there is a hidden code before the numpad key then it must be one of the
- ; extended keys, and if so the PC terminal will have ensured that the shift
- ; state has been set to negate the NUMLOCK state. So we can reverse this and
- ; set the NUMLOCK state according to the shift one.
- ;
- test PC_KFLAG3,LC_E0 ; following a hidden key ?
- jz test_nat
- cmp al,47h ; is it one affected by NUMLOCK ?
- jb test_nat
- cmp al,53h
- ja test_nat
- and ah, not NUMLOCK_BIT ; assume numlock should be off
- mov PC_KFLAG,ah
- test ah,SHFT_LEFT_BIT or SHFT_RIGHT_BIT
- jz test_nat ; if either shift key down
- or ah, NUMLOCK_BIT ; numlock should be on
- mov PC_KFLAG,ah
- ; end of NUMLOCK fix
-
- ; Test for national or U.S. keyboard
- test_nat:
- test PC_NAT,0ffh ; U.S. or national
- jz not_nat ; standard US
- test PC_NATNLSTAT$,NX_nkbd_bit ; U.S.
- jz not_nat
-
- ; National Keyboard
- cmp al,PRTSC_SCAN
- je not_nat ; don't translate
- cmp al,SCAN_102 ;; extra key - enhanced keyboard
- je nat_jmp
- cmp al,SPACE_SCAN ;; let national have space key
- ja test_pad ;; and all keys below
- nat_jmp:
- and PC_KFLAG3, not LC_E0 ; reset hidden flag
- jmp nat_kbd
-
- ; some keypad keys are translated in some languages
- test_pad:
- cmp al,DEL_SCAN ; SHIFT DEL -> conv to ','
- jne test_prt
- test PC_KFLAG3, LC_E0 ; hidden flag
- jnz not_nat
- test ah,NUMLOCK_BIT
- jz no_num
- test ah,SHFT_LEFT_BIT or SHFT_RIGHT_BIT
- jz test_lang ; NUMLOCK + no SHIFT
- jmps not_nat ; handle as normal
- no_num:
- test ah,SHFT_LEFT_BIT or SHFT_RIGHT_BIT ; no NUMLOCK + SHIFT
- jz not_nat ; no handle normal
-
- test_lang:
- cmp PC_LANGUAGE,4 ; Danish
- je conv_dot
- cmp PC_LANGUAGE,5 ; Swedish
- je conv_dot
- cmp PC_LANGUAGE,8 ; Norwegian
- je conv_dot
- test PC_KBD_TYPE$,NX_enhanced ; is it enchanced keyboard version
- jz not_nat ; no
- cmp PC_LANGUAGE,2 ; German enhanced ?
- je conv_dot ; yes
- jne not_nat
- conv_dot:
- mov al,',' ; convert '.' to ','
- mov ah,DEL_SCAN
- jmp pc_ret ; and return key
-
- test_prt:
- cmp PC_LANGUAGE,7 ; SPANISH ?
- jne not_nat ; no ..
- test PC_KBD_TYPE$,NX_enhanced ; is it enchanced keyboard version
- jnz not_nat ; yes .. no translate
- cmp al,PRTSC_SCAN ; print screen key
- jne not_nat
- mov al,'^' ; '*' converted to '^'
- mov ah,PRTSC_SCAN
- jmp pc_ret
-
-
- ; Here for U.S. keyboard support
- not_nat:
- and PC_KFLAG3, not LC_E0 ; reset hidden flag
- mov ah,al
- mov di,offset key_table
- mov bx,offset key_scan
- test PC_KFLAG,NUMLOCK_BIT ; test NUMLOCK on
- jz test_shft
- cmp al,HOME_SCAN ; is it NUMPAD
- jb test_shft
- cmp al,DEL_SCAN
- ja test_shft ; no....
- test PC_KFLAG,SHFT_LEFT_BIT+SHFT_RIGHT_BIT
- jnz ci_notshft ; use normal table if NUMLOCK shift
- mov di,offset shift_table ; else use shift table
- mov bx,offset shift_scan
-
- test_shft:
- test PC_KFLAG,SHFT_LEFT_BIT+SHFT_RIGHT_BIT
- jz ci_notshft
- mov di,offset shift_table
- mov bx,offset shift_scan
- ci_notshft:
- test PC_KFLAG,CTRL_BIT
- jz ci_notctrl
- mov di,offset ctrl_table
- mov bx,offset ctrl_scan
- ci_notctrl:
- test PC_KFLAG,ALT_BIT
- jz ci_notalt
- mov bx,offset alt_table
- xlat al
- cmp al,0FFh ; legal char ?
- je ci_ret1
- mov ah,al
- mov al,0 ; always a function key
- jmp ci_return
-
- ci_notalt:
- mov ah,al
- xlat al ; get scan code
- xchg ah,al ; save it in high byte
- mov bx,di
- xlat al ; get ASCII code
- cmp al,0FFh ; legal char ?
- je ci_ret1
- test PC_KFLAG,CAPSLOCK_BIT ; test CAPSLOCK on
- jz ci_ret2
- call case_change
- ci_ret2:
- jmp ci_return ; yes return char
- ci_ret1:
- jmp conin_wait ; else get next char
-
-
-
- ;************************************************
- ;* *
- ;* NATIONAL KEYBOARD SUPPORT *
- ;* *
- ;************************************************
-
- ; DL = console number
- ; SI = PC_ structure
- ; AL = raw scan code
- ; AH = keyboard action state
-
- nat_kbd:
- push dx ; lets save console number for retry
-
- mov PC_KBD_SCAN,al
- mov PC_SCAN_CODE,al ; temp save scan code
- cmp al,41 ; is it 1st key?
- je pc_at_swap ; yes, fix it
- cmp al,43 ; is it 2nd key?
- jne test_alt ; others are OK
- pc_at_swap: ; swap the key codes
- xor al,41 xor 43 ; 41 => 43, 43 => 41
- mov PC_SCAN_CODE,al ; save new value
- test_alt:
- test PC_KBD_TYPE$,NX_enhanced ; is it enchanced keyboard version
- jz test_alt_norm ; no .. normal keyboard
- test PC_KFLAG3,ALT_GR_BIT ; ALT GR key down ?
- jz test_ctrl_alt
-
- test PC_KFLAG1,L_ALT ; is left ALT down
- jnz test_ctrl_alt ; yes.. ignore ALT GR
- and ah,not ALT_BIT ; else remove ALT bit from status
- test ah,CTRL_BIT ; yes.. is ctrl key down
- jnz test_alt_norm ; yes .. ignore ALT GR
- jmps get_alt_gr ; else do ALT GR translate
- test_ctrl_alt:
- test ah,ALT_BIT+CTRL_BIT
- jz test_alt_norm
- not_gr:
- mov ch,ah
- and ch,ALT_BIT+CTRL_BIT
- cmp ch,ALT_BIT+CTRL_BIT
- jne test_alt_norm
-
- ; Get key from ALT GR - (CTRL\ALT) table
- ; for national enhanced keyboards
- get_alt_gr:
- mov bx,offset NX_ctrlalt$ ; pointer to CTRL\ALT table
- test ah,SHFT_LEFT_BIT or SHFT_RIGHT_BIT
- jz not_shift ; leave it if not shifted
- mov bx,offset NX_ctrlalt_shft$ ; use CTRL\ALT shift table
- not_shift:
- mov PC_TMP_US_FLG, TRUE ; disable 7 to 8 temporarily
-
- mov al,PC_SCAN_CODE ; use this value in case translated
- cmp PC_KBD_SCAN,29h
- jne test_102
- mov al,54 ; character position reserved for extra key
- test_102:
- cmp PC_KBD_SCAN,SCAN_102 ; extra key (102 keyboard)
- jne just_xlat
- mov al,2bh ; key 102 uses old char 2bh scan code
- just_xlat:
- cmp al,SPACE_SCAN ;; don't translate
- jne do_xlat
- mov al,' ' ;; space char
- jmp key_scan_ok
- do_xlat:
- xlat bx ; get ASCII char in AL
- cmp al, 0ffh ; is it undefined
- je key_scan_nok
- jmp NX_test_2nd_dkey ; no.....valid key
- jmp key_scan_ok
-
- key_scan_nok:
- mov ch,ah
- and ch,ALT_BIT + CTRL_BIT
- cmp ch,ALT_BIT + CTRL_BIT
- je test_alt_norm ; if CTRL\ALT then treat normal
- jmp key_scan_done ; else .... ignore
-
- ; Normal keyboard -
- test_alt_norm:
- test ah,ALT_BIT
- jnz test_alt_down
- jmp not_alt ; not ALT key
-
- ; The following piece of code had to be added to support ALT/letter
- ; on international keyboards, where the location of some keys is
- ; different from the US keyboard.
- test_alt_down:
- test ah,CTRL_BIT
- jz not_ctrlalt ; not CTRL\ALT
- ;; mov al, pc_scan_code ; restore scan code
- test ah,SHFT_LEFT_BIT or SHFT_RIGHT_BIT
- jz not_shft_alt
- or al, 80h ; shift marked like this in ALT table
- not_shft_alt:
- mov cx, 0
- mov cl, NX_alt_table$ ; get number of special ALT's (common)
- jcxz not_ctrlalt ; none of them
- push es
- push ds ! pop es ; point ES to DS
- mov di, offset NX_alt_table$+1 ; scan thru them
- cld
- repne scasb
- pop es
- jne not_ctrlalt
-
- sub di,offset NX_alt_table$ + 2 ; get number of scanned chars
- mov al,NX_alt_chars$[di] ; save the character
- mov PC_TMP_US_FLG, TRUE ; display as ascii (flag "CONOUT")
- jmp save_with_msb
-
-
- not_ctrlalt:
- mov al, PC_SCAN_CODE ; restore scan code
- cmp al, 2 ; scan code of digit "1"
- jb test_alt_letter ; below, forget it
- cmp al, 13 ; above "=", check if letter
- ja test_alt_letter ; check if ALT/letter
- add PC_SCAN_CODE, 118 ; ALT/1 thru ALT/0 are 120,...
- jmp turn_on_msb ; now it's all right
-
- test_alt_letter:
- mov bx, PC_NASCIITABLE ; see if letter on keyboard
- xlat bx ; lookup table
- cmp al, 'a' ; check lower boundary
- jb not_alt_letter ; too small
- cmp al, 'z' ; check upper boundary
- ja not_alt_letter ; too big
-
- push es ; save ES
- push ds ! pop es ; MOV DS,ES
- mov di, offset key_table ; scan through US key table
- mov cx, 54 ; 54 chars at most
- cld ; scan forward
- repne scasb ; find out location on US kbd
- sub di, offset key_table+1 ; subtract base + overscan
- mov ax, di ; AL = scan code
- mov PC_SCAN_CODE,al
- pop es ; restore extra segment
- jmp turn_on_msb ; return extended code for ALT
-
-
- ; test if this is an alt dead key.
- ; eat it up if it is one, continue if not.
- ; bit 7 in DEADTABLE contains shift bit,
- ; bit 6 in DEADTABLE contains alt bit
- ; (works fine because those codes are 1-59)
- ;
- not_alt_letter:
- cmp PC_NATNLMODE, 1 ; 8 bit National mode ONLY
- jne no_alt_dkey
- mov cl, PC_SCAN_CODE ; get key code
- test ah,SHFT_LEFT_BIT or SHFT_RIGHT_BIT
- jz alt_dkey_noshift ; no shift, leave it
- or cl, 80h ; turn on shift bit
- alt_dkey_noshift:
- or cl, 40h ; turn on alt bit
- mov di, PC_DEADTABLE ; find out if alt dead key
- call NX_scanstr ; look for a match
- cmp di,0FFFFh ; no match
- je no_alt_dkey ; forget it
- mov PC_LAST_DKEY, di ; save dead key
- no_alt_dkey:
- jmp key_scan_done ; eat up this code
-
-
- ; CTRL, SHIFT or NORMAL ascii national key
- not_alt:
- mov bx, PC_NASCIITABLE ; translation table for single keys
- test ah,CTRL_BIT ; is control key down ?
- jz test_for_shift ; no, try shift
-
- mov bx, PC_CTRLTABLE ; yes, point to control key table
- jmps translate ; and make control code
-
- test_for_shift:
- cmp PC_SHIFTLOCK,FALSE ;; french keyboard flag
- jnz test_caps ;; true
- test PC_ESHIFTLOCK,01h ; is german/french capslock down
- jz shift_test
- test_caps:
- test ah,CAPSLOCK_BIT
- jnz shift_t ; YES..
- shift_test:
- test ah,SHFT_LEFT_BIT or SHFT_RIGHT_BIT
- jz translate ; not shifted
- shift_t:
- mov bx, PC_SHIFTTABLE
- ; jmps translate ;use shift table if numlock
-
- translate:
- mov al,PC_SCAN_CODE ; use this value in case translated
-
- test PC_KBD_TYPE,NX_enhanced ; is it enhanced keyboard
- jz just_xlat1 ; no..
- cmp byte ptr PC_KBD_SCAN,29h ; original scan code
- jne test_102_a
- mov al,54 ; character position reserved for extra key
- test_102_a:
- cmp PC_KBD_SCAN,SCAN_102 ; extra key (102 keyboard)
- jne just_xlat1
- mov al,2bh ; key 102 uses old char 2bh scan code
- just_xlat1:
- cmp al,SPACE_SCAN ;; don't translate
- jne translate1
- mov al,' ' ;; space char
- jmps key_scan_ok
- translate1:
- xlat bx ; get ASCII char in AL
- cmp al, 0ffh ; is it undefined
- jne key_scan_ok ; no.....valid key
- jmp key_scan_done ; yes .... ignore
-
- key_scan_ok:
- call NX_isdkey ; check if this is a dead key
- cmp di, 0FFFFh ; no match in table
- je NX_test_2nd_dkey ; character is not a dead key
- jmp key_scan_done ; just save it for later combination
- NX_test_2nd_dkey:
- call NX_chk_dkey ; try to combine it with dead key
-
- test ah,CAPSLOCK_BIT ;test for caps lock
- jz save_msb ; no...
- cmp PC_SHIFTLOCK,FALSE ;; french keyboard flag
- jnz test_french ;; true
- test PC_ESHIFTLOCK,01h ; enhanced keyb shift lock supported ?
- jnz save_with_msb ; yes.. ignore CAPS translate
- test PC_KFLAG3,ALT_GR_BIT ; ALT GR key down ?
- jnz save_msb ; ignore case change
- call NX_case_change ; else check if case sensitive
- save_msb:
- jmps save_with_msb
-
- ;; Special test for FRENCH keyboard support
- ;; if CAPSLOCK numeric keys assume shift position
- test_french:
- ;; test alt_gr,ALT_GR_BIT ; ALT GR key down ?
- ;; jnz save_with_msb ; yes.. no further translation
-
- cmp PC_KBD_SCAN,2 ; numeric keys and '-' and '='
- jb save_with_msb ; ignore keys below 1
-
- cmp PC_KBD_SCAN,13 ; and above '+'
- ja save_with_msb
-
- mov al,PC_KBD_SCAN ; restore the scan code
- mov bx,PC_SHIFTTABLE ; assume no shift key down
- test ah,SHFT_LEFT_BIT or SHFT_RIGHT_BIT
- jz caps_xlat
- mov bx,PC_NASCIITABLE
- caps_xlat:
- xlat bx
- jmps save_with_msb
-
- turn_on_msb:
- mov ah, PC_KBD_SCAN
- mov al, PC_SCAN_CODE
- mov PC_KBD_SCAN,al
- xor al, al
- cmp ah, 2
- jb skip_alt_char
- cmp ah, 14
- jb save_with_msb ;check for alt and 1234567890-= keys
- cmp ah, 16 !
- jb skip_alt_char
- cmp ah, 26
- jb save_with_msb ;check for alt and qwertyuiop keys
- cmp ah, 30
- jb skip_alt_char
- cmp ah, 39
- jb save_with_msb ;check for alt and asdfghjkl keys
- cmp ah, 44
- jb skip_alt_char
- cmp ah, 51
- jb save_with_msb ;check for alt and zxcvbnm keys
-
- skip_alt_char:
- jmp key_scan_done
-
- save_with_msb:
- call NX_conin_xlat ; translate & check if valid
- jc key_scan_done ; eat it if invalid
-
- mov ah,PC_KBD_SCAN ; scan code value into AH
- ; char in AL
- pop dx ; clean console number off stack
- jmps ci_return
-
- ; Common exit if no character was detected
- key_scan_done:
- pop dx ; restore console number
- jmp fl_conin ; and wait for next char
-
-
-
- ; --------------------------------------------
- ; Keyboard input translated to Scan\Character.
- ci_return:
- push dx ; save dx on entry
- mov dl,PC_TOP_SCREEN ; get top vc screen
- call point_vc@ ; VC_ structure
- pop dx
- test VC_MODE,PCMODE_BIT ; if DOS pgrm.
- jnz pc_ret ; return immediately
- or al,al ; extended?
- jnz conin_ret1 ; no, just ascii...jump.
-
- cmp ah,TWO_SCAN ;If cntl @, leave it as null
- je conin_ret1
- cmp ah,TAB_SCAN ; if backtab, return FF
- jne not_bt
- mov al,FF ; for COPYMENU
- jmps conin_ret1
- not_bt:
- cmp ah,F1_SCAN ; nothing below is programmable
- jb conin_done ; no key yet
- call trans_pfk ; maybe a special CPM
- jnz conin_done
- cmp VC_PFK_EXP,0 ; if expansion is turned off
- je conin_done ; then return unexpanded key
- xchg ah,al ; pfk index to ah
- call point_pfk ; a programmable
- jmp fl_conin ; get first
- conin_done:
- or al,al
- jmpz ci_ret1 ; nothing, so wait more
-
- conin_ret1:
- sub ah,ah ; cpm spec
- pc_ret:
- ret
-
- ;-------------------
- ; CONIN subroutines
- ;-------------------
-
- case_change: ; check if we need to change lower case <-> upper case
- ;-----------
- cmp al, 'z' ; yes
- ja case_ret ; not alphabetic
- cmp al, 'a' ; is it lower case ?
- jae do_case ; yes $ switch case
- cmp al, 'Z'
- ja case_ret ; not alphabetic
- cmp al, 'A' ; test for upper case
- jb case_ret ; not alphabetic
- do_case:
- xor al, 020h ; switch the case
- case_ret:
- ret
-
-
- ; This routine takes an Extended scan code as returned from ROS and converts
- ; it to it's unexpanded CPM equivalent.
- ; USE COMMON TABLES FROM CONIN.A86 module.
- ; Entry: ah = scan, al = 0
- ; Exit: ZF = set, ah=PFK index, al=translation (w/ hi bit set)
- ; if a CPM programmable
- ; ZF = reset, ax = preserved if not
- trans_pfk:
- ;---------
- push es
- mov cx,ds
- mov es,cx ; point es here
- xchg al,ah
- mov cx,PFK_SCAN_LIST_SIZE ; how many to check
- cld
- mov di,offset pfk_scan_list$
- repne scasb ; look for it
- pop es
- jz found_scan ; found it
- xchg al,ah
- ret ; return w/ ZF = 0 if no match
-
- found_scan:
- dec di
- sub di,offset pfk_scan_list$
- mov ax,di
- mov ah,al
- mov al,pfk_code_tbl$[di] ; get the cpm code
- or al,80h ; set the high bit
- cmp al,al ; ZF = 1
- ret
-
- point_pfk:
- ;---------
- ; Point to PFK table -- fixed area in SETUP data
- ; **** cannot be changed ****
- ; entry: al = pfk table index
- ; bx -> vs_
- ; exit: VC_PFK_PTR -> pfk value
- ; VC_PFK_COUNT = maximum char count
-
- sub si,si ; zero offset for low table
- mov cl,PFK_L_SIZE ; chars per low pfk
- cmp al,LOW_PFKS ; check for low table
- jb point_pfk1 ; skip if unshifted F1-F10
- sub al,LOW_PFKS ; index into high table
- mov si,PFK_L_SIZE * LOW_PFKS ; offset for high table
- mov cl,PFK_H_SIZE ; chars per high pfk
- point_pfk1:
- mul cl ; index into high table
- add si,ax
- add si,VC_PFK_TBL ; add table offset
- mov VC_PFK_PTR,si ; set initial pointer
- mov VC_PFK_COUNT,cl ; and initial count
- cmp ax,ax ; set zero flag
- ret
-
-
- ;****************************************
- ;* National keyboard subroutines
- ;****************************************
-
- NX_init: ; initialize keyboard/screen/printer
- ;======= ; and PC structure
- ; Entry SI = PC_ ->
-
- mov al,NX_language$ ; get national language
- mov PC_LANGUAGE,al
- mov al,NX_natnlstat$
- mov PC_NATNLSTAT,al
- mov al,NX_natnlmode$
- mov PC_NATNLMODE,al
- mov dl,PC_CONS
- call get_su_mu ; get setup byte for console in AL
- test al,ENHANCED ; enhanced keyboard
- jz not_e
- mov PC_KBD_TYPE,NX_enhanced
- not_e:
- and al,NAT_MODE ; mask national bit
- mov PC_NAT,al
-
- test PC_KBD_TYPE,NX_enhanced ; enhanced serial ?
- jz n2 ; no
- test NX_kbd_type,NX_enhanced ; enhanced main console ?
- jz n3 ; no
- jmps n1
- n2:
- test NX_kbd_type,NX_enhanced ; enhanced main console
- jnz n3 ; yes
- n1:
- mov bx,offset NX_nasciitable$
- mov PC_NASCIITABLE,bx
- mov bx,offset NX_nshifttable$
- mov PC_SHIFTTABLE,bx
- mov bx,offset NX_nctrltable$
- mov PC_CTRLTABLE,bx
- mov bx,offset NX_deadtable$
- mov PC_DEADTABLE,bx
- jmps n4
- n3:
- mov bx,offset NX_pc_ascii$
- mov PC_NASCIITABLE,bx
- mov bx,offset NX_pc_shift$
- mov PC_SHIFTTABLE,bx
- mov bx,offset NX_pc_ctrl$
- mov PC_CTRLTABLE,bx
- mov bx,offset NX_pc_dead$
- mov PC_DEADTABLE,bx
- n4:
- mov al, PC_NATNLMODE
-
- NX_update_mode:
- cbw ; make it a word value
- mov bx, ax ; put it into index register
- mov al, NX_mode_table$[bx] ; get desired mode bits
- mov PC_NATNLSTAT, al ; setup new mode bits
-
- ;;; Handle the special case of FRENCH CAPSLOCK KEY which
- ;;; acts as a SHIFTLOCK by translating all the keys on the keyboard
- ;;; and not just azerty keys.
-
- NX_update_mode_done:
- mov PC_SHIFTLOCK,FALSE ; assume normal
- cmp PC_LANGUAGE,1 ; is it FRENCH system
- jnz NX_update_exit1
- test al,NX_nkbd_bit ; national keyboard support
- jz NX_update_exit1
- mov PC_SHIFTLOCK,TRUE
- NX_update_exit1:
- test PC_KBD_TYPE,NX_enhanced ; is it enchanced keyboard version
- jz NX_update_exit ; no .. normal keyboard
-
- ;; Handle special case of CAPSLOCK key on
- ;; FRENCH and GERMAN enhanced keyboard
-
- cmp PC_LANGUAGE,1 ; is it FRENCH system
- jnz test_german
- or PC_ESHIFTLOCK,01h
- test_german:
- cmp PC_LANGUAGE,2 ; is it GERMAN system
- jnz NX_update_exit
- or PC_ESHIFTLOCK,01h
-
- NX_update_exit:
- ret
-
-
- ;---------------
- NX_conin_xlat: ;translate 8 bit back to 7 bit if in 7 bit mode
- ;---------------
- ; Input: AL = char to translate
- ; SI = PC-> structure
- ; Output: AL = translated character
- ;
- cmp PC_NATNLMODE,3 ;Ctrl/Alt/F4 or F5 mode?
- jb NX_conin_xlat_done ;nothing to do if not
-
- mov bx,offset NX_n7to8chr$ ; scan thru 8 bit eqv chars
- NX_conin_loop:
- cmp byte ptr [bx], 0 ; see if end of translate tbl
- jz NX_conin_xlat_ignore ; yes, ignore if 8 bits
- cmp al,[bx] ; see if translation required
- jz NX_conin_8to7 ; yes, one of those characters
- inc bx ; no, may be next time
- jmps NX_conin_loop ; give it another try
-
- NX_conin_8to7:
- sub bx,offset NX_n7to8chr$ ; see how many chars checked
- mov al, NX_n7to8tbl$[bx] ; substitute it
-
- NX_conin_xlat_done:
- test al, al ; clear carry
- ret ; back to keyboard interrupt routine
-
- NX_conin_xlat_ignore:
- test al, al ; seven bits?
- jns NX_conin_xlat_done ; yes, return
- stc ; set carry
- ret
-
-
- NX_case_change: ; check if we need to change lower case <-> upper case
- ;----------------
- cmp al, 'z' ; yes
- ja NX_case_test ; not alphabetic
- cmp al, 'a' ; is it lower case ?
- jae do_case_change ; yes $ switch case
- cmp al, 'Z'
- ja NX_case_test ; not alphabetic
- cmp al, 'A' ; test for upper case
- jb NX_case_test ; not alphabetic
- do_case_change:
- xor al, 020h ; switch the case
- ret
-
- NX_case_test:
- ;--------------
- mov cl, al
- mov di, offset NX_ncasetbl$
- call NX_scanstr
- cmp di, 0FFFFh
- je NX_no_case_change
- xor di, 1 ; lower < --- > upper
- mov al, NX_ncasetbl$[di] ; pick up the other
- NX_no_case_change:
- ret
-
-
- NX_isdkey: ; check if character is a dead key
- ;----------- ; AH = Shift state
- ; SI = PC->
- mov di, -1 ; assume no dead key
- ; test ah, CTRL_BIT+ALT_BIT
- ; jnz NX_no_dkey
- cmp PC_NATNLMODE, 1 ; Ctrl/Alt/F2 mode?
- jne NX_no_dkey ; (others don't support dead keys)
- cmp al,'~'
- je is_dead
- mov cl,al
- mov di,offset NX_dead_ascii$
- call NX_scanstr
- cmp di, -1
- je NX_no_dkey
- is_dead:
- mov cl, PC_KBD_SCAN
- test PC_ESHIFTLOCK,01h ; is german/french capslock down
- jz shift_test3
- test ah,CAPSLOCK_BIT
- jnz shift_t3 ; YES..
- shift_test3:
- test ah, SHFT_LEFT_BIT or SHFT_RIGHT_BIT
- jz NX_isdkey_noshift
- shift_t3:
- or cl, 80H
- NX_isdkey_noshift:
- mov di, PC_DEADTABLE
- call NX_scanstr
- cmp di, -1
- je NX_no_dkey
- mov PC_LAST_DKEY, di
- mov cl,PC_KBD_SCAN
- mov PC_DKEY_SCAN,cl
- NX_no_dkey:
- ret
-
-
- NX_chk_dkey:
- ;-------------
- ; entry: al = character to combine with previous dead key
- ; SI = PC->
- ; exit: al = combined character
-
- mov di, PC_LAST_DKEY
- cmp di, -1
- je NX_chk_dkey_done
- mov cl, al
- shl di, 1
- mov di, NX_dkeyv$[di]
- call NX_scanstr
- cmp di, -1
- je NX_bad_dkey
-
- mov bx, PC_LAST_DKEY
- shl bx, 1
- mov bx, NX_dkeyx$[bx]
- mov al, [bx+di]
- jmps NX_chk_dkey_done
-
- NX_bad_dkey:
- mov cl,PC_DKEY_SCAN ; swap old and new scan codes
- xchg cl,PC_KBD_SCAN
- mov PC_DKEY_SCAN,cl
- mov di,PC_LAST_DKEY
- cmp al, ' ' ; DEADKEY + ' ' --> DEAD
- je NX_dkey_blank ; don't return 2nd char if blank
- mov PC_DKEY_BUFF,al ; else save second character
- NX_dkey_blank:
- test di, di ; (has index zero)
- jnz NX_chk_space
- mov al,0f9h ; insert IBM decimal point char
- jmps NX_chk_dkey_done
- NX_chk_space:
- mov al, NX_dead_key$[di]
- NX_chk_dkey_done:
- mov PC_LAST_DKEY, -1
- ret
-
-
-
- NX_xlt_7to8: ; translate 7 to 8 bit code
- ;-------------
- ; entry: cl = character to translate
- ; SI = PC->
- ; exit: cl = translated character
-
- push bx ; keep every register safe
- cmp PC_NATNLMODE,3 ; 7 bit, nat scn, nat kbd?
- jne NX_xlt78_not_xlt ; not Ctrl/Alt/F4 mode
-
- mov bx,offset NX_n7to8tbl$ ; scan thru 7 bit eqv chars
- NX_xlt78_loop:
- cmp byte ptr [bx],0 ; see if end of translate tbl
- jz NX_xlt78_not_xlt ; yes, check for paragraph
- cmp cl,[bx] ; see if translation required
- jz NX_xlt78_7to8 ; yes, one of those characters
- inc bx ; no, may be next time
- jmps NX_xlt78_loop ; give it another try
-
- NX_xlt78_7to8:
- sub bx,offset NX_n7to8tbl$ ; see how many chars checked
- mov cl,NX_n7to8chr$[bx] ; get substitution
-
- NX_xlt78_not_xlt:
- pop bx
- ret
-
-
- NX_scanstr: ; search for a character in a table
- ;------------
- ; entry: cl = character to look for
- ; di = address of string to search
- ; exit: cl = unmodified
- ; di = relative position of cl in string if match
- ; di = 0xffff if no match
-
- push ax ; save our scratch register
- mov ax, di ; save table in ax
- NX_scanstr_loop:
- cmp byte ptr [di], 0 ; end of string?
- je NX_scanstr_nomatch ; yes, definitly no match
- cmp cl, [di] ; match with character
- je NX_scanstr_match ; yes, found it
- inc di ; no, next character
- jmps NX_scanstr_loop ; another try...
-
- NX_scanstr_nomatch:
- mov di, 0ffffh ; get failure code
- jmps NX_scanstr_done ; return it
- NX_scanstr_match:
- sub di, ax ; offset to start of string
- NX_scanstr_done: ; return code
- pop ax ; restore scratch register
- ret
-
-
- ;----------------
- NX_conout_xlat:
- ;----------------
- ; Input: AL = character to translate
- ; SI = PC->
- ; Output: AL = translated character
- ; all others maintained
-
- push bx ; keep every register safe
- cmp PC_NATNLMODE, 3 ; 7 bit, nat scn, nat kbd?
- jne NX_conout_not_xlt ; not Ctrl/Alt/F4 mode
- cmp PC_TMP_US_FLG, 0 ; temparaily 7/8 xlt off
- mov PC_TMP_US_FLG, 0 ; reset temporary US display
- jnz NX_conout_not_xlt ; leap if disabled
-
- mov bx, offset NX_n7to8tbl$ ; scan thru 7 bit eqv chars
- NX_conout_loop:
- cmp byte ptr [bx], 0 ; see if end of translate tbl
- jz NX_conout_not_xlt ; yes, check for paragraph
- cmp al, [bx] ; see if translation required
- jz NX_conout_7to8 ; yes, one of those characters
- inc bx ; no, may be next time
- jmps NX_conout_loop ; give it another try
-
- NX_conout_7to8:
- sub bx, offset NX_n7to8tbl$ ; see how many chars checked
- mov al, NX_n7to8chr$[bx] ; get substitution
-
- NX_conout_not_xlt:
- cmp al, 236 ; this is how we store para
- jne NX_conout_not_para ; not paragraph char
- mov al, 21 ; IBM sez: paragraph = Ctrl/U
- NX_conout_not_para:
- pop bx
- ret ; back to display routine
-
-
-
- eject
-
- ; Serial Console output - XIOS function 2
- ; Entry :
- ; DL = virtual console number
- ; CL = output char
- fl_io_conout:
- ;------------
- cmp dl,NUM_VIR_CONS ; master console ?
- jb do_conout
- cmp dl,MAX_VIR_CONS ; is it legal ?
- jb fl_conout_test
- do_conout:
- jmp io_conout
-
- dumb_conout:
- ; we used to call io_conout with the virtual console number. This only
- ; worked when previous serial terminals had only one virtual per physical.
- ; (Windows1.A86 calculates the AUX device by subtracting NUM_VIR_CONS-1).
- ; NB. Will screw up with SR when we combine because we test for Sunriver
- ; station using the VCon number, which is now wrong.
- add al,NUM_VIR_CONS-1 ;
- mov dl,al ; VC number for dumb terminals
- jmp io_conout
-
- fl_conout_test:
- push dx ; save vs
- call get_ccb ; di -> ccb
- mov dl,C_PC[di] ; logical console number
- call test_pcterm@ ; test if emulation required
- mov al,dl ; save logical physical number
- pop dx
- jz dumb_conout ; must be dumb terminal
-
- fl_conout:
- ;---------
- call point_vc@ ; BX -> screen structure
- test VC_INSTALLED,0ffh ; flush installed yet
- jnz fl_conout1
- cmp active_vc$,dl
- je fl_conout1
-
- push dx ! push cx
- call delay1 ; no wait...
- pop cx ! pop dx
- jmps fl_conout
-
- fl_conout1:
- call get_mx ; make sure we get the MX
- push es
- mov dx,PC_SEGMENT ; make sure cursor reflects ROS value
- mov es,dx
- mov dx,es:cursor_posn_40 ; assume page zero
- pop es
- call pc_point_curs@
- mov VC_OFFSET,ax
- mov VC_CURSOR,dx ; cursor row, column
- mov al,cl ; AL, CL = character
- push bx
- call VC_VECTOR
- pop bx
- push es
- mov ax,PC_SEGMENT ; make sure cursor reflects ROS value
- mov es,ax
- mov ax,VC_CURSOR ; finally update ROS values
- mov es:cursor_posn_40,ax ; assume page zero
- pop es
- mov VC_MX,0 ; release semaphore
- ret
-
-
-
- eject
-
- ; List output status - XIOS function 2
- ; Entry :
- ; DL = list device number
- ; Exit :
- ; AL = output status
- fl_io_listst:
- ;------------
- call test_pcterm_printer@ ; is it a PC terminal ?
- jnz fl_listst ; yes, handle differently
- jmp io_listst
-
- fl_listst:
- mov bl,dl
- mov bh,0 ; BX = list device #
- sub bx,3 ; BX = serial port
- mov dl,port2pc_table$[bx] ; DL = logical physical console number
- call conout_serial_stat@ ; get output status of the serial port
- mov ah,10h ; assume not ready
- test al,al
- jz fl_listst1
- mov ah,90h ; device ready, PC Style
- fl_listst1:
- ret
-
- eject
-
- ; List output - XIOS function 4
- ; Entry :
- ; DL = list device number
- ; CL = output char
- fl_io_list:
- ;------------
- call test_pcterm_printer@ ; is it a PC terminal ?
- jnz fl_list ; yes, handle specially
- jmp io_list
-
- fl_list:
- ; entry: CL = character to write
- ; DL = list device number
- ; send the character to the aux port of the PC Terminal using an Escape
- ; sequence.
- ; NOTE:-
- ; ESCAPE chars are blocked into pairs because of problem on Wyse 60's
- ; Still potential problem printing string:- 1Bh,61h
-
- push cx
- mov bl,dl
- mov bh,0 ; BX = list device #
- sub bx,3 ; BX = serial port
- mov dl,port2pc_table$[bx] ; DL = logical physical console number
- fl_list1:
- push dx
- call conout_serial_stat@ ; get output status of the serial port
- pop dx
- test al,al ; is it ready ?
- jnz fl_list2
- push dx
- mov cx,P_DELAY ; delay until it is
- mov dx,1
- call supif@
- pop dx
- jmps fl_list1
- fl_list2:
- mov al,dl ; AL = logical physical console number
- call point_pc1@ ; get pointer to PC_ structure in SI
- pop cx
- cmp cl,ESC ; lets block up escape sequences
- jne send_on
- xchg cl,PC_LASTCHAR
- cmp cl,0
- jne send_on ; CL=ESC
- ret
-
- send_on:
- push cx ; save the char
- call ser_mx ; get serial semaphore
- mov di, offset printer_on ; turn on printer
- call ser_write
-
- mov al,PC_LASTCHAR
- mov PC_LASTCHAR,0 ; clear ESCAPE flag
- cmp al,0
- je ship_1
- call tmp_write ; write out ESCAPE char in AL
- pop ax ; get original character
-
- push ax ; and re-save
- mov di, offset printer_off ; turn off printer
- cmp al,2[di] ; is it OFF escape sequence
- jne ship_1
- call ser_write ; yes - turn printer off
- mov di, offset printer_on ; and then back on
- call ser_write
-
- ship_1:
- pop ax ; recover character to write in AX
- call tmp_write ; write out one character
- mov di, offset printer_off ; turn off printer
- call ser_write
- mov PC_BUSY,0 ; release serial semaphore
- mov cl,P_DISPATCH ; dispatch to give the screen a chance
- jmp supif@
-
- ; Print last caharcter if one outstanding
- ; Called from io_close
- ; Enter DL = LIST device number
- print_lastchar@:
- ;---------------
- mov bl,dl
- mov bh,0 ; BX = list device #
- sub bx,3 ; BX = serial port
- mov dl,port2pc_table$[bx] ; DL = logical physical console number
- mov al,dl ; AL = logical physical console number
- call point_pc1@ ; get pointer to PC_ structure in SI
- xor al,al
- xchg al,PC_LASTCHAR
- cmp al,0
- je print_exit
- push ax ; save last char
- push si
- print1:
- push dx
- call conout_serial_stat@ ; get output status of the serial port
- pop dx
- test al,al ; is it ready ?
- jnz print2
- push dx
- mov cx,P_DELAY ; delay until it is
- mov dx,1
- call supif@
- pop dx
- jmps print1
- print2:
- pop si
- call ser_mx ; get serial semaphore
- mov di, offset printer_on ; turn on printer
- call ser_write
-
- pop ax ; recover character to write in AX
- call tmp_write ; write out one character
- mov di, offset printer_off ; turn off printer
- call ser_write
- mov di, offset printer_off ; turn off printer twice "Wyse 60"
- call ser_write
- mov PC_BUSY,0 ; release serial semaphore
- print_exit:
- ret
-
-
- ; Enter DL = LIST device number
- test_pcterm_printer@:
- ;-------------------
- push cx ; save char
- push dx ; and device
- mov bl,dl
- mov bh,0 ; BX = list device #
- sub bx,3 ; BX = serial port number
- test mu_com_type$[bx],01 ; is it set up for terminal
- jz is_print
- mov al,su_mu_vs$[bx] ; get setup byte for serial port
- test al,PCTERM_EMU ; test setup bit for installed port
- is_print:
- pop dx
- pop cx
- ret ; to see if pcterm emulation required
-
-
-
-
- ; Screen switch - XIOS function 7
- ; Entry:
- ; DL = virtual console to switch to
- fl_io_switch:
- ;------------
- cmp dl,NUM_VIR_CONS ; master console ?
- jae fl_switch
- jmp io_switch ; yes .. go to standard routine
-
-
- fl_switch:
- ;---------
- call point_pc ; get PC_ structure
- mov bl,PC_TOP_SCREEN ; get current top VC
- xor bh,bh
- shl bx,1
- mov bx,ccb_list$[bx] ; get top screen ccb
- test C_STATE[bx],CSM_NOSWITCH ; switch allowed ?
- jnz no_switch ; no...
- push dx
- push si
- call get_all_mxs ; block all updates
- pop si
- pop dx
- call point_vc@ ; new vc's VC_ structure
- and VC_MODE,not MATCH_BIT ; full screen on top
- xchg dl,PC_TOP_SCREEN ; new top screen
- call point_vc@ ; old VC_ structure
- or VC_MODE,MATCH_BIT ; background old screen
- cli ; stop Flush being dispatched in
- push si
- mov al,PC_TOP_SCREEN ; new vc number to AL
- call find_flush_pin ; find flush and PIN pd's and patch
- pop si ; vc number
- mov dl,PC_TOP_SCREEN ; new vc number
-
- call point_vc@ ; new VC_
- or VC_UPDATE,UPDATE_SL ; we will want a statline update
- test VC_MODE,CURSOR_BIT
- jz switch_cursor_off
- call cursor_on ; make sure cursor turned on
- jmps switch1
- switch_cursor_off:
- call cursor_off ; or off
- switch1:
- lea di,VC_PAGE_SAVE ; get saved entry for screen segment
- or ds:PG_ATTR,PGA_DIRTY ; set it to dirty - FLUSH will
- ; then update our screen for us
- mov bx,v386_ptr$ ; get pointer to 386 specific table
- mov es,ptbl_seg ; get page table segment
- mov di,(CRT_SEG/256*4) ; get entry for screen segment
- or PG_ATTR,PGA_DIRTY ; make sure screen is set dirty
- ; when it next gets dispatched
- sti
- call free_all_mxs
- no_switch:
- ret
-
- ; Find current vc's FLUSH and PIN process descriptors
- ; and patch VC number to new VC
- ; Entry:
- ; DL = VC of current flush
- ; AL = new VC number
- ; Exit:
- ; BX = PD of flush rsp
- find_flush_pin:
- ;--------------
- push es
- mov ah,2 ; for PIN and FLUSH search
- mov bx,thrdrt$ ; search through thread list
- push ds ! pop es ; for FLUSH process
- find_flush1:
- cmp dl,P_CONS[bx] ; is process same VC number
- jne get_next
- lea di,P_NAME[bx] ; point to process name
- mov si,offset flushstr
- mov cx,5
- repe cmpsb ; is it 'Flush'
- jne not_flush ; no .. try PIN
- mov P_CONS[bx],al ; change flush rsps' vc number
- dec ah
- jz found_both
- not_flush:
- lea di,P_NAME[bx] ; point to process name
- mov si,offset PINstr
- mov cx,3
- repe cmpsb ; is it 'PIN'
- jne get_next ; no try next
- mov P_CONS[bx],al ; change flush rsps' vc number
- dec ah
- jz found_both
- get_next:
- mov bx,P_THREAD[bx] ; link to next PD
- or bx,bx
- jnz find_flush1 ; keep searching
- found_both:
- pop es
- ret
-
-
-
- ; Status line update - XIOS function 8
- fl_io_statline:
- ;--------------
- push cx
- push dx
- mov bx,rlr$ ; get pd
- mov dl,P_CONS[bx] ; get process VC number
- call get_ccb ; di -> ccb
- mov dl,C_PC[di] ; logical console number
- cmp dl,0 ; main screen
- je fl_statline_norm
- call test_pcterm@ ; test if emulation required
- jz fl_statline_dumb ; must be dumb terminal
-
- fl_statline_norm:
- pop dx
- pop cx
- jmp io_statline ; else call master statline
-
- fl_statline_dumb:
- ;---------------
- pop dx
- pop cx
- sub ax,ax ; status update - do nothing for now
- mov bx,ax
- ret
-
-
- ; Keyboard mode switch - XIOS function 32
- ; entry: dl = vcons number
- ; cl = following Bits used
- ; Bit 0 : = set when DOS program executes
- ; reset on termination
- ; Bit 1 : = process requires 25 lines
- ; Bit 2 : = process uses ANSI escape sequences
- ; Bit 3 : = process uses Ros INT 10h
- ; Bit 4 : = process accesses PC video hardware
- ;
-
- fl_pc_kbd:
- ;---------
- cmp dl,NUM_VIR_CONS ; master console ?
- jae fl_pckbd_test
- pc_kbd_dumb:
- jmp pc_kbd
-
- fl_pckbd_test:
- push dx ; save vs
- call get_ccb ; di -> ccb
- mov dl,C_PC[di] ; logical console number
- call test_pcterm@ ; test if emulation required
- pop dx
- jz pc_kbd_dumb ; must be dumb terminal
-
-
- fl_pckbd:
- ;--------
- call point_vc@ ; BX -> screen structure
- test cl,1 ; PC mode or CP/M mode?
- jnz keybd_pc ; skip if switching into DOS
- call get_mx ; make sure we get the MX
- mov dx,VC_CURSOR
- call vc_out_lf@ ; do a line feed
- mov dx,VC_CURSOR
- call z_up@ ; back up again
- mov dx,VC_CURSOR
- call z_erase_eos@ ; erase end of screen
- mov VC_CRT_ROWS,CRT_ROWS_C ; back to 24 lines
- and VC_MODE,not PCMODE_BIT ; turn off PC mode bit
- mov VC_CUR_TYPE,MONO_CURSOR
- or VC_MODE,CURSOR_BIT
- call cursor_on ; make sure cursor turned on
- mov VC_MX,0 ; release the MX
- mov sl_pc_flag$,0ffh ; turn on the status
- jmps keybdf_ret
-
- keybd_pc: ; switch into DOS mode
- or VC_MODE,PCMODE_BIT
- mov al,CRT_ROWS_C ; assume 24 lines
- test cl,CA_25LINES ; do we require 25 line mode
- jz set_lines ; no
- mov sl_pc_flag$,0h ; turn off status
- push VC_CURSOR ; save the current cursor position
- mov dx,CRT_ROWS_C*256 ; start of bottom line
- call pc_point_curs@
- mov VC_OFFSET,ax ; set cursor position there
- mov VC_CURSOR,dx
- call z_erase_eos@ ; erase end of screen
- pop dx ; now restore cursor
- call pc_point_curs@
- mov VC_OFFSET,ax ; remember offset too
- mov VC_CURSOR,dx
- mov al,CRT_ROWS_P ; set 25 lines
- set_lines:
- mov VC_CRT_ROWS,al
-
- keybdf_ret:
- sub ax,ax
- ret
-
-
- ; Return keyboard shift status - XIOS function 33
- ; entry: dl = vcons number
- ; exit: SI = PC_ pointer for VC
- ; *** SI returned for utility purposes ***
- ; Returns shift byte in AL:
- ; extended keyboard shift status in AH
-
- fl_pc_shifts:
- ;------------
- cmp dl,NUM_VIR_CONS ; master console ?
- jae fl_shifts_test
- pc_shifts_dumb:
- jmp pc_shifts
-
- fl_shifts_test:
- call get_ccb ; di -> ccb
- mov dl,C_PC[di] ; logical console number
- call test_pcterm@ ; test if emulation required
- jz pc_shifts_dumb ; must be dumb terminal
- mov al,dl ; logical console number
- call point_pc1@ ; get PC_ ->
-
- mov ch,0
- test PC_NATNLSTAT,NX_nkbd_bit ; is it US keyboard
- jz norm_kbd ; yes...
- test PC_KBD_TYPE,NX_enhanced ; international enchanced keyboard
- jz norm_kbd ; no .. normal keyboard
- mov ch,1
- norm_kbd:
- mov ah,PC_KFLAG1
- and ah,SYS_SHIFT
- mov cl,5
- shl ah,cl
- mov al,PC_KFLAG1
- and al,73h ; get rid of sys_shift,hold and insert
- or ah,al ; mash into AH
- mov al,PC_KFLAG3 ; get extended status bits
- and al,0ch ; remove hidden flag bits
- or ah,al ; and merge
-
- mov al,PC_KFLAG ; get normal status bits into al
- or ch,ch
- jz norm_kbd1
- test PC_KFLAG1,L_ALT ; is left ALT down
- jnz norm_kbd1 ; yes
- and al,not ALT_BIT ; else make sure no ALT status
- norm_kbd1: ; bit from Right ALT key
- ret
-
-
-
-
- ; XIOS function 39: Device Block Read/Write
- ; Entry: DH = device type:
- ; 0 = console output
- ; 1 = printer output
- ; 2 = aux. input
- ; 3 = aux. output
- ; DL = device number:
- ; CX = number of characters
-
- ; Param. block at SP + 6:
- ; word ptr 6[bp] = buffer offset
- ; word ptr 8[bp] = buffer segment
- ; word ptr 10[bp] = same as CX
- ; word ptr 12[bp] = same as DX
-
- ; Exit: AX = number of characters transferred (at least 1)
- ; Updated Param. block on stack
- ; buff. off. = last char + 1
- ; buff. seg. = unchanged
- ; count = # remaining in block (usually 0)
- ; dev. info = unchanged
-
-
- fl_io_devio:
- ;-----------
- cmp dh,0 ; console output
- jne fl_io_devio1 ; no..
- cmp dl,NUM_VIR_CONS ; master console ?
- jae fl_devio_test ; no must be serial
- fl_io_devio1:
- cmp dh,1
- je fl_devio_list
- jmp io_devio
-
- fl_io_devio_dumb:
- ; we used to call io_conout with the virtual console number. This only
- ; worked when previous serial terminals had only one virtual per physical.
- ; (Windows1.A86 calculates the AUX device by subtracting NUM_VIR_CONS-1).
- ; NB. Will screw up with SR when we combine because we test for Sunriver
- ; station using the VCon number, which is now wrong.
- add al,NUM_VIR_CONS-1 ;
- mov dl,al ; logical console number for dumb terms
- jmp io_devio
-
- fl_devio_test:
- push dx ; save vs
- call get_ccb ; di -> ccb
- mov dl,C_PC[di] ; logical console number
- call test_pcterm@ ; test if emulation required
- mov al,dl ; save logical physical number
- pop dx
- jz fl_io_devio_dumb ; must be dumb terminal
-
- fl_devio:
- ;--------
- mov bp,sp
- cmp word ptr 10[bp],0
- je devio_ret
- push ds
- lds si,6[bp] ; get output buffer address
- lodsb
- pop ds
- mov 6[bp],si ; update buffer offset
- dec word ptr 10[bp] ; decrement char output count
- mov cl,al ; char to CL
- push dx ; save VC number
- call fl_conout ; output char
- pop dx
- jmps fl_devio
- devio_ret:
- ret
-
- fl_devio_list:
- ;----------------
- mov bp,sp
- cmp word ptr 10[bp],0
- je devio_ret
- push ds
- lds si,6[bp] ; get output buffer address
- lodsb
- pop ds
- mov 6[bp],si ; update buffer offset
- dec word ptr 10[bp] ; decrement char output count
- mov cl,al ; char to CL
- push dx ; save device number
- call fl_io_list ; output char
- pop dx
- jmps fl_devio_list
-
- eject
-
-
- ; This function handles Int 10h calls from PC DOS applications.
- video_int:
- ;---------
- sti
- push ds
- mov ds,cs:sysdat$
- push di
- mov di,rlr$
- cmp P_CONS[di],NUM_VIR_CONS
- jae vid_int1_test ; filter out serial consoles
- vid_int_dumb:
- pop di
- pop ds
- jmpf cs:dword ptr int10_addr ; go to standard XIOS handler
-
- vid_int1_test:
- push dx ; save dx
- mov dl,P_CONS[di] ; get VC number
- call get_ccb ; di -> ccb
- mov dl,C_PC[di] ; logical console number
- call test_pcterm@ ; test if emulation required
- pop dx
- jz vid_int_dumb ; must be dumb terminal
-
-
- vid_int1:
- cld
- push si
- push bx ; extra for temp store
- push es
- push bp ! push bp
- push dx ! push cx ! push bx ! push ax
- mov bp,sp
-
- mov di,rlr$ ; get calling process
- mov dl,P_CONS[di] ; get its virtual console #
- mov VID_VCONS[bp],dl ; set virtual console
-
- call point_vc@ ; get virtual console structure
- call get_mx ; get screen semaphore
- mov ax,PC_SEGMENT ; make sure cursor reflects ROS value
- mov es,ax
- mov ax,es:cursor_posn_40 ; assume page zero
- mov VC_CURSOR,ax ; cursor row, column
- mov al,VID_AH[bp] ; get video function
- cmp al,15 ; supported range
- ja v_i_exit ; ignore if above
-
- cbw ; make it a word
- mov di,ax ; DI = sub function #
- shl di,1 ; entry into word table
- call v_i_table[di] ; invoke subfunction
-
- v_i_exit:
- mov ax,PC_SEGMENT ; make sure cursor reflects ROS value
- mov es,ax
- mov ax,VC_CURSOR ; finally update ROS values
- mov es:cursor_posn_40,ax ; assume page zero
- mov VC_MX,0 ; release semaphore
-
- pop ax ! pop bx ! pop cx ! pop dx
- pop bp ! pop bp ; restore all registers
- pop es
- pop bx ; temp store
- pop si ! pop di
-
- pop ds ; back to user data segment
- iret
-
-
- v_i_table dw v_i_smode ; 0 set video mode
- dw v_i_cursortype ; 1 set cursor type
- dw v_i_setcursor ; 2 set cursor position
- dw v_i_getcursor ; 3 get cursor position
- dw v_i_lpen ; 4 read light pen
- dw v_i_spage ; 5 select display page
- dw v_i_scroll_up ; 6 scroll window up
- dw v_i_scroll_down ; 7 scroll window down
- dw v_i_read ; 8 get attr/char at cursor
- dw v_i_write_attr ; 9 set attr/char at cursor
- dw v_i_write_char@ ; 10 set char (curr.attr) @ cur
- dw v_i_ignore ; 11 pallette / border control
- dw v_i_ignore ; 12 graphics pix write
- dw v_i_ignore ; 13 graphics pix read
- dw v_i_write_tty ; 14 write char stream as a tty
- dw v_i_gmode ; 15 current video state
-
- v_i_ignore:
- ;----------
- ret
-
- v_i_smode: ; 0 set video mode
- ;---------
- ; Entry: VID_AL = new video mode
- ;
- ; Modes: 0, 1: 40x25 16 color (CGA, EGA, MCGA, VGA)
- ; 2, 3: 80x25 16 color (CGA, EGA, MCGA, VGA)
- ; 4, 5: 320x200 4 color (CGA, EGA, MCGA, VGA)
- ; 6: 640x200 2 color (CGA, EGA, MCGA, VGA)
- ; 7: 80x25 monochrome (MDA, EGA, VGA)
- ; 8-C: -not supported- (-PC jr only-)
- ; D: 320x200 16 color (EGA, VGA)
- ; E: 640x200 16 color (EGA, VGA)
- ; F: 640x350 monochrome (EGA, CGA)
- ; 10: 640x350 16 color (EGA, VGA)
- ; 11: 640x480 monochrome (EGA, CGA)
- ; 12: 640x480 16 color (EGA, VGA)
- ; 13: 320x200 256 color (MCGA, VGA)
- ; 40: 640x400 2 color (Olivetti M24/M28)
- ; 48: 640x400 2 color (Olivetti M24/M28)
- ;
-
- mov al,VID_AL[bp] ; get video mode
- cmp al,7
- je v_i_smode1 ; is it an 80x25 mode
- cmp al,2 ; if so force a switch to
- je v_i_smode1 ; mode 7 (80x25 monochrome)
- cmp al,3
- je v_i_smode1
- mov VC_MX,0 ; release semaphore
- mov ax,offset bad_mode_msg
- mov cx,BAD_MODE_MSG_LEN
- jmp proc_abort@ ; terminate with an error msg
-
- v_i_smode1:
- mov VID_AL[bp],7 ; force to mode 7
- or VC_BLINK,20h ; always re-enable blink attribute
- sub di,di
- mov cx,CRT_ROWS_P*CRT_COLS
- mov ax,' '+(7 shl 8)
- jmp put_crt_s@
-
- v_i_cursortype: ; 1 set cursor type
- ;--------------
- ; Entry: VID_CH, VID_CL = cursor type
-
- mov cx,VID_CX[bp] ; get new cursor type
- mov VC_CUR_TYPE,cx ; save the new cursor
- test ch,60h ; setting bits 5 or 6 turns cursor off
- jnz v_i_off
- and ch,0fh ; mask start cursor line
- and cl,0fh ; and end
- cmp ch,cl ; if start > end
- ja v_i_off ; then turn cursor off
- jmp z_cursor_on ; else make sure cursor ON
- v_i_off:
- jmp z_cursor_off
-
- v_i_setcursor: ; 2 set cursor position
- ;-------------
- ; Entry: VID_DH, _DL = row, column
- ; VID_BH = page number (ignored by us)
-
- mov dx,VID_DX[bp]
- cmp dh,VC_CRT_ROWS
- jb pc_v_row_ok ; if row is too big
- mov dh,VC_CRT_ROWS ; then clip it
- dec dh
- pc_v_row_ok:
- cmp dl,VC_WIDTH
- jb pc_v_col_ok ; if column is too big
- mov dl,VC_WIDTH ; then clip it
- dec dl
- pc_v_col_ok:
-
- call pc_point_curs@
- mov VC_OFFSET,ax
- mov VC_CURSOR,dx
- ret
- ;; jmp put_cursor@ ; (updates VC_CURSOR as well)
-
- v_i_getcursor: ; 3 get cursor position
- ;-------------
- ; Entry: VID_BH = page number (ignored by us)
- ; Exit: VID_DH, VID_DL = cursor row, column
- ; VID_CH, VID_CL = current cursor type
-
- mov ax,VC_CURSOR
- mov VID_DX[bp],ax
- mov ax,VC_CUR_TYPE
- mov VID_CX[bp],ax
- ret
-
- v_i_lpen: ; 4 - read light pen position
- ;--------
- ; Exit: VID_AH = 0
-
- mov VID_AH[bp],0 ; say light pen not triggered
- ret
-
-
- v_i_spage: ; 5 - select active page
- ;---------
- ; Entry: VID_AL = new display page
-
- ret ; -not supported-
-
-
- v_i_scroll_up: ; 6 scroll rectangle up
- ;-------------
- ; Entry: VID_AL = # of lines to scroll
- ; 0 = clear entire rectangle
- ; VID_CH, VID_CL = top left corner of rectangle
- ; VID_DH, VID_DL = bottom right corner of rectangle
- ; VID_BH = attribute for spaces scrolled in
-
- mov dx,VID_CX[bp] ; top left corner to start
- call pc_point_curs@ ; di -> top left corner
- call pc_video_count ; move, erase and column counts
- jc pc_v_scroll_exit ; quit on illegal box
-
- mov al,VC_WIDTH ; next row down
- cbw ! shl ax,1
- jmps pc_v_move_erase ; shared routine from here
-
- v_i_scroll_down: ; 7 scroll window down
- ;---------------
- ; Entry: VID_AL = # of lines to scroll
- ; 0 = clear entire rectangle
- ; VID_CH, VID_CL = top left corner of rectangle
- ; VID_DH, VID_DL = bottom right corner of rectangle
- ; VID_BH = attribute for spaces scrolled in
-
- mov dh,VID_DH[bp] ; bottom row
- mov dl,VID_CL[bp] ; left column
- call pc_point_curs@ ; di -> bottom left corner
- call pc_video_count ; move, erase and column counts
- jc pc_v_scroll_exit ; quit on illegal box
-
- mov al,VC_WIDTH ; next row down
- cbw ! shl ax,1 ! neg ax
- ; jmps pc_v_move_erase ; shared routine from here
-
- pc_v_move_erase:
- ; Shared code for scroll up and down:
- ; entry: ax = + or - chars per crt row
-
- push ax ; save row increment
- imul VID_DX[bp] ; ax = move offset
- mov si,di
- add si,ax ; si -> move source
- pop dx ; dx = row increment
-
- cmp VID_CX[bp],0 ; if no moves to do
- jz pc_v_erase_loop ; then just erase
-
- pc_v_move_loop:
- mov cx,VID_AX[bp] ; get column count
- push si ! push di ; save line pointers
- call z_movsw@ ; move one screen line
- pop di ! pop si
- add si,dx ; next source line
- add di,dx ; and next destination
- dec VID_CX[bp] ; move countdown
- jnz pc_v_move_loop
-
- pc_v_erase_loop:
- mov cx,VID_AX[bp] ; get column count
- mov al,' ' ; erase to a blank
- mov ah,VID_BH[bp] ; pick up the attribute
- push dx ! push di
- call erase_pc@ ; erase one line
- pop di ! pop dx
- add di,dx ; next line to erase
- dec VID_DX[bp] ; erase countdown
- jnz pc_v_erase_loop
-
- pc_v_scroll_exit:
- ret
-
-
- pc_video_count:
- ;--------------
- ; calculate move, erase and column counts
- ; exit: VID_DX[bp] = erase count
- ; VID_CX[bp] = move count
- ; VID_AX[bp] = column count
- ; - or -
- ; cf set on illegal box
-
- mov al,VID_DH[bp] ; bottom row
- sub al,VID_CH[bp] ; minus top row
- jc pc_count_exit ; if negative, forget it
-
- cbw ! inc ax ; ax = # of rows in box
- mov dx,ax ; dx = default erase count
- sub cx,cx ; default move count = 0
- sub al,VID_AL[bp] ; subtract lines to scroll
- jbe pc_count_erase ; if too much, just erase
- cmp VID_AL[bp],0 ; if al = 0, just erase
- jz pc_count_erase
-
- mov cx,ax ; cx = move count
- sub dx,ax ; dx = erase count
- pc_count_erase:
- mov al,VID_DL[bp] ; right column
- sub al,VID_CL[bp] ; minus left column
- jc pc_count_exit ; if negative, forget it
-
- cbw ! inc ax ; ax = column count
- mov VID_DX[bp],dx ; save the move count
- mov VID_CX[bp],cx ; the erase count and
- mov VID_AX[bp],ax ; column count in the stack
- clc ; all is well
- pc_count_exit:
- ret
-
-
-
- pc_video_ret:
- ret
-
-
- v_i_read: ; 8 get attr/char at cursor
- ;--------
- ; Entry: VID_BH = page number (ignored by us)
- ; Exit: VID_AL = character read
- ; VID_AH = attribute read (undefined if graphics)
-
- mov dx,VC_CURSOR
- call get_char_attr ; call into common routine
- jmps ret_char_attr
-
- get_char_attr: ; entry point from subfunction 14
- ; to get current attribute
- call pc_point_curs@ ; di -> cursor dest
- push es
- mov es,VC_CRT_SEG
- mov ax,es:[di] ; no hurry here
- pop es
- ret_char_attr:
- mov VID_AX[bp],ax
- ret
-
-
-
- v_i_write_attr: ; 9 set attr/char at cursor
- ;--------------
- ; Entry: VID_BH = page number (ignored by us)
- ; VID_AL = character to write
- ; VID_BL = attribute (text)/xor flag (graphics)
- ; VID_CX = repeat count
-
- test VC_MODE,MATCH_BIT ; top screen ?
- jnz v_i_wr_at1 ; no
- call wait_sync ; wait for synchronized screen
- call get_point_pc ; get pointer to physical screen struc.
- call ser_mx ; lock out serial I/O
- mov ax,VC_CURSOR
- call set_pcursor ; make sure cursor in right place
- mov cx,VID_CX[bp] ; get repeat count
- mov ah,VID_BL[bp] ; get attribute
-
- v_i_wr_at_loop:
- push ax
- call do_char_attrib ; output character attribute
- pop ax
- loop v_i_wr_at_loop
- mov PC_BUSY,00h ; release serial semaphore
-
- v_i_wr_at1:
- sub si,si ; call the following
- call xlat_esc ; code w/o setting dirty bit
- mov al,VID_AL[bp] ; get character
- mov ah,VID_BL[bp] ; get attribute
- mov cx,VID_CX[bp] ; get character count
-
- pc_ch_wr_a:
- ; Entry from EGA write_string:
- push ax ; save attr/char
- mov dx,VC_CURSOR
- call pc_point_curs@ ; di -> cursor dest
- pop ax ; restor attr/char
- jmp put_crt_s@ ; go right to physical
-
-
-
- v_i_write_char@: ; 10 set char @ cur
- ;---------------
- ; Entry: VID_BH = page number (ignored by us)
- ; VID_AL = character to write
- ; VID_CX = repeat count
- ;
- ; Note: attributes are not modified
-
- mov al,VID_AL[bp] ; recover character
- mov cx,VID_CX[bp] ; repeat count
-
- pc_v_write:
- ; Write cx attr/chars at current cursor:
-
- test VC_MODE,MATCH_BIT ; top screen ?
- jnz pc_ch_wr_at1 ; no
- call wait_sync ; wait for synchronized screen
- call get_point_pc ; get pointer to physical screen struc.
- call ser_mx ; lock out serial I/O
- mov ax,VC_CURSOR
- call set_pcursor ; make sure cursor in right place
-
- mov cx,VID_CX[bp] ; get repeat count
- mov dx,VC_CURSOR
- call pc_point_curs@ ; di -> cursor dest
- pc_ch_wr_at_loop:
- inc di ; skip char
- mov es,VC_CRT_SEG ; get screen segment
- mov ah,es:[di] ; get attribute
- push di
- call do_char_attrib
- pop di
- inc di ; next char
- loop pc_ch_wr_at_loop
- mov PC_BUSY,00h ; release serial semaphore
-
- pc_ch_wr_at1:
- sub si,si ; call the following
- call xlat_esc ; code w/o setting dirty bit
- mov al,VID_AL[bp] ; get character
- mov cx,VID_CX[bp] ; get character count
-
- push ax ; save attr/char
- mov dx,VC_CURSOR
- call pc_point_curs@ ; di -> cursor dest
- pop ax ; restor attr/char
- mov es,VC_CRT_SEG ; get screen segment
- pc_ch_wr1:
- stosb ; write character only
- inc di ; skip attribute
- loop pc_ch_wr1
- ret
-
-
- ; Enter : AH = attribute
- ; VID_AL = char
-
- do_char_attrib:
- push cx
- call set_pattrib ; set physical attribute
- mov al,VID_AL[bp] ; get character
- cmp al,' ' ; check if character large enough
- jae go_pc_ch_wr ; go ahead if printable
- if 0 ; if 1: remap control codes to ASCII
- push bx
- mov bx,offset ctrl_xlat ; else translate to ASCII
- xlat ctrl_xlat
- pop bx
- else ; this works on the Wyse 60:
- cmp al,00 ; if zero then display a space
- jne go_pc_ch_wr_control ; no, send as ESC seq
- mov al,' ' ; null = ' '
- jmps go_pc_ch_wr ; go ahead as printable
- go_pc_ch_wr_control:
- push ax ; else output ESC
- mov al,ESC ; for terminal to recognize
- call tmp_write ; sequence as illegal and to
- pop ax ; and print control char
- endif
- go_pc_ch_wr:
- call tmp_write ; write character AL
- inc PC_CURCOL ; next cursor column
- cmp PC_CURCOL,CRT_COLS
- jne pc_ch_wr_at_lp1 ; skip if no wrap
- mov ah,PC_CURROW ; get current row
- inc ah
- mov al,0 ; next line, first column
- call set_pcursor ; set cursor address
- pc_ch_wr_at_lp1:
- pop cx
- ret
-
-
- v_i_set_color: ; 11 pallette / border control
- ;-------------
- ; Entry: VID_BH = color ID to set
- ; VID_BL = color value to set
-
- ret
-
-
-
- v_i_write_tty: ; 14 write char stream as a tty
- ;-------------
- ; Entry: VID_AL = character to write
- ; VID_BL = color in graphics mode
-
- mov cl,VID_AL[bp]
- mov dx,VC_CURSOR
- cmp cl,' ' ; check if any control code
- jae pc_not_bell
-
- cmp cl,BS ; backspace?
- jne pc_not_bs
- jmp vc_out_bs@
-
- pc_not_bs:
- cmp cl,CR ; cr?
- jne pc_not_cr
- jmp vc_out_cr@
-
- pc_not_cr:
- cmp cl,LF ; lf
- jne pc_not_lf
- jmp vc_out_lf@
-
- pc_not_lf:
- cmp cl,BEL ; bell?
- jne pc_not_bell
- jmp vc_out_bel@
-
- pc_not_bell:
- push cx ; save character
- call get_char_attr ; find attr on current char
- pop cx
- push word ptr VC_ATTRIB ; save default
- mov VC_ATTRIB,ah ; temp change attribute
- call vc_out@
- pop word ptr VC_ATTRIB
- ret
-
-
-
- v_i_gmode: ; 15 current video state
- ;---------
- ; Exit: VID_AL = current video mode (see v_i_smode:)
- ; VID_AH = # of columns per line
- ; VID_BH = current screen page (always 0 in CDOS)
-
- mov al,VC_VMODE ; get current ROS video mode
- mov ah,VC_WIDTH ; get screen width (40 / 80 cols)
- mov VID_AX[bp],ax
- mov VID_BH[bp],0 ; always in page 0
- ret
-
-
- eject
-
- ; Dispatcher intercept vector
- ; entry: DS:BX = SYSDAT:PD address
- ; ES = UDA segment
- ; exit: DS, ES preserved
- disp_inter:
- ;----------
- pushf
- cli
- cld
- mov dl,P_CONS[bx] ; VC number of new process
- cmp dl,MAX_VIR_CONS
- ja no_disp
- cmp dl,active_vc$ ; same console as last time?
- jne disp_1
- no_disp:
- jmp disp_retf ; yes, don't do anything
- disp_1:
- cmp dl,NUM_VIR_CONS ; check console
- jae disp_2
- jmp dsp_int1 ; skip if not serial console
- disp_2:
- push dx ; save vs
- call get_ccb ; di -> ccb
- mov dl,C_PC[di] ; logical console number
- call test_pcterm@ ; test if emulation required
- pop dx
- jz no_disp ; must be dumb terminal so ignore
-
- push es ! push bx ; swap in serial terminal
- call point_vc@ ; get VC_ in BX
- xchg active_vc$,dl
- cmp dl,NUM_VIR_CONS ; serial process active before?
- jb disp_inter1 ; no, don't save page entries
-
- ; Swapping to serial from serial
- test VC_INSTALLED,0ffh ; has flush been installed for VC
- jnz disp_3
- jmp disp1 ; no leave
- disp_3:
- push bx ; save new VC->
- push ds ; save old page entries
- push ds ! pop es ; our DS to ES
- call point_vc@ ; get old VC_ in BX
- mov al,sl_pc_flag$
- mov ah,sl_crt_flag$
- mov VC_SL_FLAGS,ax ; save status line flags
- mov ax,PC_SEGMENT ; we will be working with ROS data
- mov ds,ax
- mov ax,cursor_posn_40 ; assume active page zero
- mov es:VC_ROS_CURSOR,ax ; and save the ROS cursor posn
- disp_4:
- lea di,es:VC_PAGE_SAVE ; page save area for VC
- mov bx,es:v386_ptr$ ; get pointer to 386 specific table
- mov ds,es:ptbl_seg ; get page table
- mov si,(CRT_SEG/100h)*4 ; save page table contents
- mov cx,2*2 ; in VC_ structure
- rep movsw
- add si,4*2 ; point to physical image
- movsw
- movsw
- pop ds ; restore sysdat
- pop bx
- jmps disp_inter2
-
- ; Swapping to serial from PC terminal
- disp_inter1:
- xchg dl,active_vc$
- push dx
- push bx
- call map_top ; restore mapping
- pop bx
- pop dx
- xchg dl,active_vc$
- push ds
- push ds ! pop es
- mov al,sl_pc_flag$
- mov ah,sl_crt_flag$
- mov save_sl_flags,ax ; save status line flags
- mov ax,PC_SEGMENT ; point at ROS data
- mov ds,ax
- mov al,crt_mode_40 ; save some state of PC terminal
- mov es:save_mode,al
- mov ax,crt_cols_40
- mov es:save_cols,al
- mov ax,cursor_posn_40 ; assume active page zero
- mov es:save_cursor,ax
- mov ax,equip_flag_40 ; get ROS value
- xchg ax,es:save_equip$ ; get saved value
- or al,00110000b ; make default console b/w
- mov equip_flag_40,ax
- mov ax,MONO_PORT
- xchg ax,addr_6845_40 ; swap CRT controller values
- mov es:save_6845,ax
-
- cmp es:kbd_imhere$,0 ; in keyboard ISR ?
- je disp_inter1a
- pop ds
- jmps disp_inter4
- disp_inter1a:
- mov si,offset kb_flag_40 ; keyboard data area
- mov di,offset save_kbdata$ ; save area
- mov cx,39
- rep movsb ; save kbd flags and buffer
- pop ds
-
- ; swap serial in
- disp_inter2:
- test VC_INSTALLED,0ffh ; has flush been installed for VC
- jnz disp_inter3
- jmp disp1 ; no leave
- disp_inter3:
- cmp kbd_imhere$,0 ; in keyboard ISR ?
- jne disp_inter4 ; yes leave alone
- call get_kbd_flags@ ; get active_vc save area offset in SI
- mov ax,PC_SEGMENT
- mov es,ax
- mov di,offset kb_flag_40 ; ROS keyboard data area offset
- mov cx,39 ; flags and buffer
- rep movsb ; put new values into ROS
-
- disp_inter4:
- push es ; save ES and BX
- mov ax,VC_SL_FLAGS ; restore status line flags
- mov sl_pc_flag$,al
- mov sl_crt_flag$,ah
- mov ax,PC_SEGMENT ; we will be working with ROS data
- mov es,ax
- mov al,VC_VMODE ; store values from new console
- mov es:crt_mode_40,al
- mov al,VC_WIDTH
- xor ah,ah
- mov es:crt_cols_40,ax
- mov ax,VC_ROS_CURSOR
- mov es:cursor_posn_40,ax ; assume active page zero
- pop es
- lea si,VC_PAGE_SAVE ; page save area for VC
- mov bx,v386_ptr$ ; get pointer to 386 specific table
- mov es,ptbl_seg ; enable page table for us
- push si
- mov di,(CRT_SEG/100h)*4
- mov cx,3
- lodsw
- and al,not PGA_RW ; set write protect attribute
- stosw ; for IDLE detection
- rep movsw
-
- add di,4*2 ; physical image
- movsw
- movsw
- pop si
- mov di,(COLOR_SEG/100h)*4 ; make sure something mapped at B800h
- ; mov cx,2*2
- ; rep movsw
-
- mov ax,0f067h ; AX/DX = physical memory base
- mov dx,0ffffh
-
- stosw
- xchg ax,dx
- stosw
- xchg ax,dx
-
-
- mov bx,v386_ptr$ ; get pointer to 386 specific table
- mov es,tss_seg ; get TSS segment address
- or es:word ptr .0DEh,8530h ; disable ports 3BFh, 3B4h, 3B5h,
- ; 3BAh, 3B8h
- or es:byte ptr .074h,02h ; trap port 61h - set beeper
- disp1:
- pop bx ! pop es
- disp_retf:
- popf
- FLUSH_TLB ; discard TLB cache
- retf
-
- ; Swapping to MAIN terminal
- ; -----------------------
- dsp_int1:
- xchg dl,active_vc$ ; mark new active console
- cmp dl,NUM_VIR_CONS ; serial process active before?
- jae dsp_int1a ; yes..
- xchg dl,active_vc$
- push dx
- call map_top ; restore mapping
- pop dx
- xchg dl,active_vc$
- call map_top ; map in top screen
- jmps disp_retf
-
- dsp_int1a:
-
- ; -- from serial terminal
- ; -----------------------
- push bx ! push es
- mov ax,PC_SEGMENT ; point to ROS data area
- mov es,ax
-
- mov ax,save_equip$ ; get saved value
- mov es:equip_flag_40,ax ; and store in ROS
- mov ax,save_6845
- mov es:addr_6845_40,ax ; swap CRT controller values
-
- cmp kbd_imhere$,0 ; in keyboard ISR ?
- jne dsp_int2 ; yes..
- mov si,offset save_kbdata$ ; get saved data offset
- mov di,offset kb_flag_40 ; and store in ROS data area
- mov cx,39 ; keyboard flags and buffer
- rep movsb
-
- dsp_int2:
- call point_vc@ ; get VC_ in BX
- mov al,sl_pc_flag$
- mov ah,sl_crt_flag$
- mov VC_SL_FLAGS,ax ; save status line flags
- mov ax,es:cursor_posn_40 ; assume active page zero
- mov VC_ROS_CURSOR, ax ; and save ros cursor position
- dsp_int3:
- mov al,save_mode
- mov es:crt_mode_40,al ; restore state of PC terminal
- mov al,save_cols
- xor ah,ah
- mov es:crt_cols_40,ax
- mov ax,save_cursor
- mov es:cursor_posn_40,ax ; assume active page zero
- mov ax,save_sl_flags ; restore status line flag
- mov sl_pc_flag$,al
- mov sl_crt_flag$,ah
- test VC_INSTALLED,0ffh
- jz disp_retf1
- push ds
- push ds ! pop es ; our DS to ES
- lea di,VC_PAGE_SAVE ; page save area for VC
- mov bx,v386_ptr$ ; get pointer to 386 specific table
- mov ds,ptbl_seg ; get page table
- mov si,(CRT_SEG/100h)*4 ; save page table contents
- mov cx,2*2 ; in VC_ structure
- rep movsw
- add si,4*2 ; point to physical image
- movsw
- movsw
- pop ds ; restore sysdat
-
- mov di,(CRT_SEG/100h)*4 ; now swap in physical memory
- mov es,ptbl_seg ; ES:DI -> page table
- mov ax,(CRT_SEG*16)+67h ; AX/DX = physical memory base
- mov dx,(CRT_SEG/4096)
-
- stosw
- xchg ax,dx
- stosw
- xchg ax,dx
-
- add ax,1000h ; replace clean image
- stosw
- xchg ax,dx
- stosw
- xchg ax,dx
-
- add di,4*2
- add ax,3000h ; replace physical image
- stosw
- xchg ax,dx
- stosw
-
- mov bx,v386_ptr$ ; get pointer to 386 specific table
- mov es,tss_seg ; get TSS segment address
- and es:word ptr .0DEh,not 8530h ; enable 3BFh, 3B4h, 3B5h,
- ; 3bAh, 3B8h
- and es:byte ptr .074h,not 02h ; enable port 61h - beeper
- call map_top ;
- disp_retf1:
- pop es ! pop bx
- popf
- FLUSH_TLB ; discard TLB cache
- retf
-
- ; Map in current top console
- map_top:
- mov dl,active_vc$
- cmp dl,active_top
- je is_foreg1a ; current vc is top
-
- call map_current_vc ; else map vc buffer in screen memory
-
- mov bx,v386_ptr$ ; get pointer to 386 specific table
- mov es,tss_seg ; get TSS segment address
- or es:word ptr .0DEh,8530h ; trap 3BFh, 3B4h, 3B5h,
- ; 3BAh, 3B8h
- or es:word ptr .0E2h,8530h ; trap 3DFh, 3D4h, 3D5h,
- ; 3DAh, 3D8h
- jmps is_foreg2a
-
- is_foreg1a:
- call map_current_screen ; re-map screen memory
-
- mov bx,v386_ptr$ ; get pointer to 386 specific table
- mov es,tss_seg ; get TSS segment address
- and es:word ptr .0DEh,not 8530h ; enable 3BFh, 3B4h, 3B5h,
- ; 3bAh, 3B8h
- and es:word ptr .0E2h,not 8530h ; enable 3DFh, 3D4h, 3D5h,
- ; 3DAh, 3D8h
- is_foreg2a:
- mov dl,top_screen$ ; keep note of top_screen$ for next
- mov active_top,dl ; time thru in
- ret
-
-
- ; Map Current Virtual console buffer into screen memory area
- ; Enter : DL = active vc
- ; N.B. FLUSH_TLB must be done on return
- map_current_vc:
- push ds
- push bx
- call point_vs@
- mov di,VS_CRT_SEG ; screen seg address
- cmp di,EGA_SEG ; graphics ?
- je map_exit
- mov si,VS_VC_SEG ; VC seg address
-
- mov VS_CRT_SEG,si ; swap VS_CRT_SEG and VS_VC_SEG
- mov VS_VC_SEG,di ; pointers over
- shr di,6 ; / 100h *4 = page table entry(screen)
- shr si,6 ; page table entry(VC buff)
- mov bx,v386_ptr
- mov es,ptbl_seg ; page table
- mov ds,ptbl_seg
- OP_32 ! mov ax,[si] ; now swap over the mappings as well
- and al,not PGA_RW ; set write protect attribute
- OP_32 ! xchg ax,[di]
- and al,not PGA_RW ; set write protect attribute
- OP_32 ! mov [si],ax
- map_exit:
- pop bx
- pop ds
- ret
-
- ;Re-Map screen memory area
- ; Enter : DL = active vc
- ; N.B. FLUSH_TLB must be done on return
- map_current_screen:
- call point_vs@
- mov dh,VS_SCREEN_MODE ; get current mode
- mov di,MONO_SEG
- OP_32 ! xor ax,ax ; clear EAX
- mov ax,di
- shr di,6 ; / 100h *4 = page table entry(screen)
- mov bx,v386_ptr
- mov es,ptbl_seg ; page table
- OP_32 ! shl ax,4
- xor al,al ; ** set write protect **
- cmp dh,07 ; MONO mode
- je is_mono
- mov al,67h ; allow read/write
- is_mono:
- OP_32 ! stosw
- mov di,COLOR_SEG
- OP_32 ! xor ax,ax ; clear EAX
- mov ax,di
- shr di,6 ; / 100h *4 = page table entry(screen)
- mov bx,v386_ptr
- mov es,ptbl_seg ; page table
- OP_32 ! shl ax,4
- xor al,al ; ** set write protect **
- cmp dh,07 ; MONO mode
- jne is_color
- mov al,67h ; allow read/write
- is_color:
- OP_32 ! stosw
- ret
-
-
- eject
- ; Subroutines
- ; -----------
-
-
- get_point_pc:
- ;------------
- ; Get pointer to physical screen structure
- ; entry: BX -> pointer to VC structure
- ; exit: SI -> pointer to PC structure
-
- mov dl,VC_NUMBER ; get virtual console number
- ; jmps point_pc
-
-
-
- point_pc:
- ;--------
- ; Point to physical console structure:
- ; entry: dl = virtual console number
- ; exit: SI -> pc_
- ; DH = physical console number
- ; point_pc1@ - entry
- ; AL = physical console
-
- xor dh,dh
- mov si,dx
- shl si,1
- mov si,ccb_list$[si] ; get ccb pointer for VC
- mov al,C_PC[si] ; get physical console number
- mov dh,al ; and store in DH
- point_pc1@:
- dec al ; physical 0 is master console
- xor ah,ah
- mov si,ax
- shl si,1
- mov si,pc_table[si] ; pointer to PC_ structure
- ret
-
- ; Point to virtual console structure:
- ; entry: dl = virtual console number
- ; exit: BX = vc_
- point_vc@:
- ;--------
-
- xor dh,dh
- mov bx,dx
- sub bx,NUM_VIR_CONS ; make 0 relative
- shl bx,1
- mov bx,vc_table[bx] ; get virtual console table
- ret
-
- ; get ccb structure for virtual console
- ; entry: dl=virtual console number
- ; exit: di=ccb address
- get_ccb:
- ;-------
- xor dh,dh
- mov di,dx
- shl di,1
- mov di,ccb_list$[di] ; get ccb pointer for VC
- ret
-
-
- ; get ROS keyboard data for active_vc
- ; include flags, buffer pointers and buffer
- ; exit: SI = offset ROS keyboard data
- ; all regs preserved
- get_kbd_flags@:
- ;-------------
- push dx
- mov dl,active_vc$ ; top vc_
- cmp dl,NUM_VIR_CONS
- jae is_ser
- mov si,offset save_kbdata$ ; get main console save area
- jmps kbd_flags_ret
- is_ser:
- call point_pc ; get PC_ structure
- mov ax,word ptr PC_KFLAG
- mov si,offset pc_kbd_save ; PC terminals save area
- mov [si],ax ; insert flags at start
- kbd_flags_ret:
- pop dx
- ret
-
-
- ; test if serial console is setup for PCTERM emulation
- ; entry: dl = logical physical console number
- ; exit: ZF reset if PCTERM
- test_pcterm@:
- ;-----------
- push ax
- call get_su_mu
- test al,PCTERM_EMU ; test setup bit for installed port
- pop ax
- ret ; to see if pcterm emulation required
-
- ; return setup byte in AL
- get_su_mu:
- push bx
- mov bl,dl
- mov bh,0 ; BX = physical console #
- mov bl,pc2port_table$[bx] ; BX = serial port number
- mov al,su_mu_vs$[bx] ; get setup byte for serial port
- pop bx
- ret
-
-
- ; virtual console mutual exclusion
- ; Enter : BX=VS_ ->
- get_mx:
- ;------
- mov al,0FFh
- xchg al,VC_MX
- test al,al
- jz got_mx
- push bx ! push cx ! push dx
- call delay1
- pop dx ! pop cx ! pop bx
- jmps get_mx
- got_mx:
- ret
-
- ; Get MX's for all VS on physical console
- get_all_mxs:
- ;-----------
- mov di,rlr$ ; get running proc
- mov dl,P_CONS[di] ; get process's vc number
- xor dh,dh
- mov di,dx
- shl di,1
- mov di,ccb_list$[di] ; get ccb pointer for VC
- mov al,C_PC[di] ; get physical console number
-
- mov di,offset ccb_list$ ; search for first VC on this physical
- search_ccb:
- mov si,[di] ; ccb pointer
- inc di ! inc di
- cmp al,C_PC[si] ; our ccb
- jne search_ccb ; no get next
-
- next_mx:
- mov dl,C_VC[si] ; get VS number
- push si
- call point_vc@
- call get_mx
- pop si
- mov si,C_LINK[si] ; link to next
- cmp si,0000h ; end link ?
- jne next_mx
- ret
-
- ; Free MX's for all VS on physical console
- free_all_mxs:
- ;------------
- mov di,rlr$ ; get running proc
- mov dl,P_CONS[di] ; get process's vc number
- xor dh,dh
- mov di,dx
- shl di,1
- mov di,ccb_list$[di] ; get ccb pointer for VC
- mov al,C_PC[di] ; get physical console number
-
- mov di,offset ccb_list$ ; search for first VC on this physical
- search_ccb1:
- mov si,[di] ; ccb pointer
- inc di ! inc di
- cmp al,C_PC[si] ; our ccb
- jne search_ccb1 ; no get next
-
- next_mx1:
- mov dl,C_VC[si] ; get VS number
- call point_vc@
- mov VC_MX,0 ; release semaphore
- mov si,C_LINK[si] ; link to next
- cmp si,0000h ; end link ?
- jne next_mx1
- ret
-
- ; Serial console output mutual exclusion
- ; Entry : SI -> PC_ structure
- ser_mx:
- ;------
- mov al,0FFh
- xchg al,PC_BUSY
- test al,al
- jz ser_mx1
- push bx ! push cx ! push dx ! push si
- call delay1
- pop si ! pop dx ! pop cx ! pop bx
- jmps ser_mx
- ser_mx1:
- ret
-
- delay1:
- ;-----
- push bp
- mov cx,P_DELAY
- mov dx,1
- call supif@ ; delay by one tick
- pop bp
- ret
-
-
-
- wait_sync:
- ;---------
- ; SI preserved
-
- push es ! push bx ! push si
- wt_sync1:
- mov bx,v386_ptr$
- mov es,ptbl_seg ; get page table segment
- mov di,(CRT_SEG/256*4) ; get entry for screen segment
- test PG_ATTR,PGA_DIRTY ; test if screen is clean
- jz wt_sync2 ; continue if screen is clean
- call delay1
- jmps wt_sync1
- wt_sync2:
- pop si ! pop bx ! pop es
- ret
-
-
- ; update Physical cursor
- ; entry: AX = desired cursor address
- ; BX -> VC_ structure
- ; SI -> PC_ structure
- ; SI,BP preserved
- set_pcursor:
- ;-----------
- cmp ax,PC_CURSOR ; same as physical cursor?
- je set_pcurs_ret ; yes, leave it alone
- mov PC_CURSOR,ax ; else update it first
- xchg al,ah ; AL = row, AH = col
- add ax,2020h ; add in row/column bias
- lea di,PC_CURPOS ; get address of ESC sequence
- mov 3[di],ax ; set row/column in sequence
- call ser_write ; send ESC sequence to terminal
- set_pcurs_ret:
- ret
-
-
- ; Turn physical cursor off
- ; Entry: BX -> VC_
- cursor_off:
- ;----------
- test VC_MODE,MATCH_BIT
- jnz no_off ; background
- call get_point_pc ; get PC_ ->
- call ser_mx ; mutual exclusion
- mov di,offset cur_off_seq
- call ser_write
- mov PC_BUSY,00h ; release semaphore
- no_off:
- ret
-
- ; Turn physical cursor on
- ; Entry: BX -> VC_
- cursor_on:
- ;---------
- test VC_MODE,MATCH_BIT
- jnz no_on ; background
- call get_point_pc ; get PC_ ->
- call ser_mx ; mutual exclusion
- mov di,offset cur_on_seq
- call ser_write
- mov PC_BUSY,00h ; release semaphore
- no_on:
- ret
-
- set_pattrib:
- ;-----------
- ; entry: AH = new screen attribute
- ; BX = VC ->
- ; SI = PC ->
- ; SI,BP preserved
-
- cmp ah,PC_ATTR
- jne new_pattr
- ret
- new_pattr:
- mov PC_ATTR,ah ; save as new attribute
- mov al,0011$0001b ; invisble attribute
- cmp ah,00h
- je pattr4
-
- mov al,0111$0000b ; assume normal attribute (dim)
- cmp ah,07h
- je pattr4
- test ah,0000$1000b ; test intensity bit
- jz pattr1
- and al,1011$1111b ; turn on intensity
- pattr1:
- test VC_BLINK,20h
- jnz pattr1a ; blink not disabled
- test ah,1000$0000b ; blink attr
- jz pattr2 ; blink disabled and blink attr then
- and al,1011$1111b ; turn on intensity
- jmps pattr2
- pattr1a:
- test ah,1000$0000b ; blinking text?
- jz pattr2
- or al,0000$0010b ; turn on blinking
- pattr2:
- and ah,0111$0111b ; isolate other bits
- test ah,0111$0000b ; inverse video?
- jz pattr3
- or al,0000$0100b ; turn on reverse
- jmps pattr4
- pattr3:
- cmp ah,0000$0001b ; underlined text?
- jne pattr4
- or al,0000$1000b ; underlined bit
- pattr4:
- lea di,PC_ATTRIB ; "set attribute" sequence
- mov 3[di],al ; set desired attribute
- call ser_write ; write out ESC G attrib
- ret
-
- tmp_write:
- ;---------
- ; entry: AL = character to write
- ; BX -> VC screen structure
- ; SI -> physical screen structure
- ; SI,BP preserved
-
- lea di,PC_TMPSTR
- mov byte ptr [di],1
- mov 1[di],al
- ; call ser_write
- ; ret
-
- ser_write:
- ;---------
- ; entry:
- ; SI -> physical screen structure
- ; BP preserved
- ; DI -> string for output
- push bp
- mov al,[di]
- inc di ; 1st byte = character count
- cbw ; make it a word
- xchg ax,cx ; CX = byte count
- ser_wrt1:
- mov al,[di]
- inc di
- push bx ! push cx ! push si ! push di
- mov cl,al
- mov dl,PC_CONS ; get physical console number
- add dl,NUM_VIR_CONS-1 ; make logical VC number
- call io_conout ; call to original io_conout
- pop di ! pop si ! pop cx ! pop bx
- loop ser_wrt1
- pop bp
- ret
-
-
- xlat_esc:
- ;--------
- ; entry: SI -> escape sequence -or- 0000h
- ; return address = emulation routine
- ;
- ; Note: This code will call the code at the return
- ; address twice, once for the virtual plane
- ; and once for the physical image...
-
- test VC_MODE,MATCH_BIT ; test if foreground console
- jnz xlat_esc_bg ; skip if background
- test si,si ; test if any ESC sequence provided
- jz xlat_esc_fg
- push si
- call wait_sync ; wait for synchronized screen
- call get_point_pc ; get pointer to physical screen struc.
- call ser_mx ; lock out serial I/O
- mov ax,VC_CURSOR
- call set_pcursor ; make sure cursor in right place
- pop di ; string address to DI
- call ser_write ; for ser_write
- mov PC_CURSOR,-1 ; invalidate cursor address
- mov PC_BUSY,00h ; release serial semaphore
- xlat_esc_fg:
- pop ax ! push ax ; get & save image update routine
- mov VC_CRT_SEG,CRT_SEG+IMGOFF/16
- mov dx,VC_CURSOR
- call ax ; update physical image
- xlat_esc_bg:
- pop ax ; get image update routine
- mov VC_CRT_SEG,CRT_SEG+CLNOFF/16
- mov dx,VC_CURSOR
- call ax ; update virtual image
- mov VC_CRT_SEG,CRT_SEG ; restore screen segment
- ret
-
- eject
-
-
- con_control:
- ;-----------
- ; Handle control codes:
-
- mov di,offset norm_scan
- mov cx,NORM_COUNT
- call con_scan@ ; scan for special chars
- jmp norm_table[si]
-
- con_normal@:
- ;----------
- ; Normal console vector state:
- ; entry: cl,al = character
- ; bx = VC_ base
- ; dx = cursor
-
- cmp al,' ' ; non-character?
- jb con_control ; try to avoid jumps
-
- vc_out@:
- ;------
- ; Printable character to virtual console ram image:
- ; entry: bx -> VC_
- ; cl = character
- ; dx = cursor
-
- call get_point_pc ; get pointer to physical screen struc.
- mov al,cl
- call NX_conout_xlat ; xlat char for national 7 bit display
- mov cl,al ; translated char
- push cx ; save char
- test VC_MODE,MATCH_BIT ; top screen ?
- jnz vc_out_bg ; no...
- call wait_sync ; wait for synchronized screen
- call ser_mx ; lock out serial I/O
- mov ax,VC_CURSOR
- call set_pcursor ; make sure cursor in right place
- mov ah,VC_ATTRIB
- call set_pattrib ; set physical attribute
- pop ax ; get char
- cmp al,' ' ; check if character large enough
- jae go_vcout ; go ahead if printable
- push ax ; else output ESC
- mov al,ESC ; for terminal to recognize
- call tmp_write ; sequence as illegal and to
- pop ax ; and print control char
- go_vcout:
- push ax ; save char
- call tmp_write ; now write this character
- inc PC_CURCOL ; increment column count
- mov PC_BUSY,00h ; release serial semaphore
- vc_out_bg:
- pop ax ; get char
-
- mov dx,VC_CURSOR
- push es
- mov di,VC_OFFSET ; point to screen buffer
- shl di,1
- mov ah,VC_ATTRIB
- mov es,VC_CRT_SEG
- add di,CLNOFF
- stosw ; update virtual, don't set D
-
- test VC_MODE,MATCH_BIT ; top screen ?
- jnz vc_out_bg1
- add di,IMGOFF-CLNOFF-2
- stosw ; update physical image if top
- vc_out_bg1:
- pop es
- inc dl ; advance cursor
- cmp dl,VC_WIDTH ; if not wrapping around
- jae vc_out2 ; then do cursor
- mov VC_CUR_COL,dl ; update the cursor address
- mov ax,dx
- inc VC_OFFSET ; row/col plus index
- ret
- vc_out2:
- test VC_MODE,WRAP_BIT
- jz vc_out3 ; exit if not wrapping
- call vc_out_cr@ ; send CR, LF and update
- jmp vc_out_lf@ ; cursor
- vc_out3:
- ret ; don't touch cursor
-
-
- con_scan@:
- ;---------
- ; Scan character string for match:
- ; entry: di -> string
- ; cx = count
- ; al = charater
- ; exit: si = word table index, or just past the end
- ; of the table if character is not found
- ; al,cl = character
-
- push es
- push ds
- pop es ; local extra segment
- mov si,cx
- repnz scasb ; look for match
- jnz con_scan1 ; if no match, skip
- dec si ; correct count
- con_scan1:
- sub si,cx ; si = char number
- shl si,1 ; word pointer
- mov cl,al ; copy character
- pop es
- ret
-
-
- restore_state@:
- ;--------------
- ; Restore the state vector to normal:
- and VC_MODE,not ESC_BIT ; turn off ESC bit
- mov VC_VECTOR,offset con_normal@
- ret ; that's all
-
- leave_until_char@:
- ;----------------
- or VC_MODE,ESC_BIT ; next char. into state machine
- pop VC_VECTOR ; pop return addr into state vector
- ret
-
- vc_out_cr@:
- ;----------
- ; VC carriage return out:
-
- sub dl,dl ; first column
- ; jmps put_cursor@ ; update and display
-
- put_cursor@:
- ;-----------
- ; Update and display cursor if appropriate:
-
- call pc_point_curs@
- mov VC_OFFSET,ax
- mov VC_CURSOR,dx
- test VC_MODE,MATCH_BIT ; top screen ?
- jnz put_cursor_exit ; no .. leave
- push dx ; save cursor
- call wait_sync ; wait for synchronized screen
- call get_point_pc ; get pointer to physical screen struc.
- call ser_mx ; lock out serial I/O
- call poke_ros_cursor@ ; done below
- mov ax,VC_CURSOR
- call set_pcursor ; make sure cursor in right place
- mov PC_BUSY,00h ; release serial semaphore
- pop dx ; restore cursor
- put_cursor_exit:
- ret
-
- show_cursor@:
- ret
-
- pc_point_curs@:
- ;-------------
- ; Point to vc image from cursor row,column:
- ; entry: dx = (row,column)
- ; bx -> vc_
- ; exit: ax = vc_width*row + column
- ; di = 2*ax
- ; dx = preserved
-
- mov al,VC_WIDTH
- mul dh ; ax = row * (40 or 80)
- add al,dl ; add in the column
- adc ah,0 ; and handle the carry
- mov di,ax
- shl di,1 ; di = 2*ax
- ret
-
- poke_ros_cursor@:
- ;----------------
- push es
- push ax
- mov ax,PC_SEGMENT ; make sure cursor reflects ROS value
- mov es,ax
- mov ax,VC_CURSOR ; finally update ROS values
- mov es:cursor_posn_40,ax ; assume page zero
- pop ax
- pop es
- ret
-
- put_crt_s@:
- ;----------
- push es
- mov es,VC_CRT_SEG
- rep stosw
- pop es
- ret
-
-
- vc_out_bs@:
- ;----------
- ; VC back space:
-
- dec dl ; back one column
- jns put_cursor@ ; if not at left
- test VC_MODE,WRAP_BIT
- jz vc_bs1 ; if no wrap, done
- mov dl,VC_WIDTH ; if at left, wrap
- sub dx,0101h ; up one, left one
- jns put_cursor@ ; if not at top
- vc_bs1:
- ret ; if top left, bag it
-
- vc_out_lf@:
- ;----------
- ; VC line feed out:
-
- mov al,VC_CRT_ROWS ; get our screen size
- dec al ; al = number of last line
- cmp dh,al ; if at the bottom
- jae vc_lf_scroll ; do a scroll
- inc dh ; if not, move down
- mov VC_CURSOR,dx ; save the cursor value
- mov ax,dx
- call poke_ros_cursor@ ; in ros area too
- add VC_OFFSET,CRT_COLS
- vc_lf_show:
- jmps show_cursor@ ; display current cursor
-
- vc_lf_scroll:
- mov si,offset lf_seq ; send sequence directly
- cmp VC_CRT_ROWS,CRT_ROWS_P ; test if 24 or 25 lines
- je vc_lf_scroll1 ; skip if 25 lines
- mov si,offset lfcpm_seq ; else use some magic
- vc_lf_scroll1: ; SI -> direct sequence
- call xlat_esc ; then update the image
-
- sub ax,ax ; zero offset from
- mov di,ax ; the top left
- mov si,CRT_COLS*2 ; one row down
- jmp z_line ; delete one line to scroll
-
- vc_out_bel@:
- ;-----------
- ; VC beep the bell for top screen only:
- test VC_MODE,MATCH_BIT ; top screen ?
- jnz vc_bel_done
- call wait_sync ; wait for synchronized screen
- call get_point_pc ; get pointer to physical screen struc.
- call ser_mx ; lock out serial I/O
- mov al,BEL ; output BELL
- call tmp_write
- mov PC_BUSY,00h ; release serial semaphore
-
- vc_bel_done:
- ret
-
-
- vc_out_esc:
- ;----------
- call leave_until_char@ ; comes back here:
-
- ; Console escape sequence branch point:
- ; entry: cl,al = character
- ; bx = VC_base
- ; dx = cursor
-
- call restore_state@ ; VC_VECTOR back to normal
- mov di,offset esc_scan$
- mov cx,ESC_COUNT
- call con_scan@ ; scan for escape chars
- jmp esc_table$[si]
-
-
- ; ESC sequences and special character support:
-
- z_up@:
- ; ESC A - cursor up:
- dec dh ; next row up
- jns z_cursor ; if not already on top,
- ret ; then set cursor
-
- z_down:
- ; ESC B - cursor down:
- inc dh ; next row down
- cmp dh,VC_CRT_ROWS ; if not already at bottom,
- jb z_cursor ; then set cursor
- ret
-
- z_forward:
- ; ESC C - cursor forward:
- inc dl ; next column right
- cmp dl,CRT_COLS ; if not already at right,
- jb z_cursor ; then set cursor
- ret
-
- z_back:
- ; ESC D - cursor backward:
- dec dl ; next column left
- jns z_cursor ; if not already at left,
- ret ; then set cursor
-
- z_erase@:
- ; ESC E - erase console:
- call z_home ; get to top left
- sub dx,dx ; top left
- jmps z_erase_eos@ ; erase to end
-
- z_home:
- ; ESC H - home cursor:
- sub dx,dx ; 0,0 = top left corner
- ; jmps z_cursor
-
- z_cursor:
- jmp put_cursor@ ; save and display if visible
-
- z_rev_index:
- ; ESC I - reverse index:
- test dh,dh ; if not on the top row,
- jnz z_up@ ; then just move up
- jmp z_insert_line@ ; else scroll down from top
-
- z_erase_eos@:
- ; ESC J - erase to end of screen:
-
- mov si,offset eos_seq ; send physical sequence
- call xlat_esc ; & emulate in virtual plane
- ;#IJ mov ch,VC_CRT_ROWS ; erase to bottom corner
- mov ch,CRT_ROWS_P ; erase to bottom corner
- sub cl,cl
- call eraser ; common code
- ; the physical screen is out of step with the image on the status line
- ; so we blank the status line reference to correspond
- pusha
- push es
- mov ax,CRT_SEG ; point to screen seg
- mov es,ax
- mov cx,CRT_ROWS_C ; line length
- mov di,(2*CRT_ROWS_C*CRT_COLS)+IMGOFF
- mov ax,7*256+' ' ; make image all spaces
- cld
- rep stosw ; blank the reference image too
- pop es
-
- mov bx,rlr$
- mov dl,P_CONS[bx] ; get process VC number
- call get_ccb ; get the CCB
- mov dl,C_PC[di] ; hence the PCon number
- xor cx,cx ; normal statline call
- call fl_io_statline ; force statline update
- popa
- ret
-
- z_erase_eol@:
- ; ESC K - erase to end of line:
-
- mov si,offset eol_seq ; send physical sequence
- call xlat_esc ; & emulate in virtual plane
- mov ch,dh ; this row
- inc ch ; to the next row,
- sub cl,cl ; first column
- jmps eraser ; common code
-
- z_insert_line@:
- ; ESC L - insert a BLANK line:
-
- mov si,offset ins_seq ; send sequence directly
- cmp VC_CRT_ROWS,CRT_ROWS_P ; test if 24 or 25 lines
- je z_ins_dos ; skip if 25 lines
- pushf ; life is complicated by the
- cli ; need to modify the sequence
- mov ax,VC_CURSOR ; get virtual cursor
- xchg al,ah ; AL = row, AH = col
- add ax,2020h ; add in row/column bias
- mov inscpm_cpos,ax ; patch the sequence
- mov si,offset inscpm_seq ; this is the sequence we want
- lea di,VC_ANSI_BUF ; we can't be in ANSI seq here
- cld ; so we can reuse the buffer
- mov cx,4 ; for a per-terminal copy
- push es ; of the sequence
- push ds ; make ES=DS
- pop es ; for the copy - all this
- OP_32 ! rep movsw ; to avoid re-entrancy problems
- pop es ; restore ES
- popf ; we are safe again...
- lea si,VC_ANSI_BUF ; send out the copy
- z_ins_dos: ; SI -> direct sequence
- call xlat_esc ; perform clean update
- mov al,CRT_COLS
- mul VC_CRT_ROWS ; ax = crt size
- dec ax
- mov di,ax
- sub ax,CRT_COLS
- mov si,ax
- shl di,1 ; end of screen
- shl si,1 ; one line up
-
- sub dl,dl ; first column
- mov al,VC_WIDTH ; do pc_point_curs w/out disturbing di
- mul dh ; AX = count from top
- std ; backwards move
- jmps z_ins_del_line ; shared code
-
-
- z_erase_bos@:
- ; ESC d - erase from beginning of screen:
-
- mov cx,dx ; current location
- sub dx,dx ; top left corner start
- jmps eraser
-
- z_erase_line@:
- ; ESC l - erase entire line:
-
- sub dl,dl ; from first column
- mov cx,dx ; to the first column
- inc ch ; of the next row
- jmps eraser
-
- z_erase_bol@:
- ; ESC o - erase from beginning of line:
-
- mov cx,dx ; erase to cursor
- sub dl,dl ; from first column
- ; jmps eraser
- eject
-
- eraser:
- ; Common erase routine:
- ; entry: dx = start of erase row,column
- ; cx = one past ending row,column
-
- xchg cx,dx ; dx = one past the end
- call pc_point_curs@ ; ax = end pointer
- xchg cx,dx ; dx = start cursor
- xchg ax,cx ; cx = end pointer
- call pc_point_curs@ ; ax = start pointer
- sub cx,ax ; cx = erase char count
- jnz erase ; skip if something to erase
- ret ; return if nothing
- erase:
- mov al,' ' ; erase to blanks
- mov ah,VC_ATTRIB ; of the current attribute
- ; jmps erase_pc@
-
-
- erase_pc@:
- ; This is an entry used by the pc mode emulator:
-
- jmp put_crt_s@ ; if full top, go to physical
-
-
- z_delete_line@:
- ; ESC M - delete one line:
-
- mov si,offset del_seq ; handle ESC sequence directly
- cmp VC_CRT_ROWS,CRT_ROWS_P ; test if 24 or 25 lines
- je z_del_dos ; skip if 25 lines
- mov si,offset delcpm_seq ; else use some magic
- z_del_dos: ; SI -> direct sequence
- call xlat_esc ; & call image update
- sub dl,dl
- call pc_point_curs@ ; di -> line start
- mov si,di
- add si,CRT_COLS*2 ; next row down
- z_ins_del_line:
- push ax
- mov ax,dx
- call poke_ros_cursor@
- pop ax
- xchg VC_CURSOR,dx
- xor dh,dh
- sub VC_OFFSET,dx ; cursor moves to 1st col.
- ; jmps z_line
-
- z_line:
- ; External entry point:
- ; entry: si,di set up for movsw
- ; ax = count from top of screen
- xchg ax,cx ; cx = count
- mov al,CRT_COLS
- mul VC_CRT_ROWS ; ax = crt size
- sub ax,CRT_COLS
- xchg ax,cx
- sub cx,ax ; cx = character count
- jbe z_line1 ; skip if nothing to move
-
- call z_movsw@ ; movsw in vc_segment
- z_line1:
- mov cx,CRT_COLS ; one line's worth
- call erase ; blank one line
- cld ; clear dir. flag (insert)
- jmp show_cursor@
-
-
- z_movsw@:
- ; repeat movsw in current screen segment:
- push es
- push ds ; save around the move
- mov es,VC_CRT_SEG ; else move physical
- push es ! pop ds ; move within the seg
- rep movsw
- pop ds
- pop es
- ret
-
-
- z_delete_char:
- ; ESC N - delete one character:
- mov di,VC_OFFSET
- shl di,1 ; DI -> current char
-
- mov cx,CRT_COLS-1 ; last column
- sub cl,dl ; cx = chars to line end
- jz z_del_ch1 ; skip if at line end
- mov si,di
- inc si ; next char right
- inc si
- call z_movsw@ ; shift left one char
- z_del_ch1:
- mov cx,1 ; erase one last char
- jmp erase
-
- z_set_cursor:
- ; ESC Y - set cursor position:
- call leave_until_char@
- sub cl,' ' ; correct for space offset
- js z_set_col ; if illegal, skip row set
- cmp cl,VC_CRT_ROWS ; check upper bound
- jae z_set_col ; 25 :== 0 through 24 ok
- mov VC_CUR_ROW,cl ; save the row
- z_set_col:
- call leave_until_char@
- sub cl,' ' ; correct for space offset
- js z_set_done ; if illegal, skip col set
- cmp cl,CRT_COLS ; check upper bound
- jae z_set_done ; 80 :== 0 through 79 ok
- mov dl,cl ; dx = new cursor location
- z_set_done:
- call restore_state@ ; back to normal
- mov ax,VC_CURSOR ;
- jmp put_cursor@ ; update and display new curs.
-
- z_set_fore:
- ; ESC b - set foreground color:
- call leave_until_char@
- z_fore1@: ;ANSI entry point
- mov ah,VC_ATTRIB ; current attribute
- jmps z_fg_bg ; shared code
-
- z_set_back:
- ; ESC c - set background color:
- call leave_until_char@
- mov ah,al ; ah = bg bits
- mov cl,4
- rol ah,cl ; bg bits to ms nibble
- mov al,VC_ATTRIB
- z_fg_bg:
- and al,0fh ; take the 4 lsb's of al
- and ah,0f0h ; and the 4 msb's of ah
- or al,ah ; and mash 'em together
- mov VC_ATTRIB,al ; that's the new attribute
- jmp restore_state@ ; back to normal
-
-
- z_cursor_on:
- ; ESC e - enable cursor:
- or VC_MODE,CURSOR_BIT
- jmp cursor_on ; turn on and return
-
- z_cursor_off:
- ; ESC f - disable cursor:
- and VC_MODE,not CURSOR_BIT
- jmp cursor_off ; turn off and return
-
- z_save_cursor@:
- ; ESC j - save cursor position:
- mov VC_SAVE_CURSOR,dx
- ret ; save for later
-
- z_restore_cursor@:
- ; ESC k - restore cursor position:
- mov dx,VC_SAVE_CURSOR
- jmp put_cursor@ ; back where it was
-
- z_rev_on@:
- ; ESC p - reverse video on:
- test VC_MODE,REV_BIT ; if already reversed
- jnz z_rev2 ; then forget it
- or VC_MODE,REV_BIT ; remember
- jmps z_rev1 ; to common code
-
- z_rev_off:
- ; ESC q - reverse video off:
- test VC_MODE,REV_BIT ; if already off
- jz z_rev2 ; then forget it
- and VC_MODE,not REV_BIT
- z_rev1: ; shared code
- mov al,VC_ATTRIB ; get current colors
- mov ah,al ; copy for msb's
- and ax,8877h ; mask colors only
- mov cl,4
- rol al,cl ; swap colors
- or al,ah ; restore intense, blink
- mov VC_ATTRIB,al ; new attribute
- z_rev2:
- ret
-
- z_intense_on@:
- ; ESC r - intensity on:
- or VC_ATTRIB,08h ; set the intense bit
- ret
-
- z_intense_off:
- ; ESC u - intensity off:
- and VC_ATTRIB,0f7h ; reset the intense bit
- ret
-
- z_blink_on@:
- ; ESC s - blink on:
- or VC_ATTRIB,80h ; set the blink bit
- ret
-
- z_blink_off:
- ; ESC t - blink off:
- and VC_ATTRIB,7fh ; reset the blink bit
- ret
- eject
-
- z_wrap_on:
- ; ESC v - wrap at line end on:
- or VC_MODE,WRAP_BIT
- ret
-
- z_wrap_off:
- ; ESC w - no wrap at line end:
- and VC_MODE,not WRAP_BIT
- z_return:
- ret
-
- z_pfk_off@:
- ; esc 6 - turn pfk expansion off
-
- mov VC_PFK_EXP,0 ; expansion flag false
- ret
-
- z_pfk_on@:
- ; esc 7 - turn pfk expansion on
-
- mov VC_PFK_EXP,0FFh ; expansion flag true
- ret
-
- z_set_color@:
-
- z_set_mono@:
-
- z_video_mode:
-
- z_prog_pfk@:
-
- z_back_door:
-
- z_norm_attr:
-
- ret
-
- z_sl_color@: ; we only have mono, so turn that off
- jmp z_sl_off@
-
- z_sl_both@: ; we only have mono, so turn that on
- jmp z_sl_mono@
-
- ;#IJ These are now implemented
-
- ;#IJ z_sl_off@:
- ;#IJ z_sl_mono@:
- ;#IJ z_clk_off@:
- ;#IJ z_clk_on@:
-
-
-
-
- eject
-
- ; ANSI Escape sequence handler
- ; entry:
- ; bx = VC_base
- ; dx = cursor
-
- ; ESC '[' - ANSI lead in character
- ;
- ; The folowing ANSI standard codes (taken from the PC DOS 2.0
- ; manual are to be supported:
-
- ; ESC [ n;nH Move cursor to row, col (default 1;1)
- ; ESC [ nA Move cursor up (default 1)
- ; ESC [ nB Move cursor down (default 1)
- ; ESC [ nC Move cursor right (default 1)
- ; ESC [ nD Move cursor left (default 1)
- ; ESC [ n;nf same as "ESC [n;nH"
- ; ESC [ s save cursor position
- ; ESC [ u restore cursor position
- ; ESC [ 0J erase end of screen
- ; ESC [ 1J erase beginning of screen
- ; ESC [ 2J erase screen, home cursor
- ; ESC [ J erase screen
- ; ESC [ 0K erase end of line
- ; ESC [ 1K erase beginning of line
- ; ESC [ 2K erase entire line
- ; ESC [ K erase end of line
- ; ESC [ L insert line
- ; ESC [ M delete line
- ; ESC [ n;nm Set the Character Rendition
- ; ESC [ = n h Set the Screen Mode
- ; ESC [ = n l Reset the Screen Mode
- ; ESC [ 6 n Device Status Report
- ;
- z_ansi@:
- ;------
- mov VC_ANSI_COUNT,0 ; no number specified
- lea di, VC_ANSI_BUF ; point to number buffer
- mov cx, VC_ANSI_SIZE ; up to 15 numbers
- z_ansi1a:
- mov byte ptr [di],0ffh
- inc di
- loop z_ansi1a
-
- z_ansi1:
- call leave_until_char@ ; wait for parameters
- ; reenter handler here...
- cmp al, '0' ; is it a number?
- jb z_ansi3 ; no, delimiter or command
- cmp al, '9' ; is it a number?
- ja z_ansi3 ; no, delimiter or command
- mov si, VC_ANSI_COUNT ; Next character to add
- sub al, '0' ; make it a number
- mov cl, al ; save the character
- lea di, VC_ANSI_BUF
- add di,si
- mov al, [di] ; get numeric value from BUF
- cmp al, 0FFh ; initial digit?
- jne z_ansi2 ; skip if not first
- sub ax, ax ; zero it out
- z_ansi2:
- mov ah, 10 ; old value * 10
- mul ah ; before we add
- add al, cl ; in new digit.
- mov [di], al ; save it in VC_ANSI_BUF
- jmps z_ansi1 ; wait for more digits
-
- z_ansi3: ; it wasn't a digit
- cmp al, ';' ; is it a delimiter?
- jnz z_ansi5 ; no, must be command
-
- cmp VC_ANSI_COUNT, VC_ANSI_SIZE-2 ; is the buffer full?
- jz z_ansi1 ; skip if not yet
- inc VC_ANSI_COUNT ; move on to next number
- jmps z_ansi1
-
- z_ansi5: ; reenter handler here...
- call restore_state@ ; exit escape handling
- mov di, offset ansi_tbl ; check which one it is
- mov cx, length ansi_tbl ; number of chars to check
- call con_scan@ ; lookup table, --> jump index
- jmp ansi_jmp[si] ; invoke the handler
-
-
-
-
- con_null:
- ret
-
- ; ESC [ n A - cursor up
- ansi_cuu:
- call ansi_def1 ; how many lines
- sub dh, al ; up by N lines
- jae ansi_cur2 ; update cursor
- ret
-
- ; ESC [ n A - cursor down
- ansi_cud:
- call ansi_def1 ; how many lines
- add dh, al ; down by N lines
- cmp dh, VC_CRT_ROWS ; legal row?
- jb ansi_cur2 ; yes, update cursor
- ret
-
- ; ESC [ n A - cursor right
- ansi_cuf:
- call ansi_def1 ; how many columns
- add dl, al ; right by N column
- cmp dl, CRT_COLS
- jb ansi_cur2 ; update cursor
- ret
-
-
- ; ESC [ n A - cursor left
- ansi_cub:
- call ansi_def1 ; how many columns
- sub dl, al ; left by N column
- jae ansi_cur2 ; update cursor
- ret
-
-
- ; Esc [ n;n H
- ; ESC [ n;n f - position cursor
- ansi_cup:
- ansi_hvp:
- mov dx,word ptr VC_ANSI_BUF ; get column/row
- xchg dl, dh ; swap them round (8086 byte order)
- cmp dh,0FFh ; Check for unspecified values
- jnz ansi_cup1 ; and insert default of 1
- mov dh,1
- ansi_cup1:
- cmp dl,0FFh
- jnz ansi_cursor
- mov dl,1
-
- ansi_cursor:
- sub dx, 0101h ; ANSI is biased by one
- cmp dl, CRT_COLS ; column in range?
- jb ansi_cur1 ; truncate if not
- mov dl, CRT_COLS
- dec dl
- ansi_cur1:
- cmp dh, VC_CRT_ROWS ; row in range
- jb ansi_cur2 ; truncate if not
- mov dh, VC_CRT_ROWS
- dec dh
- ansi_cur2:
- jmp put_cursor@ ; update row/col
-
-
- ; ESC [ nn J - erase display
- ;
- ; nn = 0 - erase end of display
- ; nn = 1 - erase beginning of display
- ; nn = 2 - erase entire line
- ; (default = 0)
-
- ansi_ed:
- mov al, VC_ANSI_BUF ; point to parameter
- cmp al, 0FFh ; is it the default?
- je ansi_ed0 ; yes, erase end of display
- test al, al ; is it "0"?
- jnz ansi_ed1 ; skip if not
- ansi_ed0:
- jmp z_erase_eos@ ; handle like VT52
- ansi_ed1:
- dec al ; is it "1"?
- jnz ansi_ed2 ; skip if not
- jmp z_erase_bos@ ; erase beginning of line
- ansi_ed2:
- jmp z_erase@ ; else erase entire display
-
-
- ; ESC [ nn K - erase line
- ;
- ; nn = 0 - erase end of line
- ; nn = 1 - erase beginning of line
- ; nn = 2 - erase entire line
- ; (default = 0)
-
- ansi_el:
- mov al, VC_ANSI_BUF ; point to parameter
- cmp al, 0FFh ; is it the default?
- je ansi_el0 ; yes, erase end of line
- test al, al ; is it "0"?
- jnz ansi_el1 ; skip if not
- ansi_el0:
- jmp z_erase_eol@ ; handle like VT52
- ansi_el1:
- dec al ; is it "1"?
- jnz ansi_el2 ; skip if not
- jmp z_erase_bol@ ; erase beginning of line
- ansi_el2:
- jmp z_erase_line@ ; else erase entire line
-
-
- ; ESC [ L insert line
- ; ESC [ M delete line
- ;ansi_il equ z_insert_line@
- ;ansi_dl equ z_delete_line@
-
-
- ; ESC [ n;nm Set the Character Rendition
- ansi_sgr:
- lea si,VC_ANSI_BUF ; point at 1st parameter
- cmp byte ptr [si],0FFh ; no parameters?
- je ansi_sgr0 ; then set defaults
- ansi_sgr_next:
- lodsb ; else get parameter
- cmp al,0FFh ; stop if end of parameters
- je ansi_sgr_ret
- push si
- call ansi_sgr_x ; set attribute
- pop si
- jmps ansi_sgr_next ; more parameters
-
- ansi_sgr_ret:
- ret
-
- ansi_sgr0:
- mov al,07h ; get the initial attribute
- mov VC_ATTRIB,al ; and update the current attribute
- and VC_MODE,not REV_BIT ; turn off reverse video and leave
- ret ; wrap and cursor state unchanged.
-
- ansi_sgr_x:
- test al, al ; 0?
- jz ansi_sgr0 ; reset inverse
- ansi_sgr1:
- cmp al, 1 ; high intensity
- jne ansi_sgr4
- jmp z_intense_on@
- ansi_sgr4:
- cmp al, 4 ; underscore on
- jne ansi_sgr5
- cmp VC_CRT_SEG,MONO_SEG ; This function is only enabled on
- jnz ansi_sgr_exit ; Monochrome Screens
- mov al, 1
- jmp z_fore1@
- ansi_sgr5:
- cmp al, 5 ; blink on
- jne ansi_sgr7
- jmp z_blink_on@
- ansi_sgr7:
- cmp al, 7 ; reverse on
- jne ansi_sgr8
- jmp z_rev_on@
- ansi_sgr8:
- cmp al, 8
- jne ansi_sgr30
- and VC_ATTRIB, 88h ; make it invisible
- ret
-
- ansi_sgr30:
- ;; cmp VC_CRT_SEG,COLOR_SEG ; These functions are disabled on
- ;; jnz ansi_sgr_exit ; Monochrome Screens
-
- ansi_sgr_exit:
- ret
-
-
- ; ESC [ s save cursor position
- ; ESC [ u restore cursor position
- ;ansi_scp equ z_save_cursor@
- ;ansi_rcp equ z_restore_cursor@
-
-
- ; ESC [ = n h Set the Screen Mode
- ansi_sm: ; Set the current Screen Mode
- mov al,VC_ANSI_BUF ; Get the Selected mode and check for
- cmp al,7 ; WRAP update
- jnz ansi_rm10 ; Normal Set mode
- or VC_MODE,WRAP_BIT
- ret
-
-
- ; ESC [ = n l Reset the Screen Mode
- ansi_rm: ; Reset the screen Mode
- mov al,VC_ANSI_BUF ; Get the Selected mode and check for
- cmp al,7 ; WRAP update
- jnz ansi_rm10 ; Normal Set mode
- and VC_MODE,not WRAP_BIT
- ret
- ansi_rm10:
- cmp al,0FFh ; If no parameter was specified then
- jnz ansi_rm20 ; the default mode of 0 is selected
- mov al,0
- ansi_rm20:
- ;; jmp z_set_mode@ ; use VT52 driver
- ret ; not supported
-
-
- ; ESC [ 6 n Device Status Report
- ansi_dsr:
- call ansi_def1 ; Get the first Parameter
- cmp al,6 ; Was it 6
- jnz ansi_dsr_exit ; If not 6 then exit
-
- add dx,0101h ; Cursor address base 1 (not 0)
- mov al,dl ; Get the Column
- aam ! add ax,3030h ; Convert to ASCII
- xchg al,ah
- mov ansi_cpr_col,ax
-
- mov al,dh ; Get the Row
- aam ! add ax,3030h ; Convert to ASCII
- xchg al,ah
- mov ansi_cpr_row,ax
- mov ansi_cpr_count,ansi_cpr_len ; Force the CONIN routine to
- ansi_dsr_exit: ; return ANSI_CPR.
- ret
-
-
- ansi_def1: ; return 1st parameter or 1 if none specified
- mov al, VC_ANSI_BUF ; no parameter specified?
- cmp al, 0FFh ; is it still the default?
- jne ansi_def1_ret ; no, number specified
- mov al, 1 ; else return 1
- ansi_def1_ret:
- ret
-
-
-
- eject
- PCTERM_DATA dseg
-
-
- ; XIOS entry intercept offsets - replaced with original values at INIT
-
- xios_tbl rw 0
- dw IO_CONIN * 2 ; * 2 for word ptr
- io_conin dw offset fl_io_conin ; func 1 console input
- dw IO_CONOUT * 2
- io_conout dw offset fl_io_conout ; func 2 console output
- dw IO_LISTST * 2
- io_listst dw offset fl_io_listst ; func 3 list output
- dw IO_LIST * 2
- io_list dw offset fl_io_list ; func 4 list output
- dw IO_SWITCH * 2
- io_switch dw offset fl_io_switch ; func 7 console switch
- dw IO_STATLINE * 2
- io_statline dw offset fl_io_statline ; func 8 status line update
- dw PC_KBD * 2
- pc_kbd dw offset fl_pc_kbd ; func 32 keyboard switch
- dw PC_SHIFTS * 2
- pc_shifts dw offset fl_pc_shifts ; func 33 shift status
- dw IO_DEVIO * 2
- io_devio dw offset fl_io_devio ; func 39 block read/write
-
- NUM_FUNCS equ ( offset $ - offset xios_tbl )/4
-
- ; Global data area
- flush_install db 0 ; flush installed flag
- intercept_install db 0
-
-
- ; This string is used by the ANSI Device Status Report function to
- ; return the current cursor location to the calling routine in the
- ; standard ANSI format.
- ;
- ansi_cpr_count db 0
- ansi_cpr db 1Bh, '['
- ansi_cpr_row rw 1
- db ';'
- ansi_cpr_col rw 1
- db 'R'
- ansi_cpr_len equ offset $ - offset ansi_cpr
-
-
-
- ; Console output handlers
- ;------------------------
- norm_table dw vc_out_cr@, vc_out_lf@, vc_out_bs@
- dw vc_out_bel@, vc_out_esc, vc_out@
-
- esc_table$ dw z_up@, z_down, z_forward
- dw z_back, z_erase@, z_home
- dw z_rev_index, z_erase_eos@, z_erase_eol@
- dw z_erase_bos@, z_erase_line@, z_erase_bol@
- dw z_insert_line@, z_delete_line@,z_delete_char
- dw z_set_cursor, z_set_fore, z_set_back
- dw z_cursor_on, z_cursor_off, z_save_cursor@
- dw z_restore_cursor@,z_rev_on@, z_rev_off
- dw z_intense_on@, z_blink_on@, z_blink_off
- dw z_intense_off, z_wrap_on, z_wrap_off
- dw z_set_color@, z_set_mono@, z_video_mode
- dw z_prog_pfk@, z_sl_off@, z_sl_mono@
- dw z_sl_color@, z_sl_both@, z_clk_off@
- dw z_clk_on@, z_pfk_off@, z_pfk_on@
- dw z_back_door, z_norm_attr, z_ansi@
- dw vc_out@
-
- norm_scan db CR,LF,BS,BEL,ESC
- NORM_COUNT equ offset $ - offset norm_scan
-
- esc_scan$ db 'ABCDEH'
- db 'IJKdlo'
- db 'LMNYbc'
- db 'efjkpq'
- db 'rstuvw'
- db 'xya:01'
- db '234567'
- db '!z['
- ESC_COUNT equ offset $ - offset esc_scan$
-
-
- ; Ansi escape sequence jump table
- ansi_tbl db 'ABCDHfJKkLMmsu=?hln'
-
- ansi_jmp dw ansi_cuu, ansi_cud, ansi_cuf, ansi_cub
- dw ansi_cup, ansi_hvp, ansi_ed, ansi_el, ansi_el
- dw z_insert_line@ ; (ansi_il) use VT52 routines
- dw z_delete_line@ ; (ansi_dl)
- dw ansi_sgr
- dw z_save_cursor@ ; (ansi_scp) use VT52 routines
- dw z_restore_cursor@ ; (ansi_rcp)
- dw z_ansi@, z_ansi@, ansi_sm, ansi_rm
- dw ansi_dsr
- dw con_null
-
-
- eject
-
- ; KEYBOARD TABLES
-
- live_tbl db SHFT_RIGHT,SHFT_LEFT,CTRL,ALT
- db BREAK_SCAN,NUMLOCK,CAPSLOCK,INS_SCAN
- live_tbl_len equ offset $ - offset live_tbl
-
- live_mask db SHFT_RIGHT_BIT,SHFT_LEFT_BIT,CTRL_BIT,ALT_BIT
- db SCROLL_BIT,NUMLOCK_BIT,CAPSLOCK_BIT,INS_BIT
-
- alt_intable db 82,79,80,81,75
- db 76,77,71,72,73
- alt_intable_len equ offset $ - offset alt_intable
-
-
-
-
- key_table db -1,27,'1234567890-=',8
- db 9,'qwertyuiop[]',13
- db -1,'asdfghjkl;',39,96
- db -1,'\zxcvbnm,./',-1,'*'
- db -1,' ',-1
- db 0,0,0,0,0, 0,0,0,0,0
- db -1,-1,0,0,0,'-',0,-1,0,'+',0,0,0,0,0
-
- key_scan db -1,1,2,3,4,5,6,7,8,9,10,11,12,13,14
- db 15,16,17,18,19,20,21,22,23,24,25,26,27,28
- db 29,30,31,32,33,34,35,36,37,38,39,40,41
- db 42,43,44,45,46,47,48,49,50,51,52,53,-1,55
- db -1,57,-1
- db 59,60,61,62,63,64,65,66,67,68
- db 69,70,71,72,73,74,75,76,77,78,79,80,81,82,83
-
- shift_table db -1,27,'!@#$%^&*()_+',8
- db 0,'QWERTYUIOP{}',13
- db -1,'ASDFGHJKL:"~'
- db -1,'|ZXCVBNM<>?',-1,'*'
- db -1,' ',-1
- db 0,0,0,0,0, 0,0,0,0,0
- db -1,-1,'789-456+1230.'
-
- shift_scan db -1,1,2,3,4,5,6,7,8,9,10,11,12,13,14
- db 15,16,17,18,19,20,21,22,23,24,25,26,27,28
- db -1,30,31,32,33,34,35,36,37,38,39,40,41
- db -1,43,44,45,46,47,48,49,50,51,52,53,-1,55
- db -1,57,-1
- db 84,85,86,87,88,89,90,91,92,93
- db 69,70,71,72,73,74,75,76,77,78,79,80,81,82,83
-
- ctrl_table db -1,27,-1,0,-1,-1,-1,-1,-1,-1,-1,-1,31,-1,127
- db 9,11h,17h,5,12h,14h,19h,15h,9,15,16,27,29,10
- db -1,1,19,4,6,7,8,10,11,12,-1,-1
- db -1,-1,28,26,24,3,22,2,14,13,-1,-1,-1,-1,'*'
- db -1,' ',-1
- db 0,0,0,0,0, 0,0,0,0,0
- db -1,-1,0,-1,0,-1,0,-1,0,-1,0,-1,0,-1,-1
-
- ctrl_scan db -1,1,2,3,4,5,6,7,8,9,10,11,12,13,14
- db 15,16,17,18,19,20,21,22,23,24,25,26,27,28
- db -1,30,31,32,33,34,35,36,37,38,39,40,41
- db -1,43,44,45,46,47,48,49,50,51,52,53,-1,55
- db -1,57,-1
- db 94,95,96,97,98,99,100,101,102,103
- db -1,-1,119,-1,132,-1,115,-1,116,-1,117,-1,118,-1,-1
-
- alt_table db -1
- db -1,120,121,122,123,124,125,126,127,128,129,130,131,-1
- db -1,16,17,18,19,20,21,22,23,24,25,-1,-1,-1
- db -1,30,31,32,33,34,35,36,37,38,-1,-1,-1
- db -1,-1,44,45,46,47,48,49,50,-1,-1,-1,-1,-1
- db -1,57,-1
- db 104,105,106,107,108,109,110,111,112,113
- db -1,-1,-1,-1,-1,-1,-1,-1,-1,-1,-1,-1,-1,-1,-1
-
-
- ; Output escape sequences
- ; -----------------------
- cur_off_seq db 3, ESC, '.0' ; cursor off
- cur_on_seq db 3, ESC, '.3' ; cursor on
- clear_seq db 1, 1Ah ; erase screen
- cpos_seq db 4, ESC, '= ' ; set cursor position
- eos_seq db 2, ESC, 'Y' ; erase end of screen
- eol_seq db 2, ESC, 'T' ; erase end of line
- ins_seq db 2, ESC, 'E' ; insert blank line
- inscpm_seq db 12,ESC, '=7 ' ; cursor to 24th line
- db ESC, 'R' ; delete it
- db ESC, '=' ; position cursor at line to
- inscpm_cpos dw 0 ; insert (patch at run time)
- db ESC, 'E' ; insert blank line
- del_seq db 2, ESC, 'R' ; delete blank line
- delcpm_seq db 9, ESC, 'R' ; delete blank line
- db ESC, '=8 ' ; set cursor to last line
- db VT, ESC, 'E' ; up a line, and insert a blank
- attrib_seq db 3, ESC, 'G', 0FFh ; set new attribute
- lf_seq db 5, ESC, '=8 ', LF ; set cursor in last line, LF
- lfcpm_seq db 8, ESC, '=8 ', LF ; set cursor to last line, LF
- db VT, ESC, 'E' ; up a line, and insert a blank
- printer_on db 2, ESC, '`' ; transparent print mode on
- printer_off db 2, ESC, 'a' ; transparent print mode off
- ; ** note- the 'a' is tested
- ; in fl_list routine **
-
- ; PHYSICAL CONSOLE STRUCTURES
- ; ---------------------------
- pc_table dw pc_0,pc_1,pc_2,pc_3 ; pointers to 9
- dw pc_4,pc_5,pc_6,pc_7 ; tables
- dw pc_8
-
- pc_0 db 1 ; physical console number
- dw -1 ; physical serial cursor (invalid)
- db -1 ; physical attribute
- db 0 ; busy flag
- rb 10 ; temporary string buffer
- rb 8 ; set cursor position (8 byte ANSI ?)
- db 0 ; keyboard state flag
- db 0 ; keyboard state flag 1
- db 0 ; keyboard state flag 3
- db 0 ; ALT numpad input char
- rb 4 ; set attribute string
- db 0 ; top screen VC number
- rw 1 ; nat ascii table
- rw 1 ; nat shift table
- rw 1 ; nat ctrl table
- rw 1 ; nat dead keys table
- dw 0ffffh ; last dead key
- db 0 ; dead key buffer
- db 0 ; dead key scan code
- db 0 ; US/national flag
- db 0 ; national language
- db 0 ; 7/8 etc
- db 0 ; mode 0 through 5
- db false ; disable 7 -> 8
- db 0 ; keyboard type
- db 0 ; raw scan
- db 0 ; translated scan
- db 0 ; shift lock
- db 0 ; enhanced shiftlock
- db 0 ; last char to printer
-
- pc_1 db 2 ; physical console number
- dw -1 ; physical serial cursor (invalid)
- db -1 ; physical attribute
- db 0 ; busy flag
- rb 10 ; temporary string buffer
- rb 8 ; set cursor position (8 byte ANSI ?)
- db 0 ; keyboard state flag
- db 0 ; keyboard state flag 1
- db 0 ; keyboard state flag 3
- db 0 ; ALT numpad input char
- rb 4 ; set attribute string
- db 0 ; top screen VC number
- rw 1 ; nat ascii table
- rw 1 ; nat shift table
- rw 1 ; nat ctrl table
- rw 1 ; nat dead keys table
- dw 0ffffh ; last dead key
- db 0 ; dead key buffer
- db 0 ; dead key scan code
- db 0 ; US/national flag
- db 0 ; national language
- db 0 ; 7/8 etc
- db 0 ; mode 0 through 5
- db false ; disable 7 -> 8
- db 0 ; keyboard type
- db 0 ; raw scan
- db 0 ; translated scan
- db 0 ; shift lock
- db 0 ; enhanced shiftlock
- db 0 ; last char to printer
-
- pc_2 db 3 ; physical console number
- dw -1 ; physical serial cursor (invalid)
- db -1 ; physical attribute
- db 0 ; busy flag
- rb 10 ; temporary string buffer
- rb 8 ; set cursor position (8 byte ANSI ?)
- db 0 ; keyboard state flag
- db 0 ; keyboard state flag 1
- db 0 ; keyboard state flag 3
- db 0 ; ALT numpad input char
- rb 4 ; set attribute string
- db 0 ; top screen VC number
- rw 1 ; nat ascii table
- rw 1 ; nat shift table
- rw 1 ; nat ctrl table
- rw 1 ; nat dead keys table
- dw 0ffffh ; last dead key
- db 0 ; dead key buffer
- db 0 ; dead key scan code
- db 0 ; US/national flag
- db 0 ; national language
- db 0 ; 7/8 etc
- db 0 ; mode 0 through 5
- db false ; disable 7 -> 8
- db 0 ; keyboard type
- db 0 ; raw scan
- db 0 ; translated scan
- db 0 ; shift lock
- db 0 ; enhanced shiftlock
- db 0 ; last char to printer
-
- pc_3 db 4 ; physical console number
- dw -1 ; physical serial cursor (invalid)
- db -1 ; physical attribute
- db 0 ; busy flag
- rb 10 ; temporary string buffer
- rb 8 ; set cursor position (8 byte ANSI ?)
- db 0 ; keyboard state flag
- db 0 ; keyboard state flag 1
- db 0 ; keyboard state flag 3
- db 0 ; ALT numpad input char
- rb 4 ; set attribute string
- db 0 ; top screen VC number
- rw 1 ; nat ascii table
- rw 1 ; nat shift table
- rw 1 ; nat ctrl table
- rw 1 ; nat dead keys table
- dw 0ffffh ; last dead key
- db 0 ; dead key buffer
- db 0 ; dead key scan code
- db 0 ; US/national flag
- db 0 ; national language
- db 0 ; 7/8 etc
- db 0 ; mode 0 through 5
- db false ; disable 7 -> 8
- db 0 ; keyboard type
- db 0 ; raw scan
- db 0 ; translated scan
- db 0 ; shift lock
- db 0 ; enhanced shiftlock
- db 0 ; last char to printer
-
- pc_4 db 5 ; physical console number
- dw -1 ; physical serial cursor (invalid)
- db -1 ; physical attribute
- db 0 ; busy flag
- rb 10 ; temporary string buffer
- rb 8 ; set cursor position (8 byte ANSI ?)
- db 0 ; keyboard state flag
- db 0 ; keyboard state flag 1
- db 0 ; keyboard state flag 3
- db 0 ; ALT numpad input char
- rb 4 ; set attribute string
- db 0 ; top screen VC number
- rw 1 ; nat ascii table
- rw 1 ; nat shift table
- rw 1 ; nat ctrl table
- rw 1 ; nat dead keys table
- dw 0ffffh ; last dead key
- db 0 ; dead key buffer
- db 0 ; dead key scan code
- db 0 ; US/national flag
- db 0 ; national language
- db 0 ; 7/8 etc
- db 0 ; mode 0 through 5
- db false ; disable 7 -> 8
- db 0 ; keyboard type
- db 0 ; raw scan
- db 0 ; translated scan
- db 0 ; shift lock
- db 0 ; enhanced shiftlock
- db 0 ; last char to printer
-
- pc_5 db 6 ; physical console number
- dw -1 ; physical serial cursor (invalid)
- db -1 ; physical attribute
- db 0 ; busy flag
- rb 10 ; temporary string buffer
- rb 8 ; set cursor position (8 byte ANSI ?)
- db 0 ; keyboard state flag
- db 0 ; keyboard state flag 1
- db 0 ; keyboard state flag 3
- db 0 ; ALT numpad input char
- rb 4 ; set attribute string
- db 0 ; top screen VC number
- rw 1 ; nat ascii table
- rw 1 ; nat shift table
- rw 1 ; nat ctrl table
- rw 1 ; nat dead keys table
- dw 0ffffh ; last dead key
- db 0 ; dead key buffer
- db 0 ; dead key scan code
- db 0 ; US/national flag
- db 0 ; national language
- db 0 ; 7/8 etc
- db 0 ; mode 0 through 5
- db false ; disable 7 -> 8
- db 0 ; keyboard type
- db 0 ; raw scan
- db 0 ; translated scan
- db 0 ; shift lock
- db 0 ; enhanced shiftlock
- db 0 ; last char to printer
-
- pc_6 db 7 ; physical console number
- dw -1 ; physical serial cursor (invalid)
- db -1 ; physical attribute
- db 0 ; busy flag
- rb 10 ; temporary string buffer
- rb 8 ; set cursor position (8 byte ANSI ?)
- db 0 ; keyboard state flag
- db 0 ; keyboard state flag 1
- db 0 ; keyboard state flag 3
- db 0 ; ALT numpad input char
- rb 4 ; set attribute string
- db 0 ; top screen VC number
- rw 1 ; nat ascii table
- rw 1 ; nat shift table
- rw 1 ; nat ctrl table
- rw 1 ; nat dead keys table
- dw 0ffffh ; last dead key
- db 0 ; dead key buffer
- db 0 ; dead key scan code
- db 0 ; US/national flag
- db 0 ; national language
- db 0 ; 7/8 etc
- db 0 ; mode 0 through 5
- db false ; disable 7 -> 8
- db 0 ; keyboard type
- db 0 ; raw scan
- db 0 ; translated scan
- db 0 ; shift lock
- db 0 ; enhanced shiftlock
- db 0 ; last char to printer
-
- pc_7 db 8 ; physical console number
- dw -1 ; physical serial cursor (invalid)
- db -1 ; physical attribute
- db 0 ; busy flag
- rb 10 ; temporary string buffer
- rb 8 ; set cursor position (8 byte ANSI ?)
- db 0 ; keyboard state flag
- db 0 ; keyboard state flag 1
- db 0 ; keyboard state flag 3
- db 0 ; ALT numpad input char
- rb 4 ; set attribute string
- db 0 ; top screen VC number
- rw 1 ; nat ascii table
- rw 1 ; nat shift table
- rw 1 ; nat ctrl table
- rw 1 ; nat dead keys table
- dw 0ffffh ; last dead key
- db 0 ; dead key buffer
- db 0 ; dead key scan code
- db 0 ; US/national flag
- db 0 ; national language
- db 0 ; 7/8 etc
- db 0 ; mode 0 through 5
- db false ; disable 7 -> 8
- db 0 ; keyboard type
- db 0 ; raw scan
- db 0 ; translated scan
- db 0 ; shift lock
- db 0 ; enhanced shiftlock
- db 0 ; last char to printer
-
- pc_8 db 9 ; physical console number
- dw -1 ; physical serial cursor (invalid)
- db -1 ; physical attribute
- db 0 ; busy flag
- rb 10 ; temporary string buffer
- rb 8 ; set cursor position (8 byte ANSI ?)
- db 0 ; keyboard state flag
- db 0 ; keyboard state flag 1
- db 0 ; keyboard state flag 3
- db 0 ; ALT numpad input char
- rb 4 ; set attribute string
- db 0 ; top screen VC number
- rw 1 ; nat ascii table
- rw 1 ; nat shift table
- rw 1 ; nat ctrl table
- rw 1 ; nat dead keys table
- dw 0ffffh ; last dead key
- db 0 ; dead key buffer
- db 0 ; dead key scan code
- db 0 ; US/national flag
- db 0 ; national language
- db 0 ; 7/8 etc
- db 0 ; mode 0 through 5
- db false ; disable 7 -> 8
- db 0 ; keyboard type
- db 0 ; raw scan
- db 0 ; translated scan
- db 0 ; shift lock
- db 0 ; enhanced shiftlock
- db 0 ; last char to printer
-
-
- ; VIRTUAL CONSOLE STRUCTURES
- ; ---------------------------
- vc_table dw vc_4,vc_5,vc_6,vc_7 ; pointers to 18
- dw vc_8,vc_9,vc_10,vc_11 ; tables
- dw vc_12,vc_13,vc_14,vc_15
- dw vc_16,vc_17,vc_18,vc_19
- dw vc_20,vc_21
-
- vc_4 dw 0 ; cursor row/col
- dw CRT_ROWS_C
- dw CRT_SEG ; CRT segment base
- db 07h ; default attribute
- db INIT_MODE + UPDATE_BIT ; initial VC_MODE
- db CRT_COLS
- db 4 ; 4=VC_NUMBER
- dw 0,con_normal@
- db CRT_ROWS_C ; 24/25 lines
- dw 0B0Ch ; cursor type
- db 0 ; vc_mx
- dw 0 ; VC_OFFSET
- db 7 ; ROS video mode
- dw 0000h ; ansi options count
- rb VC_ANSI_SIZE ; ansi input buffer
-
- db 0 ; virtual port 3B4h
- rb 0 ; virtual port 3B5h
- db 61h,80,52h,0fh,25,6,25,25,2,0dh,0bh,0ch
- db 0,0,0,0,0,0,0,0
- db 0 ; virtual port 3BAh
- rd 3 ; page save area
- db 0 ; installed flag
- dw su_pfk_tbl$,0,0FF00h ; PFK info
- db 20h ; blink attr. enable
- db 0 ; update request
- dw 1ffh ; status line flag
- dw 0 ; ros cursor
-
- vc_5 dw 0 ; cursor row/col
- dw CRT_ROWS_C
- dw CRT_SEG ; CRT segment base
- db 07h ; default attribute
- db INIT_MODE+UPDATE_BIT ; initial VC_MODE
- db CRT_COLS
- db 5 ; 5=VC_NUMBER
- dw 0,con_normal@
- db CRT_ROWS_C ; 24/25 lines
- dw 0B0Ch ; cursor type
- db 0 ; vc_mx
- dw 0 ; VC_OFFSET
- db 7 ; ROS video mode
- dw 0000h ; ansi options count
- rb VC_ANSI_SIZE ; ansi input buffer
-
- db 0 ; virtual port 3B4h
- rb 0 ; virtual port 3B5h
- db 61h,80,52h,0fh,25,6,25,25,2,0dh,0bh,0ch
- db 0,0,0,0,0,0,0,0
- db 0 ; virtual port 3BAh
- rd 3 ; page save area
- db 0 ; installed flag
- dw su_pfk_tbl$,0,0FF00h ; PFK info
- db 20h ; blink attr. enable
- db 0 ; update request
- dw 1ffh ; status line flag
- dw 0 ; ros cursor
-
- vc_6 dw 0 ; cursor row/col
- dw CRT_ROWS_C
- dw CRT_SEG ; CRT segment base
- db 07h ; default attribute
- db INIT_MODE+UPDATE_BIT ; initial VC_MODE
- db CRT_COLS
- db 6 ; 6=VC_NUMBER
- dw 0,con_normal@
- db CRT_ROWS_C ; 24/25 lines
- dw 0B0Ch ; cursor type
- db 0 ; vc_mx
- dw 0 ; VC_OFFSET
- db 7 ; ROS video mode
- dw 0000h ; ansi options count
- rb VC_ANSI_SIZE ; ansi input buffer
-
- db 0 ; virtual port 3B4h
- rb 0 ; virtual port 3B5h
- db 61h,80,52h,0fh,25,6,25,25,2,0dh,0bh,0ch
- db 0,0,0,0,0,0,0,0
- db 0 ; virtual port 3BAh
- rd 3 ; page save area
- db 0 ; installed flag
- dw su_pfk_tbl$,0,0FF00h ; PFK info
- db 20h ; blink attr. enable
- db 0 ; update request
- dw 1ffh ; status line flag
- dw 0 ; ros cursor
-
- vc_7 dw 0 ; cursor row/col
- dw CRT_ROWS_C
- dw CRT_SEG ; CRT segment base
- db 07h ; default attribute
- db INIT_MODE+UPDATE_BIT ; initial VC_MODE
- db CRT_COLS
- db 7 ; 7=VC_NUMBER
- dw 0,con_normal@
- db CRT_ROWS_C ; 24/25 lines
- dw 0B0Ch ; cursor type
- db 0 ; vc_mx
- dw 0 ; VC_OFFSET
- db 7 ; ROS video mode
- dw 0000h ; ansi options count
- rb VC_ANSI_SIZE ; ansi input buffer
-
- db 0 ; virtual port 3B4h
- rb 0 ; virtual port 3B5h
- db 61h,80,52h,0fh,25,6,25,25,2,0dh,0bh,0ch
- db 0,0,0,0,0,0,0,0
- db 0 ; virtual port 3BAh
- rd 3 ; page save area
- db 0 ; installed flag
- dw su_pfk_tbl$,0,0FF00h ; PFK info
- db 20h ; blink attr. enable
- db 0 ; update request
- dw 1ffh ; status line flag
- dw 0 ; ros cursor
-
- vc_8 dw 0 ; cursor row/col
- dw CRT_ROWS_C
- dw CRT_SEG ; CRT segment base
- db 07h ; default attribute
- db INIT_MODE+UPDATE_BIT ; initial VC_MODE
- db CRT_COLS
- db 8 ; 8=VC_NUMBER
- dw 0,con_normal@
- db CRT_ROWS_C ; 24/25 lines
- dw 0B0Ch ; cursor type
- db 0 ; vc_mx
- dw 0 ; VC_OFFSET
- db 7 ; ROS video mode
- dw 0000h ; ansi options count
- rb VC_ANSI_SIZE ; ansi input buffer
-
- db 0 ; virtual port 3B4h
- rb 0 ; virtual port 3B5h
- db 61h,80,52h,0fh,25,6,25,25,2,0dh,0bh,0ch
- db 0,0,0,0,0,0,0,0
- db 0 ; virtual port 3BAh
- rd 3 ; page save area
- db 0 ; installed flag
- dw su_pfk_tbl$,0,0FF00h ; PFK info
- db 20h ; blink attr. enable
- db 0 ; update request
- dw 1ffh ; status line flag
- dw 0 ; ros cursor
-
- vc_9 dw 0 ; cursor row/col
- dw CRT_ROWS_C
- dw CRT_SEG ; CRT segment base
- db 07h ; default attribute
- db INIT_MODE+UPDATE_BIT ; initial VC_MODE
- db CRT_COLS
- db 9 ; 9=VC_NUMBER
- dw 0,con_normal@
- db CRT_ROWS_C ; 24/25 lines
- dw 0B0Ch ; cursor type
- db 0 ; vc_mx
- dw 0 ; VC_OFFSET
- db 7 ; ROS video mode
- dw 0000h ; ansi options count
- rb VC_ANSI_SIZE ; ansi input buffer
-
- db 0 ; virtual port 3B4h
- rb 0 ; virtual port 3B5h
- db 61h,80,52h,0fh,25,6,25,25,2,0dh,0bh,0ch
- db 0,0,0,0,0,0,0,0
- db 0 ; virtual port 3BAh
- rd 3 ; page save area
- db 0 ; installed flag
- dw su_pfk_tbl$,0,0FF00h ; PFK info
- db 20h ; blink attr. enable
- db 0 ; update request
- dw 1ffh ; status line flag
- dw 0 ; ros cursor
-
- vc_10 dw 0 ; cursor row/col
- dw CRT_ROWS_C
- dw CRT_SEG ; CRT segment base
- db 07h ; default attribute
- db INIT_MODE+UPDATE_BIT ; initial VC_MODE
- db CRT_COLS
- db 10 ; 10=VC_NUMBER
- dw 0,con_normal@
- db CRT_ROWS_C ; 24/25 lines
- dw 0B0Ch ; cursor type
- db 0 ; vc_mx
- dw 0 ; VC_OFFSET
- db 7 ; ROS video mode
- dw 0000h ; ansi options count
- rb VC_ANSI_SIZE ; ansi input buffer
-
- db 0 ; virtual port 3B4h
- rb 0 ; virtual port 3B5h
- db 61h,80,52h,0fh,25,6,25,25,2,0dh,0bh,0ch
- db 0,0,0,0,0,0,0,0
- db 0 ; virtual port 3BAh
- rd 3 ; page save area
- db 0 ; installed flag
- dw su_pfk_tbl$,0,0FF00h ; PFK info
- db 20h ; blink attr. enable
- db 0 ; update request
- dw 1ffh ; status line flag
- dw 0 ; ros cursor
-
- vc_11 dw 0 ; cursor row/col
- dw CRT_ROWS_C
- dw CRT_SEG ; CRT segment base
- db 07h ; default attribute
- db INIT_MODE+UPDATE_BIT ; initial VC_MODE
- db CRT_COLS
- db 11 ; 11=VC_NUMBER
- dw 0,con_normal@
- db CRT_ROWS_C ; 24/25 lines
- dw 0B0Ch ; cursor type
- db 0 ; vc_mx
- dw 0 ; VC_OFFSET
- db 7 ; ROS video mode
- dw 0000h ; ansi options count
- rb VC_ANSI_SIZE ; ansi input buffer
-
- db 0 ; virtual port 3B4h
- rb 0 ; virtual port 3B5h
- db 61h,80,52h,0fh,25,6,25,25,2,0dh,0bh,0ch
- db 0,0,0,0,0,0,0,0
- db 0 ; virtual port 3BAh
- rd 3 ; page save area
- db 0 ; installed flag
- dw su_pfk_tbl$,0,0FF00h ; PFK info
- db 20h ; blink attr. enable
- db 0 ; update request
- dw 1ffh ; status line flag
- dw 0 ; ros cursor
-
- vc_12 dw 0 ; cursor row/col
- dw CRT_ROWS_C
- dw CRT_SEG ; CRT segment base
- db 07h ; default attribute
- db INIT_MODE+UPDATE_BIT ; initial VC_MODE
- db CRT_COLS
- db 12 ; 12=VC_NUMBER
- dw 0,con_normal@
- db CRT_ROWS_C ; 24/25 lines
- dw 0B0Ch ; cursor type
- db 0 ; vc_mx
- dw 0 ; VC_OFFSET
- db 7 ; ROS video mode
- dw 0000h ; ansi options count
- rb VC_ANSI_SIZE ; ansi input buffer
-
- db 0 ; virtual port 3B4h
- rb 0 ; virtual port 3B5h
- db 61h,80,52h,0fh,25,6,25,25,2,0dh,0bh,0ch
- db 0,0,0,0,0,0,0,0
- db 0 ; virtual port 3BAh
- rd 3 ; page save area
- db 0 ; installed flag
- dw su_pfk_tbl$,0,0FF00h ; PFK info
- db 20h ; blink attr. enable
- db 0 ; update request
- dw 1ffh ; status line flag
- dw 0 ; ros cursor
-
- vc_13 dw 0 ; cursor row/col
- dw CRT_ROWS_C
- dw CRT_SEG ; CRT segment base
- db 07h ; default attribute
- db INIT_MODE+UPDATE_BIT ; initial VC_MODE
- db CRT_COLS
- db 13 ; 13=VC_NUMBER
- dw 0,con_normal@
- db CRT_ROWS_C ; 24/25 lines
- dw 0B0Ch ; cursor type
- db 0 ; vc_mx
- dw 0 ; VC_OFFSET
- db 7 ; ROS video mode
- dw 0000h ; ansi options count
- rb VC_ANSI_SIZE ; ansi input buffer
-
- db 0 ; virtual port 3B4h
- rb 0 ; virtual port 3B5h
- db 61h,80,52h,0fh,25,6,25,25,2,0dh,0bh,0ch
- db 0,0,0,0,0,0,0,0
- db 0 ; virtual port 3BAh
- rd 3 ; page save area
- db 0 ; installed flag
- dw su_pfk_tbl$,0,0FF00h ; PFK info
- db 20h ; blink attr. enable
- db 0 ; update request
- dw 1ffh ; status line flag
- dw 0 ; ros cursor
-
- vc_14 dw 0 ; cursor row/col
- dw CRT_ROWS_C
- dw CRT_SEG ; CRT segment base
- db 07h ; default attribute
- db INIT_MODE+UPDATE_BIT ; initial VC_MODE
- db CRT_COLS
- db 14 ; 14=VC_NUMBER
- dw 0,con_normal@
- db CRT_ROWS_C ; 24/25 lines
- dw 0B0Ch ; cursor type
- db 0 ; vc_mx
- dw 0 ; VC_OFFSET
- db 7 ; ROS video mode
- dw 0000h ; ansi options count
- rb VC_ANSI_SIZE ; ansi input buffer
-
- db 0 ; virtual port 3B4h
- rb 0 ; virtual port 3B5h
- db 61h,80,52h,0fh,25,6,25,25,2,0dh,0bh,0ch
- db 0,0,0,0,0,0,0,0
- db 0 ; virtual port 3BAh
- rd 3 ; page save area
- db 0 ; installed flag
- dw su_pfk_tbl$,0,0FF00h ; PFK info
- db 20h ; blink attr. enable
- db 0 ; update request
- dw 1ffh ; status line flag
- dw 0 ; ros cursor
-
- vc_15 dw 0 ; cursor row/col
- dw CRT_ROWS_C
- dw CRT_SEG ; CRT segment base
- db 07h ; default attribute
- db INIT_MODE+UPDATE_BIT ; initial VC_MODE
- db CRT_COLS
- db 15 ; 15=VC_NUMBER
- dw 0,con_normal@
- db CRT_ROWS_C ; 24/25 lines
- dw 0B0Ch ; cursor type
- db 0 ; vc_mx
- dw 0 ; VC_OFFSET
- db 7 ; ROS video mode
- dw 0000h ; ansi options count
- rb VC_ANSI_SIZE ; ansi input buffer
-
- db 0 ; virtual port 3B4h
- rb 0 ; virtual port 3B5h
- db 61h,80,52h,0fh,25,6,25,25,2,0dh,0bh,0ch
- db 0,0,0,0,0,0,0,0
- db 0 ; virtual port 3BAh
- rd 3 ; page save area
- db 0 ; installed flag
- dw su_pfk_tbl$,0,0FF00h ; PFK info
- db 20h ; blink attr. enable
- db 0 ; update request
- dw 1ffh ; status line flag
- dw 0 ; ros cursor
-
- vc_16 dw 0 ; cursor row/col
- dw CRT_ROWS_C
- dw CRT_SEG ; CRT segment base
- db 07h ; default attribute
- db INIT_MODE+UPDATE_BIT ; initial VC_MODE
- db CRT_COLS
- db 16 ; 16=VC_NUMBER
- dw 0,con_normal@
- db CRT_ROWS_C ; 24/25 lines
- dw 0B0Ch ; cursor type
- db 0 ; vc_mx
- dw 0 ; VC_OFFSET
- db 7 ; ROS video mode
- dw 0000h ; ansi options count
- rb VC_ANSI_SIZE ; ansi input buffer
-
- db 0 ; virtual port 3B4h
- rb 0 ; virtual port 3B5h
- db 61h,80,52h,0fh,25,6,25,25,2,0dh,0bh,0ch
- db 0,0,0,0,0,0,0,0
- db 0 ; virtual port 3BAh
- rd 3 ; page save area
- db 0 ; installed flag
- dw su_pfk_tbl$,0,0FF00h ; PFK info
- db 20h ; blink attr. enable
- db 0 ; update request
- dw 1ffh ; status line flag
- dw 0 ; ros cursor
-
- vc_17 dw 0 ; cursor row/col
- dw CRT_ROWS_C
- dw CRT_SEG ; CRT segment base
- db 07h ; default attribute
- db INIT_MODE+UPDATE_BIT ; initial VC_MODE
- db CRT_COLS
- db 17 ; 17=VC_NUMBER
- dw 0,con_normal@
- db CRT_ROWS_C ; 24/25 lines
- dw 0B0Ch ; cursor type
- db 0 ; vc_mx
- dw 0 ; VC_OFFSET
- db 7 ; ROS video mode
- dw 0000h ; ansi options count
- rb VC_ANSI_SIZE ; ansi input buffer
-
- db 0 ; virtual port 3B4h
- rb 0 ; virtual port 3B5h
- db 61h,80,52h,0fh,25,6,25,25,2,0dh,0bh,0ch
- db 0,0,0,0,0,0,0,0
- db 0 ; virtual port 3BAh
- rd 3 ; page save area
- db 0 ; installed flag
- dw su_pfk_tbl$,0,0FF00h ; PFK info
- db 20h ; blink attr. enable
- db 0 ; update request
- dw 1ffh ; status line flag
- dw 0 ; ros cursor
-
- vc_18 dw 0 ; cursor row/col
- dw CRT_ROWS_C
- dw CRT_SEG ; CRT segment base
- db 07h ; default attribute
- db INIT_MODE+UPDATE_BIT ; initial VC_MODE
- db CRT_COLS
- db 18 ; 18=VC_NUMBER
- dw 0,con_normal@
- db CRT_ROWS_C ; 24/25 lines
- dw 0B0Ch ; cursor type
- db 0 ; vc_mx
- dw 0 ; VC_OFFSET
- db 7 ; ROS video mode
- dw 0000h ; ansi options count
- rb VC_ANSI_SIZE ; ansi input buffer
-
- db 0 ; virtual port 3B4h
- rb 0 ; virtual port 3B5h
- db 61h,80,52h,0fh,25,6,25,25,2,0dh,0bh,0ch
- db 0,0,0,0,0,0,0,0
- db 0 ; virtual port 3BAh
- rd 3 ; page save area
- db 0 ; installed flag
- dw su_pfk_tbl$,0,0FF00h ; PFK info
- db 20h ; blink attr. enable
- db 0 ; update request
- dw 1ffh ; status line flag
- dw 0 ; ros cursor
-
- vc_19 dw 0 ; cursor row/col
- dw CRT_ROWS_C
- dw CRT_SEG ; CRT segment base
- db 07h ; default attribute
- db INIT_MODE+UPDATE_BIT ; initial VC_MODE
- db CRT_COLS
- db 19 ; 19=VC_NUMBER
- dw 0,con_normal@
- db CRT_ROWS_C ; 24/25 lines
- dw 0B0Ch ; cursor type
- db 0 ; vc_mx
- dw 0 ; VC_OFFSET
- db 7 ; ROS video mode
- dw 0000h ; ansi options count
- rb VC_ANSI_SIZE ; ansi input buffer
-
- db 0 ; virtual port 3B4h
- rb 0 ; virtual port 3B5h
- db 61h,80,52h,0fh,25,6,25,25,2,0dh,0bh,0ch
- db 0,0,0,0,0,0,0,0
- db 0 ; virtual port 3BAh
- rd 3 ; page save area
- db 0 ; installed flag
- dw su_pfk_tbl$,0,0FF00h ; PFK info
- db 20h ; blink attr. enable
- db 0 ; update request
- dw 1ffh ; status line flag
- dw 0 ; ros cursor
-
- vc_20 dw 0 ; cursor row/col
- dw CRT_ROWS_C
- dw CRT_SEG ; CRT segment base
- db 07h ; default attribute
- db INIT_MODE+UPDATE_BIT ; initial VC_MODE
- db CRT_COLS
- db 20 ; 20=VC_NUMBER
- dw 0,con_normal@
- db CRT_ROWS_C ; 24/25 lines
- dw 0B0Ch ; cursor type
- db 0 ; vc_mx
- dw 0 ; VC_OFFSET
- db 7 ; ROS video mode
- dw 0000h ; ansi options count
- rb VC_ANSI_SIZE ; ansi input buffer
-
- db 0 ; virtual port 3B4h
- rb 0 ; virtual port 3B5h
- db 61h,80,52h,0fh,25,6,25,25,2,0dh,0bh,0ch
- db 0,0,0,0,0,0,0,0
- db 0 ; virtual port 3BAh
- rd 3 ; page save area
- db 0 ; installed flag
- dw su_pfk_tbl$,0,0FF00h ; PFK info
- db 20h ; blink attr. enable
- db 0 ; update request
- dw 1ffh ; status line flag
- dw 0 ; ros cursor
-
- vc_21 dw 0 ; cursor row/col
- dw CRT_ROWS_C
- dw CRT_SEG ; CRT segment base
- db 07h ; default attribute
- db INIT_MODE+UPDATE_BIT ; initial VC_MODE
- db CRT_COLS
- db 21 ; 21=VC_NUMBER
- dw 0,con_normal@
- db CRT_ROWS_C ; 24/25 lines
- dw 0B0Ch ; cursor type
- db 0 ; vc_mx
- dw 0 ; VC_OFFSET
- db 7 ; ROS video mode
- dw 0000h ; ansi options count
- rb VC_ANSI_SIZE ; ansi input buffer
-
- db 0 ; virtual port 3B4h
- rb 0 ; virtual port 3B5h
- db 61h,80,52h,0fh,25,6,25,25,2,0dh,0bh,0ch
- db 0,0,0,0,0,0,0,0
- db 0 ; virtual port 3BAh
- rd 3 ; page save area
- db 0 ; installed flag
- dw su_pfk_tbl$,0,0FF00h ; PFK info
- db 20h ; blink attr. enable
- db 0 ; update request
- dw 1ffh ; status line flag
- dw 0 ; ros cursor
-
- ; save area for memory allocation blocks
- mp_entry_ptr dw offset mp_table_entries ; current pointer
- mp_table_entries rd 28 ; 9 phys + 18 virtual console
- ; 4k block entries, rounded up
- ; to 16k blocks
- flushstr db 'Flush' ; Flush RSP name
- PINstr db 'PIN' ; pin rsp name
-
- active_vc$ db 0 ; current active virtual cons
- active_top db 0 ; current top screen
- pc_kbd_save$ rb 39 ; ROS data area keyboard data
- ; all terminals use same dummy
- ; area.
-
- save_mode db 3 ; save crt mode on dispatch
- save_cols db 80 ; copy the ROS data here
- save_cursor dw 0 ; (and cols, and cursor)
- save_6845 dw 0 ; (and crt address)
- save_sl_flags dw 0 ; status line flag save area
-
- bad_mode_msg db 0dh, 0ah
- db 'Concurrent Error: This program can not run on a non-graphics console.'
-
- BAD_MODE_MSG_LEN equ offset $ - offset bad_mode_msg
-
- end
-
- ; END OF PCTERM.A86
-