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

📄 bdmgr.asm

📁 [随书类]Dos6.0源代码
💻 ASM
📖 第 1 页 / 共 4 页
字号:
cProc	BdAlloc,<PUBLIC,FAR,NODATA>,<SI>
	parmW	pbdOwner
	parmW	cbSize
	parmB	interpType
cBegin
	DbShiftLH			;ife RELEASE cause some heap movement
	DbChk	Heaps
	mov	dl,[interpType]
	mov	cx,[cbSize]
	mov	bx,[pbdOwner]
	DbChk	BdNotOwner,bx		;ensure that given bd isn't an owner now
	mov	[bx.BD_pb],NULL		;in case allocation fails and caller
					;  blindly calls BdFree with this bd
	DbOMCnt	BD_END
	xchg	bx,cx			;input order required by B$ILHALC
	inc	cx			;'owner' to heap manager is the actual
	inc	cx			;  pointer to the heap entry, not a pbd
	call	B$ILHALC		;call heap manager to allocate memory
	jc	BD_Crunch_BDs		;brif OM return; trim bd's, try again

BdAlloc_Success:
	mov	bx,[pbdOwner]		;assumes bdOwner not moved by allocation
	mov	[bx.BD_pb],si		;SI is data ptr returned from B$ILHALC
	mov	ax,[cbSize]		;save requested size as both logical
	mov	[bx.BD_cbLogical],ax	;  and physical size, and return it as
	mov	[bx.BD_cbPhysical],ax	;  our non-zero (i.e., 'TRUE') result
	mov	al,TRUE			;in case input size was zero
BD_END:
	cmp	[b$fVarHeapActive],FALSE
	jz	BdAlloc_Exit		;brif variable heap not active

	call	B$TglHeapSpt		;reactivate the local heap
BdAlloc_Exit:
cEnd

BD_Crunch_BDs:
	push	dx
	push	cx
	call	far ptr BdCompressAll	;trim bd's, compress heap space
	pop	cx
	pop	dx
	call	B$ILHALC		;try allocation again
	jnc	BdAlloc_Success		;  brif it worked this time
	xor	ax,ax			;OM error return
	jmp	short BD_END

;***
;BdFree(pbdOwner) - Release a Heap entry
;Purpose:
;	Release a Runtime Heap entry. If pbdOwner.BD_pb is NULL,
;	just return (as input wasn't really an owner).
;Entry:
;	parm: bd *pbdOwner - points to owner of new heap entry
;
;***************************************************************************
cProc	BdFree,<PUBLIC,FAR,NODATA>,<SI>
	parmW	pbdOwner
cBegin
	mov	bx,[pbdOwner]
	mov	si,[bx.BD_pb]
	cmp	si,NULL
	jz	BdFree_Exit		;brif bd isn't an owner

	mov	[bx.BD_pb],NULL
	call	B$LHDALC
BdFree_Exit:
cEnd

;***
;BdChgContents(pbd, psdNew) - Change contents of a buffer
;Purpose:
;	Change the contents of a given buffer. Note that the buffer may or
;	may not be an owner already; if it is an owner, it will be Free'd.
;	The buffer will then be allocated, and the input sd contents copied in.
;
;	NOTE: psdNew must not point into a heap entry!
;Entry:
;	parm: bd *pbd - points to current owner of heap entry
;	parm: bd *psdNew -   points to sd, contents of which are to be put
;				in the input bd.
;Exit:
;	if operation successful
;		[AX] = TRUE (non-zero)
;	else
;		[AX] = FALSE (0) (Out of memory), and the original contents
;							of the bd are lost.
;***************************************************************************
cProc	BdChgContents,<PUBLIC,FAR,NODATA>,<SI,DI>
	parmW	pbd
	parmW	psdNew
cBegin
	mov	si,[pbd]
	cCall	BdFree,<si>		;free original contents if any

	mov	di,[psdNew]
	DbChk	PtrNotInHeap,di

	mov	cx,[di.SD_cb]
	push	cx			;save across call

	push	si
	push	cx
	PUSHI	dx,IT_NO_OWNERS
	call	BdAlloc			;alloc to size of desired contents

	pop	cx
	or	ax,ax
	jz	BdChgContents_Exit	;brif OM error on allocation

	mov	ax,[si.BD_pb]
	mov	bx,[di.SD_pb]
	cCall	CopyBlk,<bx,ax,cx>	;copy sd contents into bd
BdChgContents_Exit:
cEnd

;***
;BdChgOwner(pbdOwner, pbdNew) - Change the owner of a Heap entry
;BdChgOwner_NoCopy(pbdOwner, pbdNew) - Change the owner of a Heap entry
;Purpose:
;	Change the owner of an Interpreter-specific Heap entry. If 
;	pbdOwner.BD_pb is NULL, just return (as it wasn't really an owner to 
;	begin with).
;	BdChgOwner copies the bd contents to the new bd.
;	BdChgOwner_NoCopy is provided as a speed improvement, and should be
;		called in cases where the bd has already been copied BEFORE
;		this routine is called.
;
;	NOTE: This routine is guaranteed not to cause heap movement to occur.
;
;	NOTE: This routine must be called AFTER a block containing the bd is
;		moved if such movement is to take place, because this routine
;		changes the contents of bdOwner to indicate that it's no longer
;		an owner.
;Entry:
;	parm: bd *pbdOwner - points to current owner of heap entry
;	parm: bd *pbdNew -   points to new owner of heap entry
;
;***************************************************************************
	PUBLIC BdChgOwner
BdChgOwner:
	mov	cx,SIZE BD		;non-zero - - - do the copy
	SKIP2_PSW			;skip to start of common code
	PUBLIC BdChgOwner_NoCopy
BdChgOwner_NoCopy:
	xor	cx,cx
cProc	Chg_The_Owner,<FAR,NODATA>,<SI>
	parmW	pbdOwner
	parmW	pbdNew
cBegin
	mov	si,[pbdOwner]
	cmp	[si.BD_pb],NULL
	jz	BdChg_Exit

	DbChk	BdOwner,si		;ensure that given bd is an owner

	jcxz	BdChg_CopyDone		;brif caller already did this copy

	push	si
	push	pbdNew
	push	cx			;set to SIZE BD for BdChgOwner
	call	CopyBlk
BdChg_CopyDone:
	mov	cx,[pbdNew]
	inc	cx			;to heap manager, 'owner' is the actual
	inc	cx			;  pointer to heap data, not a pbd
	push	si			;si is an input to B$LHChgBakPtr
	mov	si,[si.BD_pb]
	call	B$LHChgBakPtr
	pop	si			;so we can set bd.pb to NULL

	mov	[si.BD_pb],NULL		;mark that this is no longer an owner
BdChg_Exit:
cEnd

;***
;EnsPhysicalSize - ensure physical size of near heap >= ax
;Purpose:
;	Change physical size of an Interpreter-specific Heap entry if necessary.
;	This is used by BdGrow and BdCheckFree. 
;	Note that this is not an external entry point, only for use
;	within this module, and can thus use register calling conventions.
;
;	NOTE: current heap manager interface demands that the owner
;	should not be subject to heap movement. 
;Entry:
;	[di] - points to owner of heap entry
;	[ax] = new total size requested for the buffer (i.e., new minimum
;		cbPhysical desired).
;Exit:
;	if enough memory is available:
;          [ax] = TRUE (non-zero)
;	   [bx] = new value for cbLogical (i.e., [ax] exit = entry)
;	otherwise,
;	   [ax] = 0
;	
;***************************************************************************
EnsPhysicalSize PROC	NEAR
	DbChk	BdOwner,di		;ensure that given bd is an owner
	DbChk	Heaps
	push	ax			;save input requested size
	DbOMCnt Ens_End2
	cmp	ax,[di.BD_cbPhysical]
	jbe	NoChange		;branch if already big enough

	push	si			;save caller's si
	push	ax			;in case initial try fails
	sub	ax,[di.BD_cbPhysical]	;ax=amount to grow
	cmp	ax,CBBUFBLOCK
	jae	Big_Enough		;branch if growing by significant amount

	mov	ax,CBBUFBLOCK		;never grow by less than this amount
Big_Enough:
	add	ax,[di.BD_cbPhysical]	;ax=(hopefully) new cbPhysical
	push	ax			;save (hopefully) new cbPhysical
	mov	si,[di.BD_pb]
	call	B$LHREALC		;call heap manager to realloc
	pop	bx			;size we realloced to
	or	ax,ax			;test result
	jz	Ens_Crunch_BDs		;brif realloc failed

	pop	cx			;clean stack
Ens_Phy_Success:
	mov	[di.BD_cbPhysical],bx
	mov	[di.BD_pb],si		;in case realloc moved the entry
Ens_End1:
	pop	si			;restore caller's si
Ens_End2:
	pop	bx			;restore input size for retval
	ret

NoChange:
	mov	al,TRUE			;ensure TRUE return, even if passed ax=0
	jmp	short Ens_End2

EnsPhysicalSize ENDP

Ens_Crunch_BDs:
	call	far ptr BdCompressAll	;trim all bd's, compress heaps
	pop	ax			;input to B$LHREALC
	push	ax			;save for return
	mov	si,[di.BD_pb]		;may be trashed on error return
	call	B$LHREALC
	pop	bx			;cb we tried to realloc to
	or	ax,ax			;did we succeed this time?
	jz	Ens_End1		;  brif not
	jmp	short Ens_Phy_Success	;succeeded this time - - go wrap up

;***
;BdGrowVar - Grow a Runtime Heap entry in the variable heap
;Purpose:
;	Same as BdGrow (below), but for an entry in the variable heap.
;	Uses the same interface and BdGrow (see below).
;Entry, Exit, Modifies:
;	Same as BdGrow (see below).
;Note: Shares and exits via BdGrow, below
;***************************************************************************
cProc	BdGrowVar,<PUBLIC,FAR,NODATA>
cBegin	<nogen>
	DbAssertRel grs.GRS_otxCONT,z,UNDEFINED,RT,<BdlGrowVar: CAN continue>
	call	B$TglHeapSpt		;make variable heap the active one
cEnd	<nogen>				;fall into BdGrow, below

;***
;BdGrow - Increase the logical size of a Heap entry
;Purpose:
;	Change logical size of an Interpreter-specific Heap entry.  This can
;	result in the movement of this and other heap entries as well
;	as strings.  
;	When this routine actually needs to grow the physical size
;	of the heap, it grows more than needed for this request, to
;	reduce heap thrashing.
;
;	NOTE: current heap manager interface demands that the owner
;	should not be subject to heap movement. 
;Entry:
;	parm: bd *pbdOwner - points to owner of heap entry
;	parm: ushort cbGrow - number of bytes needed
;Exit:
;	if enough memory is available:
;	   pbdOwner->cbLogical += cbGrow,
;	   pbdOwner->cbPhysical >= pbdOwner->cbLogical
;	   [AX] = TRUE (non-zero)
;	else
;	   [AX] = FALSE (0) (Out of memory)
;
;***************************************************************************

cProc	BdGrow,<PUBLIC,FAR,NODATA>,<di>
	parmW	pbdOwner
	parmW	cbGrow
cBegin
	mov	di,[pbdOwner]		;di points to bd descriptor
	mov	ax,[cbGrow]		;[AX] == increase desired
	add	ax,[di.BD_cbLogical]	;[AX] == new logical size
	jc	GrowOmErr		;branch if overflow (can't grow > 64k)

	;*****************************
	;NOTE: BdRealloc jumps in here
	;*****************************
BdRealloc1:
	call	EnsPhysicalSize		;change physical size (inputs ax & di)
	or	ax,ax			;test boolean result
	jz	BdGrow_End		;brif out-of-memory case
	
	mov	[di.BD_cbLogical],bx	;new cbLogical - successful return
BdGrow_End:
	cmp	[b$fVarHeapActive],FALSE
	jz	BdGrow_Exit		;brif variable heap not active

	call	B$TglHeapSpt		;reactivate the local heap
BdGrow_Exit:
cEnd

GrowOmErr:
	xor	ax,ax
	jmp	short BdGrow_End

;***
;BdRealloc - Change the logical size of a Heap entry
;Purpose:
;	Change logical size of an Interpreter-specific Heap entry.  This can
;	result in the movement of this and other heap entries as well
;	as strings.  
;	When this routine actually needs to grow the physical size
;	of the heap, it grows more than needed for this request, to
;	reduce heap thrashing.
;
;	NOTE: current heap manager interface demands that the owner
;	should not be subject to heap movement. 
;Entry:
;	parm: bd *pbdOwner - points to owner of heap entry
;	parm: ushort cbLogicalNew - new size of heap entry
;Exit:
;	if enough memory is available:
;	   pbdOwner->cbLogical = cbLogicalNew,
;	   pbdOwner->cbPhysical >= pbdOwner->cbLogical
;	   [AX] = TRUE (non-zero)
;	else
;	   pbdOwner->cbLogical is unchanged
;	   [AX] = FALSE (0) (Out of memory)
;
;***************************************************************************

cProc	BdRealloc,<PUBLIC,FAR,NODATA>,<di>
	parmW	pbdOwner
	parmW	cbNew
cBegin
	mov	di,[pbdOwner]		;di points to bd descriptor
	mov	ax,[cbNew]		;[AX] == increase desired
	jmp	SHORT BdRealloc1
cEnd	<nogen>

;***
;BdCheckFree - Make sure buffer has some free space
;Purpose:
;	This is identical to BdGrow, but it does not alter the
;	descriptor's cbLogical field.  Some typical cases when it is
;	called include:
;	1-  Before calling BdAppend to copy from one bd to another.
;	    By calling this first, we know BdAppend won't have to
;	    grow the heap entry, causing movement, which could invalidate
;	    BdAppend's pb argument.
;	2-  When the caller is about to do an operation which will
;	    append information to a bd, but the caller doesn't know
;	    exactly how many bytes will be added, but an upper limit is known.
;
;	NOTE: current heap manager interface demands that the owner
;	should not be subject to heap movement. 
;Entry:
;	parm: bd *pbdOwner - points to owner of heap entry
;	parm: ushort cbFree - number of free bytes needed
;Exit:
;	pbdOwner->cbLogical is ALWAYS UNCHANGED
;	If enough memory is available:
;	   pbdOwner->cbPhysical >= pbdOwner->cbLogical + cbFree
;	   [AX] = TRUE (non-zero)
;	else
;	   [AX] = FALSE (0) (Out of memory)
;
;***************************************************************************
cProc	BdCheckFree,<PUBLIC,FAR,NODATA>,<DI>
	parmW	pbdOwner
	parmW	cbFree
cBegin
	mov	di,[pbdOwner]		;di points to bd descriptor

⌨️ 快捷键说明

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