home *** CD-ROM | disk | FTP | other *** search
- comment |
- This is the control program of the menu system. Its job is to
- alternately execute the user-interface program and whatever programs
- the user wants to run. It communicates with the user-interface program'
- via the inter-application communications area (IACA)
-
- Written for MASM 5.1 and TASM 1.0
- |
-
- ;----------------------------------------------------------
- ; Order of segments
- ;----------------------------------------------------------
- .MODEL SMALL,C
- .STACK
- .DATA
- .CODE
- end_seg segment
- end_seg ends
-
- ;----------------------------------------------------------
- ; Data and buffers
- ;----------------------------------------------------------
- .DATA
- IACA equ 4f0h ;Offset of IACA
- STDERR equ 2 ;Handle for STDERR
- CR equ 0dh ;Carriage return
- UI_BUFSIZE equ 800h ;Allow 2K bytes for U_I data
- ENV_SIZE equ 800h ;Allow 2K bytes for environ.
-
- EPB equ $ ;EXEC parameter block
- EPB_environ dw 0 ;Use inherited environment
- EPB_cmd_tail dw offset cmd_tail ;Address of command tail
- dw seg cmd_tail
- EPB_fcb1 dw offset fcb1 ;Pointers to FCBs
- dw seg fcb1
- EPB_fcb2 dw offset fcb2
- dw seg fcb2
-
- model_fcb db 0
- db 11 dup ('?')
- db 25 dup (0)
- fcb_len equ $-model_fcb
-
- fcb1 db fcb_len dup(0)
- fcb2 db fcb_len dup(0)
- ;----------
- ; Execution codes returned
- ; from user-interface (U-I)
- ; (add 80H or 128 to each to
- ; force a pause after program ends)
- ;----------
- call_table dw offset exit ;Code 0: EXIT to DOS
- dw offset reset ;Code 1: EXIT to DOS -
- ; & restore orig. directory
- dw offset cmd_exec ;Code 2: Exec via Command.Com
- dw offset dir_exec ;Code 3: Execute .EXE or .COM
- dw offset shell_exec ;Code 4: Shell to DOS
- dw offset change_env ;Code 5: Alter environment
- LAST_CODE equ 5
- INVALID_CODE equ 07fh
- ;-----------
- ; Buffer space
- ;-----------
- EVEN
- exec_path db 128 dup (?) ;Program path from U-I
- exec_tail db 128 dup (?) ;Command tail from U-I
- ui_buf db UI_BUFSIZE dup (?) ;U-I's memory buffer
- exec_code dw ? ;Return code from U-I
-
- cmd_path dw ? ;Ptr to Command.Com path
- ui_path dw ? ;Ptr to user interface path
- cur_drive db ?
- cur_directory db 66 dup (0)
-
- prog_path db 128 dup (0) ;Program to execute
- cmd_tail db 128 dup (0) ;Line to execute
-
- sp_save dw ? ;To save stack pointer
- ss_save dw ? ;To save stack segment
- our_psp dw ? ;Segment of our PSP
- env_seg dw ? ;Segment of environment copy
- env_end dw ? ;Offset of end of environment
- pause_flag dw 0
- ;-----------
- ; Literal strings
- ; and messages
- ;-----------
- comspec db "COMSPEC=",0 ;Environment string
- ui_spec db "PCRSHELL=",0 ;Environment string
-
- no_var db "Cannot find COMSPEC or PCRSHELL environment variable"
- no_var_len dw $-no_var
-
- bad_code db "Unknown execution code"
- bad_code_len dw $-bad_code
-
- bad_mem db "Memory allocation error"
- bad_mem_len dw $-bad_mem
-
- no_env db "Cannot allocate memory for new environment"
- no_env_len dw $-no_env
-
- long_env db "Inherited environment is too long"
- long_env_len dw $-long_env
-
- stop db " -- Program stopping"
- stop_len dw $-stop
-
- ;----------------------------------------------------------
- ; Program code
- ;----------------------------------------------------------
- .CODE
- error macro msg
- mov cx,&msg&_len
- lea dx,&msg
- call errorout
- endm
- ;-----------
- ; Program begins here
- ;-----------
- begin: mov ax,@data ;Set up registers
- mov ds,ax
- mov our_psp,es ;Save PSP
- mov ss_save,ss ; and stack segment
- cld
- call save_dir ;Save current default dir.
- call release_mem ;Release unneeded RAM
- call new_envr ;Make copy of environment
-
- push ds ;Copy data segment
- pop es ; to ES
- lea di,ui_buf ;ES:DI ==> U-I's memory buff.
- mov cx,UI_BUFSIZE/2 ;Words to fill
- sub ax,ax ;AX = 0
- rep stosw ;Clear buffer
- call find_paths ;Find paths to Command.Com
- ;------------
- ; Main program loop
- ;------------
- lp: call run_ui ;Exec user_interface
- push ds ;Copy data segment
- pop es ; to ES
- lea si,model_fcb ;Clear FCB1
- lea di,fcb1 ; by copying the
- mov cx,fcb_len ; model FCB into it
- rep movsb
- lea si,model_fcb ;Clear FCB2
- lea di,fcb2 ; in the same way
- mov cx,fcb_len
- rep movsb
- lea di,prog_path ;Clear prog_path &
- mov ax,0 ; cmd_tail
- mov cx,128
- rep stosw
-
- mov bx,[exec_code] ;Get execution code
- and bx,80h ;Isolate Pause bit
- mov pause_flag,bx ; and save it
- mov bx,[exec_code] ;Get return code again
- and bx,7fh ;Clear pause bit
- cmp bx,LAST_CODE ;Is code okay?
- jbe lp2 ;Yes -- go
- error bad_code ;Else report error
-
- lp2: add bx,bx ;BX * 2 for call table
- call [call_table+bx] ;Call requested routine
- jmp lp ;Loop back to U-I again
- ;----------------------------------------------------------
- ; Utility Routines
- ;----------------------------------------------------------
- ;-----------
- ; Find length of a string
- ; Offset and segment are received
- ; on the stack. Length is returned
- ; in AX
- ;-----------
- strlen proc uses es di cx, str_off:word, str_seg:word
- mov es,str_seg ;Put string address
- mov di,str_off ; in ES:DI
- sub al,al ;AL = 0 (end marker)
- mov cx,-1 ;Maximum possible length
- repne scasb ;Search for end
- dec di ;DI ==> last character
- mov ax,di ;Offset in AX
- sub ax,str_off ;AX = string length
- ret
- strlen endp
- ;-----------
- ; Copy a string from DS:SI to ES:DI
- ; Maximum length to copy received on stack
- ; Returns number of bytes moved in AX (including 0 byte)
- ;-----------
- strcpy proc uses di si bx cx, max_len:word
- mov cx,max_len ;Length in CX
- sub bx,bx ;BX will count bytes
- cpy1: or cx,cx ;Test for end
- jz cpy2 ;Go if at end
- lodsb ;Else get a byte
- stosb ;Move it
- inc bx ;Count it
- dec cx ;Reduce maximum left
- or al,al ;Was it end of string?
- jnz cpy1 ;No -- move another
- cpy2: mov ax,bx ;Return count of bytes
- ret
- strcpy endp
- ;-----------
- ; Save the default drive
- ; and subdirectory.
- ;-----------
- save_dir proc uses dx si
- mov ah,19h ;DOS Service: Get cur. disk
- int 21h ;Call DOS
- mov [cur_drive],al ;Save default drive
- mov dl,al ;Drive in DL
- inc dl ;A=1, B=2, etc.
- lea si,cur_directory ;SI ==> buffer
- add al,'A' ;AL has drive letter
- mov [si],al ;Save it
- mov byte ptr [si+1],':' ; and a colon
- add si,2 ;Move pointer past drive
- mov ah,47h ;DOS Service: Get cur. dir.
- int 21h ;Call DOS
- ret
- save_dir endp
- ;-----------
- ; Restore default drive
- ; and directory
- ;-----------
- restore_dir proc uses dx
- mov dl,[cur_drive] ;Get original drive
- mov ah,0eh ;DOS Service: set cur. disk
- int 21h ;Call DOS
- lea dx,cur_directory ;DX ==> directory
- mov ah,3bh ;DOS Service: Change dir.
- int 21h ;Call DOS
- ret
- restore_dir endp
- ;-----------
- ; Release unneeded memory
- ; to make room for child
- ; programs
- ;-----------
- release_mem proc uses bx
- mov ax,our_psp ;Get seg. of this program
- mov es,ax ;ES==> our PSP
- mov bx,seg end_seg ;BX = end of our program
- sub bx,ax ;BX = paragraphs to keep
- mov ah,4ah ;DOS Service: set block size
- int 21h ;Call DOS
- jc rel_mem1 ;Go if error
- ret ;Else return
- rel_mem1:
- error bad_mem ;Abort if error
- release_mem endp
- ;-----------
- ; Report error and
- ; abort program. Receives
- ; pointer to message in DX
- ; and message length in CX
- ;-----------
- errorout proc
- mov bx,STDERR ;Report to screen
- mov ah,40h ;DOS Service: write to handle
- int 21h ;Call DOS
- lea dx,stop ;DS:DX==> halting message
- mov cx,stop_len ;CX has length
- mov ah,40h ;Write to handle again
- int 21h ;Call DOS
- call restore_dir ;Restore original dir.
- mov ax,4cffh ;Exit with error
- int 21h ;Return to DOS
- errorout endp
- ;----------------------------------------------------------
- ; EXEC functions -- These routines run child programs
- ;----------------------------------------------------------
- ;----------
- ; Execute a
- ; child program
- ;----------
- execute proc uses bx cx dx di si
- push ds
- pop es ;ES ==> our data segment
- lea dx,prog_path ;DS:DX ==> prog. to execute
- lea bx,epb ;ES:BX ==> EPB
- push bp ;Save stack frame pointer
- mov [sp_save],sp ;Save stack pointer
- mov ax,4b00h ;Func. 4b: execute program
- int 21h ;Call DOS
- mov ax,@data ;Restore data segment
- mov ds,ax
- mov ss,[ss_save] ;Restore stack
- mov sp,[sp_save]
- pop bp ;Restore frame pointer
- cld ;Avoid possible bug in 2.x
- test pause_flag,-1 ;Should we pause?
- jz ex1 ;No -- go
- mov ah,8 ;Else wait for keystroke
- int 21h
- cmp al,0 ;Extended key?
- jne ex1 ;No -- go
- mov ah,8 ;Yes -- call again
- int 21h ; for rest of key code
- ex1: ret
- execute endp
- ;----------
- ; Run the user-interface program
- ; after setting up the appropriate
- ; values in the inter-application
- ; communications area (IACA)
- ;----------
- run_ui proc uses cx di si
- mov exec_code,INVALID_CODE ;Make sure of valid return
- mov pause_flag,0 ;No pause on return
- sub ax,ax ;AX = 0
- mov es,ax ;ES ==> BIOS area
- mov di,IACA ;ES:DI ==> IACA
- mov ax,ds ;Get data segment
- stosw ;Save it
- lea ax,exec_path ;Get offset of path buffer
- stosw ;Save it
- lea ax,exec_tail ;Get offset of tail buffer
- stosw ;Save it
- lea ax,ui_buf ;Get offset of memory buffer
- stosw ;Save it
- lea ax,exec_code ;Get offset of code word
- stosw ;Save it
-
- push ds ;Copy data segment
- pop es ; to ES
- lea di,cmd_tail ;ES:DI==> command tail
- sub ax,ax ;AX = 0
- stosw ;Clear command tail
-
- lea di,prog_path ;ES:DI ==> program path
- mov si,[ui_path]
- push ds ;Save DS
- mov ds,[env_seg] ;DS:SI ==> U-I path name
- mov ax,128 ;Maximum bytes to move
- push ax
- call strcpy ;Move the string
- add sp,2 ;Clear the stack
- pop ds ;Recover data segment
- call execute ;Execute U-I
- ret
- run_ui endp
- ;----------------------------------------------------------
- ; Routines to service commands from User Interface
- ;----------------------------------------------------------
- ;----------
- ; Execution code 0
- ; Exit to DOS
- ;----------
- exit proc
- mov ax,4c00h ;Return to DOS -- no error
- int 21h
- exit endp
- ;----------
- ; Execution code 1
- ; Reset original default
- ; drive & directory and
- ; exit to DOS
- ;----------
- reset proc
- call restore_dir ;Restore default dir.
- jmp exit ;Now exit
- reset endp
- ;----------
- ; Execution code 2
- ; Execute a program
- ; or DOS command
- ; via Command.Com
- ;----------
- cmd_exec proc
- push ds
- pop es ;ES==> data segment
- push ds ;Save DS
- lea di,prog_path ;ES:DI==> program name buffer
- mov si,[cmd_path]
- mov ds,[env_seg] ;DS:SI==> Command.Com path
- mov ax,128 ;Bytes to move
- push ax
- call strcpy ;Move path name
- add sp,2 ;Clear the stack
- pop ds ;Recover data segment
- lea di,cmd_tail+1 ;ES:DI==> tail buffer
- push di ;Save the address
- mov al,'/' ;Start tail with
- stosb ; "/c "
- mov al,'c'
- stosb
- mov al,' '
- stosb
- lea si,exec_tail ;DS:SI==> command to run
- mov ax,124 ;Maximum bytes
- push ax
- call strcpy ;Move the string
- add sp,2
- pop di ;DS:DI ==> cmd_tail + 1
- push ds ;Push segment of cmd_tail
- push di ; and offset of cmd_tail text
- call strlen ;Find length of tail
- add sp,4 ;Clear the stack
- mov bx,ax ;Length in BX
- cmp byte ptr [di+bx-1],CR ;Does it end with a CR?
- jne ce1 ;No -- go
- dec ax ;Else reduce count
- jmp short ce2 ;And go
- ce1: mov byte ptr [di+bx],CR ;Put carriage return at end
- ce2: mov [cmd_tail],al ;Put count in place
- call execute ;Run the program
- ret
- cmd_exec endp
- ;-----------
- ; Execution code 3
- ; Execute an .EXE or .COM
- ; program directly
- ;-----------
- dir_exec proc
- push ds ;Copy data segment
- pop es ; to ES
- lea si,exec_path ;DS:SI==> program to run
- lea di,prog_path ;ES:DI==> execution buffer
- mov ax,128 ;Maximum bytes
- push ax
- call strcpy ;Copy the string
- add sp,2 ;Clear the stack
- lea si,exec_tail ;Program tail
- lea di,cmd_tail+1 ;Execution tail
- mov ax,127 ;Maximum tail bytes
- push ax
- call strcpy ;Move the tail
- add sp,2 ;Clear the stack
- dec ax ;Don't count 0 byte
- mov bx,ax ;Length of string in BX
- cmp [cmd_tail+bx],CR ;Is last byte a CR?
- jne de1 ;No -- go
- dec ax ;Else reduce count
- jmp short de2 ;And go
- de1: mov [cmd_tail+bx+1],CR ;Terminate with a CR
- de2: mov [cmd_tail],al ;Store the count
- or al,al ;Was there a tail?
- jz dir_exec1 ;No -- go
-
- lea si,cmd_tail+1 ;DS:SI==> tail text
- lea di,fcb1 ;ES:DI==> 1st FCB
- mov ax,2901h ;DOS Service: Parse fname
- int 21h ;Call DOS
- lea di,fcb2 ;ES:DI==> 2nd FCB
- mov ax,2901h ;DOS Service: Parse fname
- int 21h ;Call DOS
- dir_exec1:
- call execute ;Run the program
- ret
- dir_exec endp
- ;-----------
- ; Execution code 4
- ; Shell to Command.Com
- ; and give user control
- ;-----------
- shell_exec proc
- push ds ;Copy data segment
- pop es ; to ES
- lea di,prog_path ;ES:DI==>execution buffer
- push ds ;Save data segment
- mov si,[cmd_path]
- mov ds,[env_seg] ;DS:SI==>Command.Com path
- mov ax,128 ;Maximum bytes
- push ax
- call strcpy ;Copy path name
- add sp,2 ;Clear the stack
- pop ds ;Recover data segment
- call execute
- ret
- shell_exec endp
- ;-----------
- ; Execution code 5
- ; Add, delete or change
- ; environment string
- ;-----------
- change_env proc
- call del_env_string ;Delete old value
- push ds ;Copy data segment
- pop es ; to ES
- lea di,exec_tail ;ES:DI==>new value
- mov cx,128 ;Maximum bytes
- mov al,"=" ;Look for "="
- repne scasb
- cmp byte ptr es:[di],0 ;Is there new text?
- je change_env1 ;No -- go
- call add_env_string ;Else add this string
- change_env1:
- call find_paths ;Readjust path pointers
- ret
- change_env endp
- ;----------------------------------------------------------
- ; Environment routines -- These routines handle our copy
- ; of the environment, which is passed to both the user-interface
- ; and to every application
- ;----------------------------------------------------------
- ;-----------
- ; Create a new environment that
- ; we can manipulate and send to
- ; child programs
- ;-----------
- new_envr proc uses bx cx si di
- mov bx,ENV_SIZE/16 ;BX = # of paragraphs for environ.
- mov ah,48h ;DOS Service: Allocate block
- int 21h ;Get memory block
- jnc env1 ;Go if okay
- error no_env ;Else report error and stop
- env1: mov [EPB_environ],ax ;Save new segment in EPB
- mov [env_seg],ax ; and for us
- mov es,ax ;ES==> new segment
- push ds ;Save DS
- mov bx,our_psp ;Get PSP address
- mov ds,bx ;DS==> PSP
- mov ds,ds:[2ch] ;DS==> inherited environment
- sub si,si ;DS:SI==> current environment
- mov di,si ;ES:DI==> new environment
- sub cx,cx ;CX will count bytes
- env2: test byte ptr ds:[si],-1 ;Are we done?
- jz env4 ;Yes -- go
- env3: lodsb ;Get a byte
- stosb ;Store it
- inc cx ;And count it
- or al,al ;End of string?
- jz env2 ;Yes -- start next string
- cmp cx,ENV_SIZE ;Past the end?
- jae env_err ;Yes -- report error
- jmp env3 ;Else do next byte
- env4: lodsb ;Get last 0
- stosb ;Store it
- pop ds ;Clear stack
- dec di ;DI ==> last 0
- mov [env_end],di ;Save address of end of env.
- ret
- env_err:
- pop ds ;Clear the stack
- error long_env ;Report error and end
- new_envr endp
- ;----------
- ; Find environment variable in
- ; our copy of the environment.
- ; Return a pointer to beginning
- ; of environment string in ES:AX
- ; Receives a pointer requested name in DS:SI
- ;----------
- find_env_var proc uses di si cx dx
- mov es,env_seg ;ES:DI ==> copy of environ.
- sub di,di
- push ds
- push si ;Pass string address
- call strlen ;Find length of string at DS:SI
- add sp,4 ;Clear stack
- mov dx,ax ;DX has length
- fen1: cmp byte ptr es:[di],0 ;End of environment?
- jz fen_err ;Yes -- error return
- mov cx,dx ;Length in CX
- push di ;Remember where we started
- push si
- repe cmpsb ;At variable name?
- pop si ;Recover start of strings
- pop di
- jz fen_found ;Found it!
- mov al,0 ;Else search for end of string
- mov cx,8000h ;Look for 32K
- repne scasb ;Move to end of string
- jmp fen1 ;And try again
- fen_err:
- mov ax,-1 ;Return impossible addr.
- jmp short fen_end
- fen_found:
- mov ax,di ;Move addr. to AX
- fen_end:
- ret ;Return to caller
- find_env_var endp
- ;-----------
- ; Find value of environment string
- ; Receives pointer to beginning of
- ; name, returns pointer to beginning
- ; of value
- ;-----------
- find_env_val proc uses es di cx, var_off:word
- mov es,env_seg
- mov di,var_off ;ES:DI ==> environ. variable
- mov al,"=" ;Look for "=" sign
- mov cx,-1 ;Maximum length
- repne scasb ;Look for "="
- mov ax,di ;Pointer to val in AX
- ret
- find_env_val endp
- ;-----------
- ; Find paths to Command.Com and user-interface
- ; by looking in our copy of the environment.
- ; Abort with an error if either is missing.
- ;-----------
- find_paths proc uses si
- lea si,comspec ;DS:SI ==> "Command.Com"
- call find_env_var ;Get addr. in environment
- cmp ax,-1 ;Was it found?
- je fp_error ;No -- go
- push ax ;Else pass offset
- call find_env_val ;Find beginning of path
- add sp,2 ;Clear stack
- mov [cmd_path],ax ;Save address
- lea si,ui_spec ;DS:SI ==> "PCRSHELL"
- call find_env_var ;Get addr. in environment
- cmp ax,-1 ;Was it found?
- je fp_error ;No -- go
- push ax ;Else pass offset
- call find_env_val ;Find beginning of path
- add sp,2 ;Clear stack
- mov [ui_path],ax ;Save address
- ret
- fp_error:
- error no_var ;Report error and abort
- find_paths endp
- ;-----------
- ; Erase environment variable by
- ; copying all following strings over
- ; it. String to erase is in exec_tail buffer.
- ;-----------
- del_env_string proc uses di si cx
- push ds
- pop es
- lea di,exec_tail ;ES:DI ==> exec_tail
- mov cx,128 ;Maximum size
- mov al,'=' ;Look for "="
- repne scasb ;Find end of variable name
- dec di ;ES:DI ==> "="
- mov byte ptr es:[di],0 ;Terminate name
- lea si,exec_tail ;DS:SI ==> name
- call find_env_var ;Find name in environment
- mov byte ptr ds:[di],'=' ;Replace "="
- cmp ax,-1 ;Did we find it?
- je del_env_end ;No -- go
- mov di,ax ;ES:DI ==> string to erase
- push di ;Save address
- mov al,0 ;Look for end of string
- mov cx,-1 ;Look until end
- repne scasb ;Move to 1st byte after end
- mov si,di ;SI ==> next string
- pop di ;ES:DI ==> beginning of string
- mov cx,[env_end] ;CX has address of end of env.
- push ds
- mov ds,env_seg ;DS:SI ==> next string
- del_env1:
- movsb ;Move a byte
- cmp si,cx ;Are we done?
- jbe del_env1 ;No -- loop back
- dec di ;ES:DI ==> last 0
- pop ds ;Restore data segment
- mov [env_end],di ;Save end address
- del_env_end:
- ret
- del_env_string endp
- ;-----------
- ; Add a string to our copy of the
- ; environment table. The string is
- ; in the exec_tail buffer
- ;-----------
- add_env_string proc uses di si cx
- mov es,[env_seg]
- mov di,[env_end] ;ES:DI ==> end of environment
- lea si,exec_tail ;DS:SI ==> new string
- push ds
- push si ;Pass address of string
- call strlen ;Find length to add
- add sp,4 ;Clear the stack
- inc ax ;Length + final 0
- mov cx,ax ;Save string length
- add ax,di ;Is there room for it?
- cmp ax,ENV_SIZE
- ja add_env_end ;No -- simply return
- rep movsb ;Move the string
- mov byte ptr es:[di],0 ;Terminate environment
- mov [env_end],di ;Save new end address
- add_env_end:
- ret
- add_env_string endp
- end begin
-