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

📄 context.asm

📁 [随书类]Dos6.0源代码
💻 ASM
📖 第 1 页 / 共 5 页
字号:
	TITLE	context.asm - context manager

;***
;context.asm - context manager for the Quick Basic Interpreter
;
;	Copyright <C> 1986, 1987 Microsoft Corporation
;
;Purpose:
;   -  Creation and Deletion of entries in the Module and Procedure Register Set
;       tables.
;   -  Swapping module and procedure register sets between the global table
;	of Rs's and the static current working register sets 'mrsCur' and
;       'prsCur'.
;
;   Note: static handling of Procedure Register Sets is performed by this
;		module; frame (per invocation) handling is performed by
;		the Procedure Manager.
;
;
;******************************************************************************

	.xlist

	include version.inc
	CONTEXT_ASM = ON
	includeOnce	architec
	includeOnce	context
	includeOnce	conint
	includeOnce	heap
	includeOnce	names
	includeOnce	pcode
	includeOnce	qbimsgs
	includeOnce	rtinterp
	includeOnce	parser
	includeOnce	sb			
	includeOnce	scanner
	includeOnce	txtmgr
	includeOnce	ui
	includeOnce	util
	includeOnce	variable
	includeOnce edit			

	.list

	assumes CS,CP
	assumes DS,DATA
	assumes SS,DATA
	assumes ES,NOTHING


sBegin	DATA
	globalB	conFlags,F_CON_StaticStructs	;static bit flags
	staticB	fCouldBeBogusPrs,FALSE		;TRUE if there's a possiblity of
	staticW	oRsTest,UNDEFINED		;For use in ValidORs
	globalW	oRsDupErr,0			;MrsMake and PrsMake tell
						; caller duplicate oRs
	globalW	oPrsFirst,UNDEFINED		; head of prs chain in tRs
	staticW	oFreePrsFirst,UNDEFINED		; head of free prs chain
	staticW	oFreeMrsFirst,UNDEFINED		; head of free mrs chain

sEnd	DATA

	extrn	B$ClearRange:FAR		;clears all owners in given rg



sBegin CP

;==============================================================================
;Notes On mrs and prs structures:
;	There is a single global table which contains both mrs and prs
;	structures. The first entry in this table MUST be the global mrs
;	(code exists which assumes the oMrs for the global mrs is OMRS_GLOBAL).
;	We also assume that, if there is an empty unnamed mrs, it is the 
;	very next struct in the table after the global mrs.
;
;	All mrs valid mrs entries are chained from this entry via the
;	oMrsNext entry; UNDEFINED marks the end of the chain.
;	Prs's are similarly chained together, with the global 'oPrsFirst'
;	pointing to the first prs.   It is NOT safe to assume that these
;	chains relate to table position; the only safe way to walk the
;	Rs table in any way is via the appropriate chain.
;
;	Table entries are fixed in place; oRs/oMrs/oPrs's are known and
;	saved outside of this component, so an mrs or prs can never move
;	within this structure. If an entry is discarded, it is added to
;	a free chain, for later re-use. Since mrs and prs structs are of
;	different size, there are two free chains; oFreePrsFirst and
;	oFreeMrsFirst are the head pointers for these chains.
;
;	Note that when an mrs or prs is 'active' (i.e., copied to mrsCur/
;	prsCur) the copy in the table should not be referenced or modified
;	but that entry remains linked in place. Care should be taken when
;	updating an Rs chain to consider the active prs and/or mrs, i.e.,
;	mrsCur and prsCur are not and cannot be linked in an rs chain.
;	
;	The actual first entries in the mrs & prs structs are the count of
;	frame temps and frame vars allocated for each instance of that
;	module or procedure. There are definite dependancies on the fact
;	that these are in the same spot in the mrs & prs structs.
;
;	For all prs's, there is guaranteed to be a name table entry for the 
;	prs name. This eliminates some OM_ERR checking when obtaining the oNam 
;	of a prs (generally via FieldsOfPrs).
;
;	At execution time, the heap-update & block copy time required by the
;	normal context switching code is too slow for CALL speed. For this
;	reason, whenever program execution is started, DisStaticStructs is
;	called to set a static flag and deactivate mrsCur, prsCur, and txdCur.
;	At execution time (only), a couple of grs fields are used to allow
;	for quickly fetching the segment address of the current text table.
;	Note that whenever this flag (F_CON_StaticStructs) is reset (FALSE), 
;	the mrsCur and prsCur structures contain garbage; only the oMrsCur, 
;	oPrsCur, and oRsCur fields in grs can be used to access current 
;	context information.
;
.errnz	SIZE MRS AND 1
.errnz	SIZE PRS AND 1
;	The two assertions above are based on the procedure manager depending
;	on an oRs always being an even number (so the low bit can be used
;	as a boolean in a special case). For oRs's to always be even, mrs
;	and prs structs must in turn both be even.
;	
;==============================================================================


;##############################################################################
;#									      #
;#			  Initialization Functions			      #
;#									      #
;##############################################################################

sEnd	CP				;initialization code goes in RARE seg
sBegin	RARE
	assumes CS,RARE

;***
;InitContext()
;
;Purpose:
;    This function is called once during BASIC initialization to initialize:
;     - the global register set (grs)
;     - the Rs table (grs.bd[l]Rs), mrsCur, and the global mrs via MrsMake
;Entry:
;	none.
;Exit:
;	grs, mrsCur initialized.
;	ax = 0 if no error, else		[18]
;	ax = standard error code.		[18]
;	PSW flags set up based on an OR AX,AX	[18]
;*******************************************************************************
cProc	InitContext,<NEAR,PUBLIC,NODATA>	
cBegin	InitContext
	mov	ax,dataOFFSET grs	;ax == pointer to global 'grs' struct
	mov	bx,SIZE GRSTYPE		;bx == size of 'grs' struct
	mov	cx,GRS_CB_ZERO_INIT	;cx == cb @ start of grs to 0-fill
	push	ax			; parm to ZeroFill
	push	cx			; parm to ZeroFill

	shr	bx,1			; convert cbStruct to cwStruct
	cCall	FillUndef,<ax,bx>	; fill whole struct with UNDEFINED
	cCall	ZeroFill		; fill first 'cbZeroes' with zeroes

	PUSHI	ax,<dataOFFSET grs.GRS_bdlDirect>
	PUSHI	ax,CB_PCODE_MIN 	;it must never be < CB_PCODE_MIN bytes
	PUSHBDL_TYPE  pgtypEBPcode,ax	; pass sb type for EB version
	call	BdlAlloc		;allocate direct mode buffer (far heap)
	or	ax,ax
	DJMP	jz	OM_Err_In_Init	
	PUSHI	ax,<dataOFFSET grs.GRS_bdRs>
	PUSHI	ax,0
	PUSHI	ax,IT_MRS
	call	BdAlloc 		;allocate table of register sets
	or	ax,ax
	jz	OM_Err_In_Init

	PUSHI	ax,OGNAM_GMRS		; make global module
	PUSHI	ax,<100h * FM2_File>

	call	far ptr MrsMake		; make initial (untitled) mrs 
	or	ax,ax			
	jnz	InitContext_Exit	; return error code to caller

	call	far ptr MakeInitMrs	;make initial mrs, ax=errCode
	; just pass retval to caller for non FV_QB4LANG case
	or	ax,ax			
	jnz	InitContext_Exit	

	PUSHI	ax,<dataOFFSET grs.GRS_bdtComBlk>
	PUSHI	ax,0
	PUSHI	ax,IT_COMMON_BLOCK
	call	BdAlloc			;allocate table of common blocks
	or	ax,ax
	jz	OM_Err_In_Init

	PUSHI	ax,UNDEFINED
	call	MakeCommon		;allocate table(s) for blank common
	inc	ax			;UNDEFINED returned if OM error
	.errnz	UNDEFINED - 0FFFFH
	jz	OM_Err_In_Init

	DbAssertRel ax,z,1,RARE,<InitContext: Unnamed block not at offset 0>
	mov	[grs.GRS_fDirect],al	;so UserInterface() thinks opEot was
					;from direct mode buffer
	sub	ax,ax			; retval; 0 == 'no errors'
InitContext_Exit:			
	or	ax,ax			
cEnd	InitContext

OM_Err_In_Init:
	mov	ax,ER_OM		
	jmp	short InitContext_Exit	

sEnd	RARE
sBegin	CP
	assumes CS,CP



;##############################################################################
;#									      #
;#	  	Context Manager Functions Common to mrs's and prs's	      #
;#									      #
;##############################################################################

;***
;InitStruct
;
;Purpose:
;	This function is designed to initialize a structure by filling
;	it partly with UNDEFINED words, and partly with zeroes. The input
;	pointer is to the start of the structure, and the input count
;	is for the number of zeroes to fill in at the beginning of the
;	structure, after first filling the entire structure with UNDEFINED.
;	The result is a structure with the first cbZeroes bytes initialized
;	to zero, the remainder filled with UNDEFINED.
;
;	Made NEAR in CP (moved from RARE) as part of revision [17].
;Entry:
;	ax = pStruct -	pointer to the start of the structure.
;	bx = cbStruct -	count of bytes in the structure
;	cx = cbZeroes -	count of bytes to fill (@ start of struct) w/0
;Exit:
;	none.
;Uses:
;	none.
;Exceptions:
;	none.
;*******************************************************************************
InitStruct PROC	NEAR
	push	ax			;parm to ZeroFill
	push	cx			;parm to ZeroFill

	shr	bx,1			;convert cbStruct to cwStruct
	cCall	FillUndef,<ax,bx>	;fill whole struct with UNDEFINED
	cCall	ZeroFill		;fill first 'cbZeroes' with zeroes
	ret
InitStruct ENDP

;***
;MrsTableEmpty - see if there are any mrs entries
;
;Purpose:
;	This function is called to check to see if there are any active 
;	mrs entries in tRs.
;	We ignore any text mrs's, i.e., if the only mrs's in the table are for 
;	text objects (rather than for modules), say that the table is empty. 
;	Also ignore the global mrs.
;
;	NOTE: it is assumed that this routine will only be called when there
;		is no current entry, i.e., grs.oMrsCur is UNDEFINED. 
;
;Entry:
;	es set to rs table segment
;Exit:
;	PSW.Z set if table empty, clear if it has one or more active entries.
;	if table not empty, bx = oMrs for active entry.
;Uses:
;	none.
;Exceptions:
;	none.
;*******************************************************************************
cProc	MrsTableEmpty,<NEAR>,<ES>
cBegin	MrsTableEmpty
	GETRS_SEG   es,bx,<SIZE,LOAD>	
	mov	bx,OMRS_GLOBAL		; es:bx points to the global mrs
					;  (ignore the global mrs)
	RS_BASE  add,bx 		;add base of tRs to bx
Walk_Loop:
	mov	bx,PTRRS[bx.MRS_oMrsNext] ;advance to next mrs
	inc	bx			;end of chain?
	.errnz	UNDEFINED - 0FFFFH
	jz	Exit_Table_Walk		;  brif so - - - no module mrs's found
	dec	bx

	RS_BASE  add,bx 		;add base of tRs to bx
	test	BPTRRS[bx.MRS_flags2],FM2_Include
	jnz	Walk_Loop		;brif found an include file - ignore
	test	BPTRRS[bx.MRS_flags2],FM2_NoPcode
	jnz	Walk_Loop		;brif active mrs found for a non-file 
					;  mrs (ignore it)
	RS_BASE  sub,bx 		;subtract base of tRs from bx
	or	sp,sp			;clear PSW.Z
Exit_Table_Walk:
cEnd	MrsTableEmpty

;***
;RsTableSearch - search the Rs table
;
;Purpose:
;	This function is shared by mrs-specific and prs-specific code to
;	search for a matching structure entry. 'procType' (ax input value) 
;	indicates whether we're to search the mrs or prs chain; in addition, 
;	it cues us in on additional search logic needed in the case we're to 
;	search for a DEF FN (must then also match oMrs and oTyp).
;	
;	[10] This shared routine is only possible so long as the ogNam fields
;	[10] are in the same place relative to the start of prs & mrs structs,
;	[10] and the ogNam field of an valid prs or mrs entry can never be 
;	[10] UNDEFINED (which is the signal that an entry is active,
;	[10] and is thus a 'hole' in the table).
;	[10] Also, note that a special case (mrs chain only) exists where
;	[10] an "untitled" entry can exist, whose ogNam field will be 
;	[13] OGNAM_UNNAMED.
;
;	[10] Note that the global mrs has an ogNam that can't possibly be a
;	[10] valid ogNam, yet is not UNDEFINED, so no tMrs search should ever 
;	[10] 'find' the global mrs unless it's specifically being looked for
;	[10] but it shouldn't be, since it ALWAYS exists, and is always at 
;	[10] offset 0.
;
;	NOTE: This routine assumes that names are unique - - - a simple
;	NOTE: comparison is done to see if they match, so any differences
;	NOTE: w.r.t. file paths will cause no match to occur. Case Sensitivity
;	NOTE: is, however, ignored in the comparison (i.e., 'a' == 'A' for
;	NOTE: the search).
;
;Entry:
;       al == procType - If this is PT_NOT_PROC, then the mrs chain is searched
;			otherwise, it must be PT_SUB, PT_FUNCTION, or PT_DEFFN.
;			PT_SUB and PT_FUNCTION use the same search logic as
;			PT_NOT_PROC, but for PT_DEFFN, additional matching logic
;			is used.
;       dl == oTyp, IF ax == PT_DEFFN; only used in the case we're searching
;			the prs table for a DEF FN. If ax is not PT_DEFFN,
;			then dl is undefined, and not used in search.
;			Only used for FV_QB4LANG versions.
;	es set to rs table segment (if FV_FAR_RSTBL)
;	ogNam -	Name of entry to search for (ogNam field).
;			If ogNam == OGNAM_UNNAMED, then we know we're searching
;			for an entry (in the mrs chain) whose ogNam entry is 
;			also OGNAM_UNNAMED.
;	NOTE: it is assumed on entry that there is no 'current' entry for
;		the table being searched, i.e., if the prs chain is to be 
;		searched, it is assumed that grs.oPrsCur == UNDEFINED - - - 
;		therefore, callers of this routine should call 
;		Mrs/PrsDeActivate first.
;	NOTE: it is assumed by at least one caller of this routine that it
;		cannot trigger any heap movement.
;Exit:
;	AX == offset into the appropriate table if the search is successful,
;		or UNDEFINED if it is not.
;	BX == if AX is UNDEFINED, then this is an offset into the 
;		appropriate table to the last 'hole', or UNDEFINED if there 
;		are no holes in the table.
;		If, however, AX is a table offset, BX is a pointer to the
;		found entry.
;	ES will be set to the tRs seg (if FV_FAR_RSTBL)
;Uses:
;	none.
;Exceptions:
;	none. 
;*******************************************************************************
cProc	RsTableSearch,<NEAR,NODATA>,<SI,DI>
	parmW	ogNam			
	LocalB	oTyp
	LocalB	procType
	LocalW	oRsFree
cBegin	RsTableSearch
	mov	[oTyp],0
	mov	[procType],al
	mov	di,[ogNam]		
	mov	bx,[oFreePrsFirst]	;assume we're searching prs chain
	cmp	al,PT_NOT_PROC		;Should we search the prs chain?
	jnz	Search_tPRS		;  brif so

	DbAssertRel grs.GRS_oMrsCur,e,UNDEFINED,CP,<grs.oMrsCur not UNDEFINED in RsTableSearch in context.asm>
	mov	si,OMRS_GLOBAL		; offset to the global mrs
	mov	bx,[oFreeMrsFirst]
	jmp	short	Search_Table

Search_tPRS:
	DbAssertRel grs.GRS_oPrsCur,e,UNDEFINED,CP,<grs.oPrsCur not UNDEFINED in RsTableSearch context.asm>
	mov	si,[oPrsFirst]
	cmp	al,PT_DEFFN		;are we searching for a DEF FN?

⌨️ 快捷键说明

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