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

📄 nhlhutil.asm

📁 Microsoft MS-DOS6.0 完整源代码
💻 ASM
📖 第 1 页 / 共 4 页
字号:
	TITLE	NHLHUTIL - Local Heap utilities
;***
; NHLHUTIL - Local Heap utilities
;
;	Copyright <C> 1986, Microsoft Corporation
;
;Purpose:
;
;******************************************************************************
	INCLUDE switch.inc
	INCLUDE baslibma.inc
	INCLUDE files.inc
	INCLUDE rmacros.inc

		USESEG	_DATA
		USESEG	_BSS
		USESEG	NH_TEXT


	INCLUDE seg.inc
	INCLUDE nhutil.inc	;for heap definitions
	INCLUDE idmac.inc
	INCLUDE array.inc	;for array definitions

sBegin	_BSS


	externW b$STRING_FIRST		;defined in NHSTUTIL.ASM
	externW b$NH_first		;defined in NHINIT.ASM
	externW b$NH_last		;defined in NHINIT.ASM

	externW b$HEAP_FIRST		; heap start pointer
	externW b$HEAP_FREE		
	externW b$HEAP_END		
	externW b$P_HEAP_GROW		

CW_SWAP_VARS	EQU	4		; must swap 4 words to chg context
	externW b$HEAP_FIRST_SWAP	
	externW b$HEAP_END_SWAP 	

	externW b$fVarHeapActive	; non-0 when variable heap
					; is active

	externB b$Chaining	; in chain flag
	externW b$commonfirst	
	externW b$commonlast	

sEnd	_BSS

sBegin	_DATA

	externW b$pFHRaiseBottom	;vector for B$FHRaiseBottom

sEnd	_DATA



sBegin	NH_TEXT

	ASSUMES CS,NH_TEXT

	PUBLIC	B$NHCPCT	;compact all dynamic space
	PUBLIC	B$NHMOV	;mov dynamic space boundaries


	PUBLIC	B$LHFDBLOC	; find file entry for file number given
	PUBLIC	B$LHLOCFDB	; find file number for file entry given

	PUBLIC	B$ILHALC	;allocate heap entry - error code return

	PUBLIC	B$LHFLDDESCADD	; add descriptor to heap backpointer string

	PUBLIC	B$LHChgBakPtr	;called to change the location of an LH owner
	PUBLIC	B$LHREALC	;reallocate heap entry
	PUBLIC	B$ILHADJ	;update backpointer in a given LH entry
	PUBLIC	B$LHForEachEntry ;call given function for each LH entry
	PUBLIC	B$LH_SPLIT

	externNP B$LHADJ	; adjust heap entry
	externNP B$LHDALC	; deallocate heap entry
	externNP B$LHSetFree	; set free heap entry pointer
	externNP B$LH_ALC_FREE	; try to allocate the free heap entry
	externNP B$LH_CPCT	
	externNP B$LH_FROM_SS	

	externNP B$LH_PTR_CHECK ; check entry at [SI] for consistency
	externNP B$LH_PTR_FROM_DATA 
	externNP B$LH_SCAN	

	externNP B$STDALC
	externNP B$STALCTMPSUB
	externNP B$STCPCT
	externNP B$STFromLH
	externNP B$STMOV
	externNP B$STDALCTMPDSC
	externNP B$ERR_OM_NH		 

	externNP B$SSClean	

	externNP B$IHeapEntryMoved


SET_ES_TO_DS	MACRO
	PUSH	DS
	POP	ES
	ENDM

ASSERT_NOT_VARHEAP	MACRO	SEG	;
	ENDM				;


;Given a user requested size, convert to total resulting size of entry
GET_ENTRY_SIZE	MACRO	CBGIVEN,LHTYPE
	LOCAL	CONTINUE
	.xlist
	ADD	CBGIVEN,LH_STD_HDR_LEN+2+1 ;add for hdr, backlength, & roundup
	AND	CBGIVEN,0FFFEh	;finish roundup
	CMP	LHTYPE,LOW LH_FILE
	JNZ	CONTINUE	;brif not an fdb entry
	ADD	CBGIVEN,(LH_FDB_HDR_LEN - LH_STD_HDR_LEN)
				;fdb header is bigger than standard header
CONTINUE:
	.list
	ENDM


;***
; B$LHALC_CPCT - Compact local heap and allocate heap entry.  Added with [44]
;
; Purpose:
;	Combined with B$LHALC as part of [44]
;	Same as B$ILHALC, below, but jumps to B$ERR_OM on out of memory error.
;	Also, compacts heap before allocation.
;
; Inputs:
;	BX = Length of local heap space required.
;	DL = type of heap entry to allocate.
;	CL = if DL=LH_FILE, file number
;	CX = if DL anything else, ptr to owner (where backptr should point to)
; Outputs:
;	SI = Address of start of data of the allocated entry.
; Modifies:
;	None.
; Preserves:
;	ES
; Exceptions:
;	Will jump to B$ERR_OM if insufficient memory for allocation.
;****

cProc	B$LHALC_CPCT,<NEAR,PUBLIC>
cBegin
	CALL	B$LH_CPCT		; compact heap before allocation
	CALL	B$ILHALC		; allocate the entry
	JC	BLHALC_OM_ERR		; psw.c set on error
cEnd

BLHALC_OM_ERR:
	JMP	B$ERR_OM_NH		; out of memory error

;***
; B$ILHALC - allocate local heap entry
; Purpose:
;	Find and allocate an appropriate entry of the local heap.
;	Ten bytes will be added to the requested length with 2 bytes
;	for the backlength and 8 bytes for the heap header.  The
;	This value is rounded up to the next 8-byte value since all
;	allocations are multiples of this value.
;
;	Each successive step is performed until the allocation is done:
;
;	1. Test the free heap entry pointed by [b$HEAP_FREE] for
;	   being unallocated and having the adequate room.
;
;	2. The local heap space is searched from start to end for the
;	   first unallocated entry large enough to satisfy the allocation.
;	   Adjacent unallocated entries are concatenated as they are
;	   found before the allocation is attempted.  If no allocation
;	   can be done, the free heap entry is moved to just past the
;	   last allocated entry in the heap.
;
;	3. If the free string entry is unallocated and the last in string
;	   space, the string-heap boundary is moved so that its space
;	   is added to the free heap entry.  The free entry is tested.
;
;	4. A compaction of string space is performed, leaving a free
;	   unallocated string in high memory.  This storage is placed
;	   in the local heap as in step 3.  The free entry is then tested.
;
;	5. If this is an interpreter-version of the runtime, compact the
;	   Local Heap, and try the free heap entry again.
;
;	If no allocation cannot be done, the program is aborted by
;	   an "Out of Memory" error.
;
;	If the allocation is successful and string space was converted
;	   to heap space, the remaining free heap space is given back
;	   to the string space.
;
;	NOTE: it is assumed that the input owner-to-be is NOT in
;	the local heap (and thus, that heap movement will not cause the
;	owner to move).
;
; Inputs:
;	BX = Length of local heap space required.
;	DL = type of heap entry to allocate.
;	CL = if DL=LH_FILE, file number
;	CX = if DL anything else, ptr to owner (where backptr should point to)
;
; Outputs:
;	if PSW.C is clear
;		SI = Address of start of data of the allocated entry.
;	else (PSW.C set) out of memory error return.
; Modifies:
;	SI
; Preserves:
;	ES
; Exceptions:
;	None.
;****

B$ILHALC	PROC	NEAR
	PUSH	AX		;save the registers used...
	PUSH	BX
	PUSH	ES		


	SET_ES_TO_DS		;set ES = DS if interpreter version

	GET_ENTRY_SIZE	BX,DL	;convert input size to total entry size needed

;	Step 1 - Test if free heap entry can perform allocation.

	CALL	B$LH_ALC_FREE	; try to allocate the free heap entry
	JNC	ALCLHP_FIRST	;if successful, then jump to return

	PUSH	CX		;push more registers...
	PUSH	DX
	PUSH	DI

;	Step 2 - Scan local heap from beginning to end.

	CALL	B$LH_SCAN	;scan the local heap
	JNC	ALCLHP_DONE	;jump if allocation successful

	CALL	[b$P_HEAP_GROW] ; call appropriate routine to complete
				;   allocation (carry clear on return if 
				;   successful)
ALCLHP_DONE:
	POP	DI		;restore registers used...
	POP	DX
	POP	CX

ALCLHP_FIRST:
	POP	ES		
	POP	BX
	POP	AX
	RET			;return with SI pointing to heap data area
B$ILHALC	ENDP

;***
; B$VAR_ALC_GROW - Grow var heap to support allocation of a block of given size
; Purpose:
;	Added with revision [23].
;	Called when B$ILHALC called to [re]alloc a var heap entry and has
;	insufficient space in the var heap.
;	Grows the var heap by (just) the required amount, recurses to B$ILHALC
;	to actually do the allocation.
; Inputs:
;	ES = DS
;	BX = total size of local heap space to be allocated
;	DL = type of heap entry to allocate.
;	CL = if DL=LH_FILE, file number
;	CX = if DL anything else, ptr to owner (where backptr should point to)
; Outputs:
;	Carry Clear if allocation accomplished successfully
; Modifies:
;	SI
; Exceptions:
;
;****
cProc	B$VAR_ALC_GROW,<NEAR,PUBLIC> 
	LocalW	junk
cBegin
;	Step 3 - Compress the variable heap and try to alloc again
	CALL	B$LH_CPCT	;combine all free entries into one
	CALL	B$LH_SCAN	;scan the local heap
	JNC	VAR_ALC_EXIT	;jump if allocation successful

;	Step 4 - Allocate a local heap entry of required size. If this fails,
;		 quit. If it succeeds, free that entry, move string space up
;		 (putting the required freespace in variable heap), and
;		 recurse to B$ILHALC to do the allocation.
	PUSH	BX			; save original request size
	PUSH	DX
	PUSH	CX
	ADD	BX,LH_STD_HDR_LEN+2	; grab enough space from LH for
					; required entry PLUS overhead
	DbAssertRelB  dl,nz,<LOW LH_FILE>,NH_TEXT,<VAR_ALC_GROW: FDB entry>
	; the above assertion is due to the fact that we're just adding
	; in overhead for a standard heap entry, not an FDB

	PUSH	BX
	CALL	B$TglHeapSptNEAR	; switch context to local heap
	LEA	CX,[junk]		;for back ptr
	CALL	B$ILHALC		;If this succeeds, we now have
					;  sufficient space in DGROUP for alloc
	JC	VAR_ALC_FAIL		; brif insufficient space in system

	CALL	B$LHDALC		;deallocate that space now
	POP	SI			
	PUSH	SI			
	ADD	SI,[b$STRING_FIRST]	; we want to move SS up to here
	CALL	B$STMOV
	JNC	BSTMOV_SUCCESS  	; brif success

	CALL	B$LH_CPCT		; compact local heap
	CALL	B$STMOV		; try again

BSTMOV_SUCCESS:				
	CALL	B$TglHeapSptNEAR	; switch context back to var heap
	POP	BX
	POP	CX
	POP	DX
	;Move top of Var Heap up to string space
	ADD	[b$HEAP_FIRST],BX	
	MOV	SI,[b$HEAP_FIRST]	
	;Mark this as a free entry
	MOV	[SI].LHTYPE,LOW LH_FREE
	MOV	[SI].LHLEN,BX
	MOV	[b$HEAP_FREE],SI
	SUB	SI,BX			
	MOV	[SI+1],BX		; backlength of free entry
	POP	BX			; restore original size request
	CALL	B$ILHALC		;MUST succeed
	JNC	VAR_ALC_EXIT

	DbHalt NH_TEXT,<VAR_ALC_GROW: B$ILHALC call failed!>
VAR_ALC_FAIL:
	CALL	B$TglHeapSptNEAR	; switch context back to var heap
	POP	BX			; restore stack for exit
	POP	CX			
	POP	DX			
	POP	BX			
	STC				; signal failure
VAR_ALC_EXIT:
cEnd

;***
; B$VarHeap_CPCT - Compact the Variable heap down, put free space in SS.
; Purpose:
;	Added with revision [23].
;	Compact the variable heap down, give all resulting free space to
;	string space.
; Inputs:
;	None
; Outputs:
;	None
; Modifies:
; Exceptions:
;	None
;****
cProc	B$VarHeap_CPCT,<PUBLIC,NEAR>,<SI>
cBegin
	ASSERT_NOT_VARHEAP NH_TEXT	
	CALL	B$TglHeapSptNEAR	; switch context to variable heap
	CALL	LH_MOV_DOWN		;crunches heap down, leaving hole
					;  above; returns new b$HEAP_FIRST in SI
	INC	SI			;SI points to where SS is to start at
	CALL	B$STMOV		;mov SS down
	CALL	B$TglHeapSptNEAR	; switch context back to local heap
cEnd






;***
; B$LHREALC - reallocate a Local Heap entry
; Purpose:
;	Given a pointer to the start of data in an existing local heap
;	entry (which is guaranteed to have a back pointer in the header)
;	and a byte count, reallocate the entry to be of the given byte
;	count size.
;	Note that, if the reallocation results in a reduction or no
;	change in the size, this routine is guaranteed not to cause
;	heap movement.
;	Note also that this routine will succeed if sufficient space
;	exists for the reallocation; it does NOT require the heap to
;	have the full input size free, as it just grabs the additionally
;	required space and combines it with the given entry.
;
;	NOTE: it is assumed that the owner of the given entry is NOT in
;	the local heap if the entry is growing (and thus, that heap movement
;	will not cause the owner to move).
;
; Inputs:
;	AX = number of bytes to realloc to.
;	SI = pointer to start of data in an LH entry; note that the
;		entry is assumed to have a back pointer.
; Outputs:
;	AX = FALSE if insufficient memory for reallocation,
;	     TRUE (non-zero) if operation successful.
;	SI = pointer to the start of data for the reallocated entry if
;		AX = TRUE (note, however, that SI is trashed if AX = FALSE).
;		This may or may not be different from the entry. Note that,
;		although we do have a backpointer, this routine does not
;		update the pointer - - - the return value of SI is provided
;		for the caller to do that.
; Modifies:
;	AX & SI are outputs, plus BX,CX,DX are be modified, and ES = DS,
;		regardless of input value.
; Exceptions:
;
;****
B$LHREALC	PROC	NEAR
	SET_ES_TO_DS		;set ES = DS if interpreter version
	PUSH	DI
	MOV	DI,AX		;DI = copy of input size request
	CALL	B$LH_PTR_FROM_DATA ;get entry pointer from SI data pointer

 	; The below assertion is based on assumptions below on the size
 	; of the entry header - - - which is just to save bytes
 	DbAssertRelB [SI].LHTYPE,NZ,LH_FILE,NH_TEXT,<can't realloc fdb's>
 	ADD	AX,LH_STD_HDR_LEN+2+1 ; add for hdr, backlength, & roundup
 	AND	AX,0FFFEh	; finish roundup

	MOV	CX,AX		;save size of desired entry in CX
	MOV	BX,[SI].LHLEN	;get length of existing entry
	SUB	AX,BX		;subtract existing size from desired size
	JA	BLHREALC_Grow	;brif we must grow the existing entry

	NEG	AX		;make difference a positive number
	CALL	B$LH_SPLIT	;split this entry; free entry out of spare space
	MOV	SI,DI		;SI = pointer to realloc'd entry
	SUB	SI,[SI].LHLEN	;move SI back to previous entry, and then
	ADD	SI,3		;  make it data pointer to realloc'd entry
	JMP	REALC_TRUE_Exit ;done - return TRUE to signal success

BLHREALC_Grow:
;	Algorithm:
;		get and save backpointer
;	    STEP1:
;		call B$ILHALC with the input byte count
;		if this succeeds, block copy the contents of the original
;			entry and free it; ensure the back pointer in the
;			new entry is correct - exit and return TRUE
;	    STEP2:
;		call B$ILHALC for the additional space required
;		if this fails, return FALSE
;		free the newly obtained entry, but keep a pointer to it.
;		if this entry is above entry to realloc in memory, collapse
;			the Local Heap, split resulting free entry so that
;			higher of two is required size, set free ptr to that
;		else set free ptr to newly free'd entry.
;		call LH_MOV_DN_RG to move all from free ptr and entry to
;			realloc down
;		change header and trailer to combine free entry with given
;			entry

⌨️ 快捷键说明

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