home
***
CD-ROM
|
disk
|
FTP
|
other
***
search
/
Power-Programmierung
/
CD1.mdf
/
magazine
/
pcmagazi
/
1990
/
16
/
cmdedit.asm
< prev
next >
Wrap
Assembly Source File
|
1990-06-26
|
47KB
|
1,747 lines
;
; CMDEDIT.ASM
;(c) 1989, 1990 PC Magazine and Ashok P. Nadkarni
;
SIGNATURE1 equ <"CMDEDIT 2.0 (c) 1990 Ziff Communications Co.">
SIGNATURE2 equ <"PC Magazine">
SIGNATURE3 equ <"Ashok P. Nadkarni">
; Main module for command line editor.
INCLUDE common.inc
INCLUDE general.inc
INCLUDE ascii.inc
INCLUDE buffers.inc
INCLUDE dos.inc
INCLUDE bios.inc
PUBLIC dos_version_major
PUBLIC dos_version_minor
PUBLIC resident
PUBLIC macro_level
PUBLIC cur_macro
PUBLIC cur_macro_len
PUBLIC linebuf
PUBLIC linelimit
PUBLIC dot
PUBLIC lastchar
PUBLIC LINEBUF_END
PUBLIC edit_mode
PUBLIC default_imode
PUBLIC caller_cursor
PUBLIC omode_cursor
PUBLIC pgm_name
PUBLIC macrosize
PUBLIC symsize
PUBLIC dossize
PUBLIC dirsize
PUBLIC mfilename
PUBLIC mfile_seen
PUBLIC macro_ignore_char
PUBLIC cmdlen
PUBLIC silent
PUBLIC endm_cmd
PUBLIC defs
PUBLIC defm
PUBLIC tsr_install_end
PUBLIC source
PUBLIC abort_processing
PUBLIC disp_line
PUBLIC set_disp_marks
PUBLIC insert_at_dot
PUBLIC insert_chars
PUBLIC remove_chars
PUBLIC erase_to_dot
PUBLIC init_over
PUBLIC line_to_scr
PUBLIC get_next_line
PUBLIC reset_line
PUBLIC in_appl
PUBLIC user_command
PUBLIC our_break_handler
PUBLIC prev_isr1b
PUBLIC old_int21vec
PUBLIC cmdedit_isr
PUBLIC makeroom
PUBLIC locate_dosenv
PUBLIC cmdedit
IFE TSR
PUBLIC cmdedit_cmd
PUBLIC debug_loop
PUBLIC freadline
PUBLIC get_file_line
PUBLIC read_cmdfile
PUBLIC disp_prompt
PUBLIC prompt
PUBLIC init_screen
ENDIF
DGROUP GROUP CSEG
CSEG SEGMENT PARA PUBLIC 'CODE'
EXTRN install_begin:BYTE
EXTRN install:PROC
EXTRN execute_defs:PROC
EXTRN execute_defm:PROC
EXTRN execute_dels:PROC
EXTRN execute_delm:PROC
EXTRN execute_cmdstat:PROC
EXTRN execute_pushd:PROC
EXTRN execute_popd:PROC
EXTRN execute_chd:PROC
EXTRN hist_init:PROC
EXTRN hist_type:PROC
EXTRN hist_top:PROC
EXTRN dirs_init:PROC
EXTRN macro_init:PROC
EXTRN symbol_init:PROC
EXTRN expand_macro:PROC
EXTRN expand_symbol:PROC
EXTRN get_macro_line:PROC
EXTRN skip_whitespace:PROC
EXTRN skip_nonwhite:PROC
EXTRN stre_cmp:PROC
EXTRN get_kbd_line:PROC
EXTRN getargs:PROC
EXTRN file_error:BYTE
EXTRN abort_install:PROC
EXTRN expand_var:PROC
EXTRN execute_rsthist:PROC
EXTRN execute_rstmac:PROC
EXTRN execute_rstsym:PROC
EXTRN execute_rstdir:PROC
; Define important fields in the PSP.
ASSUME CS:DGROUP
ORG 2Ch
env dw ? ;Segment of environment block
ORG 80h
PROMPT_BUF_SIZE EQU 80
prompt LABEL BYTE ;buffer used for prompt after TSRing
cmdlen DB ? ;Offset 80h in the PSP contains length of command
; line when program is invoked
ORG 80h+PROMPT_BUF_SIZE
prompt_length dw ?
cur_macro LABEL BYTE ;Start of area used after TSRing to
; store the current macro expansion.
ASSUME CS:DGROUP,DS:DGROUP,ES:DGROUP,SS:DGROUP
ORG 100h
entry: jmp install
; The following variables are LOST after TSRing since the space is
; reused for other purposes.
mfilename db 64 DUP (0) ;Storage for ASCIIZ filename
mfile_seen db 0 ;Indicate if command line
; specified an init file
mfile_handle dw ? ;Handle for open file
; Entry init_over is jumped to from the installation code after all the
; command line parsing has been done. This part of the installation
; remains resident. It is not kept with the install code because that
; code sections gets overwritten with various buffers.
init_over proc near
; The command parameters have been parsed. Now get ready to terminate.
mov si,offset DGROUP:install_begin
;First location in installation code
mov bx,si ; is where the buffers start.
mov ax,dossize ;Size of DOS history buffer
add si,ax ;SI <- end of DOS buffer
xor cx,cx ;Indicate DOS mode
call near ptr hist_init ;Initialize DOS history buffer
mov bx,si ;Repeat for directory stack
mov ax,dirsize
add si,ax
call near ptr dirs_init
mov bx,si ;And finally for the macros
mov ax,macrosize
add si,ax
call near ptr macro_init
mov bx,si ;And finally for the macros
mov ax,symsize
add si,ax
call near ptr symbol_init
; SI->end of buffer area
; Read in the command file
call near ptr init_screen ;Need to do this because
; reset_line (called by
; execute_defm) restores cursor shape.
call near ptr read_cmdfile
; Initialize var source to get the next line from the keyboard.
mov source,offset DGROUP:get_kbd_line
; All data structures initalized. Now setup stack pointer, release
; unneeded memory back to DOS, set up interrupt handler and TSR.
push es ;save ES
mov es,env ;Don't need environment block
ASSUME ES:NOTHING
mov ah,49h
int 21h ;Release the block
IF TSR
mov ax,3521h ;Get old interrupt vector
int 21h
mov old_int21vec,bx ;Remember offset
mov old_int21vec+2,es ;Remember segment
mov dx,offset DGROUP:cmdedit_isr ;Our handler
;DS = CS already
mov ax,2521h ;Set intr vector
int 21h
ENDIF
pop es ;Restore ES
ASSUME ES:DGROUP
lea dx,STACK_SIZE+15[si] ;Calculate end of TSR portion
; DX<-num bytes to keep resident
and dl,0f0h ; rounded to para
; Note DX->BEYOND last byte of program
mov new_sp,dx ;Remember it
mov resident,1 ;Indicate we're TSR
IFE TSR
; Don't actually TSR
debug_loop:
@init_over_10:
@DispCh CR
@DispCh LF
lea dx,dummy_prompt
@DispStr dx
mov dx,offset DGROUP:debug_buf ;Offset
mov debug_buf,DEBUG_BUFSIZE-2
mov ah,0Ah ;Function code
pushf ;Simulate interrupt
push cs ;Simulate interrupt
call near ptr cmdedit_isr ;Simulate interrupt
jmp short @init_over_10 ;Keep looping
debug_buf db 256 DUP (?)
DEBUG_BUFSIZE equ $-debug_buf
dummy_prompt db "dummy>",DOLLAR
ENDIF
int 27h ;TSR
init_over endp
;+
; FUNCTION : read_cmdfile
;
; Reads commands from a file. The filename is in the variable
; mfilename. The space occupied this function is overwritten
; after TSRing so it must NOT be called once the program is resident.
;
; Parameters:
; None.
;
; Returns:
; AX = 0 on success, any other value if failure
;
; Register(s) destroyed:
; AX,BX,CX,DX
;-
read_cmdfile proc near
@save si,di
cmp mfile_seen,0
je @read_cmdfile_100 ;No file specified
@OpenFil mfilename,0
jc @read_cmdfile_92 ;CF=1 for errors
@read_cmdfile_30:
mov source,offset DGROUP:get_file_line
; We want get_next_line to read
; from the file.
mov mfile_handle,ax ;Save file handle
@read_cmdfile_50:
mov dx,offset DGROUP:linebuf ;Destination for file line
mov ax,LINEBUF_SIZE
call near ptr freadline ;Get next line into buffer
;AX contains line length
jnc @read_cmdfile_80 ;no error or EOF
or ax,ax ;No more bytes ?
jz @read_cmdfile_99 ;EOF is not error
jmp short @read_cmdfile_90 ;Error, abort install
@read_cmdfile_80:
mov dx,offset DGROUP:linebuf
add dx,ax
mov lastchar,dx ;Update end of line
call near ptr cmdedit_cmd ;Execute as a command
jnc @read_cmdfile_50 ;If not a command, better be a
; blank line
call near ptr blankline
jnc @read_cmdfile_50 ;Ignore blank lines
; If not blank line and not CMDEDIT command, then error error handler
@read_cmdfile_90:
; Come here for error
@ClosFil mfile_handle ;Close the file
@read_cmdfile_92:
@DispStr file_error
mov ax,-1 ;Indicate exit code
jmp abort_install ;Exit program
@read_cmdfile_99:
@ClosFil mfile_handle ;Close the file
jc @read_cmdfile_92 ;Abort if error closnig file
@read_cmdfile_100:
@restore
ret
read_cmdfile endp
;+
; FUNCTION : get_file_line
;
; Called indirectly through the global variable 'source'.
; Currently this routine exists only during installation and must
; NOT be called once the program is a TSR. The next line from the
; file is copied to linebuf. If there is no next line, the
; installation is aborted.
;
; Parameters:
; None.
;
; Returns:
; Nothing.
; Register(s) destroyed:
; AX,BX,CX,DX
;-
get_file_line proc near
mov dx,offset DGROUP:linebuf
mov ax,LINEBUF_SIZE
call near ptr freadline
jnc @get_file_line_99
;Error reading file or EOF
@DispStr file_error
jmp abort_install
@get_file_line_99:
mov dx,offset DGROUP:linebuf
add dx,ax
mov lastchar,dx ;Update end of line
ret
get_file_line endp
;+
; FUNCTION : freadline
;
; Reads a line at a time from the file whose handle is in
; mfile_handle into the buffer pointed to by AX. If the buffer is
; too small or if there are any errors, the routine returns with CF set.
; If EOF, then AX = 0 and CF is set.
;
; Parameters:
; DX = address of buffer
; AX = size of buffer
;
; Returns:
; CF = 0 if no errors (and not EOF), else 1.
; AX = num chars in line if CF = 0.
; 0 if EOF, ffff for other errors if CF = 1
;
; Register(s) destroyed:
;-
freadline proc near
@save si,di
mov di,dx ;DI->buffer
mov bx,mfile_handle
mov si,ax ;SI<-num bytes to read
xchg cx,ax ;CX<-num bytes to read
mov ah,3Fh ;File read function
int 21h
jc @freadline_99 ;Error!
mov cx,ax ;CX<-num bytes read
jcxz @freadline_99_a ;EOF (note AX is 0 indicating EOF)
xchg dx,ax ;DX<-num bytes read
mov bx,di ;BX->start of buffer
mov al,CR
repne scasb ;Hunt for CR
je @freadline_50 ;Found
; No CR found, this better be the last line in file.
cmp dx,si ;Were fewer bytes read than requested?
cmc
jc @freadline_99 ;Error
push dx ;Save length of line
xor ax,ax ;AX<-num extra bytes read
jmp short @freadline_60
@freadline_50:
stc ;Assume line too long
jcxz @freadline_99 ;error if match in last char
; (line too long)
cmp BYTE PTR [di],LF ;Next char must be linefeed
stc ;Assume error
jne @freadline_99 ;Indeed an error if not LF
mov ax,di
sub ax,bx ;AX<-num chars including CR
sub dx,ax
xchg ax,dx
dec dx ;DX<-num chars in line
dec ax ;AX<-num extra chars read
push dx ;Save num chars in line
@freadline_60:
; Top of stack contains num bytes in line.
; Now position file pointer to 'unread' characters.
; AX contains the num of extra characters read.
neg ax
cwd
mov cx,ax
xchg cx,dx ;CX:DX<-num bytes to 'unread'
mov bx,mfile_handle
mov ax,4201h ;Move file ptr relative
int 21h ;Seek file relative
; CF set/reset by error status
pop ax ;AX<-num bytes in line
clc ;No errors
jmp short @freadline_100
@freadline_99:
mov ax,0ffffh ;Non-EOF error
@freadline_99_a:
stc ;Indicate error or EOF
@freadline_100:
@restore
ret
freadline endp
;+
; FUNCTION : blankline
;
; Checks whether the line in linebuf is blank or not. Also treats it
; as blank line if it begins with a `-'.
;
; Parameters:
; None.
;
; Returns:
; CF = 0 if blank line, else 1.
; Register(s) destroyed:
; AX,BX,CX,DX
;-
blankline proc near
@save si
mov si,offset DGROUP:linebuf
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
@get_next_line_99:
ret
get_next_line endp
;+
; FUNCTION : replace_vars
;
; Replaces all the variables in the current line with their
; expansions. If the line is too long, aborts with a truncation
; error.
;
; Parameters:
; None.
;
; Returns:
; Nothing.
; Register(s) destroyed:
; AX,BX,CX,DX
;-
replace_vars proc near
call near ptr expand_var ;CF set if error. AX
; contains error code
jnc @replace_vars_99
jmp near ptr abort_processing ;Abort processing
@replace_vars_99:
ret
replace_vars endp
;+
; FUNCTION : get_curpos
;
; Returns the current cursor position.
;
; Parameters:
; Global video_page indicates the page.
;
; Returns:
; DX = Current cursor position.
; CX = Current cursor scan lines.
; Register(s) destroyed: AX,BX
;-
get_curpos proc near
@GetCur video_page
ret
get_curpos endp
;+
; FUNCTION : set_disp_marks
;
; Sets the marks disp_begin and disp_end to indicate the start
; and end positions in the line that have been changed. The
; routine is passed two parameters which indicate
; the potentially new values for disp_begin and disp_end
; respectively. However the global disp_begin is changed only if
; the new value is less than the current value. Similarly
; disp_end is changed only if the new value is greater than the
; current value.
;
; Parameters:
; AX = potential disp_end
; DX = potential disp_begin
;
; Returns:
; Nothing.
; May set globals disp_begin and disp_end.
;
; Register(s) destroyed: None.
;-
set_disp_marks proc near
cmp ax,disp_end ;New value greater ?
jb @set_disp_marks_10 ;No
mov disp_end,ax ;New disp_end
@set_disp_marks_10:
cmp dx,disp_begin ;New value smaller
jnb @set_disp_marks_20 ;No
mov disp_begin,dx ;New disp_begin
@set_disp_marks_20:
ret
set_disp_marks endp
;+
; FUNCTION : disp_line
;
; Displays the current contents of the line buffer. Since the
; entire line is not redisplayed everytime, all procedures that
; change the contents of the line buffer have to follow certain
; rules in order to make sure the display correctly shows the
; line. The variable disp_begin must be set to the earliest
; position in the line that has been changed and disp_end to beyond
; last position in the line that has been changed.;
; Parameters:
; None.
;
; Returns:
; Nothing
; Register(s) destroyed:
;-
disp_line proc near
@save si,di
mov ax,disp_begin ;Lower limit of changed chars
mov si,ax
mov cx,disp_end ;CX->byte after last char that
; has changed
sub cx,si ;CX<-num chars to be output
jcxz @disp_line_90 ;Nothing to be updated
push cx ;Save CX across calls
call near ptr line_to_scr ;Move cursor to corresponding
; position on the screen.
; OK, now we are ready to begin updating the screen.
call near ptr get_curpos ;DX<-current cursor position
pop cx ;Restore CX
mov di,lastchar ;DI->beyond last char
cmp si,di ;Beyond last char?
je @disp_line_25 ;Go display blanks
@disp_line_10: ;Loop to output chars
lodsb ;AL<-next char
@DispCh al ;Display it
push cx ;Save CX
push dx ;Save old cursor position
call near ptr get_curpos ;DX<-new cursor position
; BX destroyed
pop bx ;BX<-old cursor position
pop cx ;Restore CX
or dl,dl ;Column 0 ?
jne @disp_line_20 ;Nope
;Col 0
cmp bh,dh ;Is the row the same
jne @disp_line_20
;yes, screen scrolled
dec initial_curpos+1 ;Decrement the row for initial
; cursor position
@disp_line_20:
mov bx,dx ;New cursor position
cmp si,di ;Beyond last char?
loopne @disp_line_10 ;Keep looping until count exhausted or
; beyond last char
@disp_line_25:
; Now all changed positions have been displayed. If CX is not 0,
; then the remaining char positions have to be
; replaced with blanks. Note that since we are now overwriting
; previously displayed positions, no need to check for line
; wraparound or scroll.
jcxz @disp_line_90 ;No more chars
mov al,' ' ;Overwrite with blanks
@disp_line_30:
@DispCh al
loop @disp_line_30
@disp_line_90:
mov ax,dot
mov disp_begin,ax ;Initialize for next call
mov disp_end,ax
call near ptr line_to_scr ;Set cursor at dot
@restore
ret
disp_line endp
;+
; FUNCTION : line_to_scr
;
; Places the cursor at the screen position corresponding to a
; specific position in the line buffer. The entire line buffer
; upto that position must have been displayed before.
;
; Parameters:
; AX = Pointer into the line buffer
;
; Returns:
; Nothing.
; Register(s) destroyed: AX, BX, DX
;-
line_to_scr proc near
sub ax,offset dgroup:linebuf ;ax<-num chars
mov dx,initial_curpos ;Initial cursor position
; dh<-row, dl<-column
xor bh,bh
mov bl,dl ;BX<-original column
add ax,bx ;Compensate for initial position.
; AX is now the 'virtual column'
mov bl,screen_width ;BX<-width of screen
@line_to_scr_10: ;Loop to skip over chars that
; do not need to be updated
cmp ax,bx ;Num of chars fit on a line?
jb @line_to_scr_20 ;Yes, exit loop
sub ax,bx ;Go to next line
inc dh ;Increment the row
jmp short @line_to_scr_10
@line_to_scr_20:
; al now contains the column and dh the row where the cursor should
; be placed
mov dl,al ;dx<-screen position
@SetCurPos ,,video_page ;Set the cursor position
ret
line_to_scr endp
;+
; FUNCTION : insert_chars
;
; Inserts a string of chars at the specified position in the
; linebuffer. If the length would exceed the size of the line buffer,
; chars are only store until the buffer is full and the carry flag is
; set. Dot is updated appropriately.
;
; Parameters :
;
; SI - ptr to source string
; DI - ptr to insert position. This must lie in the line buffer.
; AX - length of source string
;
; Returns:
; CF = 1 if could not be fitted into linebuf
; 0 otherwise
;
; Registers destroyed:
; AX,CX,DX
insert_chars proc near
@save si,di
mov dx,di ;Save insert position in DX
mov di,lastchar ;First empty position
mov cx,offset DGROUP:linebuf_suffix
sub cx,di ;Subtract current last position
; CX<-max chars that will fit
cmp cx,ax ;Will all chars fit ?
jb @insert_chars_5 ;Not all chars will fit
xchg ax,cx ;All chars will fit
@insert_chars_5:
; CX is number of chars to insert
pushf ;Remember CF
; Make place for the characters to be inserted by moving current
; characters up by CX.
mov ax,di
sub ax,dx ;AX<-num chars to move
push si ;Remember source address
mov si,di ;SI->first char to be moved
add di,cx ;DI -> new value of lastchar
mov lastchar,di ;Store it
xchg ax,cx ;AX<-num chars to insert
; CX<-num chars to move
std ;Direction is downward
cmpsb ;Decrement SI,DI
rep movsb ;Make place
cld
pop si ;Restore string source
; Before inserting the chars, update the dot if it is affected.
cmp dx,dot ;Is the dot at or after the insert
; position ?
jb @insert_chars_50 ;No, jump
add dot,ax ;Else update the dot
@insert_chars_50:
mov di,dx ;DI->insert position
xchg cx,ax ;CX<-num chars to insert
rep movsb ;Copy string into linebuffer
mov ax,lastchar
call near ptr set_disp_marks ;AX,DX are parameters
popf ;Restore CF
@restore
ret
insert_chars endp
;+
; FUNCTION : insert_at_dot
;
; Inserts a string of characters into the line buffer in the
; position pointed to by dot. If the length specified in global
; caller_buflen will be exceeded,chars are only stored until the
; buffer is full and CF is set.
;
; Parameters:
; SI = ptr to source string
; AL = length of string
;
; Returns:
; CF = 1 if could not be fitted into linebuf
; 0 otherwise
; Register(s) destroyed:
; <TBA>
;-
insert_at_dot proc near
@save si,di,dx
xor ah,ah ;AX<-length of source string
mov di,dot ;DI-> insert position
call near ptr insert_chars ;Params SI,DI,AX, returns status in CF
@restore
ret
insert_at_dot endp
;+
; FUNCTION : remove_chars
;
; Removes a string of chars at the specified position in the
; linebuffer. The display markers and the lastchar global are updated
; accordingly.
;
; Parameters :
;
; SI - ptr to position in linebuf from which to delete
; AX - number of chars to delete.
;
; Returns:
; Nothing.
;
; Registers destroyed:
; AX,CX,DX
remove_chars proc near
@save si,di
mov di,ax ;Save delete count
; First update the display markers
mov ax,lastchar
mov dx,si
call near ptr set_disp_marks ;AX,DX params
mov ax,lastchar
sub ax,si ;Num chars after delete position
cmp ax,di ;More than the specified number ?
jb @remove_chars_10 ;No, so just delete that many bytes
mov ax,di
@remove_chars_10:
; AX is number of bytes to delete. See if the dot needs to be updated.
mov di,si ;DI->delete position
add si,ax ;SI->first char after delete string
cmp di,dot
jnb @remove_chars_40 ;dot before delete pos, so
; unaffected
cmp si,dot ;Is dot beyond it delete range
jb @remove_chars_30 ;Yes
; dot is in delete region. Update it to point to first delete position
mov dot,di
jmp short @remove_chars_40
@remove_chars_30:
; dot is beyond delete position. So subtract delete bytes from it.
sub dot,ax
@remove_chars_40:
; Now that the screen markers and dot have been updated, get down to the
; real business at hand. SI points to first char after delete string, DI is
; the delete position. AX is number of bytes to be deleted.
mov cx,lastchar
sub lastchar,ax ;Update lastchar
sub cx,si ;CX<-num bytes to move
rep movsb ;Move 'em
; All done
@restore
ret
remove_chars endp
;+
; FUNCTION : erase_to_dot
;
; Deletes all characters from the line buffer between the
; positions AX and dot. (Either AX or dot may be specify the
; beginning of range to be deleted). The markers disp_begin and
; disp_end are set to reflect the changed positions in the line.
; Global lastchar is also updated.
; Parameters:
; AX = One endpoint of the range to be deleted.
; Global dot is the other.
; Returns:
; Nothing.
; Register(s) destroyed:
;-
erase_to_dot proc near
@save si
mov si,dot
cmp ax,si ;Make sure AX is after dot
jnb @erase_to_dot_10 ;Yes it is
xchg si,ax ;Else exchange
@erase_to_dot_10: ;AX is low end, SI high end
sub ax,si ;AX is num bytes to delete
call near ptr remove_chars ;Delete AX chars starting at [SI]
@restore
ret
erase_to_dot endp
;+
; FUNCTION : cmdedit_cmd
;
; Checks if the line buffer contains a CMDEDIT command and if so
; executes it.
;
; Parameters:
; None.
;
; Returns:
; CF = 0 if the line was a command
; 1 otherwise.
; Register(s) destroyed:
; AX,BX,CX,DX
;-
cmdedit_cmd proc near
@save si,di
mov si,offset DGROUP:linebuf ;SI->linebuf
mov di,lastchar ;DI->end of line in linebuf
; Skip leading whitespace
mov cx,di
sub cx,si ;CX<-num chars in linebuf
call near ptr skip_whitespace ;SI->first non-whitespace char
; CX<-num remaining chars
jcxz @cmdedit_cmd_99 ;No command on line
mov di,si ;DI->first char of word
; Skip first word (name of this command)
call near ptr skip_nonwhite ;SI->first whitespace after
; command name
; CX<-num remaining chars
mov ax,si
sub ax,di ;AX<-num chars in word
cmp ax,MAX_CMD_LEN ;Word too long to be command?
ja @cmdedit_cmd_98 ;Yes, exit
; Now search thru the command table to see if the first word in the line is a
; CMDEDIT command. Currently, DI->start of word, AX = num chars in word
xor dx,dx ;DX<-Command number
mov si,offset dgroup:cmd_table ;SI->Start of commands
@cmdedit_cmd_10:
xor ch,ch ;Clear high bits
mov cl,[si] ;CX<-Length of command
jcxz @cmdedit_cmd_98 ;End of table, exit
inc si ;SI->command
cmp cx,ax ;Lengths match
jne @cmdedit_cmd_30 ;No, go try next command
xchg bx,ax ;BX<-num chars in word
call near ptr stre_cmp ;Compare strings
xchg ax,bx ;AX<-num chars in word
je @cmdedit_cmd_50 ;Command matched
@cmdedit_cmd_30:
xor ch,ch
mov cl,-1[si] ;AX<-length of command
add si,cx ;SI->length of next command
inc dx ;Increment the command number
jmp short @cmdedit_cmd_10 ;Try next command
@cmdedit_cmd_50: ;Found command
mov si,di ;SI->first char of command
add si,ax ;SI->first char after command
mov cx,lastchar
sub cx,si ;CX<-num chars after command
mov di,dx ;BX<-command number
shl di,1 ;BX<-offset into table
call cmd_func_table[di] ;Execute it
; Params:
; SI->first char after command
; CX = remaining length of line
; (after command)
cmp source,offset DGROUP:get_kbd_line
jne @cmdedit_cmd_60
call near ptr disp_prompt ;Display user prompt
@cmdedit_cmd_60:
clc ;CF = 0
jmp short @cmdedit_cmd_99
@cmdedit_cmd_98: ;No command found
stc ;CF = 1
@cmdedit_cmd_99:
@restore
ret
cmdedit_cmd endp
;+
; FUNCTION : abort_processing
;
; Called by various routines in case of any errors that require
; aborting of any ongoing processing. An error message is
; displayed and CMDEDIT state is reset to accept input from the
; keyboard. The routine adjusts the stack pointer to a previously
; stored state. Execution then continues at a `abort entry'
; point. The routine does NOT return to the caller.
;
; Parameters:
; AX = Error message number.
;
; Returns:
; Does NOT return to caller.
;
; Register(s) destroyed:
; Potentially all but irrelevant since routine does not return to
; caller.
;-
abort_processing proc near
mov macro_level,0 ;Reset macro level
mov source,offset DGROUP:get_kbd_line ;Set input to keyboard
; Display a message
mov si,offset DGROUP:abort_msg_hd
mov di,offset DGROUP:linebuf
mov dot,di ;dot MUST be at
; beginning of line
; since this position is
; stored in the main routine
mov cx,ABORT_HDR_LEN
rep movsb ;Copy message header
sal ax,1
sal ax,1 ;AX is now index into msg table
xchg ax,bx
mov si,abort_msg_ptrs[bx] ;SI->message
mov cx,abort_msg_ptrs[bx+2] ;CX<-length of message
rep movsb ;Copy msg into linebuf
mov si,offset DGROUP:abort_msg_tl
mov cx,ABORT_TAIL_LEN
rep movsb ;Copy tail of message
mov lastchar,di
mov ax,di ;Set display marks
mov dx,offset DGROUP:linebuf
call near ptr set_disp_marks
call disp_line ;Display message
call near ptr restore_cursor ;Restore cursor to user shape
@DispCh CR
@DispCh LF
call near ptr disp_prompt
mov sp,abort_entry_stack
jmp near ptr cmdedit_abort_entry
abort_processing endp
;+
; FUNCTION : restore_cursor
;
; Restores the cursor to the user's shape.
;
; Parameters:
; Global caller_cursor contains original shape
;
; Returns:
;
; Register(s) destroyed:
; None.
;-
restore_cursor proc near
@save ax,cx
mov cx,caller_cursor
IF TOGGLE_CURSOR
@SetCurSz ch,cl
ENDIF
@restore
ret
restore_cursor endp
;+
; FUNCTION : reset_line
;
; Called to init various things like cursor shape, history buffer
; character positions etc.
;
; Parameters:
; None.
;
; Returns:
; Nothing.
;
; Register(s) destroyed:
; AX,BX,CX,DX
;-
reset_line proc near
call near ptr hist_top ;Reset history stack ptr to top
call near ptr restore_cursor ;Reset cursor shape
mov ax,offset dgroup:linebuf
mov lastchar,ax ;End of line
mov dot,ax ;current pos in line
mov disp_begin,ax ;first pos that changed
mov disp_end,ax ;last pos that changed
; Init overstrike/insert mode
mov bl,default_imode ;Default edit mode
; (insert/overstrike)
mov edit_mode,bl ;Init insert/overtype mode
; Initialize the cursor shapes for insert and overstrike mode
mov ax,caller_cursor ;Caller's cursor shape
IF TOGGLE_CURSOR
mov ah,al
sub ah,3
mov imode_cursor,ax ;Insert mode cursor
mov ah,al
sub ah,1
mov omode_cursor,ax ;Overtype mode cursor
; Init cursor shape
xor bh,bh
add bx,bx
mov cx,omode_cursor[bx]
mov ah,01h
int 10h
ELSE
mov omode_cursor,ax
mov imode_cursor,ax
ENDIF
mov bh,video_page
@GetCur bh
mov initial_curpos,dx ;Initial cursor position
ret
reset_line endp
;+
; FUNCTION : init_screen
;
; Inits various screen parameters. Reads the current prompt from
; the screen and store in the prompt buffer. prompt buffer is
; assumed to be at most the width of the screen.
;
; Parameters:
; None.
;
; Returns:
; Nothing.
; Register(s) destroyed:
; AX,BX,CX,DX
;-
init_screen proc near
@save si,di
@GetMode ;Get the video mode
mov video_page,bh ;Store page
mov screen_width,ah ; and width of display
@GetCur bh ;Get the cursor shape and position
mov initial_curpos,dx ;Initial cursor position
mov caller_cursor,cx ;Caller's cursor shape
mov di,offset DGROUP:prompt
mov cx,PROMPT_BUF_SIZE ;CX<-size of prompt buffer
; (assumed not 0)
mov si,dx ;DX<-cursor pos
xor dl,dl ;DX<-position at start of row
@init_screen_5:
; BH holds video page, DX is cursor position, SI is ending cursor
; position, CX is remaining space in prompt buffer
@SetCurPos ,,bh ;Set cursor position
cmp dx,si ;Reached original position ?
je @init_screen_10 ;Yes, all done
@GetChAtr bh ;Get char at cursor
stosb ;Store in prompt buffer
inc dl ;Increment cursor position
loop @init_screen_5 ;loop unless prompt buffer full
@init_screen_10:
sub di,offset DGROUP:prompt
mov prompt_length,di ;Store length of prompt
@restore
ret
init_screen endp
;+
; FUNCTION : disp_prompt
;
; Called to display the user's prompt. The prompt is taken from
; the buffer 'prompt'.
;
; Parameters:
; None.
;
; Returns:
; Nothing.
; Register(s) destroyed:
; <TBA>
;-
disp_prompt proc near
@save si
@DispCh CR
@DispCh LF
mov cx,prompt_length
jcxz @disp_prompt_99
mov si,offset DGROUP:prompt
@disp_prompt_10:
lodsb
@DispCh al
loop @disp_prompt_10
@disp_prompt_99:
@restore
ret
disp_prompt endp
;+
; FUNCTION : makeroom
;
; Called to push a specified number of characters from the end of a
; line to the back of the line buffer.
;
; Parameters:
; CX - number of chars to push back
;
; Returns:
; DI - points to the first char of the string pushed back.
; Register(s) destroyed:
; CX
;-
makeroom proc near
@save si
mov si,lastchar ;end of line
dec si
mov di,offset DGROUP:linebuf_suffix ;Di->end of linebuf (we
; want to move chars in
; reverse order)
std
rep movsb ;Move up characters
cld
inc di ;DI->start of string
@restore
ret
makeroom endp
;+
; FUNCTION : getpsp
;
; Returns the PSP of the current process
;
; Returns:
; BX - segment of current PSP
;
; Registers destroyed :
; AX,BX
;-
getpsp proc near
; Get the PSP of the current process
cmp dos_version_major,2
jbe @getpsp_10
; DOS 3.x or above - use documented call
mov ah,62h
jmp short @getpsp_90
@getpsp_10:
; DOS version 2.x - use undocumented call
mov ah,51h
@getpsp_90:
int 21h ;BX->PSP segment
ret
getpsp endp
;+
; Function : locate_dosenv
;
; Locates the segment in which the current environment is located.
; This environment is the 'current' environment which may not
; necessarily be the root environment.
;
; Parameters:
; None.
;
; Returns:
; AX - segment of environment
;
; Register(s) destroyed:
; AX
;-
locate_dosenv proc near
@save bx,si,es
call near ptr getpsp ;BX->segment of psp
mov es,bx ;ES->segment of psp
; Loop to find the current command.com psp
mov si,16h ;ES:SI->parent psp
xor ax,ax ;Init for loop
jmp short @locate_dosenv_20 ;'while' loop
@locate_dosenv_10:
mov ax,es:[si] ;AX<-psp seg
mov es,ax ;ES->psp of parent
@locate_dosenv_20:
cmp ax,es:[si] ;Is psp == parent psp ?
jne @locate_dosenv_10
; ES contains DOS PSP.
mov ax,es:[2ch] ;Offset 2c is env address
; AX->DOS environment
; mov dos_envseg,ax
cmp dos_version_major,2 ;DOS 2.x ?
je @locate_dosenv_50
; Versions 3.x or higher
cmp dos_version_minor,10 ;3.1 or below ?
jle @locate_dosenv_50 ;If so handle like 2.x
cmp dos_version_minor,30 ;3,3 or above ?
jge @locate_dosenv_99 ;Then all done
; DOS version higher than 3.1 but below 3.3.
jmp short @locate_dosenv_60
@locate_dosenv_50:
; DOS version 2.x-3.1. If the environement is non-0, all done. Else the
; environment is the memory block below the command.com.
or ax,ax ;0 ?
jne @locate_dosenv_99 ;No, all done
@locate_dosenv_60:
mov si,es
dec si ;SI is segment of memory
; control block of command.com
mov es,si
mov ax,es:[3] ;AX->size of command.com in
; paragraphs
inc ax ;Add size of MCB to AX (in
; paras)
add ax,si ;AX->MCB of environment
inc ax ;AX->environment
; mov dos_envseg,ax ;Store it.
@locate_dosenv_99:
; OK, now dos_envseg supposedly contains the environment segment. DO some
; heuristics to make sure it is really what we think it is.
@restore
ret
locate_dosenv endp
;+
; FUNCTION : our_break_handler
;
; This takes over the Ctrl-Break interrupt and sets a flag when
; Ctrl-Break is hit. It then jumps to the original Ctrl-Break handler.
;
; Parameters:
;
;
; Returns:
;
; Register(s) destroyed:
;-
our_break_handler proc near
inc CS:check_break
cmp CS:trap_break,1
jne @our_break_handler_10
iret
@our_break_handler_10:
jmp CS:prev_isr1b
our_break_handler endp
CSEG ENDS
END entry