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

📄 ldthunk.asm

📁 dos 1.0 其中包含quick basic源代码、内存管理himem emm386 发展历史
💻 ASM
📖 第 1 页 / 共 2 页
字号:
;*
;*	COW : Character Oriented Windows
;*
;*	ldthunk.asm : code THUNK reloader

	TITLE	LDTHUNK - THUNK handler

	.xlist
	include kernel.inc
	include galloc.inc
	include sstack.inc
	.list

IFDEF DEBPUB	;* Debugging publics
	PUBLIC	ReloadSegment, RelruSegment, ReturnThunk
ENDIF ;DEBPUB


sBegin	DATA
    assumes DS,DGROUP

externW     <psLom>
externW     <pGlobalHeap>
externW	    <bpOldStack, ssOldStack, pStackMin>

IFNDEF NOPCODE
externW     <$q_mpsnq>			;* HandleTable - 2
ENDIF ;!NOPCODE

sEnd	DATA

sBegin	BSS
    assumes DS,DGROUP

staticB	    levelLru,0			;* 0 => no Relru's since last sweep
					;* 1 => recent Relru's since last sweep
					;* >1 => major Relru's since last sweep
staticB     fLockoutSweep,0		;* TRUE => in the middle of changing thunks

sEnd	BSS


sBegin	KERNEL
    assumes CS,KERNEL
    assumes DS,NOTHING		;* may be called from anywhere
    assumes SS,DGROUP

externNP    <LoadSegment>			;* from ldseg.asm

globalW	bpSaveThunk,0
globalW	spSaveThunk,0
globalW	ssSaveThunk,0
staticW	axSaveThunk,0
staticW	bxSaveThunk,0

IFDEF KERNEL_SWAP_STACK
globalW	sstVap,SST_NO_VAP		; Current Vap Stack State

;*
;*	*  Variables associated with Current Vap Stack

globalW	spVap,?
globalW	ssVap,?
globalW bpVap,?

;*	* Variables associated with Kernel Stack

globalW	spKernel,0
globalW	ssKernel,0
globalW bpKernel,0

ENDIF						;* KERNEL_SWAP_STACK

;*	* Variables in the code segment !!! *

staticW csSave,?
staticW ipSave,?
staticW flagsSave,?

;* * since LRU may occur for resident segments, separate variables are needed
staticW ipSaveLru,?
staticW flagsSaveLru,?
staticW	csSaveLru,?


;********** ReloadSegment **********
;*	entry : MUST be called in the following format
;*		and must be part of ENTMOVE1 structure - in psLom !!
;*			CALLN to near, then JMPF ReloadSegment
;*			DW offset
;*			DB segno
;*	* Load the requested segment, fix up entry table
;*	* then jump to the entry point
;*	exit : never return to caller, jump to destination segment/offset
;*	* DOES NOT ALTER ANY REGISTERS (ignores changing DS)

cProc	ReloadSegment,<FAR>
cBegin	nogen	;ReloadSegment

    assumes DS,NOTHING
	pop	ipSave
	pushf
	pop	flagsSave
;*	* point return address to start of ENTMOVE
	Assert	<offDestEntmove1-opcEntmove1 EQ 3>	;* Near call size
	sub	ipSave,offDestEntmove1-opcEntmove1

IFNDEF KERNEL_SWAP_STACK
	SetStackToDds	1
ELSE
;*	* REVIEW: replace this with CRMGR stack interface
	;*	See if called with the kernel's stack or with a vap stack.

	cmp	sstVap,SST_ACT_VAP	; Is the vap currently active?
	jne	rs10
	
	;*
	;*	Create a stack frame for this function -- may need to back
	;*		batch the call to here if we discard the wrong segment
	;*
	
	inc	bp
	push	bp
	mov	bp,sp
	
	;*	The Vap stack is currently active!!
	;*	Change to the KERNEL stack since ss==DGROUP must be true.
	
	mov	bpVap,bp		; Save the vap's stack
	mov	ssVap,ss
	mov	spVap,sp
	
	mov	bp,bpKernel		; Now load in the kernel's stack
	cli
	mov	ss,ssKernel
	mov	sp,spKernel
	sti
	
	;	Now that stack are changed continue with the real code

rs10:
ENDIF							;* KERNEL_SWAP_STACK
	inc	bp
	push	bp
	mov	bp,sp
	push	ds
	push	es		    ; These registers used
	push	dx
	push	cx
IFDEF KERNEL_SWAP_STACK
	push	bx
	push	ax
ENDIF

	    ; Get address of interrupt instruction within entry table
	mov	es,psLom			;* call from psLom
	mov	csSave,es			;* save this for later
	mov	bx,ipSave
	    ; Get segment number to load
	xor	cx,cx
	mov	cl,es:[bx+segnoEntmove1]
	push	cx			;* segno

	cCall	LoadSegment	;<cx> - returns ax = ps (ignore)

IFDEF KERNEL_SWAP_STACK
	pop	ax
	pop	bx
ENDIF
	pop	cx
	pop	dx
	pop	es
	pop	ds
	pop	bp
	dec	bp
	
IFNDEF KERNEL_SWAP_STACK
	RestoreStackFromDds 1
ELSE
;*	* REVIEW: replace this with CRMGR stack interface
	;	Now - Do we need to restore the vap's stack?

	cmp	sstVap,SST_ACT_VAP	; Is the vap currently active?
	jne	rs99
	
	mov	bp,bpVap
	cli
	mov	ss,ssVap
	mov	sp,spVap
	sti
	
	pop	bp			;* Remove the stack frame
	dec	bp
	
	; Now that the correct stack is pointed to, set-up the return
	;	address as an interupt return.   We indirect back through
	;	the thunk entry which is now a near call to the routine
	;	RelruSegment rather than a near call to this routine.

rs99:
ENDIF						;KERNEL_SWAP_STACK
	push	flagsSave
	push	csSave
	push	ipSave
	iret

cEnd	nogen	;ReloadSegment


;********** RelruSegment **********
;*	entry : MUST be called in the following format
;*		and must be part of ENTMOVE1 structure - in psLom !!
;*			CALLN to near, then JMPF RelruSegment
;*			DW offset
;*			DB segno
;*	* Segment MUST! be loaded, just update LRU
;*	exit : never return to caller, jump to destination segment/offset

cProc	RelruSegment,<FAR>
cBegin	nogen	;ReluSegment

    assumes DS,NOTHING
	pop	ipSaveLru		;* near call return address
	pushf
	pop	flagsSaveLru

IFNDEF KERNEL_SWAP_STACK
	SetStackToDds	0		;* no swapping will occur
ELSE
;*	* REVIEW: replace this with CRMGR stack interface
	;*	See if called with the kernel's stack or with a vap stack.

	cmp	sstVap,SST_ACT_VAP	; Is the vap currently active?
	jne	rls10
	
	;*	The Vap stack is currently active!!
	;*	Change to the KERNEL stack since ss==DGROUP must be true.
	
	mov	bpVap,bp		; Save the vap's stack
	mov	ssVap,ss
	mov	spVap,sp
	
	mov	bp,bpKernel		; Now load in the kernel's stack
	cli
	mov	ss,ssKernel
	mov	sp,spKernel
	sti
	
	;	Now that stack are changed continue with the real code

rls10:
ENDIF						;KERNEL_SWAP_STACK

	push	ds
	push	es		    ; These registers used
	push	dx
	push	cx
IFDEF KERNEL_SWAP_STACK
	push	bx
	push	ax
ENDIF

	mov	fLockoutSweep,1

;*	* point return address to start of ENTMOVE1
	Assert	<offDestEntmove1-opcEntmove1 EQ 3>	;* Near call size
	mov	ax,ipSaveLru
	sub	ax,offDestEntmove1-opcEntmove1
	mov	ipSaveLru,ax
	mov	dx,ax

;*	* Get segment number to re-lru
	mov	ds,psLom
    assumes DS,NOTHING
	mov	csSaveLru,ds
	mov	bx,dx				;* call was in psLom
	mov	al,ds:[bx+segnoEntmove1]
	dec	al
	xor	ah,ah
	mov	bx,ax				;* bx = zero based segment #
	add	bx,ds:[neLom.ne_psegrefbytes]
	xor	cl,cl
	xchg	cl,ds:[bx]			;* re-lru'd
						;* stuff 0, cl = old count
	or	cl,cl
	js	negative_segref
	or	levelLru,cl			;* if segref > 1 then
						;* levelLru will be > 1
	jmp	short resume_segref

;*	* negative_segref
;*	-- a segref was negative, the only allowed negative segrefs are
;*	-- for bound segments (assert that) and restore segref
;*	-- (i.e. bound stay bound).

negative_segref:
	AssertEq cl,segrefBound
	mov	ds:[bx],cl 		;* restore it

resume_segref:

;*	* get segment address
	Assert	<SIZE NEW_SEG1 EQ 10>
	shl	ax,1
	mov	bx,ax				;* times 2
	shl	ax,1
	shl	ax,1
	add	bx,ax				;* times 10
	add	bx,ds:[neLom.ne_segtab]		;* ds:bx => NEW_SEG1
	mov	bx,ds:[bx].ns_handle		;* MUST BE A HANDLE
	AssertReset bx,1			;* (i.e. odd)
;*	* deference handle - cheap
	mov	es,pGlobalHeap
	AssertNe es:[bx].he_flags,HE_DISCARDED	;* MUST be resident
	mov	ax,es:[bx].he_address

;*	* change ENTMOVE1 (relru) to ENTMOVE
	mov	bx,dx				;* ES:BX => ENTMOVE / ENTMOVE1
	AssertEq ds:[bx].opcEntmove,opcCalln	;* should have been a call
	mov	ds:[bx].opcEntmove,opcJmpf
	mov	dx,ds:[bx].offDestEntmove1
	mov	ds:[bx].offEntmove,dx
	mov	ds:[bx].segEntmove,ax		;* ps of loaded code segment

;*	* done
	mov	fLockoutSweep,0
IFDEF KERNEL_SWAP_STACK
	pop	ax
	pop	bx
ENDIF
	pop	cx
	pop	dx
	pop	es
	pop	ds

IFNDEF KERNEL_SWAP_STACK
	RestoreStackFromDds 0		;* no swapping will occur
ELSE
;*	* REVIEW: replace this with CRMGR stack interface
	;	Now - Do we need to restore the vap's stack?

	cmp	sstVap,SST_ACT_VAP	; Is the vap currently active?
	jne	rls99
	
	mov	bp,bpVap
	cli
	mov	ss,ssVap
	mov	sp,spVap
	sti
	
	; Now that the correct stack is pointed to, set-up the return
	;	address as an interupt return.   We indirect back through
	;	the thunk entry which is now a jump to the real address
	;	rather than a near call to this routine.

rls99:
ENDIF						;KERNEL_SWAP_STACK
	push	flagsSaveLru
	push	csSaveLru
	push	ipSaveLru
	iret

cEnd	nogen	;RelruSegment



;********** ReturnThunk **********
;*	entry : MUST be called in the following format
;*		and must be part of entry table:
;*			CALLN then JMPF to ReturnThunk
;*			DB segno
;*			DW offset
;*	* Return via a return thunk
;*	* DS is actually the destination IP
;*	* the return CS:IP has the handle of the proper DS encoded in it.
;*	* load in the returned segment (if needed), return to the proper
;*	*  place with the proper DS
;*	exit : never return to caller, jump to return address
;*	* DOES NOT ALTER ANY REGISTERS (other than DS)

cProc	ReturnThunk,<FAR>
cBegin	nogen ;ReturnThunk

    assumes DS,NOTHING
	pop	ipSave					;* => segno
	pushf
	pop	flagsSave

IFNDEF KERNEL_SWAP_STACK
	SetStackToDds	1
ELSE
;*	* REVIEW: replace this with CRMGR stack interface
	;*	See if called with the kernel's stack or with a vap stack.

	cmp	sstVap,SST_ACT_VAP	; Is the vap currently active?
	jne	rt10
	
	;*
	;*	Create a stack segment for insurance
	;*
	
	inc	bp
	push	bp
	mov	bp,sp
	
	;*	The Vap stack is currently active!!
	;*	Change to the KERNEL stack since ss==DGROUP must be true.
	
	mov	bpVap,bp		; Save the vap's stack
	mov	ssVap,ss
	mov	spVap,sp
	
	mov	bp,bpKernel		; Now load in the kernel's stack
	cli
	mov	ss,ssKernel
	mov	sp,spKernel
	sti
	
	;	Now that stack are changed continue with the real code

rt10:
ENDIF						; KERNEL_SWAP_STACK
	inc	bp
	push	bp
	mov	bp,sp
	push	ds
	push	es		    ; These registers used
	push	dx
	push	cx
IFDEF KERNEL_SWAP_STACK
	push	bx
	push	ax
ENDIF

;*	* Get address after return thunk's call instruction
	mov	es,psLom			;* call from psLom
	mov	bx,ipSave
;*	* Get return offset
	mov	cx,es:[bx+offEntret-3]		;* after near call
	mov	ipSave,cx			;* return offset
	mov	es:[bx+offEntret-3],-1		;* top entry already found
;*	* Get segment number to load
	Assert	<segnoEntret EQ 3>		;* after near call
	xor	cx,cx
	mov	cl,es:[bx+segnoEntret-3]
	push	cx			;* segno

	cCall	LoadSegment	;<es,cx,bx,bx> - returns AX = psLoaded
	mov	csSave,ax

IFDEF KERNEL_SWAP_STACK
	pop	ax
	pop	bx
ENDIF
	pop	cx
	pop	dx
	pop	es
	pop	ds
	pop	bp
	dec	bp

IFNDEF KERNEL_SWAP_STACK	
	RestoreStackFromDds 1
ELSE
;*	* REVIEW: replace this with CRMGR stack interface
	;	Now - Do we need to restore the vap's stack?

	cmp	sstVap,SST_ACT_VAP	; Is the vap currently active?
	jne	rt99
	
	mov	bp,bpVap
	cli
	mov	ss,ssVap
	mov	sp,spVap
	sti

	pop	bp			;* Remove stack frame
	dec	bp
	
rt99:
ENDIF						; KERNEL_SWAP_STACK
	push	flagsSave
	push	csSave				;* return to proper segment
	push	ipSave
	iret

cEnd	nogen ;ReturnThunk

;*****************************************************************************

;*	* Thunk Patch Routines *

    assumes ds,nothing


;********** PatchThunkMoved **********
;*	entry : segno = segment number that moved (1 based)
;*		psNew = new physical segment it is located at
;*	* Fix up thunks & other info for moved segment
;*		1) fix up moveable entry table
;*	exit : n/a

cProc	PatchThunkMoved,<NEAR,PUBLIC>,<DS>
    parmB segno
    parmW psNew
cBegin	PatchThunkMoved

	mov	fLockoutSweep,1

;*	* Scan the entry table
	mov	ds,psLom			;* assumed throughout
	mov	bx,ds:[neLom.ne_rgentmove]
	mov	cx,ds:[neLom.ne_cmovent]
	mov	al,segno
	mov	es,psNew
pmv_lp:
	cmp	al,ds:[bx].segnoEntmove		;* segment in question ?
	jne	pmv_nxt
	cmp	ds:[bx].opcEntmove,opcJmpf
	jnz	pmv_nxt				;* ignore if Relru
	mov	ds:[bx].segEntmove,es		;* fix direct jump address
pmv_nxt:
	add	bx,SIZE ENTMOVE
	loop	pmv_lp

	mov	fLockoutSweep,0

cEnd	PatchThunkMoved



;********** PatchThunkLoaded **********
;*	entry : segno = segment number that got loaded (1 based)
;*		psNew = new physical segment it is located at
;*	* Fix up thunks & other info for moved segment
;*		1) fix up moveable entry table
;*		2) clear segment reference byte
;*	exit : n/a

cProc	PatchThunkLoaded,<NEAR,PUBLIC>,<DS>
    parmB segno
    parmW psNew
cBegin	PatchThunkLoaded

	mov	fLockoutSweep,1

;*	* Scan the entry table
	mov	ds,psLom			;* assumed throughout
	mov	bx,ds:[neLom.ne_rgentmove]
	mov	cx,ds:[neLom.ne_cmovent]
	mov	al,segno
	mov	es,psNew
pld_lp:
	cmp	al,ds:[bx].segnoEntmove		;* segment in question ?
	jne	pld_nxt
	AssertEq ds:[bx].opcEntmove,opcCalln	;* should have been a call
	mov	ds:[bx].opcEntmove,opcJmpf
	mov	dx,ds:[bx].offDestEntmove1
	mov	ds:[bx].offEntmove,dx
	mov	ds:[bx].segEntmove,es
pld_nxt:
	add	bx,SIZE ENTMOVE
	loop	pld_lp

;*	* clear segment reference byte
	dec	al
	xor	ah,ah
	add	ax,ds:[neLom.ne_psegrefbytes]
	mov	bx,ax
	Assert	<segrefLoaded EQ 0>
	mov	byte ptr ds:[bx],segrefLoaded

	mov	levelLru,0ffh			;* force sweep
	mov	fLockoutSweep,0

cEnd	PatchThunkLoaded



;********** PatchThunkDiscarded **********
;*	entry : segno = segment number that got discarded (1 based)
;*		DS => DDS
;*	* Fix up thunks & other info for moved segment
;*		1) fix up moveable entry table
;*		2) set segment reference byte to 0ffh
;*	exit : n/a

⌨️ 快捷键说明

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