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

📄 bdmgr.asm

📁 [随书类]Dos6.0源代码
💻 ASM
📖 第 1 页 / 共 4 页
字号:
	mov	ax,[cbFree]		;[AX] == increase desired
	add	ax,[di.BD_cbLogical]	;[AX] == resulting size
	jc	CheckOmErr		;branch if overflow (can't grow > 64k)

	call	EnsPhysicalSize		;change physical size (inputs ax & di)
BdCheck_End:
cEnd

CheckOmErr:
	xor	ax,ax
	jmp	short BdCheck_End

;***
; boolean BdShiftRight(pbd, obStart, cb)
;
; Purpose:
;	Grow the buffer descriptor, and shift its contents right
;	(copying content to higher addresses) starting at offset
;	obStart until the end of the buffer.
;
;	NOTE: current heap manager interface demands that the owner
;	should not be subject to heap movement. 
;
; Entry:
;	parmW pbd points to the buffer descriptor
;	parmW obStart = byte offset for 1st byte to be shifted right
;	parmW cb = number of bytes each byte is to be shifted
;
; Exit:
;	If not enough memory can be obtained,
;		[AX] = FALSE
;	else
;		pbdDst->cbLogical is updated
;		[AX] = TRUE
;
;   Before BdShiftRight(pbd, 2, 2):
;	high memory 	
;	  pbd->cbLogical------->+-----+
;				|  E  |
;				|  D  |
;				|  C  |
;				|  B  |
;				|  A  |
;	low memory		+-----+
;
;   After:
;	high memory 	
;	  pbd->cbLogical------->+-----+
;				|  E  |
;				|  D  |
;				|  C  |
;				|  D  |
;				|  C  |
;				|  B  |
;				|  A  |
;	low memory		+-----+
;
;***************************************************************************
cProc	BdShiftRight,<PUBLIC,FAR,NODATA>,<SI,DI>
	parmW pbd
	parmW obStart
	parmW cb
cBegin
	push	pbd
	push	cb
	call	BdCheckFree		;1st grow the buffer
	or	ax,ax
	je	BdShiftExit		;branch if out-of-memory, return 0
	mov	bx,pbd			;bx -> descriptor
	mov	cx,[bx.BD_cbLogical]	;[CX] = current size of buffer
	mov	si,[bx.BD_pb]		;si points to start of buffer
	add	si,cx			;si points beyond end of current content
	dec	si			;si points to 1st byte to copy
	mov	di,si
	mov	ax,cb
	add	di,ax			;di points to dst for 1st byte to copy
	add	[bx.BD_cbLogical],ax	;update size of buffer
	sub	cx,obStart		;[CX] = number of bytes to copy
	jcxz	Copy0Bytes
	push	ds
	pop	es			;es=ds
	std				;copy from high to low address
	rep movsb			;do the block copy
	cld
Copy0Bytes:
	mov	ax,TRUE
BdShiftExit:
cEnd

;***
; boolean BdShiftLeft(pbd, obStart, cb)
;
; Purpose:
;	Shrink the buffer descriptor, and shift its contents left
;	(copying content to lower addresses) starting at offset
;	obStart until the end of the buffer.
;
; Entry:
;	parmW pbd points to the buffer descriptor
;	parmW obStart = byte offset for 1st byte to be deleted
;	parmW cb = number of bytes to be deleted
;
; Exit:
;	pbdDst->cbLogical is updated
;	no return value
;
;   Before BdShiftLeft(pbd, 2, 2):
;	high memory 	
;	  pbd->cbLogical------->+-----+
;				|  E  |
;				|  D  |
;				|  C  |
;				|  B  |
;				|  A  |
;	low memory		+-----+
;
;   After:
;	high memory 	
;	  pbd->cbLogical------->+-----+
;				|  E  |
;				|  B  |
;				|  A  |
;	low memory		+-----+
;
;***************************************************************************
cProc	BdShiftLeft,<PUBLIC,FAR,NODATA>,<SI,DI>
	parmW pbd
	parmW obStart
	parmW cb
cBegin
	mov	bx,pbd			;bx -> descriptor
	mov	di,[bx.BD_pb]		;di points to start of buffer
	add	di,obStart		;di points to 1st byte to delete
	mov	si,di
	add	si,cb			;si points beyond last byte to delete
	mov	cx,[bx.BD_cbLogical]	;[CX] = current size of buffer
	sub	cx,cb			;cx = new size of buffer
	mov	[bx.BD_cbLogical],cx	;update descriptor
	sub	cx,obStart		;cx = # bytes to copy
	jcxz	LeftExit		;brif 0 bytes to copy
	push	ds
	pop	es			;es=ds
	rep movsb			;do the block copy
LeftExit:
cEnd

;***
; boolean BdAppend(pbdDst, pbSrc, cb)
;
; Purpose:
;	Append a string of bytes to a Buffer Descriptor.
;	If this is preceeded by a call to BdCheckFree(pbdDst, cb)
;	then pbSrc can point within another heap entry with no
;	fear of movement before the copy is complete.  Otherwise,
;	pbSrc had better not point within a heap entry.
;
;	NOTE: current heap manager interface demands that the owner
;	should not be subject to heap movement. 
;
; Entry:
;	parmW pbdDst points to the destination buffer descriptor
;	parmW pbSrc points to 1st byte to be copied into buffer
;	parmW cb = number of bytes to be copied
;
; Exit:
;	If not enough memory can be obtained,
;		[AX] = FALSE
;	else
;		pbdDst->cbLogical is updated
;		[AX] = TRUE
;
;***************************************************************************
cProc	BdAppend,<PUBLIC,FAR,NODATA>,<SI,DI>
	parmW pbdDst
	parmW pbSrc
	parmW cb
	localW pbDst
	localW cbTemp
cBegin
	push	pbdDst
	push	cb
	call	BdCheckFree
	or	ax,ax
	je	BdAppendExit		;branch if out-of-memory, return 0
	mov	cx,cb			;[CX] = # bytes to copy
	mov	di,pbdDst		;di -> destination descriptor
	mov	ax,[di.BD_cbLogical]	;ax = current size of buffer
	add	[di.BD_cbLogical],cx	;update size of buffer
	mov	di,[di.BD_pb]		;di points to start of dest buffer
	add	di,ax			;add new bytes at end of buffer
	mov	si,pbSrc		;si = source byte ptr
	push	ds
	pop	es			;es=ds
	rep movsb			;do the block copy
	mov	ax,TRUE
BdAppendExit:
cEnd


;-----------------------------------------------------------------
;---   Large Far Heap Buffer Descriptor Management Routines    ---
;-----------------------------------------------------------------


FAR_EXTRA = 512		;never grow a far heap entry by less than 512 bytes

;***
;AllocBdl - Allocate a Far Heap entry (workhorse for BdlAlloc)
;AllocBdl_Sb - same, but allocates a given sb for this
;Purpose:
;	Allocate a Heap entry from the Far Heap.  This can cause
;	movement of Runtime and String heap entries.
;	Note that this routine should ask for only the amount of space asked
;	for; growing a buffer will increase requests to some minimal block size,
;	but many buffers need to be initially allocated to some minimal 
;	(possibly zero) size.
;Entry:
;	di = pbdlOwner - points to owner of new heap entry
;	si = cbSize - number of bytes needed
;	For EB versions, bx = type constant for type of bdl buffer
;	For AllocBdl_Sb, cx = sb to use
;Exit:
;	if entry was successfully allocated:
;	   pbdlOwner->cbLogical = cbSize
;	   pbdlOwner->cbPhysical = cbSize
;	   [AX] = TRUE (non-zero)
;	   pbdlOwner->status != NOT_OWNER
;	else
;	   [AX] = FALSE (0) (Out of memory)
;	PSW.Z is set on exit based on an 'OR AX,AX' instruction
;
;***************************************************************************
cProc	AllocBdl,<NEAR,NODATA>
cBegin	<nogen>
	mov	cx,0			; use any sb that's free
cEnd	<nogen>
cProc	AllocBdl_Sb,<NEAR,NODATA>
cBegin
	mov	ax,si

	DbAssertRel ax,be,0FFF0H,RT,<BdlAlloc: caller asked for more than FFF0H>
	;The above assertion is based on the problem where a request to
	;   B$IFHAlloc for greater than 0FFF0H bytes will be rounded UP to past
	;   64k, with no error reported.
	xor	dx,dx			;DX:AX is input size to B$IFHAlloc
	mov	bx,di
	DbChk	BdlNotOwner,di
	mov	[bx.BDL_cbLogical],ax
	call	B$IFHAlloc		;allocate a far heap entry (0 if can't)
	or	ax,ax			;set zero flag for caller
cEnd	AllocBdl


;***
;BdlAlloc - Allocate a Far Heap entry
;Purpose:
;	Allocate a Heap entry from the Far Heap.  This can cause
;	movement of Runtime and String heap entries.
;	Note that this routine should ask for only the amount of space asked
;	for; growing a buffer will increase requests to some minimal block size,
;	but many buffers need to be initially allocated to some minimal 
;	(possibly zero) size.
;
;	[5] Note that at least some callers depend on the new block being zero-
;	[5] filled (EB varmgr code, for one).
;Entry:
;	parm: bdl *pbdlOwner - points to owner of new heap entry
;	parm: ushort cbSize - number of bytes needed
;Exit:
;	if entry was successfully allocated:
;	   pbdlOwner->cbLogical = cbSize
;	   pbdlOwner->cbPhysical = cbSize
;	   [AX] = TRUE (non-zero)
;	   pbdlOwner->status != NOT_OWNER
;	else
;	   [AX] = FALSE (0) (Out of memory)
;
;***************************************************************************
cProc	BdlAlloc,<PUBLIC,FAR,NODATA>,<si,di>
	parmW	pbdlOwner
	parmW	cbSize
cBegin
	DbOMCnt	BdlAlloc_Exit
	mov	di,[pbdlOwner]
	mov	si,[cbSize]
	cCall	AllocBdl
	jnz	BdlAlloc_Exit		;brif success

	call	far ptr BdCompressAll	;trim bd's, compress heap space
	cCall	AllocBdl
BdlAlloc_Exit:
cEnd

;***
;BdlAllocSb - Allocate a Far Heap entry, given a desired sb
;Purpose:
;	Same as BdlAlloc, but accepts as a third parm the sb value that
;	is to be used.
;	Added as revision [13].
;Entry:
;	parm: bdl *pbdlOwner - points to owner of new heap entry
;	parm: ushort cbSize - number of bytes needed
;	parm: ushort sbInput - sb we must use for this allocation
;			(caller guarantees this is unallocated).
;Exit:
;	if entry was successfully allocated:
;	   pbdlOwner->cbLogical = cbSize
;	   pbdlOwner->cbPhysical = cbSize
;	   [AX] = TRUE (non-zero)
;	   pbdlOwner->status != NOT_OWNER
;	else
;	   [AX] = FALSE (0) (Out of memory)
;
;***************************************************************************
cProc	BdlAllocSb,<PUBLIC,FAR,NODATA>,<si,di>
	parmW	pbdlOwner
	parmW	cbSize
	parmW	sbInput
cBegin
	DbOMCnt BdlAllocSb_Exit
	mov	di,[pbdlOwner]
	mov	si,[cbSize]
	mov	cx,[sbInput]		
	cCall	AllocBdl_Sb
BdlAllocSb_Exit:
cEnd

;***
;BdlFree - Release a far Heap entry
;Purpose:
;	Release a far Heap entry. If bdl is not an owner, this routine just
;	returns, with no error.
;Entry:
;	parm: bdl *pbdlOwner - points to owner of new heap entry
;Exit:
;	bdl is released; pbdlOwner->status = NOT_OWNER
;
;***************************************************************************
cProc	BdlFree,<PUBLIC,FAR,NODATA>
	parmW	pbdlOwner
cBegin
	mov	bx,[pbdlOwner]
	cmp	[bx.BDL_status],NOT_OWNER
	jz	BdlFree_Exit		;brif bdl already free

	DbChk	BdlOwner,bx		;ensure that given bdl is an owner
	push	bx
	call	B$FHDealloc		;free an allocated far heap entry
	pop	bx
	mov	[bx.BDL_status],NOT_OWNER ;indicate that bdl is not an owner
BdlFree_Exit:
cEnd

;***
;BdlChgOwner(pbdlOwner, pbdlNew) - Change the owner of a Far Heap entry
;Purpose:
;	Change the owner of a Far Heap entry. If pbdlOwner.BDL_status is 
;	NOT_OWNER, just return (as it wasn't really an owner to begin with).
;
;	NOTE: This routine is guaranteed not to cause heap movement to occur.
;
;	NOTE: This routine must be called AFTER a block containing the bdl is
;		copied, as the far heap manager modifies the FHD according to
;		its original location. This copy MUST be done by the caller
;		prior to this routine being called.
;		Note also that it is NOT safe to block copy a range containing
;		multiple bdl's and then call this routine once per bdl - - -
;		Since the far heap code chains all bdl's together, a call to
;		BdlChgOwner can cause another bdl to be modified (in the 
;		'status' a.k.a. 'pNext' field).
;Entry:
;	parm: bdl *pbdlOwner - points to current owner of far heap entry
;	parm: bdl *pbdlNew -   points to new owner of far heap entry
;Exit:
;	none.
;
;***************************************************************************
cProc	BdlChgOwner,<PUBLIC,FAR,NODATA>,<SI>
	parmW	pbdlOwner
	parmW	pbdlNew
cBegin
	mov	si,[pbdlOwner]
	cmp	[si.BDL_status],NOT_OWNER
	jz	BdlChg_Exit		;brif bdl wasn't an owner

⌨️ 快捷键说明

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