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

📄 ssscan.asm

📁 Microsoft MS-DOS6.0 完整源代码
💻 ASM
📖 第 1 页 / 共 2 页
字号:
	dec	ax			;Point into previous pcode
	mov	[grs.GRS_oTxCur],ax	;Location of error
	mov	[EmitErrOtx],UNDEFINED
	jmp	SortOtx

OTxMatch:
	mov	cx,[SsReturnBp]
	cmp	cx,dataOFFSET grs.GRS_oTxCONT	;Is it current PC?
	jz	SetOtxCont
	cmp	cx,dataOFFSET EmitErrOtx	;Is it the location of an error?
	jz	SetErrorLoc

	;At this point, it has been determined that CX contains the offset into
	;DGROUP of a word containing an Otx into the current pcode table.  To
	;update this word to account for descaning and subsequent scanning,
	;an opcode is inserted with an operand of the DGROUP offset.  The
	;scan routine for this opcode will update the static location without
	;emitting the executor or operand.  To prevent this oTx from being
	;found on the next pass through SortOTx, it is set to UNDEFINED (0ffff).
	;If CX is odd then CX contains the location minus one where the update
	;should occur.	This location is the address of an error handler or
	;event handler and the opcode must be inserted after the BOL to
	;prevent an edit of lines before the handler from messing up the
	;update.

	mov	ax,opNoList1		;Return address opcode
	TestM	[SsNextOTx],1		; Is this a handler address?
	jz	@F			; Brif not
	mov	ah,HIGH (opNoList1+OPCODE_MASK+1)
@@:					
	mov	bx,di			;Insert right here
	call	Insert1Op
	mov	bx,cx
	mov	[bx],UNDEFINED		;Blast original oTx
	jmp	SortOTx

SetNext:
	pop	di
	pop	si
;
; See if there is a smaller otx in the Invoke chain.
;

	;See if any event handlers need update

	    push    dx			;Save referenced oTx
	    push    [grs.GRS_oRsCur]
	    call    B$IFindEvHandler	;Get smallest event handler oTx
	    mov     bx,dx		;Offset of smallest
	    pop     dx
	    call    CheckUpdateSkipBOL

	    ;See if references in MRS need update.

	    test    byte ptr [grs.GRS_oRsCur+1],80H  ;At module level?
	    jnz     SetNextOtx

	    ;Update module level error handler

	    mov     bx,dataOFFSET mrsCur.MRS_otxHandler
	    call    CheckUpdateSkipBOLAX

	    ;Update current Data position

	    mov     bx,dataOFFSET mrsCur.MRS_data_otxCur
	    call    CheckUpdateRs

SetNextOtx:
	add	dx,[SsCbTxExpand]	;Adjust for current source position
	jnc	ValidOtx
	mov	dx,UNDEFINED
ValidOtx:
	mov	[SsNextOTx],dx		;oText we're looking for
ContDescanLoop:
	cmp	si,[SsNextOTx]		;Looking for this oText?
	jae	OTxMatch		;Brif current otx >= next update loc

	LODSWTX 			;Load executor
	mov	bx,ax
	GetCodeIntoDs	SCAN		
	mov	ax,[bx-2]		;Load opcode for executor
	push	ss			
	pop	ds			;Move back to data segment
	mov	bx,ax
	and	bh,HIGH OPCODE_MASK
	DbAssertRel bx,be,OP_MAX,SCAN,<Descan: opcode out of range>
	shl	bx,1			;Move to word offset
	mov	bx,mpOpScanDisp[bx]	;Load scan routine address
	jmp	cs:SsProcParse[bx]	;And dispatch w/ ax = opcode


;DescanTerm is installed in ScanRet by descan to SS_PARSE dispatch routines
;that terminate descan.  For example, see SsD_Eot.

public	DescanTerm
DescanTerm:
	mov	al,SS_PARSE
	cCall	UpdateTxdBdl		;Update the TXD or BDL for text table
	call	FCanCont		; See if we can continue
	jz	DescanX			;Can't cont
	and	byte ptr [grs.GRS_otxCont],not 1 ;Reset LSB of CONT otx
	cmp	[SsErr],0		;Any errors?
	jz	DescanX
	call	CantCont		;If errors, can't continue

;DescanX is installed in ScanRet by descan to SS_RUDE dispatch routines
;that terminate descan.  For example, see SsV_Eot
Public	DescanX
DescanX:
	DbChkTxdCur			;perform sanity check on txdCur
	DbMessTimer	SCAN,<Leave SsDeScan - >
cEnd	SsDescan

;*** CheckUpdate,CheckUpdateSkipBOL
;Purpose:
;
;   See if the oTx at [bx] is smaller than the one in dx and is
;   in the same text table.
;
;Input:
;
;   ax = oTx (CheckUpdateSkipBOL only)
;   ds:bx = pointer to an oTx
;   cx = oRS of oTx at [bx]
;   dx = current smallest oTx in current text table
;
;Outputs:
;
;   dx updated with new smallest
;
;Preserves:
;
;   bx,cx

CheckUpdateSkipBOLAX:			
	mov	ax,word ptr [bx]	

CheckUpdateSkipBOL:
	inc	ax
	jz	UpdateX
	dec	ax
	push	bx
	GetCodeIntoDs	SCAN		
	mov	bx,ax			;oTx to bx
	add	bx,ss:[SsCbTxExpand]
	mov	bx,PTRTX[bx]		;Get executor
	mov	bx,[bx-2]		;Get opcode
	push	ss			
	pop	ds
	mov	bl,mpOpAtr[bx]		;Load attribute byte
	and	bx,OPA_CntMask		;Get the operand count from attribute
	add	ax,bx			;Compute oTx after BOL
	dec	ax			; LSB indicates BOL Update
	pop	bx
	jmp	short CheckUpdateAx

CheckUpdate:
	cmp	cx,[grs.GRS_oRsCur]	;In current text table?
	jnz	UpdateX
CheckUpdateRs:
	mov	ax,[bx]
CheckUpdateAx:
	cmp	dx,ax
	jbe	UpdateX
	xchg	dx,ax			;New smallest oTx
	mov	[SsReturnBp],bx		;Location being updated
UpdateX:
	ret

;*** GetOtxRs
;Inputs:
;	cx = any oRS
;Purpose:
;	Map oRS of DefFn back to it oMRS
;Outputs:
;	cx = oRS that owns text table of input oRS
;Preserves:
;	bx,dx,es

GetOtxRs:
	push	es			
	or	cx,cx
	jns	OtxRs			;If MRS, have text table
;See if oPRS is of a DefFn
	xchg	ax,bx			;Preserve bx
	xchg	cx,ax			;cx = old bx, ax = oRS
	and	ax,not 8000H		;Reset MSB
	call	PPrsOPrsSCAN		; bx = pPRS
	or	ax,8000H		;Make ax an oRS again
	cmp	BPTRRS[bx].PRS_procType,PT_DEFFN ; Is proc a DefFn?
	jnz	UsePRS			;If not, PRS in ax is OK
	mov	ax,PTRRS[bx].PRS_oMRS	; Get oMRS for DefFn
UsePRS:
	xchg	cx,ax			;cx = oRS
	xchg	bx,ax			;Restore bx
OtxRs:
	pop	es			
	ret


;***
;SsFrameType - determine type of scanner frame
;Purpose:
;	Report error if there was a scanner frame on the stack.
;Inputs:
;	ax = scan stack entry
;	si = scan source oTx
;	di = scan emit oTx
;	[sp+2] = oTx of source of scanner frame
;Ouputs:
;	if ax = 0, nothing
;	else report appropriate error
;***************************************************************************
	public	SsFrameType

SsFrameType:
	or	ax,ax
	jz	IgnoreErr
	cmp	[SsErr],0		;Already have an error?
	jnz	IgnoreErr		;If so, leave it
	mov	cx,ER_FN		;FOR without Next
	testx	ax,STYP_For		;In FOR block?
	jnz	CxErr
	mov	cx,ER_WH		;WHILE without WEND
	testx	ax,STYP_While
	jnz	CxErr
	mov	cx,MSG_Do		;DO without LOOP
	testx	ax,STYP_Do
	jnz	CxErr
	mov	cx,MSG_Select		;SELECT without END SELECT
	testx	ax,STYP_Case
	jnz	CxErr

	    mov     cx,MSG_DefNoEnd	;DEF without END DEF
	    testx   ax,STYP_DefFn
	    jnz     CxErr
;
;Insert additional control structure tests here
;Scan stack entry must be oTx of last operand
;
	testx	ax,STYP_If+STYP_Else	;In IF block?
	mov	ax,ER_IER		;Internal error if not
	jz	SsError
	mov	cx,MSG_IWE		;Block IF without END IF
CxErr:
	pop	dx			;Return address
	pop	bx			;oTx of error
	push	bx
	push	ax			;Restore frame
	push	dx			;Put return address back
	xchg	ax,cx			;Error code to ax
;	jmp	SsErrorBx		;Fall into SsErrorBx
	
;***
;SsError,SsErrorBx - scanner error handler
;
;Purpose:
;
;   Record scanner error, setting variables as follows:
;
;   [SsErr]		    = error code
;   [grs.GRS_oTxCur]	    = oTx in unscanned pcode of error
;   [SsErrOTx]		    = oTx in scanned pcode when error was found
;
;   This routine returns normally and scanning continues so that
;   all the various link chains will be properly updated.  If a
;   second error is encountered, it is ignored.
;
;Input:
;
;   ax = error code
;   si = Source oTx of pcode that caused the error. (SsError)
;   bx = Emit oTx of error (SsErrorBx)
;   di = Current emit oTx
;
;Modifies:
;
;   none.
;
;Preserves:
;
;   bx,cx,dx
;
;***************************************************************************
public	SsError,SsErrorBx

;NOTE: fallen into by SsFrameType above!
SsErrorBx:
;This variation of SsError reports bx as the emit location of the error
;instead of si as the source location
	cmp	[SsErr],0		;Already have an error?
	jnz	IgnoreErr		;If so, leave it
	mov	[SsErr],ax		;Record error code
	mov	[EmitErrOTx],bx		;Location of error
	mov	[SsErrOTx],di		;Remember current emit oTx
	ret


SsError:
	cmp	[SsErr],0		;Already have an error?
	jnz	IgnoreErr		;If so, leave it
	mov	[SsErr],ax		;Record error code
	mov	ax,si
	sub	ax,[SsCbTxExpand]	;Compute unscanned pcode address
	dec	ax
	dec	ax			;oTx - 2
	mov	[grs.GRS_oTxCur],ax	;Report location of error
	mov	[SsErrOTx],di		;Remember scanned error address too
IgnoreErr:
	ret


subttl	ScanAndExec and ExecuteFromScan
page
;*** ScanAndExec
;
;Purpose:
;
;   Called by rude scanner to scan to execute state, then
;   execute a line of code.  Used for assigning constants.
;
;	Modified in revision [12] to take inputs on stack, use cMacros,
;	become a far entry point.
;Inputs:
;	parm1 = oTx of pcode to execute
;	parm2 = cb of pcode
;Outputs:
;
;   ax = error code, 0 if no error; flags set
;	    if ax != 0, high-bit set indicates that pcode was not changed
;	    (i.e., still contains an oNam, not an oVar).
;   es = current text segment
;
;*** ExecuteFromScan
;
;Purpose:
;
;   Fires up execution from the scanner.  Used to DIM $STATIC arrays
;   in COMMON.	DIM executor direct jumps to ScanExExit to terminate.
;
;	Modified in revision [12] to take dummy parms on stack, use cMacros,
;	become a far entry point.
;Inputs:
;
;   [SsScanExStart] has starting oTx
;
;***************************************************************************
ScanExGrow	=	20
	public	ScanAndExec,SsScanExExit
	public	ExecuteFromScan,ScanExExit

cProc	ExecuteFromScan,<NEAR>,<si,di>	
	parmW	dummy1			; parms provided to match frame
	parmW	dummy2			; conditions of ScanAndExec
cBegin					
	DbAssertRel [SsErr],e,0,SCAN,<ExecuteFromScan: SsErr != 0>
	push	[b$curframe]
	push	[txdCur.TXD_bdlText_cbLogical]
DJMP	jmp	short StartExec		
cEnd					; nogen

cProc	ScanAndExec,<NEAR>,<si,di>	
	parmW	oTxPcode		
	parmW	cbPcode 		
cBegin					
	mov	[ScannerFlags],SSF_ScanAndExec*100H	;Scanning CONST statement
	push	[b$curframe]
	mov	di,[txdCur.TXD_bdlText_cbLogical]
	push	di			;Save current text size
	mov	si,[oTxPcode]		
	mov	cx,[cbPcode]		
	push	cx
	add	cx,ScanExGrow+2 	;Allow some growth and END executor
	push	cx
	call	TxtFreeFar		; Extend text table
	or	ax,ax			
	jz	ScanExOME		;Insufficient memory

	GETSEGTXTCUR			; es = the text segment
	pop	cx
	mov	[SsScanExSrc],si	;Save true oTx of source
	push	di			;Emit address
	add	di,ScanExGrow		;Source address
	push	di
	shr	cx,1			;cx = count of words
	cli				;Double prefix! No interrupts!
rep	movs	PTRTX[si],PTRTX[di]	;Copy pcode to end of text table
	sti
	mov	ax,opEOT
	STOSWTX
	mov	[txdCur.TXD_bdlText_cbLogical],di ;Extend text table
	pop	si
	pop	di
	mov	[SsScanExStart],di
	mov	[SsCbTxExpand],ScanExGrow


	jmp	ScanToExeStart

ScanExOME:
	pop	cx
	pop	dx			;Clean junk off stack
	mov	ax,08000H OR ER_OM	;high bit says pcode is unchanged
	jmp	short ScanExErr

SsScanExExit:
	mov	PTRTX[di],codeOFFSET exScanExExit
	mov	ax,[SsErr]
	or	ax,ax			;Any scanner errors?
	jnz	ScanExErr
StartExec:
;Dispatch execution
	call	far ptr StartExecCP
ScanExErr:
	GETSEGTXTCUR			;es = the text segment
	and	[SsFlags],not SSF_ScanAndExec
	pop	[txdCur.TXD_bdlText_cbLogical]
	pop	[b$curframe]
	or	ax,ax			; Any scanner errors?
cEnd					

sEnd	SCAN

sBegin	CP

assumes cs, CP
assumes ds, DATA
assumes es, NOTHING
assumes SS, DATA

cProc	StartExecCP,<FAR>
cBegin

	call	RtPushHandler		;Save current RT error handler
	mov	ax,cpOFFSET RtScanExTrap
	call	RtSetTrap		;Assign new RT error handler
	call	DisStaticStructs	;Deactivate mrsCur
	mov	[b$curframe],bp 	;Required by math executors
	    TestM   [SsScanExStart],1	; Is this implicit Dim?
	    jnz     @F			; Brif yes
	mov	si,[SsScanExStart]

	jmp	far ptr Start

@@:					
	jmp	DimImplicit		

ScanExExit:
	xor	ax,ax
RtScanExTrap:
	push	ss
	pop	ds			;restore ds == DGROUP from execution
	xchg	ax,si			;Save error code
	call	RtPopHandler
	call	EnStaticStructs 	;Re-activate mrsCur
	xchg	ax,si			;Restore error code


cEnd

sEnd	CP

sBegin	CODE

assumes cs, CODE
assumes ds, DATA
assumes es, NOTHING
assumes SS, DATA

	extrn	Start:far

exScanExExit:	jmp	far ptr ScanExExit

sEnd	CODE

end

⌨️ 快捷键说明

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