📄 cmdedit.asm
字号:
cmp byte ptr [si],'-' ;Comment char ?
jne @blankline_20
clc
jmp short @blankline_99
@blankline_20:
mov cx,lastchar
sub cx,si ;CX<-num chars in line
call near ptr skip_whitespace ;CF=1 if end of string
cmc
@blankline_99:
@restore
ret
blankline endp
; Extend the resident part of the installation code to form a buffer to
; hold the prompt and one to hold the current macro line arguments.
; - 128 bytes from PSP + initial portion of CSEG.
tsr_install_end LABEL BYTE
IF ($-entry) LT (2+PROMPT_BUF_SIZE+LINEBUF_SIZE - 128)
DB (2+PROMPT_BUF_SIZE+LINEBUF_SIZE - 128 - ($-entry)) DUP (?)
ENDIF
pgm_name db SIGNATURE1,CR,LF
copyrite db SIGNATURE2,32,254,32,SIGNATURE3,CR,LF,LF,DOLLAR,26
; Major and minor DOS versions.
dos_version_major db ?
dos_version_minor db ?
;dos_envseg dw 0 ;Segment for DOS
; environment. 0 indicates
; we don't know it.
resident db 0 ;1 after becoming resident
abort_entry_stack dw ? ;Storage for stack state to be
; restored when processing is aborted
abort_msg_hd db '*** CMDEDIT : ' ;Header for abort message
ABORT_HDR_LEN equ $-abort_msg_hd
abort_msg_tl db ' Any ongoing macro aborted! ***' ;Tail for abort message
ABORT_TAIL_LEN equ $-abort_msg_tl
; The following are error messages displayed by routine abort_processing.
; ALL MESSAGES MUST BE SHORT ENOUGH TO FIT INTO LINEBUF TOGETHER WITH
; abort_msg_hd and abort_msg_tl. The order of messages must be same as
; the order of Error code definitions in file common.inc
abort_msg_table LABEL BYTE
line_trunc_msg db 'Line too long.'
saw_sig_msg db 'Command aborted by user.'
dirstk_empty_msg db 'Directory stack empty.'
dirstk_msg db 'Invalid dir or stack full.'
dirstk_only_dos db 'Command is DOS only.'
nested_macro_msg db 'Nested macro definition.'
nested_delm_msg db 'DELM used inside macro.'
ctrl_brk_msg db 'Control-Break.'
abort_msg_end LABEL BYTE
; The following table holds pointers to each entry in the message table
; above. The length of each message is also stored here.
abort_msg_ptrs LABEL WORD
dw line_trunc_msg
dw saw_sig_msg-line_trunc_msg
dw saw_sig_msg
dw dirstk_empty_msg-saw_sig_msg
dw dirstk_empty_msg
dw dirstk_msg-dirstk_empty_msg
dw dirstk_msg
dw dirstk_only_dos-dirstk_msg
dw dirstk_only_dos
dw nested_macro_msg-dirstk_only_dos
dw nested_macro_msg
dw nested_delm_msg-nested_macro_msg
dw nested_delm_msg
dw ctrl_brk_msg-nested_delm_msg
dw ctrl_brk_msg
dw abort_msg_end-ctrl_brk_msg
macrosize dw 512 ;Default size of macro buffer
symsize dw 512 ;Default size of symbol buffer
dossize dw 512 ;Default size of DOS history buffer
dirsize dw 128 ;Default size of directory stack buffer
;+-------------------------+
;| CMDEDIT state variables |
;+-------------------------+
; The variables source and macro_level together indicate the source of
; the next line. If macro_level is non-zero, the next line is obtained
; from an ongoing macro expansion. If macro_level is 0, then the
; variable source contains the address of the function to call to
; return the next line. This will be either get_kbd_line or
; get_file_line.
macro_level dw 0
source dw ? ;filled in during initialization
;+----------------------------------------------------------+
;| CMDEDIT commands. All commands preceded by a length byte.|
;| For each command that is added, make sure you update the |
;| table cmd_func_table below. |
;+----------------------------------------------------------+
cmd_table LABEL BYTE
defs db 4,'defs' ;Define a single line macro
defm db 4,'defm' ;Start multiline macro definition
pushd db 5,'pushd' ;Push on directory stack
popd db 4,'popd' ;Pop from directory stack
chd db 3,'chd' ;Change disk and directory
dels db 4,'dels' ;Delete a symbol
delm db 4,'delm' ;Delete a macro
rsthist db 7,'rsthist' ;Reset history stack
rstmac db 6,'rstmac' ;Reset macro buffer
rstsym db 6,'rstsym' ;Reset symbol buffer
rstdir db 6,'rstdir' ;Reset directory stack
cmdstat db 7,'cmdstat' ;Show macro and symbol status
cmd_table_end db 0 ;Terminate with a 0
MAX_CMD_LEN equ 7 ;Length of longest command
; Note endm is not a command except during a macro definition.
endm_cmd db 4,'endm' ;End multiline macro definition
;+--------------------------------------------------------------+
;| CMDEDIT command functions. Must be in same order as commands.|
;+--------------------------------------------------------------+
cmd_func_table label WORD
dw execute_defs
dw execute_defm
dw execute_pushd
dw execute_popd
dw execute_chd
dw execute_dels
dw execute_delm
dw execute_rsthist
dw execute_rstmac
dw execute_rstsym
dw execute_rstdir
dw execute_cmdstat
linebuf_prefix db 0 ;Fill byte/Sentinel before linebuf.
; Used in code to allow uniform
; checking of first linebuf character.
linebuf db LINEBUF_SIZE DUP (?) ;Temporary line buffer.
LINEBUF_END equ $
linebuf_suffix db ? ;Need a byte at end of
; linebuf in various places
macro_ignore_char db ';' ;Character used to prevent macro
; and symbol expansion.
lastchar dw ? ;Points beyond last char in the line
cur_macro_len dw ? ;Length of data in cur_macro
dot dw ? ;Current position in line
disp_begin dw ? ;disp_begin and disp_end are
disp_end dw ? ; markers into the line buffer
; that are used to keep track
; of the range that has been
; changed. This is used to
; selectively update the display.
edit_mode db ? ;1 if insert mode, else 0
default_imode db 0 ;By default overtype mode
linelimit dw ? ;Upper limit for linebuf based
; on user's buffer length
noted_dos_seg db 0 ;1 after we have noted DOS segment
dos_seg dw ? ;Stores DOS segment
in_appl db 0 ;0 if dos, 1 if application
user_command db 0 ;This is set to 1 by certain
; CMDEDIT commands to return a
; string to the caller.
; (Basically put in as a kluge
; to get the prompt right after
; a pushd/popd/chd)
;+------------+
;| Video data |
;+------------+
video_page db ? ;Current video page
screen_width db ? ;width of screen
initial_curcol label byte ;initial cursor column
initial_curpos dw ? ;Initial cursor position
;Next two words must be contiguos
omode_cursor dw ? ;Cursor for overtype mode
imode_cursor dw ? ;Cursor for insert mode
caller_cursor dw ? ;Cursor shape of caller
silent db 0 ;non-0 if bell should not be rung
;+-------------------------------------------------------------------------+
;|Storage areas for various registers when called through INT 21 interface.|
;+-------------------------------------------------------------------------+
ssreg dw ?
spreg dw ?
old_int21h LABEL DWORD ;Storage for previous int 21h vector
old_int21vec DW 2 DUP (?)
new_sp dw ? ;Store our stack ptr (bottom of stack).
;This is first para BEYOND cmdedit's memory.
prev_isr1b dd ? ;Previous control break handler
; check_break is set to 1 on entry to cmdedit, and restored to 0 on exit. If
; 1 on entry, then calling program must have been aborted with a break or
; critical error. The CMDEDIT Ctrl-Break ISR increments this flag every
; time it is called. If it is > 1, inside CMDEDIT, it indicates that a
; ctrl-break was entered. This allows runaway macros and symbols to be
; aborted.
check_break dw 0
trap_break db 0 ;If 1, does not allow original
; Ctrl-Break handler to see the
; Ctrl_break
;+
; FUNCTION : cmdedit_isr
;
; This is our replacement for the DOS INT 21h handler.
;
; Parameters:
; AH = function code
;
; Register(s) destroyed:
;-
cmdedit_isr proc far
ASSUME CS:DGROUP,DS:NOTHING,ES:NOTHING,SS:NOTHING
pushf ;Save flags
cmp ah,0Ah ;Is it the buffered input function ?
je @cmdedit_isr_10 ;If so go on carry out our duty
popf ;else restore flags
jmp cs:old_int21h ;and execute the original ISR
@cmdedit_isr_10:
;Save registers
mov cs:ssreg,ss ;Stack segment
mov cs:spreg,sp ; and pointer
cli ;Wanna change stack
push cs
pop ss
mov sp,cs:new_sp ;Bottom of stack
ASSUME SS:DGROUP
sti ;OK to interrupt now
@save ax,bx,cx,dx,si,di,bp,ds,es
xchg bx,dx
mov al,byte ptr ds:[bx] ;Length of caller buffer
xchg dx,bx
xor ah,ah ;AX<-length of caller's buffer
push ds ;Save user segment
mov cx,cs
mov ds,cx ;Init DS, ES to point to DGROUP
mov es,cx
ASSUME DS:DGROUP,ES:DGROUP
add ax,offset dgroup:linebuf ;AX->last allowable linebuf
; location + 1
dec ax ;Need room for CR at end of line
mov linelimit,ax ;Store it
pop ax ;AX <- User's buffer segment
;DX already contains offset of
; user buffer
call near ptr cmdedit ;Main routine
@restore
cli
mov ss,cs:ssreg
mov sp,cs:spreg
sti
popf
iret
cmdedit_isr endp
;+
; FUNCTION : cmdedit
;
; Main routine called by the INT 21h ISR to get next line.
; General Algorithm:
; (1) Get the next line from the keyboard/macro expansion/file.
; (2) Check for line begins with a macro. If so, expand it and
; repeat step (2). Else go onto step (3).
; (3) Check if the line is an internal CMDEDIT command. If so, execute
; it and return to step (1).
; (4) Copy line to caller's buffer and return.
;
; Parameters:
; AX = segment of user's buffer
; DX = offset of user's buffer
;
; Returns:
; The next input line is copied into the user's buffer.
; Register(s) destroyed:
; All except segment registers.
;-
cmdedit proc near
push es ;Save ES
push ax ;Caller's buffer segment
push dx ;Caller's buffer offset
mov trap_break,1 ;Trap Ctrl-Break handler
mov cx,1
xchg cx,CS:check_break ;Check if last call did not
; exit normally. Also set flag
; for this call.
jcxz @cmdedit_0 ;Last exit was OK
mov macro_level,0 ;No it was not, so reset input
mov source,offset DGROUP:get_kbd_line
@cmdedit_0:
call near ptr init_screen ;Get screen/cursor data
cmp noted_dos_seg,0 ;Have we noted the DOS segment ?
jne @cmdedit_1 ;Jump if we know it already
mov noted_dos_seg,1 ;Remember that we now know it
mov dos_seg,ax ;Else remember it
;No point jumping over next
;couple of statements.
@cmdedit_1:
mov cx,1 ;Assume caller is not DOS
cmp ax,dos_seg ;Is the caller DOS ?
jne @cmdedit_2
dec cx ;Yes, CX<-0
@cmdedit_2:
mov in_appl,cl ;Rememeber whether caller is dos
call near ptr hist_type ;Set the history type (DOS/appl)
; cmdedit_abort_entry is the entry point when command proessing is
; aborted for any reason. It is jumped to from abort_processing
mov abort_entry_stack,sp ;Remember stack state
cmdedit_abort_entry LABEL PROC
@cmdedit_3:
call near ptr reset_line ;Reset cursor, line etc.
call near ptr get_next_line ;Get the next line from appropriate
; source (stored in linebuf)
@cmdedit_10:
cmp check_break,2 ;Check for any control breaks
jb @cmdedit_11 ;No ctrl-breaks
mov check_break,1
mov ax,E_CTRL_BREAK ;Message number
jmp abort_processing
@cmdedit_11:
;If the first character is a ignore character, do not do a macro or symbol
;expansion.
mov cx,lastchar ;End of line
mov si,offset DGROUP:linebuf ;SI->line buffer
sub cx,si ;CX<-length of line
jcxz @cmdedit_15 ;Empty line, keep going since it
; can still be a macro or symbol
mov al,[si] ;AL<-first char of line
cmp al,macro_ignore_char
jne @cmdedit_15
; First is an ignore character so move up all characters and return
mov di,si ;DI->start of line
inc si ;SI->first char to copy
dec cx ;1 less character
dec lastchar
; Assume ES==DS, direction flag clear
rep movsb ;Move the bytes
jmp @cmdedit_25 ;Yes, exit with carry flag set
@cmdedit_15:
call near ptr expand_symbol ;Check if symbol and expand
jnc @cmdedit_10 ;If expanded, recurse
call near ptr expand_macro ;Check if line is a macro
; and expand if possible.
jnc @cmdedit_10 ;If expanded, do recursively.
; (note that currently recursion
; will take place only on the
; last line of a macro definition)
@cmdedit_25:
mov user_command,0 ;Init flag
call near ptr cmdedit_cmd ;Check if CMDEDIT command
jc @cmdedit_30 ;No
; CMDEDIT command, but might want to return to caller anyway.
cmp user_command,1 ;If 1, then return string to caller
je @cmdedit_30 ; klugery here for PUSHD/POPD/CHD
; to intentionally return a
; blank line to DOS in order to
; get prompt right.
jmp short @cmdedit_3
@cmdedit_30:
; Expand variables if any.
call near ptr replace_vars
; Check if line too long for user buffer.
mov ax,lastchar ;AX->last character in buffer
cmp ax,linelimit
jbe @cmdedit_80 ;We're OK
mov ax,E_TRUNCATE ;error - line too long
jmp near ptr abort_processing
@cmdedit_80:
sub ax,offset DGROUP:linebuf ;AX<-length of line
; OK now we have a line to give to the caller. Copy it into caller's
; buffer and return.
pop di ;Caller's buffer offset
pop es ;Caller's buffer segment
inc di ;ES:DI->second byte of user buffer
stosb ;Store line length
mov si,offset DGROUP:linebuf ;SI->Source string
xchg cx,ax ;CX<-length of string
rep movsb ;Copy bytes
mov al,CR
stosb ;Store terminating carraige-return
; Set cursor shape to caller's shape
call near ptr restore_cursor ;Restore user's cursor shape
mov check_break,0 ;Reset flag
mov trap_break,0 ; Ctrl-Break handler
pop es ;Restore ES
ret
cmdedit endp
;+
; FUNCTION : get_next_line
;
; Gets the next line from the appropriate source and stores it in
; the line buffer. THe source of the line may be either a macro
; expansion or a file or the keyboard.
;
; Parameters:
; None.
;
; Returns:
; Nothing
; Register(s) destroyed:
;-
get_next_line proc near
mov lastchar,offset DGROUP:linebuf
;Empty line (in case not
; already done)
call near ptr get_macro_line ;Get next line in expansion
jnc @get_next_line_99 ;Jump if there is a next line
;No next line in expansion, so
;get line from keyboard/file
@get_next_line_10:
call [source] ;get_kbd_line / get_file_line
⌨️ 快捷键说明
复制代码
Ctrl + C
搜索代码
Ctrl + F
全屏模式
F11
切换主题
Ctrl + Shift + D
显示快捷键
?
增大字号
Ctrl + =
减小字号
Ctrl + -