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

📄 bdmgr.asm

📁 [随书类]Dos6.0源代码
💻 ASM
📖 第 1 页 / 共 4 页
字号:
	DbChk	BdlOwner,si		;ensure that bdlOwner is an owner

	mov	dx,si			;pFHD for FHD that's being moved
	mov	cx,[pbdlNew]
	sub	cx,si			;cx = pNew - pOld (adjustment factor)
	call	B$FHAdjOneDesc

	mov	[si.BDL_status],NOT_OWNER
BdlChg_Exit:
cEnd

;***
;BdlRealloc - reallocate a Far Heap entry
;Purpose:
;	reallocate a Heap entry from the Far Heap.  This can cause
;	movement of String and Runtime heap entries.
;
;	[5] Note that at least some callers depend on additional space being
;	[5] zero-filled (EB varmgr code, for one).
;Entry:
;	parm: bdl *pbdlOwner - points to owner of heap entry
;	parm: ushort cbNew - new buffer size desired
;Exit:
;	if entry was successfully reallocated:
;	   pbdlOwner->cbLogical = cbNew
;	   pbdlOwner->cbPhysical >= cbNew
;	   [AX] = TRUE (non-zero)
;	else
;	   [AX] = FALSE (0) (Out of memory)
;
;***************************************************************************
cProc	BdlRealloc,<PUBLIC,FAR,NODATA>,<di>
	parmW	pbdlOwner
	parmW	cbNew
	localB	fTryAgain
cBegin
	mov	[fTryAgain],TRUE
	DbOMCnt	BdlRealloc_Exit
	mov	di,[pbdlOwner]
	mov	bx,[di.BDL_cPhysical]
	SHIFT	H,L,bx,4		;shift left to convert cPara to cbytes
	mov	ax,[cbNew]
	cmp	bx,ax
	jae	Change_cbLogical	;brif physical size is big enough

	cmp	ax,0FFE0H		;if ask far heap for > FFE0H, it will
					;  round request up to para boundary ...
	jbe	BdlRealloc_Cont		;brif request not too large

	xor	ax,ax			;Out of Memory return
	jmp	short BdlRealloc_Exit

BdlRealloc_Crunch:
	cmp	[fTryAgain],FALSE
	jz	BdlRealloc_Exit		;brif we've already tried this - give up

	mov	[fTryAgain],FALSE	;remember this is the 2nd attempt
	call	far ptr BdCompressAll	;trim all bd's, compress heaps,
	mov	ax,[cbNew]		;and try again w/o blocking factor
	jmp	short BdlRealloc_Cont1

BdlRealloc_Cont:
	add	ax,FAR_EXTRA		;ax = ax + FAR_EXTRA to reduce thrashing
	;Under DOS 3, we know the heap manager actually allocates in 16-byte
	;  (paragraph) quantities, so to ensure we don't waste an average of
	;  8 bytes per bdl, pay a few bytes of code here to round up
	jc	RealcForMax		;brif this puts us over 64k

BdlRealloc_Cont1:
	add	ax,000FH		;constant for rounding up to paragraph
	jnc	TryToRealloc		;brif still under 64k

RealcForMax:
	mov	ax,0FFE0H		; try for maximum - - - note that
					;'maximum' can't be FFFFH, because
					;the far heap code will round this
					;up to the nearest paragraph boundary
TryToRealloc:
	and	al,0F0H 		;[9] finish rounding size up to para
	mov	dx,0FFE0H		
	cmp	ax,dx			; is result > legal max?
	jbe	ReallocAttempt		; brif not

	xchg	ax,dx			
ReallocAttempt:
	DbChk	BdlOwner,di		;ensure that bdlOwner is an owner
	xor	dx,dx
	mov	bx,di
	call	B$FHRealloc
	or	ax,ax
	jz	BdlRealloc_Crunch	;brif insufficient memory
	mov	ax,[cbNew]		;requested size
Change_cbLogical:
	mov	[di.BDL_cbLogical],ax	;save new logical size
	mov	ax,sp			;signal success (cbNew could be zero ..)
BdlRealloc_Exit:
cEnd

;***
;BdlCheckFree - Make sure far heap entry has some free space
;Purpose:
;	Change size of a far Heap entry if necessary to
;	ensure that there is a certain number of free bytes at the
;	end of the entry.  This can result in the movement of this
;	and other heap entries.
;	This routine does not work with HUGE heap entries (i.e. > 64k)
;Entry:
;	parm: bdl *pbdlOwner - points to owner of heap entry
;	parm: ushort cbFree - number of free bytes needed
;Exit:
;	If enough memory is available:
;	   pbdlOwner->cbLogical is unchanged
;	   pbdlOwner->cbPhysical >= pbdlOwner->cbLogical + cbFree
;	   [AX] = TRUE (non-zero) (successful return)
;	else
;	   [AX] = FALSE (0) (Out of memory)
;
;***************************************************************************
cProc	BdlCheckFree,<PUBLIC,FAR,NODATA>,<di>
	parmW	pbdlOwner
	parmW	cbFree
cBegin
	DbOMCnt	BdlCheckFreeExit
	mov	di,[pbdlOwner]
	mov	ax,[di.BDL_cPhysical]	;ax = current physical size
	SHIFT	H,L,ax,4		;shift left to convert cPara to cbytes
	push	ax
	sub	ax,[di.BDL_cbLogical]	;ax = current free size
	sub	ax,cbFree		;ax = new free size
	jnc	SizeIsOk		;brif we're already big enough

	neg	ax
	pop	bx
	add	ax,bx			;ax = minimum new free size
	jc	BdlCheckDenied		;error if attempting to grow > 64k

	push	[di.BDL_cbLogical]	;save this across call to BdlRealloc
	cCall	BdlRealloc,<di,ax>
	pop	[di.BDL_cbLogical]
BdlCheckFreeExit:
cEnd

BdlCheckDenied:
	xor	ax,ax			;return ERROR result (zero)
	SKIP1_PSW			;this 'eats' the next instruction
SizeIsOk:
	pop	ax			;cPhysical known to be non-zero
	jmp	short BdlCheckFreeExit

;***
;BdlGrow - Increase the logical size of a Heap entry
;Purpose:
;	Change logical size of a bdl.  This can result in the movement of this
;	and other heap entries.
;	When this routine actually needs to grow the physical size
;	of the bdl, it grows more than needed for this request, to
;	reduce heap thrashing.
;
;	Added as part of revision [9].
;Entry:
;	parm: bd *pbdlOwner
;	parm: ushort cbGrow - number of additional bytes needed
;Exit:
;	if enough memory is available:
;	   pbdlOwner->cbLogical += cbGrow,
;	   pbdlOwner->cPhysical increased to account for >= cbLogical bytes
;	   [AX] = TRUE (non-zero)
;	else
;	   [AX] = FALSE (0) (Out of memory)
;
;***************************************************************************
cProc	BdlGrow,<PUBLIC,FAR>
	parmW	pbdlOwner
	parmW	cbGrow
cBegin
	mov	bx,[pbdlOwner]
	mov	ax,[cbGrow]
	add	ax,[bx.BDL_cbLogical]
	cCall	BdlRealloc,<bx,ax>
cEnd

;***
;BdlCopyFrom - Copy data from a far Heap entry to DS
;Purpose:
;	Copy data from a far Heap entry to DS
;	Does not work with HUGE heap entries (i.e. > 64k)
;Entry:
;	parm: bdl *pbdlOwner - points to owner of new heap entry
;	parm: ushort oSrc - 16 bit offset into bdl to source
;	parm: char *pbDst - points to 1st byte of destination
;	parm: ushort cb - number of bytes to copy
;
;***************************************************************************
cProc	BdlCopyFrom,<PUBLIC,FAR,NODATA>,<si,di>
	parmW	pbdlOwner
	parmW	oSrc
	parmW	pbDst
	parmW	cb
cBegin
	mov	si,[oSrc]		;si = source offset
	mov	di,[pbDst]		;di = destination offset
	mov	bx,[pbdlOwner]
	DbChk	BdlOwner,bx		;ensure that bdlOwner is an owner
	GETSEG	ax,[bx.BDL_seg],,<SIZE,LOAD> ;[4] seg of far heap entry
	mov	bx,ds			;bx -> DGROUP
	mov	ds,ax			;set up source seg (heap entry)
	mov	es,bx			;set up destination seg (DGROUP)
CopyCommon:
	mov	cx,cb			;cx = byte count
	shr	cx,1			;convert to word count
	rep	movsw			;transfer from ds:si to es:di
	jnc	CopyFrom_Even		;no carry if count was even
	movsb				;move the last (odd) byte
CopyFrom_Even:
	mov	ds,bx			;restore ds->DGROUP
cEnd

;***
;BdlCopyTo - Copy data from DS into a far Heap entry
;Purpose:
;	Copy data from DS into a far Heap entry
;	Does not work with HUGE heap entries (i.e. > 64k)
;Entry:
;	parm: bdl *pbdlOwner - points to owner of new heap entry
;	parm: ushort oDst - 16 bit offset into bdl to destination
;	parm: char *pbSrc - points to 1st byte of source
;	parm: ushort cb - number of bytes to copy
;
;***************************************************************************
cProc	BdlCopyTo,<PUBLIC,FAR,NODATA>,<si,di>
	parmW	pbdlOwner
	parmW	oDst
	parmW	pbSrc
	parmW	cb
cBegin
	mov	si,[pbSrc]		;si = source offset
	mov	di,[oDst]		;di = destination offset
	mov	bx,[pbdlOwner]
	DbChk	BdlOwner,bx		;ensure that bdlOwner is an owner
	GETSEG	ax,[bx.BDL_seg],,<SIZE,LOAD> ;[4] seg of far heap entry
	mov	es,ax			;set up destination seg
	mov	bx,ds
	jmp	short CopyCommon
cEnd	nogen


;***
;BdlCopyFromTo - Copy data from one bdl to another
;Purpose:
;	Copy data from one far heap entry into another.
;	Does not work with HUGE heap entries (i.e. > 64k)
;
;	Added as part of revison [7]
;Entry:
;	parm: bdl *pbdlSrc - points to source bdl
;	parm: ushort oSrc - 16 bit offset into bdl to source
;	parm: bdl *pbdlDst - points to destination bdl
;	parm: ushort oDst - 16 bit offset into bdl to destination
;	parm: ushort cb - number of bytes to copy
;Exit:
;	none.
;***************************************************************************
cProc	BdlCopyFromTo,<PUBLIC,FAR,NODATA>,<si,di,ds>
	parmW	pbdlSrc
	parmW	oSrc
	parmW	pbdlDst
	parmW	oDst
	parmW	cb
cBegin
	mov	si,[pbdlDst]		
	DbChk	BdlOwner,si		;ensure that bdlDst is an owner
	GETSEG	dx,[si.BDL_seg],,<SIZE,LOAD>  
					; dx = seg of far heap entry (dst)
	mov	bx,[pbdlSrc]
	DbChk	BdlOwner,bx		;ensure that bdlSrc is an owner
	GETSEG	ds,[bx.BDL_seg],,<SIZE,LOAD,NOFLUSH>	
					; ds = seg of far heap entry (src)
assumes DS,NOTHING
	mov	es,dx			
	mov	si,[oSrc]		;si = source offset
	mov	di,[oDst]		;di = destination offset
	mov	cx,[cb]
	shr	cx,1			;convert to word count
	rep	movsw			;transfer from ds:si to es:di
	jnc	CopyFrom_Even2		;no carry if count was even
	movsb				;move the last (odd) byte
CopyFrom_Even2:
cEnd
assumes DS,DATA


;***
;BdlTrim - trim given bdl down to cbLogical
;Purpose:
;	Releases excess space in a given bdl
;Entry:
;	parm: bdl *pbdl
;
;***************************************************************************
cProc	BdlTrim,<PUBLIC,FAR,NODATA>,<si,di>
	parmW	pbdl
cBegin
	mov	bx,[pbdl]
	DbChk	BdlOwner,bx		;ensure that bdlOwner is an owner
	mov	ax,[bx.BDL_cbLogical]	;size to realloc to
	xor	dx,dx
	call	B$FHRealloc		;must succeed; we're either reducing
					;  or asking for existing entry size
cEnd


;seg_rt = segment address for the RT segment
;It can be referenced from any module as follows:
	;	EXTRN	seg_rt:abs
	;	mov	ax,SEG seg_rt
	
	PUBLIC	seg_rt
	seg_rt	EQU	SEG BdlTrim

sEnd	RT


;------------------------------------------------------------
;---  Interpreter Buffer Descriptor Management Routines   ---
;------------------------------------------------------------
sBegin	DATA
	staticB	bdGrabSpace,NULL,<SIZE BD>
sEnd	DATA

sBegin 	CODE
assumes	CS,CODE

CBNEAR_GRAB equ 2 * CBBUFBLOCK

;***
;GrabSpace - grab some heap space
;Purpose:
;	Allocates CBNEAR_GRAB bytes via BdAlloc. 
;	Called to lock up a chunk of heap space so we ensure that
;	enough space exists to do simple things like CLEAR for more memory!
;
;	NOTE: It's important that grabspace just grab space from the near
;		heap, not the far heap; if we grabbed far space instead,
;		this could allow the user to tie up all of DGROUP with
;		variable tables with plenty of DGROUP space free.
;Entry:
;	none.
;Exit:	
;	ax = 0 if insufficient memory, else ax != 0
;***************************************************************************
cProc	GrabSpace,<PUBLIC,FAR,NODATA>
cBegin
	mov	ax,[bdGrabSpace.BD_pb]
	or	ax,ax
	jnz	GotSpace		;return ax<>0 if already have space
	PUSHI	ax,<dataOFFSET bdGrabSpace>
	PUSHI	ax,CBNEAR_GRAB
	PUSHI	ax,IT_NO_OWNERS
	call	BdAlloc
	or	ax,ax
GotSpace:
cEnd

;***
;ReleaseSpace - Release the space grabbed by GrabSpace
;Purpose:
;	Deallocates the bd allocated by GrabSpace if it is currently allocated.
;	Note that it's perfectly o.k. to call this even when no space has
;	been grabbed.
;Entry:
;	none.
;Exit:
;	ax = 0.
;***************************************************************************
cProc	ReleaseSpace,<PUBLIC,FAR,NODATA>
cBegin
	PUSHI	ax,<dataOFFSET bdGrabSpace>
	call	BdFree			;deallocate bd if couldn't allocate bdl
cEnd

sEnd	CODE

	end

⌨️ 快捷键说明

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