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

📄 ssbos.asm

📁 Microsoft MS-DOS6.0 完整源代码
💻 ASM
📖 第 1 页 / 共 3 页
字号:
page	49,132
	TITLE	ssbos - scan support for begin of statement opcodes
;***
;ssbos - scan support for begin of statement opcodes
;
;	Copyright <C> 1986, Microsoft Corporation
;
;Purpose:
;
;   This module contains scan dispatches for label definitions and
;   label reference opcodes.
;
;   Labels refer to line numbers or alpha-numeric labels.  There is
;   no difference notable in the scanner.
;
;   The scanner is responsible for the following tasks:
;
;	1. Reference scope.  For each label reference opcode thereis only one
;	   scope in which the label may be legally defined.  Scope checking is
;	   simply a matter of searching the reference chain in the appropriate
;	   link list.
;	   NOTE: The main level code must be scanned first.  This allows
;	   immediate binding without fixups whenever a procedure references
;	   a label at the main level.  The main level may never reference a
;	   procedure label.
;
;	2. Binding.  Label references are bound to the text table
;	   in SS_EXECUTE state only.  In other states, they are bound to the
;	   name table.
;	   Binding involves replacing the oName in the label reference with
;	   the oTx for the label.  References to the main level from within
;	   a procedure are never ambiguous, so no oPrs or other flag is needed.
;
;	   Backward references are bound simply by searching
;	   the label chain.
;
;	   Forward references are handled by linking the
;	   reference into the label chain at the definition point.  The
;	   backward pointer is identifiable when scanning the label definition
;	   opcodes, and the reference is bound when the definition is bound.
;
;	3. Debinding.  Debinding label references is done in a separate pass
;	   on the text at descan time.
;
;	4. Duplicate label detection. Duplicate labels are detected by the
;	   text manager.
;
;
;****************************************************************************

	.xlist
	include 	version.inc
SSBOS_ASM = ON
	IncludeOnce	context
	IncludeOnce	optables
	IncludeOnce	opcontrl
	IncludeOnce	opstmt
	IncludeOnce	pcode
	IncludeOnce	qbimsgs
	IncludeOnce	scanner
	IncludeOnce	ssint
	IncludeOnce	txtmgr
	IncludeOnce	ui
	IncludeOnce	variable
	.list

assumes es,nothing
assumes ds,DATA
assumes ss,DATA
assumes cs, SCAN

sBegin	DATA
	externW	pSsCOMcur		;defined in SsDeclar.asm
	oRsExpected DW	?		;expected oRs when binding labels
	fRestoreLab DB	0		;non-zero if binding RESTORE
sEnd	DATA

extrn	exNoList1:near
extrn	exStRestore1:near

extrn	exStDefFn:near


sBegin	SCAN

DWBOL	MACRO	cSpace
	DWEXT	exBol&cSpace
	endm

CBOL_EXECS EQU 25  ;number of opBol executors (for indentation 0..24)
mpBol	label	word
cSpace	=	0
	REPT	CBOL_EXECS
	DWBOL	%cSpace
cSpace	=	cSpace+1
	endm


;***
;Ss_BolLabDef,Ss_LabDef - scan Bos opcode varients
;Purpose:
;	Scan general begin of statement opcodes.
;	This task is simply opcodes to executors and copying any operands.
;
;	Update the begin of statement pointer, and reset scanner flags.
;
;	Update the pointer to the pcode following begin of statement.
;	This pointer is used to isolate DIMs for $STATIC arrays.  See the
;	comments in exarray.asm.
;
;	Scan label definition varients.
;
;	Label definition tasks include:
;	1. If link points to code on emit side then the link is to a label
;	   reference that has not yet been bound (forward reference problem).
;		bind ref at link side
;		pick up ref in link side item
;		goto 1 (there may be more than one forward ref to this label)
;	2. maintain the link list.
;
;	A link points to an opcode that has an operand which is a scanned
;	reference if the low bit is set.
;
;	Label links point to the opcode that has a link field of the next
;	label, or are UNDEFINED.  Label offsets to the unscanned source are
;	not relocated when text expands.
;
;	The label list control structure is in struc TXLNK at [SsLinkCtl].
;	It contains fields as follows:
;	TXLNK_LabDefNext - offset of next label definition
;			   (unrelocated for expansion)
;	TXLNK_LabDefLast - offset of last bound label definition
;
;Input:
;	ax	= opcode
;	bx	= opcode * 2
;	es:si	= source code address of operands (if any)
;	es:di	= destination code address.
;Output:
;	si/di	updated
;Modifies:
;	ax,bx,cx,dx modifies
;***********************************************************************
SsProc	LabDef
	mov	dx,di			;Preserve the emit address
	call	EmitExCopyOps		;Emit executor and operand(s)
	jmp	short LabDef		;Now handle the label definition

SsProc	BolLabDef,rude
	mov	dx,di			;Preserve the emit address
	call	Bos0_0Com		;Process standard BOS issues
LabDef:
	xchg	dx,di			;Preserve next emit address
					; and move to link field on emit side
	mov	cx,di			;Save oTx for forward reference linking
	inc	di			;Move to link field on emit side
	inc	di
	mov	bx,di
	mov	ax,PTRTX[bx]		;Load link operand of current label

;Reenter here if we fixed up some previous forward ref.
BosForwardRefChk:
	cmp	ax,UNDEFINED		;Test for end of link list
	jz	NotForwardRefFixup	;End of list - can't be a fixup
	test	ax,1			;Is a link to a forward reference?
	jz	NotForwardRefFixup	;This is not a previous forward ref.

;Fix up the previous forward ref
	dec	ax			;Remove link flag
	mov	bx,ax
	mov	ax,PTRTX[bx]		;Load link from referenced location
	mov	PTRTX[bx],cx		;Bind to beginning of BOL varient
	jmp	short BosForwardRefChk	;Check if this is another old forward

NotForwardRefFixup:
	mov	bx,[SsLinkCtl]		;Address of TXLNK control struc
	mov	[bx].TXLNK_LabDefNext,ax;oTx for next label before any
					; expansion is accounted for.
	mov	cx,di
	xchg	cx,[bx].TXLNK_LabDefLast;Address of last label link
	mov	bx,cx
	jcxz	BolFirst		;This is the first defined label.
					; as oTxLastLabDef starts at 0
	mov	PTRTX[bx],di		;Link last label to this one
BolFirstLabDefCont:			;Continue here after handling first
					; label definition
	or	al,1			;set low bit on emitted side to
					;specify end of Bound label chain
	mov	PTRTX[di],ax		;Emit link to next label def
	dec	di			;Back to BOL executor address
	dec	di
	jmp	short BolCom		;Handle general BOL considerations


;Here if this is the first label definition encountered.
BolFirst:
	mov	txdCur.TXD_otxLabLink,di;Update text descriptor to point to
					; the first label in the link chain
	jmp	short BolFirstLabDefCont;Continue label definition handling


;***
;Ss_Bos,Ss_Bol,SsEot,Ss_0_0 - Scan opcodes with no args, emit nothing, executor in mpOpExe
;Purpose:
;	Scan opcodes which:
;	1. have no arguments (consume nothing)
;	2. emit no value
;	3. have no special operand processing.
;	   (operand count is in mpOpAtr)
;	4. executor is in mpOpExe
;
;	For example, this includes:
;	opBos, opBol, opBolSp, opBolCont, opWatch, opInclude
;
;Input:
;	ax	= opcode
;	bx	= opcode * 2
;	es:si	= source code address of operands (if any)
;	es:di	= destination code address.
;Output:
;	si/di	updated
;Modifies:
;	ax,bx,cx,dx modified
;***********************************************************************
SsProc	Bos,rude
	push	[ScanRet]		;Set return address
	DJMP	jmp SHORT Bos0_0Com	;Continue through shared BOS code

SsProc	Eot,rude
	test	[SsFlags],SSF_ScanAndExec
	jnz	ScanExExitJ
	mov	[ScanRet],scanOFFSET ScanExit	;Terminate scan dispatching
	jmp	short SsBol			; after performing BOL work

ScanExExitJ:
	jmp	SsScanExExit

SsProc	BolEmit,rude
	jmp	short SsBol

SsProc	Bol,rude
	mov	al,es:[si-1]		;Get high byte of opcode
	and	ax,HIGH (not OPCODE_MASK) ;Get count of spaces * 2
	xchg	ax,bx			;Preserve opcode*2 in bx
.errnz	OPCODE_MASK - 3FFH
	shr	bx,1			;cSpace is shifted left one bit
DbAssertRel	bx,be,2*CBOL_EXECS,SCAN,<Ss_Bol: cSpace too large>
	mov	bx,[bx].mpBol		;Get appropriate executor
	xchg	ax,bx
SsBol:
	mov	dx,di			;Preserve BOL executor address
	call	Bos0_0Com		;Handle end of statement
	xchg	dx,di			;Back to BOL executor, preserving next emit addr
BolCom:
	mov	ax,[SsLineCount]
	inc	ax
	mov	[SsLineCount],ax
	test	al,LineUpdate-1	;Time to update line count on screen?
	jnz	NoLineUpdate
	push	dx
	cCall	UpdStatusLn,<ax>
	GETSEGTXTCUR		
	pop	dx
NoLineUpdate:
	test	SsFlags,SSF_If	;Is there special per line work?
	jnz	BolControlBind	
BolComX:
	mov	di,dx		;Back to next emit address
	jmp	[ScanRet]

;BolControlBind
;Purpose:
;	Bind control structure frames found on the stack.
;
;	This routine binds all non-block, non-label IF and ELSE entries
;	to this BOL.
;
;	Label varients of IF are discarded.  They were on the stack in order
;	to allow the scanner to correctly check IF/ELSE scoping.
;
;	The label and nop varients of ELSE cause no stack entry.
;
;	Block varients of ELSE and IF are popped by the matching block type
;	opcodes only.

BolDoBind:
	pop	bx		;Get IF operand address from frame
	mov	[SsBosStack],sp ; SP at BOS
	pop	cx		;throw away block if Brach chain

	test	ax,STYP_Lab	;Label IFs and ElseNops are popped, but don't require binding
	jnz	BolControlBind	;Label IF frame - go check next stack entry

	mov	PTRTX[bx],di	;Store address of this BOL

BolControlBind:
	pop	ax			;Get frame type
	testx	ax,STYP_If+STYP_Else	;Bind If and Else
	jz	BolControlBindX
	testx	ax,STYP_Block		;Don't bother with block If/Else
	jz	BolDoBind		;Not Block IF or ELSE - perform the binding
BolControlBindX:
	push	ax			;Replace frame type
	and	SsFlags,not SSF_If	;Clear IF flag
	jmp	short BolComX		;exit through BolCom


;Bos0_0Com
;Purpose:
;	Handle standard BOS issues
;
;	SsCbFrameTemp is the number of bytes needed for the statement
;	just scanned.  It is used to keep a high water mark for the
;	number of temps needed by any statement.  This count is zeroed
;	in preparation for the next statement.
;
;	If we CAN continue, then there may be oTx's in the stack, in
;	MrsCur, etc., that need to be updated to account for text
;	expansion during scan.  References to these oTexts have been
;	marked with opNoList1, whose operand points to the reference.
;	The scan routine for opNoList1 updates the reference to point to
;	the current emit address.  However, a subsequent insertion (for
;	coercion, for example) could cause the point being referenced to
;	move again.  For this reason, the opNoList1 is left in the pcode
;	(as exNoList1) and two flags are maintained in SsBosFlags.
;	If both SSBOSF_Inserted and SSBOSF_PcUpdate are true, then an
;	insertion might have moved an opNoList1.  This routine will search
;	for exNoList1 and re-patch the references.
;
;	If a COMMON statement was being scanned, then there is a frame
;	on the stack with the owners of the Type and Value tables.  These
;	owners are moved back to the COM structure in the COMMON block
;	table.
;
;NOTE: This routine is fallen into by Ss_BOS and is also called.
;Input:
;	Standard Scan entry convention.
;Preserves:
;	dx
Bos0_0Com:
	push	di			;Save current emit oTx
	call	EmitExCopyOps		;Handle 0 consume 0 emit issues

;Report delayed Argument Count Mismatch errors
	mov	ax,UNDEFINED
	xchg	ax,[SsDelayCnt]		;Get count, reset to -1
	inc	ax			;Any errors?
	jz	UpdateTemp
	push	si
	mov	si,[SsDelayLoc]		;Source oTx of error
	mov	ax,[SsDelayErr]
	call	SsError
	pop	si

UpdateTemp:
;Update count of temporaries
	xor	ax,ax
	xchg	ax,[SsCbFrameTemp]	;Get count of temps needed
	mov	bx,dataOFFSET prsCur.PRS_cbFrameTemp
	test	byte ptr [grs.GRS_oRsCur+1],80H	;MRS?
	jnz	CheckTemps
	mov	bx,dataOFFSET mrsCur.MRS_cbFrameTemp
CheckTemps:
	cmp	ax,[bx]			;Using more temps?
	jb	FewerTemps
	mov	[bx],ax 		;Set new max temp count
FewerTemps:

;Now check for PC update
	test	[SsBosFlags],SSBOSF_Inserted + SSBOSF_PcUpdate
	jz	NoPcUpdate
	jpo	NoPcUpdate		;If only 1 set, no work
;Have inserted pcode on line with PC Update pcode
	push	dx
	mov	bx,[SsOTxBos]		;Start of previous line
UpdateLoop:
	mov	ax,codeOFFSET exNoList1 ;pc update executor
	call	SsFindOpNoList1
	jc	ExitPcUpdate
	mov	ax,PTRTX[bx-2]		;Get offset of reference
	xchg	ax,bx
	mov	[bx],ax			;Adjust to new location
	xchg	ax,bx
	jmp	UpdateLoop

ExitPcUpdate:

⌨️ 快捷键说明

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