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

📄 bdmgr.asm

📁 [随书类]Dos6.0源代码
💻 ASM
📖 第 1 页 / 共 4 页
字号:
	TITLE BdMgr.asm - Buffer Descriptor Management Routines

COMMENT	\

--------- --- ---- -- ---------- ----
COPYRIGHT (C) 1985 BY MICROSOFT, INC.
--------- --- ---- -- ---------- ----

\

;============================================================================
; Module: BdMgr.asm - Buffer Descriptor Management Routines
;	This is a layer of routines which depends on the BASCOM Runtime Heap
;	Management routines in source file (strutl.asm).
;	It manages entries in the Interpreter and Far heap.
; System: Quick BASIC Interpreter
;============================================================================

	.xlist

	include version.inc
	BDMGR_ASM = ON
	includeOnce	architec
	includeOnce	context
	includeOnce	heap
	includeOnce	parser
	includeOnce	txtmgr
	includeOnce	util

	.list

;	.sall


assumes	DS,DATA
assumes	ES,DATA
assumes	SS,DATA

sBegin	DATA

; HMEM_ constants used by SBMGR allocation routines

HMEM_FIXED	EQU	0000H		
HMEM_MOVEABLE	EQU	0002H		
HMEM_NOCOMPACT	EQU	0010H		
HMEM_ZEROINIT	EQU	0040H		
HMEM_DISCARDABLE EQU	0F00H		

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

DbOMCnt	MACRO	label
	ENDM

sEnd	DATA

	EXTRN	AdjustCommon:FAR
	EXTRN	AdjustVarTable:FAR


sBegin RT
assumes	CS,RT

	EXTRN	B$ILHALC:NEAR
	EXTRN	B$LHREALC:NEAR
	EXTRN	B$LHDALC:NEAR
	EXTRN	B$LHChgBakPtr:NEAR
	EXTRN	B$ILHADJ:NEAR
	EXTRN	B$LHForEachEntry:NEAR
	EXTRN	B$NHCPCT:NEAR
	EXTRN	B$TglHeapSpt:FAR

	EXTRN	B$IFHAlloc:NEAR 	
	EXTRN	B$FHDealloc:NEAR	
	EXTRN	B$FHRealloc:NEAR	
	EXTRN	B$FHAdjDesc:NEAR	
	EXTRN	B$FHAdjOneDesc:NEAR	

CBBUFBLOCK equ 512	;Never grow a near heap by less than this
			; number of bytes to reduce heap thrashing.

VAR_EXTRA equ 30	;we want to keep up to this much free space beyond
			; cbLogical in IT_VAR (variable) tables when compressing
			; other bd's all the way back to cbLogical. This is to
			; help the user's chances of edit and CONTinuing.




;------------------------------------------------------------
;---  Interpreter Buffer Descriptor Management Routines   ---
;------------------------------------------------------------
;***
;B$IHeapEntryMoved - handle movement of Interpreter-specific Heap entry
;Purpose:
;	This routine is called by the Runtime Heap management
;	code just before it moves an Interpreter-specific Heap entry.
;	This routine performs any updating necessary due to
;	the movement of an Interpreter-specific Heap entry
;	it does not need to update entry pointer in the bd[p] for
;	the entry being moved; it just dispatches based on the
;	heap entry type to a routine which finds all string/heap
;	owners within the heap entry being moved, and calls the heap
;	management code to update the backpointers. Note that each 
;	such routine will be located in it's own component; these 
;	routines will call the runtime heap manager directly, but
;	will do so via a macro to keep runtime heap interface knowledge
;	confined to this module and associated header files.
;Entry:
;	AX = number of bytes the heap entry has moved.
;	       A positive number indicates the entry has moved
;	       to a higher address.
;	BX = pointer to the bd[p].pb field of the buffer descriptor for
;		the heap entry being moved.
;	CL = type constant for the heap type being moved (IT_MRS, ... etc.)
;
;Exit:
;	none.
;Modifies:
;	May modify BX, CX, or PSW - no others
;***************************************************************************
cProc	B$IHeapEntryMoved,<PUBLIC,NEAR,NODATA>,<AX,DX,ES,SI,DI>
cBegin

	mov	si,bx
	cmp	cl,IT_NO_OWNERS_BDP	;a bdp entry being moved?
	jnz	Not_Bdp			;brif not

	add	[bx.BDP_pbCur-2],ax	;adjust the pbCur field
	jmp	short Entry_Moved_Exit	;that's all, folks

Not_Bdp:
	mov	di,ax			;communicate adjustment factor in DI
	mov	ax,[bx-2]		;put cbLogical (table end offset) in ax
	mov	bx,[bx]
	push	ax			;save until Entry_Moved_Cont
	push	bx			;save until Entry_Moved_Cont
	push	cx			;save until Entry_Moved_Cont

	cmp	cl,IT_COMMON_VALUE	
	jae	Update_Stack_Ptrs	;brif we have to update stack ptrs, or
					;var or common table
	cmp	cl,IT_PRS		; no bd's in prs tables
	jz	Entry_Moved_Cont	; brif prs table

	cCall	AdjustITable,<bx,ax,cx> ;adjust the table, whatever it is.

Entry_Moved_Cont:
	pop	cx			;restore type constant
	pop	bx			;restore start of range
	pop	dx

FHD_TBL EQU NOT IT_M_INTERP AND (IT_MRS OR IT_PRS OR IT_COMMON_VALUE OR IT_VAR)
	test	cl,FHD_TBL
	jz	Entry_Moved_Exit	;brif entry can't contain far heap desc.

	;prs and mrs tables contain bdl's - - - get far heap to update these
	add	dx,bx			;dx is now end of range
	mov	ax,di			;adjustment factor
	call	B$FHAdjDesc

Entry_Moved_Exit:
cEnd

Update_Stack_Ptrs:
	jnz	Upd_Stk_Ptrs_Cont	;brif cl != IT_COMMON_VALUE
	call	AdjustCommon		;update backpointers to any string 
					;descriptors or string array descriptors
					;in given IT_COMMON_VALUE heap entry
	jmp	short Entry_Moved_Cont
Upd_Stk_Ptrs_Cont:
	DbAssertRelB  cl,z,IT_VAR,RT,<B$IHeapEntryMoved: cl == IT_VAR expected>
	call	AdjustVarTable		;update backpointers to any string 
					;descriptors or string array descriptors
					;in given IT_VAR heap entry
	jmp	short Entry_Moved_Cont

;***
;BdCompress - Compress a Runtime Heap entry
;Purpose:
;	Call B$LhRealloc to reduce cbPhysical to cbLogical for a Bd whose
;	pb field is at a given location.
;	Called via B$LHForEachEntry by BdCompressAll.
;
;	Note that variable tables are handled specially - - they're trimmed
;	back so that they keep up to VAR_EXTRA free space at the end of the
;	table to maximize the change of CONTinuing after variables are added.
;Entry:
;	BX = pointer to owner of a local heap entry - - - for interpreter
;		buffers, that amounts to a pointer to the 'pb' field of the
;		owning bd.
;	DL = heap entry type.
;Exit:
;	none.
;Preserves:
;	CX,SI
;Exceptions:
;	none.
;
;***************************************************************************
cProc	BdCompress,<NEAR,NODATA>
cBegin	BdCompress
	DbChk	Heaps			;ife RELEASE & checking enabled, check
					;	Local & Far Heaps for problems
	test	dl,IT_M_INTERP		;is this an interpreter buffer?
	jz	BdCompress_Exit

	dec	bx			;turn bx into a real pBd (for cmp below)
	dec	bx

	mov	ax,[bx.BD_cbLogical]
	cmp	dl,IT_VAR		;is this a variable table?
	jnz	BdCompress_Cont		;  brif not
	
	add	ax,VAR_EXTRA		;want to have up to VAR_EXTRA bytes
					;  left in each var table to improve
					;  chances of user adding a few 
					;  variables and still CONTinuing
	cmp	ax,[bx.BD_cbPhysical]
	jae	BdCompress_Exit		;brif cbPhysical <= size we want buffer
					;  to be - - - leave buffer alone
BdCompress_Cont:
	lea	dx,[ps.PS_bdpDst.BDP_cbLogical]
	cmp	bx,dx			;brif not special parser buffer that 
	jnz	BdCompress_Cont1	;  must always have a minimal amount

	cmp	ax,CB_PCODE_MIN		;never trim below this minimum
	ja	BdCompress_Cont1	;brif cbLogical > Minimum required

DbAssertRel [bx.BD_cbPhysical],ae,CB_PCODE_MIN,RT,<BdCompress:Parser buffer is too small>
	mov	ax,CB_PCODE_MIN
BdCompress_Cont1:
	push	cx			;preserve for caller
	push	si			;preserve for caller
	mov	[bx.BD_cbPhysical],ax	;set new desired cbPhysical
	mov	si,[bx.BD_pb]		;pointer to start of data in buffer
	call	B$LHREALC		;reduce entry to cbLogical size
					;  MUST succeed and CANNOT cause
					;  heap movement, because it is either
					;  reducing entry size or doing nothing

	pop	si
	pop	cx
BdCompress_Exit:
cEnd	BdCompress

;***
;BdCompressHeap - Compress all Runtime Heap entries in currently active heap
;Purpose:
;	Same as BdCompressAll (below), but only crunches bd's in the currently
;	active heap (either the local heap or the variable heap).
;Input:
;	none.
;Output:
;	none.
;Modifies:
;	no permanent registers.
;Exceptions:
;	Chance of string space corrupt.
;***************************************************************************
cProc	BdCompressHeap,<NEAR,NODATA>
cBegin
	mov	cx,RTOFFSET BdCompress
	call	B$LHForEachEntry	;compress all bd's down to cbLogical
					;  (effect is to create free blocks
					;   out of extraneous space in bd's)
	cmp	[b$fVarHeapActive],FALSE
	jnz	BdCompressHeap_Exit	;don't compact the variable heap
					;  only runtime init. does that - - 
					;  B$NHCPCT assumes local heap active.
	call	B$NHCPCT		;compact Local Heap and String Space
BdCompressHeap_Exit:
	DbChk	Heaps
cEnd
;***
;BdCompressAll - Compress all Runtime Heap entries
;Purpose:
;	To increase the speed of BdGrow, we keep a little free
;	space at the end of each heap entry.  When the program
;	begins execution, this routine is called to
;	release all this space and compact interpreter-specific entries
;	to the top of the Runtime Heap. 
;	Note that this routine is ONLY called by interpreter code, 
;	and never by the shared-runtime code.
;
;	NOTE: after this operation is complete, the 'pbCurrent' field in
;		bdp's will still be correct and useable, assuming that
;		such pointers weren't pointing beyond cbLogical ...
;Input:
;	none.
;Output:
;	none.
;Modifies:
;	no permanent registers.
;Exceptions:
;	Chance of string space corrupt.
;
;***************************************************************************
cProc	BdCompressAll,<PUBLIC,FAR,NODATA>
cBegin
	call	BdCompressHeap		;compress the active heap
	call	B$TglHeapSpt		;activate the other heap
	call	BdCompressHeap		;compress the active heap
	call	B$TglHeapSpt		;reactivate the originally active heap
cEnd

;***
;BdAdjust(pBd)
;	This routine takes a pointer to a bd as a parameter and assumes
;	that an adjustment factor (the bd is being moved) is in DI.
;	It calls a heap manager routine which updates the entry backpointer,
;	if the bd is an owner (i.e., if the pb field is not NULL).
;Entry:
;	pBd - pointer to a bd that's being moved
;	DI contains adjustment factor it's being moved by
;Exit:
;	none.
;Modifies:
;	none. (no permanent registers)
;Exceptions:
;	if anything wrong with heap entry for this bd, can end up calling
;	the non-trapable "String Space Corrupt" error.
;***************************************************************************
cProc	BdAdjust,<PUBLIC,FAR,NODATA>
	parmW	pBd
cBegin	BdAdjust
	mov	bx,[pBd]
	mov	ax,[bx.BD_pb]
	cmp	ax,NULL
	jz	BdAdjust_Done

	call	B$ILHADJ		;get heap manager to do adjustment
BdAdjust_Done:
cEnd	BdAdjust
	page


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

;***
;BdAlloc - Allocate a Runtime Heap entry
;Purpose:
;	Allocate an Interpreter-specific Heap entry from the Runtime
;	Heap.
;	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.
;	NOTE: current heap manager interface demands that the owner-to-be
;	should not be subject to heap movement (i.e., not in heap, or
;	heap locked). 
;Entry:
;	parm: bd *pbdOwner - points to owner-to-be of new heap entry
;	parm: ushort cbSize - number of bytes needed
;if	NOT FV_LMEM
;	parm: char interpType - type of interp. table (IT_VALUE etc)
;endif
;Exit:
;	if entry was successfully allocated:
;	   pbdOwner->cbLogical = cbSize
;if	FV_LMEM
;	   pbdOwner->ppb = ptr to ptr to new heap entry (and is now owner)
;else
;	   pbdOwner->pb = pointer to new heap entry (and is now a heap owner)
;	   pbdOwner->cbPhysical = cbSize
;endif
;	   [AX] = TRUE (non-zero)
;	else
;	   [AX] = FALSE (0) (Out of memory)
;Modifies:
;	none  (NOTE: DOES modify ES)
;
;***************************************************************************

⌨️ 快捷键说明

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