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

📄 ssbos.asm

📁 Microsoft MS-DOS6.0 完整源代码
💻 ASM
📖 第 1 页 / 共 3 页
字号:
;	was in a SUB or FUNCTION.  If the label was found and was
;	in a module level text table, oRsExpected is compared against
;	the oRs of the label def to ensure that illegal binding
;	across DEF FN boundaries has not occurred.
;
;	The actual binding occurs as follows:
;
;	- If the oRsExpected text table is the same as the current emit
;	  text table, then the label links are searched from the scanner
;	  source address to the end of the pcode.
;
;	  If found in this range, link the emit address into the label list.
;	  This label reference will be bound at label definition time.
;	  The low bit of the label definition link is set to indicate a link
;	  in the label definition list is pointing to an unbound reference.
;
;	- If not found in the step above, or if the text table we are
;	  searching is not the emit text table, then search from the
;	  root of the label chain in the appropriate text table for a
;	  definition of the referenced label.
;
;	  If the search text table is the same as the emit text table,
;	  the search terminates at the scanner emit address.
;
;	  If the label is found in this search, bind the label.  Not finding
;	  the label is declared as an error.
;
;	RESUME 0 , ON ERROR GOTO 0, and ON <event> GOSUB 0 have the special
;	label oNam UNDEFINED.  This label is emitted as UNDEFINED.
;
;
;Entry:
;	ax - oRs of expected scope (LabelBindCom, LabelBind)
;	bx - oTx of label chain start (LabelBind)
;	cx - count of labels to bind
;	dx - test seg containing label chain (LabelBind)
;	es:si - start of label oNam list to bind.
;	es:di - emit address for bound label oTx.
;Exit:
;	source and emit addresses advances appropriately.
;Exceptions:
;	Label not defined.

; CX = count of labels to bind

public	LabelBindCur			;Entry point to bind a label to
LabelBindCur:				;current context
	mov	ax,grs.GRS_oRsCur	;expected same scope

	    test    txdCur.TXD_flags,FTX_mrs	;are we in a module text table?
	    jnz     LabelBindCom		;brif so

	or	al,1			;set low bit to indicate that we are
					;binding to SUB or FUNCTION


;	AX = oRs of expected scope (low bit set if binding TO a SUB/FUNCTION)
;	CX = count of labels to bind

;	Common entry for LabelBindMrs

LabelBindCom:
	GETSEG	dx,[txdCur.TXD_bdlText_seg],,<SIZE,LOAD> ;[3] set text table to current
					; text tbl in case we are already 
					; at module level
	mov	bx,txdCur.TXD_otxLabLink ;get cur label link chain


;At this point, DX = text table to bind to, BX = start of label def chain
;		AX = oRs of expected scope, CX = count of labels to bind
;		ES:SI = pcode addr of oNam/ref label ref list to be bound

;	Common entry for LabelBindMrs

LabelBind:
	mov	oRsExpected,ax		;remember expected scope
LabelBindLoop:
	push	cx			;save label count
	LODSWTX 			;get label oNam
	cmp	[SsErr],0		;Any errors so far?
	jne	@F			;If so,don't bind labels
	cmp	ax,0fffeh		; Is this RESUME 0/NEXT or ON ERROR/EVENT
	jae	@F			;GOTO/GOSUB 0? skip bind if so.
	push	bx			;remember start of label chain
	call	LabelSearch		;Search for label in specified text table
	pop	bx
@@:
	STOSWTX 			;bind label/or emit oNam
	pop	cx			;restore label count
	loop	LabelBindLoop
	mov	fRestoreLab,cl		;reset Binding RESTORE flag
	jmp	[ScanRet]		;return to main scan loop

page

;LabelSearch - search for label definition
;
;Purpose:
;	This routine searches for labels in the specified context.
;	The label definition will either be at the same scope as
;	the label reference, or at the module level.  If this is not
;	the case, either an Undefined Label, or Subprogram error
;	will be generated.  If the direct mode buffer is being bound,
;	then the current Continue context will be used to determine
;	scoping errors.
;Entry:
;	 oRsExpected = oRs of expected scope.
;	 ax  = oNam of label to be found
;	 bx  = start of label def chain
;	 dx  = Text table seg to search.
;	 es:si	= text table addr of label ref
;	 es:di	= text table emit addr
;Exit:
;	 ax  = oTx of found label, or oNam if not found.
;Preserves:
;	 dx

LabelSearch:
	push	ds
	mov	cx,es
	cmp	cx,dx			;are we searching in current table?
	jnz	LabelNotCurTxt		;brif not, table already bound

;Searching for a label definition in same txt table as label reference.

	mov	cx,[SscbTxExpand] 	;get table expansion factor
	mov	bx,[SsLinkCtl]		;address of label control structure
	mov	bx,[bx].TXLNK_LabDefNext ;Next unbound label reference
	mov	ds,dx			;set ds to txt table of search
	jmp	short LabSearchSrc	;Search forward through unbound source

SkipRef:
	dec	bx			;Reset LSB of reference
NextLink:
	mov	bx,[bx]			;Get link to next
LabSearchSrc:
	cmp	bx,-1			;End of chain?
	jz	LabelNotForwardRef	;Label not found - go look in already
					; bound section of current text table
	test	bl,1			;Just a forward reference?
	jnz	SkipRef
	add	bx,cx			;Adjust by SsCbTxExpand
	cmp	ax,[bx+2]		;oNames match?
	jnz	NextLink

	mov	ax,bx
;Forward Reference Case
	pop	ds			;recover dgroup
	push	bx			;preserve ptr to def
	call	CheckLabelScope 	;check for scoping errors before
					;linking into forward ref chain
	pop	bx			;recover ptr to def
	jnz	LabelSearchX		;brif invalid scope

	push	ds
	mov	ds,dx			;set ds to label def txt table
	mov	cx,[bx] 		;Load link field from definition
	mov	ax,di
	inc	ax			;Mark as forward reference link
	mov	[bx],ax 		;Emit forward reference link to current
					; label reference
	xchg	ax,cx			;AX = pcode address of next
					; unbound label definition offset
	pop	ds			;recover DGroup

LabelSearchX:				;finished was a forward ref
	ret

LabelNotForwardRef:
;Search the section of the current text table that is already bound.
assumes	ds,nothing
	mov	bx,txdCur.TXD_otxLabLink;Start at first label
LabelNotCurTxt:
	mov	ds,dx			;search in specified table
	jmp	short LabSearchBound	;Search from start through bound source

BoundLoop:
	cmp	ax,[bx+2]		;oNames match?
	jz	LabFound
	mov	bx,[bx]			;Link to next
LabSearchBound:
	test	bl,1			;End of chain (either unbound or -1)
	jz	BoundLoop
	pop	ds			;Label not found

LabelScopeError:
	mov	ax,ER_UL		;"Undefined Label" or incorrect scoping
	dec	si
	dec	si			;Back up to oName (sets error location)
	call	SsError
	LODSWTX 			;recover oName
	or	sp,sp			;reset psw.z
	ret


LabFound:
	mov	ax,bx
;   ax = address of definition
;es:di = address of reference
	dec	ax			;Move back to oTx of BOL pcode
	dec	ax
	pop	ds			;recover ds = dgroup
assumes	ds,data

; fall into CheckLabelScope.

page
;CheckLabelScope - find and check oRs for passed oTx, verify expected scope
;
;Purpose:
;	This routine verifies that the found label is in the expected
;	scope.	If not, an Undefined label error is issued.
;Entry:
;	 oRsExpected = oRs of expected scope.
;	 ax  = oTx
;	 dx  = Text table seg of of label def.
;	 es:si	= text table addr of label ref
;Exit:
;	 psw.z - indicates valid scope.
;	 psw.nz - indicates scoping error detected, and Undefined label error
;		  has been recorded.
;	 ax  = oTx of label if valid scope, or oNam if invalid scope.
;Preserves:
;	dx
;
;NOTE: CheckLabelScope is called from forward ref case, and fallen into.
;      from the already backwards ref/not current table case.

CheckLabelScope:

; Find oRs of found oTx and check against expected oRs.  If mismatch,
; then we have a scoping error.

	mov	bx,oRsExpected		;get expected oRs
	shr	bx,1			;see if in sub or function
	jc	LabelScopeX		;brif so, scope is ok

; oRs could be in a DEF FN or at module level.	Verify it is at expected
; scope.
	shl	bx,1			;restore expected oRs
	call	ScanORsOfOtx		;cx = oRs of label def.
	cmp	bx,cx			;is oRs expected oRs?
	jz	LabelScopeX		;brif so, no error

; Check for the special case of RESTORE <lab/line> which can bind
; to either the current DEF FN, or to the Module level.
	cmp	fRestoreLab,0		;is this special case of RESTORE?
	jz	LabelScopeError 	;brif not, issue error

; We only can get here if the RESTORE statement was in a DEF FN and
; the label definition was also in a DEF FN.  Make sure that the label
; def and the RESTORE statement are in the same DEF FN.
	cmp	cx,grs.GRS_oRsCur	;is this the same DEF FN?
	jnz	LabelScopeError 	;brif not - Label Scoping error

LabelScopeX:
	xor	bx,bx			;return with psw.z set - scope ok
	ret

page
;ScanORsOfOtx - find oRs of passed oTx.
;
;Purpose:
;	Given an  offset within the text table table defined by
;	DX, return the oRs of the DEF FN, or module which it falls
;	within.  This routine understands how defs are bound in execute
;	and non execute states, and can bridge the Scan gap if
;	this is the current text table.
;
;	The DEF FN chain is preserved in SS_EXECUTE state.  If a table
;	has been fully bound, then the DEF FN chain for the module is
;	directly walkable.  If the text table is partially bound, then
;	if SsLinkCtl.TXLNK_DefFn is 0 then no DEF FNs have been bound
;	yet.  The DEF FN chain is walkable by adjusting all entries
;	by the size of the scan gap.  If the SsLinkCtl.TXLNK_DefFn
;	is non-zero, then the scan bound/unbound gap is defined by
;	a single entry in the DEF FN chain with the low order bit set.
;	This entry indicates that the NEXT entry starts the unbound
;	DEF FN chain.  The unbound entries are walkable by applying
;	the size of the scan gap as an adjustment value.
;	The DEF FN chain is terminated by an UNDEFINED ptr.
;
;Entry:
;	ax = otx
;	dx = text table seg
;Exit:
;	cx = oRs of module or DEF FN containing the oTx.
;Preserves:
;	ax, bx, dx.
;

ScanORsOfOtx:
DbAssertRel ax,nz,UNDEFINED,SCAN,<Invalid oTx passed to ScanORsOfOtx>
	push	es
	push	di
	push	si
	push	bx
	push	dx			;save text seg of bind
	mov	cx,[grs.GRS_oMrsCur]	;default return value = oMrsCur
	mov	di,CODEOffset exStDefFn ;search is for DEF FN executors
	mov	si,es
	mov	es,dx			;es = seg adr of search txt tbl
	mov	bx,[mrsCur.MRS_otxDefFnLink] ;start at head of DEF FN list

	cmp	dx,si			;are we searching txdCur?
	mov	dx,0			;default adjustment for scan gap.
					;we start out assuming that we are
					;searching bound pcode.
	jnz	DefFnLoop		;brif not, table has already been bound
	push	bx			;save start of DefFn chain
	mov	bx,SsLinkCtl
	cmp	[bx].TXLNK_DefFn,0	;have any DEF FN entries been bound?
	pop	bx			;recover start of DEF FN list
	jnz	DefFnLoop		;brif so, search bound pcode first


	or	bl,1			;flag that we are crossing scan gap
					;search unbound pcode
DefFnLoop:
	cmp	bx,UNDEFINED		;are we at the end of DEF FN list?
	jz	DefFnExit		;brif so
	shr	bx,1			;clear lsb - Are we crossing scan gap?
	jnc	NotCrossingGap		;brif not


	mov	di,opStDefFn		;search for DEF FN opcodes in
					;unbound pcode
	mov	dx,SscbTxExpand 	;get table expansion factor for unbound
					;def fn links
NotCrossingGap:
	shl	bx,1			;recover oTx of next DEF FN link
	add	bx,dx			;adjust for text expansion
	cmp	bx,ax
	ja	DefFnExit		;brif beyond otx of interest
	mov	cx,[grs.GRS_oMrsCur]	;default return value = oMrsCur

	cmp	WORD PTR es:[bx-4],opNoList0 ;is this the CONT statement?
	je	GotContContext		;brif so - exceptional case
	cmp	WORD PTR es:[bx-4],di	;is this a DEF FN executor/opcode?
	jne	NotInDef		;brif its an END DEF
ContInDef:
	mov	cx,es:[bx+2]		;ax = oPrs of this DEF FN
	or	ch,80H			;make it into an oRs
NotInDef:
	DbChk	DefFnLink		;perform sanity check on this link.
	mov	bx,es:[bx]		;bx points to next in linked list
	jmp	SHORT DefFnLoop 	;applies standard BOUND adjustment

; Handle very special case where we are in Edit and Continue, AND the
; current statment is a DEF FN or END DEF that has yet to be scanned.
; In this case opNoList0 was inserted into the pcode for the opStDefFn
; or opStEndDef.  The real opcode is in SsErrOpcode.

GotContContext:
       cmp	[SsErrOpcode],di	;is this a DEF FN?
       je	ContInDef		;brif so
       jmp	short NotInDef		;must be END DEF

DefFnExit:
	pop	dx
	pop	bx
	pop	si
	pop	di
	pop	es
	ret

page
;DebChkDefFnLink - perform sanity check on Def Fn chain link.
;
;Purpose:
;	Verifies that current link in Def Fn chain is valid.
;Entry:
;	es:bx - pcode addr of chain link
;Exit:
;	none.
;Uses:
;	none.
;Exceptions:
;	Invalid DefFn chain link.


sEnd	SCAN
end

⌨️ 快捷键说明

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