⭐ 欢迎来到虫虫下载站! | 📦 资源下载 📁 资源专辑 ℹ️ 关于我们
⭐ 虫虫下载站

📄 process.a86

📁 一个dos操作系统DRDOS的源码
💻 A86
📖 第 1 页 / 共 3 页
字号:
;    File              : $PROCESS.A86$
;
;    Description       :
;
;    Original Author   : DIGITAL RESEARCH
;
;    Last Edited By    : $CALDERA$
;
;-----------------------------------------------------------------------;
;    Copyright Work of Caldera, Inc. All Rights Reserved.
;      
;    THIS WORK IS A COPYRIGHT WORK AND CONTAINS CONFIDENTIAL,
;    PROPRIETARY AND TRADE SECRET INFORMATION OF CALDERA, INC.
;    ACCESS TO THIS WORK IS RESTRICTED TO (I) CALDERA, INC. EMPLOYEES
;    WHO HAVE A NEED TO KNOW TO PERFORM TASKS WITHIN THE SCOPE OF
;    THEIR ASSIGNMENTS AND (II) ENTITIES OTHER THAN CALDERA, INC. WHO
;    HAVE ACCEPTED THE CALDERA OPENDOS SOURCE LICENSE OR OTHER CALDERA LICENSE
;    AGREEMENTS. EXCEPT UNDER THE EXPRESS TERMS OF THE CALDERA LICENSE
;    AGREEMENT NO PART OF THIS WORK MAY BE USED, PRACTICED, PERFORMED,
;    COPIED, DISTRIBUTED, REVISED, MODIFIED, TRANSLATED, ABRIDGED,
;    CONDENSED, EXPANDED, COLLECTED, COMPILED, LINKED, RECAST,
;    TRANSFORMED OR ADAPTED WITHOUT THE PRIOR WRITTEN CONSENT OF
;    CALDERA, INC. ANY USE OR EXPLOITATION OF THIS WORK WITHOUT
;    AUTHORIZATION COULD SUBJECT THE PERPETRATOR TO CRIMINAL AND
;    CIVIL LIABILITY.
;-----------------------------------------------------------------------;
;
;    *** Current Edit History ***
;    *** End of Current Edit History ***
;    $Log$
;    PROCESS.A86 1.25 94/07/13 16:15:27 
;    Int21/26 (create PSP) copies 1st 20 entries of parental XFT
;    PROCESS.A86 1.24 94/06/28 11:15:28
;    Don't issue an int 21 to get curret psp while within int21/4B load overlay
;    PROCESS.A86 1.20 93/09/28 19:44:03 
;    Don't lose 8th character of name in DMD during exec
;    PROCESS.A86 1.14 93/06/18 21:00:57
;    Support for Int 21/4B05 added
;    PROCESS.A86 1.13 93/06/11 02:11:20
;    GateA20 disabled on EXEC for EXEPACKED apps
;    Fix termination code 
;    ENDLOG
;

 	include	pcmode.equ
	include fdos.def
	include	i:psp.def
	include i:mserror.equ
	include	vectors.def
	include i:msdos.equ
	include i:exe.def
	include	i:char.def
	include	i:redir.equ
	include	i:doshndl.def

HILOAD	equ	TRUE

PCM_CODE	CSEG	BYTE
	extrn	check_dmd_id:near
	extrn	dbcs_lead:near
	extrn	error_exit:near
	extrn	fdos_nocrit:near
	extrn	free_all:near
	extrn	get_dseg:near		; Get the PCMODE Data Segment
	extrn	int21_exit:near
	extrn	invalid_function:near
	extrn	dos_entry:near
	extrn	return_AX_CLC:near
	extrn	set_owner:near
	extrn	strlen:near
	extrn	toupper:near
	extrn	valid_drive:near
;
;
;PC-DOS PSP Creation Update and Maintance routines
;
;	*****************************
;	***    DOS Function 55    ***
;	***    Create New PSP     ***
;	*****************************
;
;	entry:	DX = New PSP Segment
;		SI = Top of Available
;
;	This function copies the existing PSP and generates a new Process
;	environment. The file table is updated and dos_SI is used to determine
;	the process' memory size. The PSP is then made the CURRENT_PSP

	Public	func55
func55:
	mov	cx,PSPLEN/2		; copy whole PSP
	call	create_psp
    mov al,0F0h     
    ret             
	
create_psp:
	mov	ax,current_psp		; All based on the Current PSP
	call	copy_psp		; Do the Basic Copy
	mov	ax,current_psp		; get the Current PSP address
	mov	PSP_PARENT,ax		;   and save it in child's psp

	cmp	ax,dx			; Is this the ROOT level DOS process
	 jz	create_psp10		; Yes because Current PSP == New PSP
					; therefore skip the EXEC function
					; because this is done by P_CREATE

	mov	FD_FUNC,FD_EXEC		; Must Update the Open Counts ETC.
	mov	FD_PSPSEG,dx		; New PSP address
	call	fdos_nocrit

create_psp10:
	mov	current_psp,es		; set the New PSP address
	ret

;
;	*****************************
;	***    DOS Function 26    ***
;	***    Create New PSP     ***
;	*****************************
;
;	entry:	DX = New PSP Segment
;
	Public	func26
func26:
	les	di,int21regs_ptr	; Get pointer to INT 21 structure of
	mov	es,es:reg_CS[di]	; IP/CS/Flags and get the USER CS this
	mov	si,PSP_MEMORY		; is used as the PSP for this function 
	mov	ax,es			; call and NOT current_psp
	mov	cx,PSPLEN/2		; copy whole PSP
	push	dx
	call	copy_psp
	pop	es
	mov	cx,20			; default XFT table has twenty files
	mov	di,offset PSP_XFT	;  and is in the PSP at this offset
	mov	PSP_XFNMAX,cx		; say we have 20 files max
	mov	PSP_XFTOFF,di
	mov	PSP_XFTSEG,es
	push	ds
	mov	ds,current_psp		; we copy 1st 20 entries of current
	lds	si,ds:PSP_XFTPTR	;  XFT to the child PSP
	rep	movsb			; we do not update file handle use
	pop	ds			;  counts, unlike Int21/55
	ret

copy_psp:
; copy CX words from AX:0 to DX:0, SI = memory top
	push	si			; Save the Memory TOP
	push	ds
	mov	es,dx			; Point ES to the New PSP
	mov	ds,ax			; Get the current PSP for this function
	xor	ax,ax
	mov di,ax ! mov si,ax
	rep	movsw			; Copy into New PSP

	mov	ds,ax			; Copy the current Terminate, Critical 
	mov	si,INT22_OFFSET		; Error and Control Break Handlers
	mov	di,offset PSP_TERM_IP	; into the new PSP
	mov	cl,6
	rep	movsw			; BREAK,TERM, CRIT ERR SAVED HERE
	pop	ds
	pop	PSP_MEMORY

	mov	PSP_INT20,020CDh	; Interrupt 20h Terminate
	mov	PSP_RES1,0FFFFh
	mov	PSP_RES2,0FFFFh
	mov	PSP_DOSCALL,021CDh	; INT 21h Function Call
	mov	PSP_DOSRETF,0CBh	; RETF

	mov	PSP_LONGCALL,09Ah	; CALLF AnySeg:MemSize
	mov	ax,PSP_MEMORY		; Get the Top of Memory
	sub	ax,dx			; Convert it to Memory Size
	cmp	ax,1000h		; Check for Over 64Kb
	mov	bx,0FEF0h		; Assume Over 64Kb
	jae	sce_10
	mov	bx,ax			; Convert the Paragragh Length
	mov	cl,4			; to a Byte Length	
	shl	bx,cl
	sub	bx,110h			; Reserve 110h Bytes for .COM Stack
sce_10:	
	push	dx
	mov	PSP_LONGOFF,bx		; Save the Byte Length
	xor 	dx,dx			; Call 5 Entry Segment
	mov 	ax,INT30_OFFSET		; Call 5 Entry Offset
	mov	cl,4			
	shr	ax,cl			; Entry Offset/16 => EO
	shr	bx,cl			; Jump Offset/16 => JO
	add	ax,dx			; EO + ES
	sub	ax,bx			; EO + ES - JO => JS 
	mov	PSP_LONGSEG,ax
	pop	dx
	ret

;
;	*****************************
;	***    DOS Function 50    ***
;	***    Set Current PSP    ***
;	*****************************
;
	Public	func50

; WARNING - called on USER stack

func50:
	mov	current_psp,bx
	ret

;	*****************************
;	***  DOS Function 51/62   ***
;	***    Get Current PSP    ***
;	*****************************
;
	Public	func51, func62

; WARNING - called on USER stack

func51:
func62:
	mov	bx,current_psp
	mov	reg_BX[bp],bx
	ret

eject
;**************************************************
;**************************************************
;***						***
;***	    Process Control Functions		***
;***						***
;**************************************************
;**************************************************

;	*****************************
;	***    DOS Function 31    ***
;	***   Terminate and Keep  ***
;	*****************************
;
	Public	func31
func31:
	mov	ax,6			; make 6 paragraphs our minimum size
	cmp	ax,dx			; Are we at our minimum size ?
	 jb	func31_05
	xchg	ax,dx			; no, enforce 6 paragraphs
func31_05:
	mov	exit_type,TERM_RESIDENT	; Exit by Terminate and Stay Resident
	mov	bx,current_psp		; and set the termination PSP to
	mov	term_psp,bx		; be the Current PSP

	push	ds			; Attempt to modify the memory
	mov	ds,bx			; partition size to that given in DX
	mov	bx,dx			; Remember DS and ES are swapped for
	call	mem_setblock		; the internal function.

	mov	ax,ds			; Now update the PSP_MEMORY field to
	add	ax,bx			; reflect the memory available to
	mov	ds:PSP_MEMORY,ax	; to the application now. Required by
	pop	ds			; MicroPro WordFinder

	mov	load_psp,0000		; Do not free PSP memory
	jmp	f31_term		; Common terminate handler

;
;	*****************************
;	***    DOS Function 4B    ***
;	*** Load or Execute Prog  ***
;	*****************************
;
;	An extra sub-function has been defined which is used by the
;	ROOT DOS process loader to ensure compatibility between the
;	Initial Register conditions for the ROOT DOS process and that
;	of any child process.
;
;	4B80h	-	GO Sub-Function expects all the internal and
;			external data areas to have been setup by a 
;			previous 4B01h function. Never Fails !
;
; Undocumented feature:
;	AX=4B03 returns SETVER version in AX, or zero
;

	Public	func4B
func4B:
	cmp	al,80h			; Is this the special GO sub-function
	 jnz	f4B_01			; No Process Normally
	jmp	start_child		; Go for It every thing else OK

f4B_01:
	cmp al,5 ! je f4B05		; Sub-Func 5:- Exec Hook
	cmp al,3 ! je f4B_02		; Sub-Func 3:- Load Overlay
	cmp al,1 ! jbe f4B_02		; Sub-Func 1:- Load and No Execute
					; Sub-Func 0:- Load and Execute
f4B_invalid:
	jmp	invalid_function	; Otherwise illegal Sub-Function

f4B05:
;-----
; On Entry:
;	ES:DX -> ExecState
esReserved	equ	word ptr 0	; reserved, must be zero
esFlags		equ	word ptr 2	; type flags
esProgName	equ	dword ptr 4	; points to ASCIIZ name
esPSP		equ	word ptr 8	; PSP of new program
esStartAddress	equ	dword ptr 10	; CS:IP of new program
esProgSize	equ	dword ptr 14	; program size, including PSP
;
;	type flags
ES_EXE		equ	0001h
ES_OVERLAY	equ	0002h
;
; On Exit:
;	None (A20 gate disabled)
;
	mov	di,dx			; ES:DI -> ExecState
	test	es:esFlags[di],not ES_EXE
	 jnz	f4B_invalid		; only COM or EXE supported
    call    return_AX_CLC       ; assume success
	lds	si,es:esProgName[di]	; DS:SI -> ASIIZ name
	mov	es,es:esPSP[di]		; ES = PSP
	push	es			; save for DX on exit
	call	SetPspNameAndVersion	; set up the name/version fields
	pop	dx			; DX = PSP
	push	ss
	pop	ds			; DS = pcmode data again
	cli				; Stop anybody interfering
	les	bp,int21regs_ptr	; point to user stack
	mov	es:reg_AX[bp],0		; return successful
	and	es:reg_FLAGS[bp],not CARRY_FLAG
	mov	ax,prev_int21regs_off
	mov	int21regs_off,ax
	mov	ax,prev_int21regs_seg
	mov	int21regs_seg,ax
	dec	indos_flag		; no longer in DOS
	jmpf	func4B05_stub		; exit via stub code


f4B_02:
	xor	ax,ax
	mov	load_env,ax		; Load environment NOT allocated
	mov	load_psp,ax		; Load memory NOT allocated
	dec	ax
	mov	load_handle,ax		; Mark Load file as CLOSED

	push es ! push dx		; expand the filename to a
	call	get_filename		;  full path to be inherited
	pop dx ! pop es			;  in the environment
	 jc	f4B_10			; Exit on error
	mov	ax,(MS_X_OPEN*256)+20h	; Open File
;	mov	al,0$010$0$000B		; ReadOnly & DenyWrite
	call	dos_entry
	 jnc	f4B_05			; Save Handle if No Error

	cmp	ax,ED_SHAREFAIL		; Check for a Sharing Error or Access
	 jz	f4B_04			; Denied if neither error codes then
	cmp	ax,ED_ACCESS		; Don't retry the Open function
	 jnz	f4B_10			; in compatibility

f4B_04:
	mov	ax,(MS_X_OPEN*256)+0	; retry the open in read-only
;	mov	al,0$000$0$000B		;  compatibility mode
	call	dos_entry
	 jc	f4B_10			; Stop On error

f4B_05:
	push ds ! pop es		; ES local again
	mov	load_handle,ax		; Save for Error Handling
	xchg	ax,bx			; Get the File Handle
	mov	si,offset exe_buffer
	call	get_execdata
	 jc	f4B_10
	call	point_param_block	; CL = subfunc, ES:DI -> param block
	cmp	cl,3			; Sub-Func 3:- Load Overlay
	 jne	f4B_go			; Sub-Func 0:- Load and Execute
					; Sub-Func 1:- Load and No Execute

	mov	si,es:2[di]		; si = Relocation Factor
	mov	di,es:[di]		; di = Load Segment

	call	loadimage		; load and relocate image
	 jc	f4B_10			; f4B_error - Return with an error
if DOS5
	mov	si,offset load_file	; Copy the process name into the DMD
	call	FindName		; DS:SI -> start of name
	call	GetVersion		; AX = version to return
	mov	es,current_psp		; poke the current psp
	mov	PSP_VERSION,ax		;  with the version number
endif
	jmp	return_AX_CLC		; All done
f4b_10:
	jmp	f4B_error


;
;	F4B_GO loads and executes the file whose handle is in BX.
;	This routine corresponds to sub-functions 0 and 1.
;
f4B_go:
	xor	ax,ax
	mov	si,offset exe_buffer	; .COM and .EXE file loading
	mov	exe_loadhigh,al		; Reset the Load High Flag
	cmp	ax,EXE_MAXPARA[si]
	 jnz	f4B_g15			; Load High Flag (MAXPARA == 0)
	dec	ax
	mov	exe_loadhigh,al		; Set the internal LOADHIGH flag
	mov	EXE_MAXPARA[si],ax	; and allocate all memory
f4B_g15:
	mov	ax,es:[di]		; get ENV pointer from param block
	call	build_env		; Build the environment
	 jc	f4B_error		; Stop on error

	call	calc_psp		; calculate new psp
	 jc	f4B_error		; Stop on error
	call	pblk_to_psp		; Copy parameters into PSP
	mov	si,load_image		; read the Load image
	mov	di,si			; to previously calculated address
	call	loadimage		; load in com file
	 jc	f4B_error		; quit if no memory
	call	set_up_psp		; build child's psp
	mov	dx,load_psp		; point at PSP seg

	mov	exit_type,TERM_NORMAL	; Initialise the Return code type
	mov	si,offset exe_buffer	; to normal an go
	call	check_exe
	 jc	f4B_go_com	

	mov	dx,load_image		; Get the Load Paragraph
	add	EXE_CS[si],dx		; bias the code segment
	add	EXE_SS[si],dx		;   and the stack segment too
	jmp	start_child		; goodbye!

;
f4B_go_com:				; Go for it .COM
;	mov	dx,load_psp		; based at PSP seg
	mov	EXE_CS[si],dx		; set up initial cs:ip
	mov	EXE_IP[si],100h		;   and ss:sp for child
	mov	EXE_SS[si],dx
	mov	es,dx
	mov	bx,PSP_LONGOFF		; ax = segment size in bytes
	add	bx,110h - 2		; Initialise stack in reserved area
	mov	EXE_SP[si],bx		; save as stack ptr
	mov	es:word ptr[bx],0	; put one zero on the stack
	jmp	start_child		; goodbye!

;
;	Function 4B Error Handler. This exit routine will free all
;	resources allocated to a process during the EXEC function and
;	exit to the standard error handler with the original error code
;	if any further errors occur they are ignored.
;
f4B_error:
	push	ax			; Save the return Code
	mov	bx,load_handle		; Is the load file still open ?
	inc	bx			; (FFFF = closed)
	 jz	f4B_e10			; YES then Close
	dec	bx
	mov	ah,MS_X_CLOSE
	call	dos_entry
f4B_e10:				; Now Free any memory allocated
	mov	cx,load_psp		; during the execution of FUNC4B
	call	conditional_mem_free	; firstly free PSP/code/data memory
	mov	cx,load_env		; Secondly free the memory allocated
	call	conditional_mem_free	; to hold the ENVIRONMENT
	pop	ax			; Restore the return code and exit
	mov	valid_flg,OK_RF		; fiddle to resume func 4B if we get
	mov	retry_sp,sp		;  a critical error
	mov	retry_off,offset func4B
	call	error_exit		; call the standard error handler
	cmp	ax,-ED_FORMAT		; errors less than ED_FORMAT are OK.
	 jb	f4B_e20			;  (eg. ED_MEMORY, ED_FILE)
	mov	ax,load_handle		; if we didn't manage to open exec file
	inc	ax			;  load_handle=FFFF and we want to
	mov	al,-ED_PATH		;  return ED_PATH
	 jz	f4B_e20			; else we had an error during the load
	mov	al,-ED_FORMAT		;  and should return ED_FORMAT
f4B_e20:
	ret

eject	
start_child:
	mov	es,current_psp		; ds -> psp
	mov	dx,0080h		; default dma offset
	mov	ah,MS_F_DMAOFF		; Set the DMA address
	call	dos_entry		; set child's dma address
	mov	si,offset exe_buffer	; Get EXE Buffer Offset
	call	point_param_block	; CL = subfunc, ES:DI -> param block
	cmp	cl,1
	 jne	start_child_go		; load restisters and go
;
;	The following code updates the Extended parameter block
;	used with the LOAD for DEBUG sub-function.
;
	add	di,DWORD*3+WORD		; skip user supplied info
	mov	ax,EXE_SP[si]
	dec ax ! dec ax			; return ss:sp-2
	stosw
	xchg	ax,bx			; save SP for later
	mov	ax,EXE_SS[si]
	stosw

	push	ds
	mov	ds,ax

⌨️ 快捷键说明

复制代码 Ctrl + C
搜索代码 Ctrl + F
全屏模式 F11
切换主题 Ctrl + Shift + D
显示快捷键 ?
增大字号 Ctrl + =
减小字号 Ctrl + -