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

📄 nhstutil.asm

📁 Microsoft MS-DOS6.0 完整源代码
💻 ASM
📖 第 1 页 / 共 4 页
字号:
	PUSH	BX
	MOV	BX,[BX+2]	;Get pointer to data
	ADD	BX,DX
	MOV	BYTE PTR [BX],0
	POP	BX
	POP	DX
	RET
PAGE
;***
; B$STSetFree - set free string entry pointer
; Purpose:
;	Determines if the current free string is both the last string
;	entry and unallocated.	If so, its current value is returned
;	in SI.	Otherwise, the free string pointer b$STRING_FREE is set to
;	the string space end and its value returned in SI.
;
; Inputs:
;	None.
; Outputs:
;	SI = pointer to free string (b$STRING_FREE).
; Modifies:
;	AX.
; Exceptions:
;	None.
;****

B$STSetFree:
	MOV	SI,[b$STRING_FREE] ;get pointer to current free string
	MOV	AX,[SI] 	;get header of free string
	TEST	AL,1		;test if free string allocated
	JZ	SS_SET_END	;if so, then jump
	INC	AX		;get length of free entry
	JZ	SS_SET_RETURN	;jump if free entry was at end of string space
	ADD	AX,SI		;get pointer to entry after free string
	CMP	AX,[b$STRING_END] ;test if free was last string in space
	JE	SS_SET_RETURN	;if so, jump to leave pointer unchanged
SS_SET_END:
	MOV	SI,[b$STRING_END] ;get end pointer of string space
	MOV	[b$STRING_FREE],SI ;and set the free string to it
SS_SET_RETURN:
	RET			;return with SI set to new free string
PAGE
;***
; B$STFromLH - get string space from local heap space
; Purpose:
;	Determine if a free entry exists at the end of the
;	local heap.  If so, change the string and heap space
;	pointers so that it is now part of string space.
;
; Inputs:
;	None.
; Outputs:
;	[b$STRING_FREE] = pointer to new free string containing any space
;		   retrieved from the local heap.
; Modifies:
;	None.
; Exceptions:
;	None.
;****

B$STFromLH:
	PUSH	AX		;save registers...
	PUSH	SI
	PUSH	DI

	CALL	B$LHSetFree	;DI points to trailing heap free entry
	CMP	DI,[b$HEAP_END]	;test if any free space at all
	JE	SS_LH_RETURN	;if not, nothing to reclaim

;	The new END heap entry is now at [DI].	Setup the entry and
;	set the heap end pointer [b$HEAP_END].  If the heap free pointer
;	[b$HEAP_FREE] pointed within the reclaimed area, set it to
;	[b$HEAP_END] to give it a valid value.

	MOV	[DI].LHTYPE,LOW LH_END ;define the new END heap entry
	MOV	[b$HEAP_END],DI	;define heap end pointer
	CMP	DI,[b$HEAP_FREE] ;test if free pointer in reclaimed area
	JB	SS_LH_FREE	;if not, then do not set it
	MOV	[b$HEAP_FREE],DI ;otherwise, set it to the heap end
SS_LH_FREE:

;	The new end of string space is the word before the heap END
;	entry.

	SUB	DI,LH_STD_HDR_LEN+1 ;point to new string space end
	MOV	[DI],0FFFFH	;set string space end entry
	CALL	B$STSetFree	;get free string pointer in SI
	MOV	[b$STRING_END],DI ;define new end of string space

;	Form new free string entry from [SI] up to [DI].

	SUB	DI,SI		;get length of new entry
	DEC	DI		;make header for entry
	MOV	[SI],DI 	;put header into entry

SS_LH_RETURN:
	POP	DI		;restore registers...
	POP	SI
	POP	AX
	RET			;return with new free string
PAGE
;***
; B$STGETFRESIZ - get size of free string
; Purpose:
;	Return the current size of the free string in string space.
;
; Inputs:
;	None.
; Outputs:
;	BX = size of free string in bytes.
; Modifies:
;	None.
; Exceptions:
;	None.
;****

B$STGETFRESIZ:
	MOV	BX,[b$STRING_FREE] ;get location of free entry in string space
	MOV	BX,[BX] 	;get free string header
	TEST	BL,1		;test if string entry is allocated
	JZ	GETFRESIZ_ZERO	;if so, then return zero as size
	CMP	BX,0FFFFH	;test if at end of string space
	JNE	GETFRESIZ_NZERO ;if not, header is one more than size
GETFRESIZ_ZERO:
	MOV	BX,1		;size will be zero after decrementing
GETFRESIZ_NZERO:
	DEC	BX		;get the free string size
	RET			;return to caller
PAGE
;***
; B$STSWAPDESC - swap string descriptor contents
; Purpose:
;	Swap the contents of the two string descriptors and adjust the
;	string backpointers, if necessary.
;
; Inputs:
;	SI = pointer to first string descriptor
;	DI = pointer to second string descriptor
; Outputs:
;	None.
; Modifies:
;	None.
; Exceptions:
;	None.
;****

B$STSWAPDESC:
	PUSH	BX		;save register

	MOV	BX,[SI] 	;get length in first descriptor
	XCHG	BX,[DI] 	;exchange with length in second
	MOV	[SI],BX 	;put exchanged length back in first

	MOV	BX,[SI+2]	;get offset in first descriptor
	XCHG	BX,[DI+2]	;exchange with offset in second
	MOV	[SI+2],BX	;put exchanged offset back in first

	MOV	BX,[SI+2]	;get offset to first descriptor
	CMP	BX,[b$STRING_FIRST] ;test if before string space
	JB	SWAP_NO_FIX	;if so, then do not adjust
	CMP	BX,[b$STRING_END] ;test if after string space
	JAE	SWAP_NO_FIX	;if so, then do not adjust
	MOV	[BX-2],SI	;adjust the first backpointer
SWAP_NO_FIX:
	MOV	BX,[DI+2]	;get offset to second descriptor
	CMP	BX,[b$STRING_FIRST] ;test if before string space
	JB	SWAP_RETURN	;if so, then do not adjust
	CMP	BX,[b$STRING_END] ;test if after string space
	JAE	SWAP_RETURN	;if so, then do not adjust
	MOV	[BX-2],DI	;adjust the first backpointer
SWAP_RETURN:
	POP	BX		;restore register
	RET			;return to caller in SWAP.ASM
PAGE
;***
; B$STINIT - Initialize string space
; Purpose:
;	Initialize the necessary pointers and structures for string space.
; Inputs:
;	SI = last word of string space
;	AX = first word of string space
; Outputs:
;	None.
; Modifies:
;	SI, DI
; Exceptions:
;	None.
;****

B$STINIT:
	MOV	[b$STRING_END],SI	;string space ends here
	MOV	[SI],0FFFFH		;mark end of string space
	MOV	[b$STRING_FIRST],AX	;dynamic space start is string start
	MOV	DI,AX			;get offset of string space start
	MOV	[b$STRING_FREE],DI	;and set it as the free string
	SUB	SI,DI			;get the total size of string space
	DEC	SI			;allow for header size less one
	MOV	[DI],SI 		;and set the string header
$$XSTS:
	MOV	b$curlevel,0		;main program level is zero
	MOV	CX,NUMTEMP		;Number of string temporaries
	MOV	DI,OFFSET DGROUP:TMPL	;First temp
	MOV	[TMPHDR],DI
	MOV	BX,-1			;Flag for each temp indicates free
	MOV	AX,OFFSET DGROUP:TMPL+LENTEMP ;second temp
	PUSH	ES			
	PUSH	DS			
	POP	ES			;Set ES = DS
LINKTMP:
	STOSW				;Link to next temp
	XCHG	AX,BX
	STOSW				;Store free flag
	STOSW				;in level field of descriptor too
	XCHG	AX,BX
	ADD	AX,LENTEMP		;bytes per temp
	LOOP	LINKTMP
	POP	ES			

	MOV	WORD PTR [DI-LENTEMP],0 ;Last temp must point to nul
	RET
PAGE
	SUBTTL	B$SSClean - Clean String Space
	PAGE
;***
;B$SSClean - Clean String Space
;
;Purpose:
; Scan string space and delete all strings not in the function key table or the
; local heap, or if chaining not in blank common.
;
;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.
;
;****
assumes	ES,DGROUP		
assumes	DS,NOTHING		
cProc	B$SSClean,<NEAR,PUBLIC>
cBegin
	XOR	AX,AX
	CMP	ES:b$Chaining,AL ; If we are not chaining, clear 0-ffff
	JZ	SSCleanAll
;
; clear out all items from 0 to b$commonfirst
;
	MOV	BX,ES:[b$commonfirst]
	CMP	BX,AX		; nothing to clear?
	JE	ClearNext	
	DEC	BX		;Range is inclusive
	CALL	B$SSClearRange

ClearNext:			
;
; Clear out all items from b$commonlast (or start of COMMON if chaining and
; not EI_QB) to 0FFFFH.
;
	MOV	AX,ES:[b$commonlast]



SSCleanAll:
	MOV	BX,0FFFFH
cEnd	nogen			;Fall into B$SSClearRange

	SUBTTL	B$SSClearRange - Clear SS of entries in a range
	PAGE
;***
;B$SSClearRange - Clear SS of entries in a range
;
;Purpose:
; Scan the string space and deallocate all strings whose descriptors are in
; range, and not in the local heap area. (When this routine is used, the local
; heap must be cleaned before, such that the only strings left are fielded
; string backpointer strings or string dynamic array elements.
;
;Entry:
;	AX	= Start address of range in which to delete
;	BX	= End address of range in which to delete (range is inclusive)
;	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:
; None.
;
;Modifies:
; Per Convention
;
;****
cProc	B$SSClearRange,<NEAR,PUBLIC>,SI
cBegin
	MOV	SI,ES:[b$STRING_FIRST] ;initialize scanning pointer
	MOV	CX,BX		;[CX] = end address
;
; Test if string entry is allocated.  If not, then compute the next entry and
; try again. If string space end, then jump to exit.
;
SS_CLEAN_LOOP:
	MOV	BX,[SI] 	;[BX] = string entry header
	TEST	BL,1		;test if entry is allocated
	JZ	SS_CLEAN_ALLOC	;if not, then jump to test if kept
	INC	BX		;[BX] = total length of entry
	JZ	SS_CLEAN_DONE	;if string space end, then jump to finish
	ADD	SI,BX		;[SI] = pointer to next entry in string space
	JMP	SHORT SS_CLEAN_LOOP ;jump to process next entry
;
; String entry is allocated.  Keep string if in blank COMMON.
;
SS_CLEAN_ALLOC:
	CMP	BX,AX		;test if before range
	JB	SS_CLEAN_SKIP	;if so, skip deletion
	CMP	BX,CX		;test if after range
	JA	SS_CLEAN_SKIP	;if so, skip deletion
;
; Keep string if in softkey string table.
;
	CMP	BX,OFFSET DGROUP:B$STRTAB	;test if before softkey table
	JB	SS_CLEAN_VAR_HEAP_TEST		;if so, then jump to next test
	CMP	BX,OFFSET DGROUP:B$STRTAB_END	;test if in the softkey table
	JB	SS_CLEAN_SKIP			;if so, then keep the string

SS_CLEAN_VAR_HEAP_TEST:
	CMP	BX,ES:[b$HEAP_END_SWAP]	;test if before VarHeap
	JB	SS_CLEAN_HEAP_TEST	;if so, then jump to next test
	CMP	BX,ES:[b$HEAP_FIRST_SWAP];test if in VarHeap
	JB	SS_CLEAN_SKIP		;if so, then keep the string

;
; Keep string if descriptor is in the local heap.  Since the local heap was
; cleaned first, the string is either fielded to a file block heap entry or an
; element of a dynamic array.
;
SS_CLEAN_HEAP_TEST:
	CMP	BX,ES:[b$HEAP_END]	;test if in the local heap
	JAE	SS_CLEAN_SKIP		;if so, then keep the string
;
; String is to be deallocated. Compute next entry offset and jump.
;
	MOV	BX,[BX] 	;get length of string data
	INC	BX		;roundup to next word...
	OR	BL,1		;and add one to get unallocated header value
	MOV	[SI],BX 	;put header into string entry
	STC			;set carry
	ADC	SI,BX		;add string header plus one for next entry
	JMP	SHORT SS_CLEAN_LOOP ;branch to process next string entry
;
;	String is to be kept - just compute next offset.
;
SS_CLEAN_SKIP:
	ADD	SI,[BX] 	;add length of string data
	ADD	SI,3		;add two for header and one for roundup...
	AND	SI,NOT 1	;finish roundup to next word
	JMP	SHORT SS_CLEAN_LOOP ;branch to process next string entry

;	Done - restore registers and return.

SS_CLEAN_DONE:
cEnd
assumes	DS,DGROUP		
assumes	ES,NOTHING		

	PAGE
;***
;B$ISdUpd - Adjust string entry backptr when sd moves
;
;Purpose:
;	Added with revision [16].
; QB calls this routine to adjust a string entry backptr when the variable
; table owning the string moves. The variable table is allocated in the local
; heap. Assumes that the variable heap is active.
;
;Entry:
;	pSd	- pointer to string descriptor that is moving
;	Delta	- distance that descriptor is moving
;Exit:
;	string entry backpointer is adjusted
;Uses:
;	AX, BX
;Exceptions:
;	None.
;****

labelFP <PUBLIC,B_ISdUpd>		;Intepreter reachable Label
cProc	B$ISdUpd,<PUBLIC,FAR>,ES	
parmW	pSd
parmW	Delta
cBegin

	CALL	B$TglHeapSptNEAR	; switch context to local heap
	ASSERT_NOT_VARHEAP NH_TEXT	

	MOV	AX,Delta	
DbAssertRel	AX,NE,0,NH_TEXT,<Invalid Delta passed to B$ISdUpd>

	MOV	BX,pSd		;get ptr to string descriptor

	PUSH	DS		; set ES=DS
	POP	ES		
	cCall	B$STADJ	; Adjust backpointer

	CALL	B$TglHeapSptNEAR	; switch context to var heap

cEnd
PAGE


sEnd	NH_TEXT


	END

⌨️ 快捷键说明

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