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

📄 nhlhutil.asm

📁 Microsoft MS-DOS6.0 完整源代码
💻 ASM
📖 第 1 页 / 共 4 页
字号:
	OR	AX,AX		;Done, clear carry

LHSetEnd_EXIT:

cEnd

;***
; B$LHFLDDESCADD - add descriptor to field backpointer string.
; Purpose:
;	Add the descriptor value specified to the backpointer string
;	in the heap entry in SI.
;
; Inputs:
;	BX = address of descriptor to be added.
;	SI = FDB address of heap entry.
; Outputs:
;	None.
; Modifies:
;	SI.
; Exceptions:
;	None.
;****


B$LHFLDDESCADD:		
	ASSERT_NOT_VARHEAP NH_TEXT 
	PUSH	AX		;save registers...
	PUSH	BX
	PUSH	CX
	PUSH	DX
	PUSH	DI

;	Compute heap entry descriptor from the FDB address specified.

	CALL	B$LH_PTR_FROM_DATA ;heap entry pointer is now SI
	ADD	SI,LHPLEN	;move pointer to heap backpointer descriptor

;	Copy backpointer string to temp string two bytes longer.

	MOV	AX,BX		;save added descriptor value
	MOV	BX,SI		;get copy of heap descriptor pointer
	XOR	CX,CX		;copy from the string start
	MOV	DX,[BX] 	;get backpointer string length
	ADD	DX,2		;new string is to be two bytes longer
	CALL	B$STALCTMPSUB	;BX is ptr to desc of longer copy of string

;	Add fielded descriptor to string at the end.

	MOV	DI,DX		;get length of new string
	ADD	DI,[BX+2]	;point past end of the new string
	MOV	[DI-2],AX	;add descriptor to string at last two bytes

;	Deallocate old string data pointed by SI.

	XCHG	BX,SI		;BX=old string desc - SI=new string desc
	CALL	B$STDALC	;deallocate old string data (BX desc)

;	Copy new descriptor at SI to old descriptor at BX and then adjust
;	the new string backpointer to point to BX. (BX is in heap entry)

	ADD	WORD PTR [BX],2 ;new string is always two bytes longer
	MOV	DI,[SI+2]	;get new string data offset
	MOV	[BX+2],DI	;put into heap entry descriptor
	MOV	[DI-2],BX	;set new string backpointer

;	Free the temp descriptor at SI.

	MOV	BX,SI		;get temp descriptor pointer
	CALL	B$STDALCTMPDSC ;and free the descriptor

	POP	DI		;restore registers...
	POP	DX
	POP	CX
	POP	BX
	POP	AX
	RET			;return to caller

;***
; B$LHLOCFDB - return file number from FDB pointer
; Purpose:
;	Return the file number of the heap entry containing the
;	FDB pointed by the specified value.
;
; Inputs:
;	SI = pointer to FDB
; Outputs:
;	BL = file number
; Modifies:
;	None.
; Exceptions:
;	B$ERR_ssc if heap entry is inconsistent.
;****

B$LHLOCFDB:			
	PUSH	SI		;save FDB pointer
	CALL	B$LH_PTR_FROM_DATA ;get heap entry pointer (check entry lengths)
	MOV	BL,[SI].LHFNUM	;get file number from heap entry
	POP	SI		;restore FDB pointer
	RET			;return

;***
;B$LHFDBLOC - locate FDB with a specified file number
;DBCS-callback
;
;Purpose:
;	Return a pointer to the FDB in the local heap FILE
;	entry that contains the specified file number.
;
;Inputs:
;	BL = file number
;
;Outputs:
;	SI = pointer to FDB (if found) or 0 (if not found).
;	ZF = clear (if found) or set (if not found)
;
;Modifies:
;	None.
;
;Exceptions:
;	None.
;****

B$LHFDBLOC:			
	MOV	SI,[b$HEAP_FIRST];start pointer at start of local heap
FDBLOC_LOOP:
	CMP	[SI].LHTYPE,LOW LH_END ;test if at heap end
	JE	FDBLOC_END	;if so, jump to note failure
	CMP	[SI].LHTYPE,LOW LH_FILE ;test if file entry
	JNE	FDBLOC_NEXT	;if not, then jump to try for next entry
	CMP	[SI].LHFNUM,BL	;test if correct file number
	JE	FDBLOC_FOUND	;jump to show success
FDBLOC_NEXT:
	SUB	SI,[SI].LHLEN	;point to next entry
	JMP	SHORT FDBLOC_LOOP ;and jump to try the next one
FDBLOC_FOUND:
	SUB	SI,[SI].LHLEN	;point to entry after one found
	ADD	SI,3		;point past backlength to FDB start
	RET			;return (with ZF clear)
FDBLOC_END:
	XOR	SI,SI		;clear SI to show failure
	RET			;return (with ZF set)

	SUBTTL	B$NHCLEAN - Clean string space and local heap
	PAGE
;***
;B$NHCLEAN - Clean string space and local heap
;
;Purpose:
; To clean the string space and local heap of entries whose descriptors are not
; in blank COMMON or other special areas. This routine is used during the
; CHAINing process.
;
;Entry:
; [DS]	= segment that heap is in
; [ES]	= segment that state vars are in
;	  Normally, this means ES=DS=DGROUP, execpt for DOS 5 chain, during
;	  which this routine is called with ES = DGROUP, DS = the shared memory
;	  selector.
;
;Exit:
; None.
;
;Modifies:
; NONE
;
;Preserves:
; ALL (for previous compatibility)
;
;******************************************************************************
assumes	ES,DGROUP		
assumes	DS,NOTHING		
cProc	B$NHCLEAN,<PUBLIC,NEAR>,<AX,BX,CX,DX>
cBegin
	CALL	B$LHClean	;the local heap must be cleaned first
	CALL	B$SSClean	;then the string space can be cleaned
cEnd

	SUBTTL	B$LHClean - Clean the local heap
	PAGE
;***
;B$LHClean - Clean the local heap
;
;Purpose:
; Scan the heap and process each entry accordingly:
;
; If CHAINing (b$Chaining <> 0):
;
;     FILE:	deallocate the fielded strings not in COMMON and update the
;		fielded string backpointer string.
;     ARRAY:	determine if the array descriptor is wholly within COMMON and
;		if not, delete the array using LH_ADJ.
;
; ELSE:
;
;     FILE:	deallocate all fielded strings
;     ARRAY:	delete the array
;
;Entry:
; [DS]	= segment that heap is in
; [ES]	= segment that state vars are in
;	  Normally, this means ES=DS=DGROUP, execpt for DOS 5 chain, during
;	  which this routine is called with ES = DGROUP, DS = the shared memory
;	  selector.
;
;Exit:
; None.
;
;Modifies:
; Per Convention.
;
;****
cProc	B$LHClean,<NEAR,PUBLIC>
cBegin
;
; If chaining, clear out all items from 0 to b$commonfirst
;
	XOR	AX,AX
	CMP	ES:b$Chaining,AL ; If we are not chaining, clear 0-ffff
	JZ	LHCleanAll

	MOV	BX,ES:[b$commonfirst]
	DEC	BX		;Range is inclusive
	XOR	CX,CX		; only release string arrays and fdb's
	CALL	B$LHClearRange
;
; Clear out all items from b$commonlast to 0FFFFH
;
	MOV	AX,ES:[b$commonlast]
LHCleanAll:
	MOV	BX,0FFFFH
	XOR	CX,CX		; only release string arrays and fdb's
cEnd	nogen			;Fall into B$LHClearRange

	SUBTTL	B$LHClearRange - Clean the local heap of entries
	PAGE
;***
;B$LHClearRange - Clean the local heap of entries
;
;Purpose:
;
; Scan the heap and process each entry accordingly:
;
;   FILE:	fielded strings whose descriptors fall into the passed range
;		deallocated, and the fielded string back pointer string is
;		updated.
;
;   ARRAY:	If the array descriptor falls into the range, delete the array
;		using LH_ADJ.
;
;Entry:
;	AX	= Start address of range in which to delete
;	BX	= End address of range in which to delete (Range is inclusive)
;	CX	= non-zero if we're to release ALL owners in given range
;		  zero if we should release only string arrays and fdb's
;	DS	= Segment containing the near heap
;	ES	= Segment containing heap state vars (& stack)
;
;		    Normally, this means ES=DS=DGROUP, execpt for DOS 5 chain,
;		    during which this routine is called with ES = DGROUP, DS =
;		    the shared memory selector.
;
;Exit:
;
;Modifies:
; Per Convention.
;
;Exceptions:
; None.
;
;******************************************************************************
cProc	B$LHClearRange,<NEAR,FORCEFRAME,PUBLIC>,DI
cBegin
	PUSH	CX		; [BP-2] = flag - release ALL owners if TRUE
	PUSH	BX		; [BP-4] = end offset
	PUSH	AX		; [BP-6] = start offset

	MOV	DI,SP		;[SS:DI] = pointer to start and end data
	MOV	CX,OFFSET LHCleanRangeEntry	;[CX] = routine to call
	CALL	B$LHForEachEntry		;Scan Local Heap

	POP	AX		;Clean stack
	POP	BX
	POP	CX		
cEnd
;*** 
; LHCleanRangeEntry - Clear local heap entry, if conditions are right
;
;Purpose:
;
; Process heap entry accordingly:
;
;   FILE:	fielded strings whose descriptors fall into the passed range
;		deallocated, and the fielded string back pointer string is
;		updated.
;
;   ARRAY:	If the array descriptor falls into the range, delete the array
;		using LH_ADJ.
;
;Entry:
;	DL	= Heap entry type
;	BX	= Offset of heap entry owner
;	SS:DI	= Pointer to range words:
;			[SS:DI]   = start
;			[SS:DI+2] = end
;			[SS:DI+4] = flag - only in EI_QB versions. 
;					zero means release only LH_FILE and
;					LH_ARRAY entries. non-zero means
;					release ALL entries. 
;	DS:SI	= Pointer to heap entry
;	DS	= Segment containing the near heap
;	ES	= Segment containing heap state vars (& stack)
;
;Exit:
; None
;
;Uses:
; Per Convention
;
;******************************************************************************
cProc	LHCleanRangeEntry,NEAR
cBegin
;
;	If file entry, test if any fielded strings and call FIELD
;	to remove any fielded strings from the backpointer string.
;
	CMP	DL,LH_FILE	;test if file entry
	JNE	LH_NOT_FILE	;if not, then jump

	CMP	WORD PTR [SI].LHPLEN,0 ;test if any fielded strings
	JE	LH_DONE 	;if not, then try for the next entry
	CALL	LHCleanRangeField ;clean out entries
	JMP	SHORT LH_DONE	;done - try for the next entry
;
;	If ARRAY entry, compute the offset of the LAST word of the array
;	descriptor, and base decisions on that.
;
LHCleanQBIEntry:		
	CMP	WORD PTR SS:[DI+4],0	
	JNE	LHClean_Dealc	
	JMP	SHORT LH_DONE	; brif we only want to free arrays & fdb's

LH_NOT_FILE:
	MOV	BX,[SI].LHBAKP	;get backpointer to owner
	CMP	DL,LH_ARRAY	;test if array entry
	JNE	LHCleanQBIEntry ; brif not array entry

;  QB allocates static arrays at scan time.  We can't blindly release
;  the array data, or we will get SSC.  So, we treat this like other
;  QBI heap entries. They get released at new, rude edit, etc.

	TEST	[BX].AD_fFeatures,FADF_STATIC ;QBI static string array?
	JNE	LHCleanQBIEntry ;brif so, treat like QB entry
	MOV	AL,[BX].AD_cDims;get the number of dimensions of array
	CBW			;make it a word value in AX
	SHL	AX,1		;now make in a word index in AX
	ADD	BX,AD_tDM-2	;point to word before first dimension entry
	ADD	BX,AX		;one word per dimension - so last in desc.
LHClean_Dealc:			
	CMP	BX,SS:[DI]	;before start?
	JB	LH_DONE 	;jump if so, don't touch
	CMP	BX,SS:[DI+2]	;after end?
	JA	LH_DONE 	;jump if so, don't touch

	XOR	AX,AX		;set flag for deletion
	CALL	B$LHADJ	;unallocate the heap entry
	MOV	[SI].LHTYPE,LOW LH_FREE ; set entry type to FREE, in case
					; this is not a string array entry
LH_DONE:
cEnd

;***
;LHCleanRangeField - clean out fielded strings
;
;Purpose:
; fielded strings whose descriptors fall into the passed range deallocated, and
; the fielded string back pointer string is updated. Ignores strings whose
; descriptors are in the local heap, as they are part of dynamic strign arrays,
; dealt with elsewhere.
;
;Entry:
;	SS:DI	= Pointer to range words:
;			[SS:DI]   = start
;			[SS:DI+2] = end
;	DS:SI	= Pointer to file heap entry
;	DS	= Segment containing the near heap
;	ES	= Segment containing heap state vars (& stack)
;
;Exit:
; None.
;
;Modifies:
; Per Convention
;
;******************************************************************************
cProc	LHCleanRangeField,NEAR,
cBegin
;
;	Compute pointers to starting and ending word offsets of the
;	fielded string backpointer string.
;
	PUSH	SI		;Save heap entry pointer
	MOV	BX,[SI].LHPLEN	;[BX] = length of backpointer string
	MOV	SI,[SI].LHPOFF	;[SI] = pointer to start of backpointer string
	LEA	BX,[BX+SI-2]	;[BX] = pointer to end of backpointer string
;
;	Loop here for each backpointer string word element.
;
FIELD_LOOP:

	LODSW			;[AX] = next string element to process

	CMP	AX,ES:[b$HEAP_END] ;String in near heap?
	JA	FIELD_NOTIN	;jump if so, don't touch
	CMP	AX,SS:[DI]	;before start?
	JB	FIELD_NOTIN	;jump if so, don't touch
	CMP	AX,SS:[DI+2]	;after end?
	JA	FIELD_NOTIN	;jump if so, don't touch
;
; Delete the element but keep the backpointer string at the same offset (as
; well as the same backpointer). This is done by moving the last element of the
; string (at [BX]) over the deleted element (at [SI]), setting the entry at
; [BX] to 1 (a null string entry), and finally moving BX forward to point to
; the new last element. Note that the setting of [BX] occurs before setting
; [SI] so the case of a one-element string (BX=SI) works.
;
	DEC	SI
	DEC	SI		;[SI] = ptr back to processed element
	MOV	AX,[BX] 	;[AX] = last element value; last elem = null
	MOV	[SI],AX 	;overwrite deleted element with last one
	MOV	WORD PTR [BX],1
	DEC	BX
	DEC	BX		;backup over null string header
;
;	Test if last element to process.  If not, then loop for next.
;
FIELD_NOTIN:
	CMP	SI,BX		;test if last element to process
	JBE	FIELD_LOOP	;if not, then loop
;
;	Compute new string length for descriptor.
;
	XCHG	AX,SI		;[AX] = address of last element
	POP	SI		;[SI] = pointer to heap entry
	SUB	AX,[SI].LHPOFF	;get new length of backpointer string
	MOV	[SI].LHPLEN,AX	;put new length in descriptor
	JNZ	FIELD_NOT_EMPTY ;if new string not empty, then jump
;
;	Backpointer string empty, deallocate string header and clear offset.
;
	MOV	WORD PTR [BX],1 ;clear string header
	MOV	[SI].LHPOFF,AX	;clear the heap descriptor offset

FIELD_NOT_EMPTY:
cEnd

sEnd	NH_TEXT

	END

⌨️ 快捷键说明

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