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

📄 nhstutil.asm

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

		USESEG	_DATA
		USESEG	_BSS
		USESEG	NH_TEXT
		USESEG	COMMON	


	INCLUDE seg.inc
	INCLUDE idmac.inc
	INCLUDE nhutil.inc	


ASSERT_NOT_VARHEAP	MACRO	SEG	;
	ENDM				;

sBegin	_DATA

	PUBLIC	b$nuldes	

NULSTR		DW	DGROUP:b$nuldes  ;Backpointer to descriptor
b$nuldes	DW	0,DGROUP:NULSTR+2 ;Descriptor for zero-length string

	NUMTEMP = 20D		;number of string temps
	LENTEMP = 6		;descriptor length is six bytes

TMPL		DW	NUMTEMP*(LENTEMP/2) DUP(-1) ;temp string descriptors
TMPH		LABEL	WORD

	externW	b$NH_first	; defined in nhinit.asm
sEnd	_DATA

sBegin	_BSS

	PUBLIC	b$STRING_FIRST
b$STRING_FIRST	DW	1 DUP(?)	;String space FWA (even)
	PUBLIC	b$STRING_FREE
b$STRING_FREE	DW	1 DUP(?)	;Scan for free string space from here
	PUBLIC	b$STRING_END
b$STRING_END	DW	1 DUP(?)	;String space LWA (odd)

	EXTRN	b$HEAP_FREE:WORD ;defined in LHUTIL.ASM
	EXTRN	b$HEAP_END:WORD	;defined in LHUTIL.ASM

	EXTRN	b$STRTAB:WORD		
	EXTRN	b$STRTAB_END:WORD	

	EXTRN	b$HEAP_FIRST_SWAP:WORD	;defined in LHUTIL.ASM
	EXTRN	b$HEAP_END_SWAP:WORD	;defined in LHUTIL.ASM

TMPHDR		DW	1 DUP(?)

	externW b$curlevel		;current program level

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

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


sEnd	_BSS

PAGE
sBegin	NH_TEXT

	ASSUMES CS,NH_TEXT

	PUBLIC	B$STINIT	;initialize string space
	PUBLIC	B$STCHKTMP	;check if temp string
	PUBLIC	B$STALCTMP	;allocate temp string
	PUBLIC	B$STALCTMPCPY	;allocate temp string copy
	PUBLIC	B$STALCTMPSUB	;allocate temp substring copy
	PUBLIC	B$STALCMAXTMP	;allocate maximum length temp string
	PUBLIC	B$STALCMAXTMPNC ; allocate max len temp str w/o compacting
	PUBLIC	B$STDALCTMP	;deallocate if temp string
	PUBLIC	B$STDALCTMPDSC ;deallocate temporary string desc
	PUBLIC	B$STDALCALLTMP ;deallocate all temp strings
	PUBLIC	B$STADJ	;deallocate/adjust string

	PUBLIC	B$STALC	;allocate string data
	PUBLIC	B$STDALC	;deallocate string
	PUBLIC	B$STMOV	;move string space start

	PUBLIC	B$STCPCT	;compact string space

	PUBLIC	B$STGETFRESIZ	;get size of free string in string space
	PUBLIC	B$STSWAPDESC	;swap the given string descriptors
	PUBLIC	B$STGETSTRLEN	;get string length

	PUBLIC	B$STFromLH
	PUBLIC	B$STSetFree

	PUBLIC	B$STPUTZ

PAGE
externNP B$ERR_SSC		

	externNP B$LHFLDDESCADJ 
	EXTRN	B$LHSetFree:NEAR
	EXTRN	B$ERR_OS:NEAR	
	EXTRN	B$ERR_ST:NEAR	

externNP B$TglHeapSptNEAR	; switch context to local heap

;*** 
;B$ISTALCTMPSUB - Allocate temporary substring copy
;
;Purpose:
;	FAR entry point for Interpreter added with revison [42].
;Entry:
;	Same as B$STALCTMPSUB
;Exit:
;	Same as B$STALCTMPSUB
;Uses:
;	Same as B$STALCTMPSUB
;Preserves:
;	Same as B$STALCTMPSUB
;Exceptions:
;	Same as B$STALCTMPSUB
;******************************************************************************
cProc	B$ISTALCTMPSUB,<FAR,PUBLIC>
cBegin
	call	B$STALCTMPSUB		; do a near call to do the work
cEnd

;*** 
;B$ISTDALCTMP - Deallocate if temporary string
;
;Purpose:
;	FAR entry point for Interpreter added with revison [42].
;Entry:
;	Same as B$STDALCTMP
;Exit:
;	Same as B$STDALCTMP
;Uses:
;	Same as B$STDALCTMP
;Preserves:
;	Same as B$STDALCTMP
;Exceptions:
;	Same as B$STDALCTMP
;******************************************************************************
cProc	B$ISTDALCTMP,<FAR,PUBLIC>
cBegin
	call	B$STDALCTMP		; do a near call to do the work
cEnd


PAGE
;***
; B$STALC - allocate string
; Purpose:
;	Find and allocate an appropriate chunk of string space.
;	The requested length will be rounded up if odd because
;	allocation is by 16-bit words only.  An extra word is
;	added to the front as required by the string format for
;	the backpointer.  This backpointer is NOT set up but it
;	must be before any scan of string space is made (by
;	B$STALC, B$STCPCT, etc.).
;
;	Each successive step is tried until the allocation is done:
;
;	1. Test the free string entry.	This entry, pointed by [b$STRING_FREE],
;	   can usually allocate the desired storage unless the space is
;	   nearly filled or extremely fragamented.  It usually follows
;	   last allocated entry or is the unallocated storage after a
;	   string space compaction.
;
;	2. String space is searched for the first unallocated space large
;	   enough to satisfy the requested length.  Adjacent unallocated
;	   entries are concatenated as they are found before any
;	   allocation is attempted.  The string space segment from the
;	   free pointer [b$STRING_FREE] to the end pointer [b$STRING_END] is
;	   scanned first. The segment from the start pointer [b$STRING_FIRST]
;	   to the free pointer is then scanned if allocation did not occur.
;
;	3. If the local heap free entry is unallocated and last in the
;	   heap space, the heap-string boundary is moved to reclaim the
;	   entry into string space.  The space now becomes part of the
;	   free string which is then tested for allocation.
;
;	4. The string space is compacted, with all allocated strings
;	   adjacent in lower memory and the remaining space made into
;	   the free string.  The free string is then tested.
;
;	5. The local heap is compacted with all allocated entries adjacent
;	   in upper dgroup, and the remaining free space given to string
;	   space.  The free string is then tested.
;
;	6. The Far Heap is asked to move its bottom....in case it had
;	   previously robbed space from DS. We then grab any additional space
;	   from near heap, and try the resulting free string.
;
;	7. If QBI version, the user library data images are released, the
;	   far heap is moved up in memory, the local heap is moved up, and
;	   and any resulting free space is returned to string space.
;
;	If no allocation can be done, the program is aborted by
;	   the nontrappable  "Out of Memory" error.
;
; Inputs:
;	BX = Length of string space required (may be odd).
; Outputs:
;	BX = Address of string data.  BX-2 is the header location.
; Modifies:
;	None.
; Exceptions:
;	None.
;****
B$STALC:

DbAssertRel	[b$STRING_FREE],BE,[b$STRING_END],NH_TEXT,<B$STALC: b$STRING_FREE past b$STRING_END> 
DbAssertRel	[b$STRING_FREE],AE,[b$STRING_FIRST],NH_TEXT,<B$STALC: b$STRING_FREE prior to b$STRING_FIRST> 

	PUSH	AX		;save the registers used...
	PUSH	SI

;	Round up BX to an even value and then add one.	This value
;	would be the unallocated string header value that could just
;	accomodate the allocation.

	INC	BX		;add one and...
	JZ	OutOfSS		; brif overflow -- out of string space
	OR	BL,1		;set bit for header value

;	Step 1 - Test if free string can perform allocation.

	CALL	SS_ALC_FREE	;try to allocate from free string
	JNC	ALCSTR_FREE	;if successful, then jump to return

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

;	Step 2 - Scan [b$STRING_FREE] to [b$STRING_END],
;		 then [b$STRING_FIRST] to [b$STRING_FREE].

	CALL	SS_SCAN 	;scan around the free pointer
	JNC	ALCSTR_DONE	;jump if allocation successful

;	Step 3 - Combine adjoining heap entries, test free string.

	CALL	B$STFromLH	;combine trailing entries into free string
	CALL	SS_ALC_FREE	;test if free string can handle allocation
	JNC	ALCSTR_DONE	;jump if allocation successful

;	Step 4 - Perform string space compaction, test free string.

	CALL	B$STCPCT	;perform the compaction
	CALL	SS_ALC_FREE	;test free string for room
	JNC	ALCSTR_DONE	;jump if allocation successful

;	No allocation possible, jump to error routine.

OutOfSS:			
	JMP	B$ERR_OS	; give "Out of string space" error

;	Allocation successful - clean stack and return.

ALCSTR_DONE:
	POP	DI		;restore registers used...
	POP	DX
	POP	CX

ALCSTR_FREE:
	POP	SI
	POP	AX

DbAssertRel	BX,BE,[b$STRING_END],NH_TEXT,<B$STALC: String alloc past b$STRING_END> 
DbAssertRel	BX,AE,[b$STRING_FIRST],NH_TEXT,<B$STALC: String alloc prior to b$STRING_FIRST> 

	RET			;return with BX pointing to new data
PAGE
;***
; SS_ALC_FREE - test if free string can allocate the request length
;
; Inputs:
;	BX - length of string data to allocate.
;	[b$STRING_FREE] - pointer to string to test
;
; Outputs:
;	CF=0 - allocation was successful.
;	     BX - pointer to data in new string.
;	     [b$STRING_FREE] - updated to new free string.
;	CF=1 - allocation failed.
;****

SS_ALC_FREE:
	MOV	SI,[b$STRING_FREE] ;point to the free string
	MOV	AX,[SI] 	;get free string header
	TEST	AL,1		;test if free string allocated
	JZ	SS_ALC_NO_ALLOC ;if so, cannot allocate from it
	CMP	AX,0FFFFH	;test if free string at string space end
	JZ	SS_ALC_NO_ALLOC ;if so, cannot allocate from it
	CMP	BX,AX		;test requested header against free header
	JA	SS_ALC_NO_ALLOC ;if requested too large, cannot allocate

;	SS_ALC - allocate string from string space entry pointed by SI.
;		 BX - header of requested string allocation
;		 AX - header of current entry pointed by SI
;		 ZF - set if BX=AX else cleared

SS_ALC:
	JE	SS_ALC_EXACT	;jump if exact allocation to be done

;	Split the current string into the requested allocation in lower
;	addressed portion and the new free string in the higher portion.

	MOV	[SI],BX 	;move in new allocated string header
	INC	BX		;length of allocated string entry (hdr+data)
	SUB	AX,BX		;subtract to get new free header value
	XCHG	BX,SI		;BX=alloc string entry ptr - SI=alloc length
	ADD	SI,BX		;pointer to new free string entry
	MOV	[SI],AX 	;move in new free string header value
	MOV	[b$STRING_FREE],SI ;update free string pointer
	ADD	BX,2		;pointer to allocated string data (carry clear)
	RET			;return to caller in B$STALC

;	Exact allocation just updates the free string pointer [b$STRING_FREE]
;	and points to the data location of the current string entry.

SS_ALC_EXACT:
	STC			;set carry for add to follow
	ADC	[b$STRING_FREE],AX ;add current entry length (hdr+data)
	MOV	BX,SI		;get current entry pointer
	ADD	BX,2		;and point to the data part (carry clear)
	RET			;return to caller in B$STALC

;	If failure, then set carry for return

SS_ALC_NO_ALLOC:
	STC			;carry set for failure
	RET			;return to caller in B$STALC
PAGE
;***
; SS_SCAN - scan string space for allocation
; Purpose:
;	Scan string space for a first-fit allocation of the specified
;	amount of space.  The scan starts from the free string to
;	string space end.  If unsuccessful, the scan continues from
;	string space start to the free string.
;
; Inputs:
;	BX = amount of space to allocate
; Outputs:
;	CF=0 - allocation successful
;	       BX = pointer to string data
;	       [b$STRING_FREE] = points to entry past one allocated
;	CF=1 - allocation failed
;	       [b$STRING_FREE] = points past last allocated entry
;****

SS_SCAN:

;	Scan from free string to end of string space.

	MOV	SI,[b$STRING_FREE] ;start of search
	MOV	DX,[b$STRING_END]	;end of search
	CALL	SS_SCAN_START	;start the scan...
	JNC	SS_SCAN_RETURN	;jump if allocation successful

;	Scan from start of string space to free string.
;	DX contains the pointer past the last allocated entry

	MOV	SI,[b$STRING_FIRST] ;start of search
	XCHG	DX,[b$STRING_FREE] ;swap last entry and end of search
	CALL	SS_SCAN_START	;start the scan...
	JNC	SS_SCAN_RETURN	;jump if allocation successful

;	Determine the last allocated entry in string space and
;	set the free string pointer just past it.  This will be needed
;	for the next allocation step of combining the free heap entry.

	CMP	DX,[b$STRING_FREE] ;test if the pointer should be changed
	JA	SS_SCAN_FREE	;if not, then jump
	MOV	[b$STRING_FREE],DX ;update the pointer
SS_SCAN_FREE:
	STC			;note allocation failure
SS_SCAN_RETURN:
	RET			;and return to B$STALC
PAGE
;***
; SS_SCAN_START - scan string for allocation of length requested.
;
; Inputs:
;	BX - length of string data to allocate.
;	SI - pointer to start of search.
;	DX - pointer to end of search.
; Outputs:
;	CF=0 - search was successful.
;	       BX - pointer to data in new string.
;	       [b$STRING_FREE] - updated to new free string.
;	CF=1 - search failed.
;	       DX - pointer past last allocated entry
;		    (either string space end or the last entry
;		     when it is unallocated)
;****

;	Test if string at scan pointer (SI) is allocated.
;	If so, get length of string header and data in AX.
;	Jump if string space end encountered (0FFFFH entry).

SS_SCAN_START:
	MOV	AX,[SI] 	;get scan ptr string header
	TEST	AL,1		;test if string is allocated
	JZ	SS_SCAN_SKIP	;if allocated, then jump
	INC	AX		;get length of string header and data
	JZ	SS_SCAN_FAILED	;jump if string space end was read

;	Compute pointer to next entry in DI.

	MOV	DI,SI		;get copy of current entry pointer
	ADD	DI,AX		;add entry length (header and data) for next
	DEC	AX		;return header value (data+1)

;	Test next block (pointed by DI) for possible combination with

⌨️ 快捷键说明

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