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

📄 nhlhutil.asm

📁 Microsoft MS-DOS6.0 完整源代码
💻 ASM
📖 第 1 页 / 共 4 页
字号:
	XCHG	AX,SI		;[SI] = proposed new physical heap end
	CALL	LHSetEnd	;Set the new end of var heap

	CALL	LH_MOV_DOWN	;Move the var heap down

	XCHG	AX,SI		;[AX] = var heap's new b$HEAP_FIRST
	CALL	B$TglHeapSptNEAR ; use local heap pointers

	INC	AX		;[AX] = new b$NH_First
	MOV	CX,[b$NH_Last]	;[CX] = unchanged last
	CALL	B$NHMOV		;Move near heap around
	MOV	[b$NH_First],AX

NHMOVALL_DONE:
	OR	AX,AX		;Successfull return
NHMOVALL_EXIT:

cEnd

	SUBTTL

;***
; B$NHMOV - move dynamic space (strings and local heap)
; Purpose:
;	Moves the contents of the string and local heaps to the beginning
;	and ending word offsets given.
;
; Inputs:
;	AX = offset to define start of dynamic space
;	CX = (if nonzero) offset to define end of dynamic space
;	     (if zero) offset is to be minimum possible
; Outputs:
;	AX = starting offset of dynamic space
;	CX = ending offset of dynamic space
;	CF = 0 - move successful - offsets reflect those requested
;	     1 - move unsuccesssful - request space too small
; Modifies:
;	None.
; Exceptions:
;	None.
;****

B$NHMOV  PROC	  NEAR		
	ASSERT_NOT_VARHEAP NH_TEXT 
	PUSH	SI		;save register...

;	If CX=0, the local heap is to be adjacent to the string heap
;	with no intervening free space.  Assume here that the local
;	heap will move down.

	JCXZ	MOVDYN_LH_DOWN	;heap will move down

;	Test that dynamic space start is before the end.  If not,
;	then report the error by returning with carry set.

	INC	CX		;heap header index is on odd byte of last word
	CMP	CX,AX		;test if start is before end
	JB	MOVDYN_DONE	;if not, then jump with carry set for error

;	Jump if local heap will move down.

	CMP	CX,[b$HEAP_FIRST] ;test if heap moves down
	JBE	MOVDYN_LH_DOWN	;brif so

;	Local heap moves up to offset in CX.  Then move the string heap
;	to offset in AX.

	MOV	SI,CX		;get offset to move local heap
	CALL	LH_MOV	;move the local heap up
	MOV	CX,SI		;update end offset of dynamic space (+1)
	MOV	SI,AX		;get offset to move string heap
	CALL	B$STMOV	;move the string heap (up or down)
	XCHG	AX,SI		; [AX] = offset of dynamic space
	JMP	SHORT MOVDYN_DONE_CLC ;jump to nonerror return

;	Local heap is to be moved down in memory.  Test if string heap
;	is moved down or up.

MOVDYN_LH_DOWN:
	CMP	AX,[b$STRING_FIRST] ;test if strings moving down
	JBE	MOVDYN_SS_DOWN	;if so, then jump

;	The string heap is moving up and the local heap is moving down.
;	First, compact the heap and give any free space to string heap.

	CALL	B$LH_CPCT	   ;compact local heap
	CALL	B$STFromLH	;give any local heap free space to string heap

;	Move string heap to requested location.

MOVDYN_SS_DOWN:
	MOV	SI,AX		;get request offset for string heap
	CALL	B$STMOV	;move the string heap
	XCHG	AX,SI		; [AX] = starting offset of dynamic heap
	JC	MOVDYN_DONE	;if error moving string heap, return with carry

;	If local heap need not be moved, then finished.

;MOVDYN_SS_SAME:
	CMP	CX,[b$HEAP_FIRST] ;test if local heap need be moved
	JE	MOVDYN_DONE	;if not, done, return with carry clear

;	Move local heap down be first making it adjacent to the string
;	heap.  If this was originally requested, then finished.

	XOR	SI,SI		;clear for minimum local heap offset
	CALL	LH_MOV	;move local heap next to string heap
	XCHG	CX,SI		;swap requested offset and return offset
	OR	SI,SI		;test if requested offset was zero
	JZ	MOVDYN_DONE	;if so, then return with carry clear

;	Move heap to final requested location.

	CMP	SI,CX		;compare requested location with returned one
	JBE	MOVDYN_DONE	;if less, ran out of room, return with carry
				;if equal, request finished, return w/o carry
	CALL	LH_MOV	;move the local heap to requested offset in SI
	MOV	CX,SI		;update end offset of dynamic space

;	Finished with no error - return carry cleared.

MOVDYN_DONE_CLC:
	CLC			;clear carry for no error

;	Finished - carry set or cleared appropriately.

MOVDYN_DONE:
	DEC	CX		;point to even byte of ending offset
	POP	SI		;restore register
	RET			;near return to caller
B$NHMOV  ENDP			

;***
; LH_MOV - move local heap
; Purpose:
;
; Moves local heap to the offset specified in SI if SI<>0.  IF SI=0, then move
; heap just under allocated string space. Local heap start [b$HEAP_FIRST] is set
; appropriately. The space is returned compacted.
;
; Inputs:
;	SI = offset for new local heap start, or 0 for reverse compaction.
; Outputs:
;	SI = offset of new local heap start.
; Modifies:
;	None.
; Exceptions:
;	B$ERR_SSC - nontrappable error if compaction finds corruption
;		  in local heap structure.
;****
LH_MOV	PROC	NEAR
	PUSH	AX		;save register
	OR	SI,SI		;test if moving heap to under string space
	JNZ	LH_MOV_UP	;if not, then jump to move heap up

;	SI=0, so perform the reverse compaction of the local heap just
;	under string space and return the new heap start offset in SI.

	CALL	B$LH_FROM_SS	;get any leading string entries to heap
	CALL	LH_MOV_DOWN	;perform reverse compaction to under strings
	JMP	SHORT LH_MOV_RETURN ;jump to set new heap start and return

;	SI nonzero, so prefix the heap with an unallocated entry from the
;	new start offset to the present start offset, then perform a
;	heap compaction.

LH_MOV_UP:
	MOV	AX,SI		;compute length of new entry to prefix...
	SUB	AX,[b$HEAP_FIRST] ;by difference between the two offsets
	CMP	AX,LH_STD_HDR_LEN
	JC	LH_MOV_NOMOVE	; If not moving by enough, don't add free
	MOV	[SI].LHTYPE,LOW LH_FREE ;set type of unallocated heap block
	MOV	[SI].LHLEN,AX	;set length of new heap block
	MOV	[b$HEAP_FIRST],SI ;set new entry as heap start
	SUB	SI,AX		;point to old heap start offset
	MOV	[SI+1],AX	;set new heap backlength
LH_MOV_NOMOVE:			
	CALL	B$LH_CPCT	   ;compact heap including new entry

LH_MOV_RETURN:
	MOV	SI,[b$HEAP_FIRST] ;report back start of heap
	POP	AX		;restore register
	RET			;return to caller
LH_MOV	ENDP

;***
; LH_MOV_DOWN - move local heap down in memory
; Purpose:
;	Compacts the local heap to low memory starting at the last
;	entry to the first.  Sets b$HEAP_FIRST to the new location of
;	the first allocated entry as no unallocated entry exists.
;	The heap will be just after the string space.
;
; Inputs:
;	None.
; Outputs:
;	[b$HEAP_FIRST] and [b$HEAP_FREE] of compacted heap.
;	[SI] - new value of b$HEAP_FIRST
; Modifies:
;	AX,SI
; Exceptions:
;	None.
;****

LH_MOV_DOWN:
	PUSH	CX		;save registers...
	PUSH	DI
	PUSH	DX

;	Scan local heap from [b$HEAP_END] to [b$HEAP_FIRST] by using the
;	entry backlengths to determine the next entry.

	MOV	SI,[b$HEAP_END] ;initialize pointer for scan
	MOV	[b$HEAP_FREE],SI ;free pointer will point to last heap entry

;	Skip over allocated entries as these are not moved.  If the last
;	entry to be scanned in [b$HEAP_FIRST], exit with no compaction.

LH_MOV_SKIP_LOOP:
	CMP	SI,[b$HEAP_FIRST]  ;test if end of scanning
	JE	LH_MOV_NO_COMPACT ;if so, then no compaction needed
	ADD	SI,[SI+1]	; [SI] = pointer to next entry header
	CMP	[SI].LHTYPE,LOW LH_FREE ;test if entry is allocated
	JNE	LH_MOV_SKIP_LOOP ;try for next allocated entry

	MOV	DX,[b$HEAP_FIRST] ;end of range to move
	CALL	LH_MOV_DN_RG	;given 1st unallocated entry, move all down

;	Finish reverse compaction by setting [b$HEAP_FIRST] to the last
;	entry in the compacted heap.

	MOV	[b$HEAP_FIRST],DI;put into pointer of heap start
LH_MOV_NO_COMPACT:
	MOV	SI,[b$HEAP_FIRST];return new pointer to new first entry
	POP	DX
	POP	DI		;restore registers...
	POP	CX
	RET			;return to caller

;***
; LH_MOV_DN_RG
; Purpose:
;	Compacts the local heap to low memory starting at a given unallocated
;	entry (bottom of range to be compacted) and ending with a given
;	allocated entry (the last entry (entry at highest memory of the
;	range) to be compacted).
;	Note that nothing is done to the free space which bubbles up to
;	the top of the range; no header is given to it.
;	NOTE: if the interpreter refuses permission for LH entries to move,
;		this routine will result in no movement (exit values will
;		be correctly set up for this case).
;
; Inputs:
;	SI = pointer to heap entry hdr for unallocated entry at bottom of
;		range to be compacted.
;	DX = pointer to heap entry hdr for allocated entry at top of range
;		to be compacted.
; Outputs:
;	DI = pointer to heap entry hdr for allocated entry at top of range
;		after compaction
;	DX = same as input value of DX, i.e., pointer to top of range allocated
;		heap entry hdr prior to compaction
; Modifies:
;	AX,CX,SI,DI
;
; Exceptions:
;	None.
;****
LH_MOV_DN_RG:
;	Set up pointer DI as the destination offset as the first byte of the
;	given unallocated entry.
	PUSH	ES		
	PUSH	DS		
	POP	ES		;Set ES = DS
	MOV	DI,SI		;get pointer to the unallocated entry
	SUB	DI,[SI].LHLEN	;point to one less than entry backlength
	INC	DI		;entry backlength - compaction starts here

;	Loop for entries after the given unallocated entry.
;	Check for entry consistency and heap end.

LH_MOV_ENTRY_LOOP:
	CMP	SI,DX		;test if end of scanning
	JE	LH_MOV_FINISH	;if so, then jump to finish
	ADD	SI,[SI+1]	; [SI] = pointer to next entry header
	CALL	B$LH_PTR_CHECK	 ;check entry at [SI] for consistency
	CMP	[SI].LHTYPE,LOW LH_FREE ;test if entry is allocated
	JE	LH_MOV_ENTRY_LOOP ;if so, loop to check it, etc.
;
;	Allocated entry needs to be block transferred to ES:DI.
;	First adjust the entry, then move the entry itself.
;
	LEA	CX,[SI+1]	; get pointer one past entry to be moved
	SUB	CX,[SI].LHLEN	;point to backlength, ready for transfer

	MOV	AX,DI		;compute adj by destination backlength ptr...
	SUB	AX,CX		;less the source backlength pointer
	CALL	B$LHADJ	;adjust the entry backpointers

	MOV	SI,CX		;put source backlength pointer in reg
	MOV	CX,[SI] 	;backlength number of bytes
	SHR	CX,1		;convert to number of words to transfer
	REP	MOVSW		;perform the transfer - DI ready for next

; Now there is a void between two entries and the heap is not walkable.
; Make the void a free entry.
	NEG	AX			;convert back to positive byte count
	DEC	SI			; si = pHdr for new free entry
	MOV	[SI].LHLEN,AX		; stuff in length
	MOV	[SI].LHTYPE,LOW LH_FREE	; mark it as free
	MOV	[DI],AX 		; fill in backlength for new free entry
	NEG	AX			; back to negative adjustment factor

	JMP	SHORT LH_MOV_ENTRY_LOOP ;jump to process next entry

LH_MOV_FINISH:
	DEC	DI		;last byte is header offset

	;now set the free block up with a hdr & backlength in case this is req'd
	MOV	CX,DX
	SUB	CX,DI		;CX = size of new free block
	MOV	SI,DX
	MOV	[SI].LHLEN,CX
	MOV	[SI].LHTYPE,LOW LH_FREE
	MOV	[DI+1],CX	;backlength for free block
LH_MOV_RG_EXIT:
	POP	ES		
	RET



;***
; B$LH_I_ADJ
; Purpose:
;	Update the backpointers to any owners contained in an entry that's
;	about to be moved.
; Inputs:
;	SI = hdr ptr to entry about to be moved
;	AX = adjustment factor (to be added to backpointers to any owners
;		in this entry).
; Outputs:
;	none.
; Modifies:
;	BX, CX
;****
cProc	B$LH_I_ADJ,<PUBLIC,NEAR>
cBegin				
	MOV	CL,[SI].LHTYPE
	TEST	CL,LOW LH_IM_CALL_BACK
	JZ	LH_I_ADJ_DONE	;brif no owners in entry being moved

	TEST	CL,LH_IM_ENTRY
	JZ	LH_I_ADJ_DONE	;brif not an interpreter entry

	MOV	BX,[SI].LHBAKP	;put backpointer in BX
	CALL	B$IHeapEntryMoved ;call interpreter to do the work of
				;  updating backptrs to owners in this entry
				;  AX,BX,CL are parms
LH_I_ADJ_DONE:
cEnd				



;***
; B$LHForEachEntry
; Purpose:
;	Given a pointer to a (NEAR) function, walk the local heap, calling
;	This function for each entry, with the entry backpointer (pointer
;	to the entry owner) and the entry type byte.
;
;	On entry to routines called for each entry,
;		BX = pointer to entry owner,
;		DL = entry type byte
;	Users within this module can also use the fact the SI will be a pointer
;		to the header for the current entry.
;	Called functions must preserve all registers except BX and DX.
;	Callers of this function may pass other parameters to their called
;		function via AX and/or DI, which are not used by this routine.
;
;	NOTE: for entries which do not have backpointers, the called function
;		will receive (in BX) whatever is in the field corresponding
;		to the backpointer for that entry.
;
; Inputs:
;	CX = pointer to function to call for each entry.
;	ES = segment that the state vars are in
;	other parameters may be in AX and/or DI, to be passed to the function
;		whose pointer is given in CX. (BC only)
; Outputs:
;	none.
; Modifies:
;	none, unless called function modifies some register(s).
; Exceptions:
;	none (does not check entries for integrity).
;****
assumes	ES,DGROUP			
B$LHForEachEntry	PROC	NEAR
	PUSH	DX
	PUSH	BX
	PUSH	SI
	MOV	SI,[b$HEAP_FIRST]	
ForEach_Loop:
	CMP	SI,[b$HEAP_END] 	; done searching heap?
	JBE	ForEach_Exit		;  brif so

	MOV	DL,[SI].LHTYPE		;get type byte
	MOV	BX,[SI].LHBAKP		;get pointer to owner
	CALL	CX			;call function

	SUB	SI,[SI].LHLEN		;move down to next entry
	JMP	SHORT ForEach_Loop

ForEach_Exit:
	POP	SI
	POP	BX
	POP	DX
	RET
B$LHForEachEntry	ENDP
assumes	ES,NOTHING			

	SUBTTL	LHSetEnd - Set new HEAP_END
	PAGE
;*** 
;LHSetEnd - Set new HEAP_END
; Added, revision [26]
;
;Purpose:
; Truncate or expand the trailing free entry in the heap in order to set a new
; b$HEAP_END pointer.
;
;Entry:
; [SI]	= Proposed new b$HEAP_END
;
;Exit:
; Carry set on failure
;
;Uses:
; Per convention
;
;******************************************************************************
cProc	LHSetEnd,NEAR,DI
cBegin
	CALL	B$LHSetFree	;[DI] = trailing free heap entry
	CMP	SI,[b$HEAP_END] ;Determine which way the pointer is moving
	JC	LHSetEnd_DOWN	;Jump if we're expanding down

	CMP	DI,SI		;See if trying to move above the free entry
	JC	LHSetEnd_EXIT	;Jump if we are (carry set). Can't do that
	JZ	LHSetEnd_Empty	;Jump if we are not moving (carry not set).

LHSetEnd_DOWN:
	MOV	AX,DI		;[AX] = trailing free heap entry
	SUB	AX,SI		;[AX] = new size of free entry in AX
	MOV	[DI].LHTYPE,LOW LH_FREE ;set heap entry type
	MOV	[DI].LHLEN,AX	;set free heap entry length
	MOV	[SI+1],AX	;set free heap entry backlength

LHSetEnd_Empty:
	MOV	[SI].LHTYPE,LOW LH_END ;define the entry type
	MOV	[b$HEAP_END],SI ;define the heap end pointer

⌨️ 快捷键说明

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