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

📄 prsutil.asm

📁 Dos6.0
💻 ASM
📖 第 1 页 / 共 3 页
字号:
	jz	OverFlow		; brif too many
	inc	[cbCompressed]		;compressed 1 more char
	jmp	CompressNext

OverFlow:				
	dec	byte ptr [di-2] 	; restore count of special chars
	jmp	StartNewRun		; start another run


;*********************************************************************
; CompressText
;
; Purpose:
;	Compress text in buffer DI if possible.
;	Note: this routine should only be called from EmitSrcCompress,
;	as it utilizes frame variables defined by EmitSrcCompress.
;
; Entry:
;	[cbRep] = repeat count for last char in buffer.
;	[cbCompressed] = current count of compressed chars in buffer.
;
; Exit:
;	[cbCompressed] updated if text was compressed
;	DI updated for compression
; Preserves:
;	AX
;*********************************************************************
CompressText:
	push	ax			;save chCur
	mov	ax,[cbRep]		;get repetition factor for chLast

	cmp	al,3			;Don't compress if repeat count < 3
	jbe	CompressTextExit
	sub	di,ax			;back up pDst to first repeated char
	add	[cbCompressed],ax	;bump count of compressed bytes
	sub	[cbCompressed],3	; - compression overhead (2)
					; - 1 (make cbRep 0 relative)
	mov	ah,al			;high byte has count
	mov	al,STR_EncodedText	;low byte has encoded flag
	stosw				;emit encoded flag/cb encoded
	inc	di			;skip char
	mov	byte ptr[di],0		;zero potential extra byte

CompressTextExit:
	pop	ax			;recover chCur
	ret


;*********************************************************************
; boolean ListStdMsgToBd(iMsg, pbdDst)
;
; Purpose:
;	List a standard ASCII message to the end of a buffer.
;
; Entry:
;	iMsg is standard error index from qbimsgs.h
;	pbdDst points to buffer descriptor where message is to be listed
;
; Exit:
;	If out-of-memory error, returns FALSE
;	else returns TRUE
;
;*********************************************************************
cProc	ListStdMsgToBd,<PUBLIC,FAR,NODATA>
	parmW	iMsg
	parmW	pbdDst			
cBegin	ListStdMsgToBd
	push	[iMsg]
	call	ListStdMsgFar		;copy text of msg to bufStdMsg
					; ax = # bytes in message
	;return(BdAppend(pbdDst, pMsgText, cbText))
	push	[pbdDst]			;pass ptr to destination buffer
	PUSHI	bx,<dataOFFSET bufStdMsg>
					;pass ptr to 1st byte of text
	push	ax			;push byte count
	call	BdAppend		;ax = FALSE if out-of-memory
ListMsgExit:
cEnd	ListStdMsgToBd


;*************************************************************************
; ListIRW 
; Purpose:
;	Map a reserved word from index (0..n) to ASCII.
;	Used by user-interface's context sensitive help.
; Entry:
;	parm1: reserved word index (0,1,2,...n)
; Exit:
;	returns byte count (0 if index is too large).
;	zero terminated string for reserved word is copied to bufStdMsg
;
;*************************************************************************
cProc	ListIRW,<PUBLIC,FAR>,<si,di>
	parmW	iRw
	localW	pbDst			
	localW	iRwCur
	localB	letterCur
cBegin
	mov	ax,IRW_ALPHA_FIRST
	mov	[iRwCur],ax		;initialize cur res word counter/index
	mov	bx,[iRw]		;bx=reserved word of interest
	cmp	bx,ax
	jae	NotSpecChar		;brif iRw represents a word from
					; res word table, and not a special
					; char like +, *,$ etc.
	mov	al,BYTE PTR cs:mpIRWtoChar[bx]
	mov	[letterCur],al
	sub	cx,cx			;cbNam = 0
	jmp	SHORT SrchEnd

NotSpecChar:
	mov	[letterCur],'A'
	mov	ax,cs:[tRw]		;ax points to A's res word tbl
	inc	ax			;skip IRW for 1st entry in table
	inc	ax
	xchg	si,ax			;si points into A's res word tbl
	push	cs
	pop	es			;es = CP segment (for GetRwFromTab)

;Register usage:
;	si->current res word, cx = cbNam, dx=cbAtr
;	es = segment adr of reserved word table (CP)
;
SrchLoop:
	cmp	BYTE PTR cs:[si],0
	jne	NotEndOfTbl		;brif not at end of current table

	;we just moved into next letter's reserved word table
	inc	[letterCur]
	sub	dx,dx			;prepare to return 0
	cmp	[letterCur],'Z'
	ja	ListEnd 		;brif IRW not found (return 0)
	add	si,3			;skip 0-byte terminator and
	jmp	SHORT SrchLoop		; iRw for 1st entry in next table

NotEndOfTbl:
EXTRN	GetRwFromTabCP:near
	call	GetRwFromTabCP		;cx = size of res word's name
					;dx = size of res word's atr block
					;si points to 1st byte of res word name
	mov	ax,[iRwCur]		;ax = current reserved word's index
	inc	[iRwCur]
	cmp	ax,[iRw]
	je	SrchEnd			;brif current res word is one
					; we've been looking for
	add	si,cx			;skip cbNam bytes
	add	si,dx			;skip cbAtr bytes
	jmp	SHORT SrchLoop

;[letterCur] = 1st letter of reserved word
;cx = # bytes in reserved word, excluding first char
;
SrchEnd:
	mov	dx,cx
	inc	dx			;dx = real number of bytes in res word
	push	ds
	pop	es			;es=ds for block transfer
	mov	di,DATAOFFSET bufStdMsg
	mov	al,[letterCur]
	stosb				;store 1st char in buffer
	jcxz	ListExit		;branch if 1 letter res word (like +)
OutLoop:
	lods	BYTE PTR cs:[si]	;al = next letter of res word
	stosb				;store it in buffer
	loop	OutLoop			;until cx=0
	lods	BYTE PTR cs:[si]	;al = flags byte
	test	al,RWF_STR
	je	ListExit		;brif doesn't end with '$'
	mov	al,'$'
	stosb				;store it in buffer
	inc	dx			;dx = real number of bytes in res word
ListExit:
	xchg	ax,cx			;ax = 0
	stosb				;store 0-terminator
ListEnd:
	xchg	ax,dx			;return result in ax
cEnd


subttl	Error reporting functions

;=======================================================================
;	  E R R O R    R E P O R T I N G    F U N C T I O N S
;
; Example:
;	Assume the statement we are parsing is defined by the parse tree:
;
;	            A
;	           / \
;	          B   C
;	           \   \
;	            +---+
;	                 \
;	                 <accept>
;
; and assume A is a non-terminal which is described by the parse tree:
;
;	            X
;	           / \
;	          /   Z
;	          \    \
;	           +----+
;	                 \
;	                 <accept>
;
; If Parse(A) fails to match A or B, we want to produce the error message
; "Expected X or B" (since A is really known to the user as X).
;	The way this is accomplished is as follows:
;	- Every NonTerminal parsing function (like Parse() and Ntxxx())
;	  returns 1 of 3 values:
;	  PR_GoodSyntax if tokens were recognized & pcode emitted
;	  PR_NotFound if tokens were not recognized, and no tokens were consumed
;	  PR_BadSyntax if some tokens got consumed before we detect a syntax
;	   error.  In this case, the NonTerminal parsing function is responsible
;	   for generating a complete error message by calling one or more of
;	   the functions: PErrState(), PErrExpectedOr(), PErrMsg(),
;	     PErrExpMsg(), PErrExpRw().
;
;  Control Flow:
;
;	      PErrState
;                 |
;           +-----+----+
;           |          |
;       PErrExpMsg PErrExpRw
;           |
;       PErrMsg_AX ParseErrOm ParseErr0 PErrVarMgr ParseErrTokScan
;           |           |        |          |           |
;           +-----------+--------+----------+-----------+
;                       |
;	           ParseErr
;
;=====================================================================

;*********************************************************************
; void NEAR ParseErr(ax:errCode, bx:pTokErr)
; Purpose:
;	Record the fact that a parser error has occurred.
; Entry:
;	ax = errCode is a standard error code from qbimsgs.h or
;	     PSERR_fAsciiMsg with 0 or more of: PSERR_fAlert, PSERR_fRude
;	bx = pointer to token where error occurred (used for column
;	     error reporting).
;	     bx = 0 if caller doesn't know what token caused the error.
; Exit:
;	psFlags bit PSIF_fBindVars is reset so we don't continue binding
;	   variables in a statement which is already known to be bad
;
;********************************************************************/

PUBLIC	ParseErrOm
ParseErrOm PROC NEAR
	mov	ax,ER_OM OR PSERR_fAlert
ParseErrOm ENDP
	;fall into ParseErr0
PUBLIC	ParseErr0
ParseErr0 PROC NEAR
	sub	bx,bx			;token/source-column = unknown
ParseErr0 ENDP
	;fall into ParseErr
PUBLIC	ParseErr
ParseErr PROC NEAR
	mov	dx,ax
	and	dx,PSERR_errcode
	cmp	dx,ER_CN
	jne	NotCantCont

	;variable mgr and context mgr return ER_CN if asked to grow a
	;variable table when CONT is possible.  Since variable tables
	;can't move during program execution, either AskCantCont will
	;disable CONT, or the edit must be backed out of.
	
	DbAssertRelB [txdCur.TXD_scanState],ne,SS_RUDE,CP,<ParseErr: err1>
	;If this assertion failed, we could be in an infinite loop of retries.

	call	AskCantCont_CP		;ask user "Want to back out?"
	mov	al,PSF_UndoEdit
	je	BackOut			;brif user wants to back out
	mov	al,PSF_fRetry		;tell caller to call ParseLine again
BackOut:
	or	[ps.PS_flags],al
	mov	al,ER_IER		;this error should never get to user
;ax = errCode
NotCantCont:
	mov	[ps.PS_errCode],ax
	or	bx,bx
	je	PerrNoOSrc		;brif we don't know column of error
	mov	bx,[bx.TOK_oSrc]	;bx = token's source line offset
PerrNoOSrc:
	mov	[ps.PS_oSrcErr],bx
	and	[psFlags],NOT PSIF_fBindVars
	ret
ParseErr ENDP

;*********************************************************************
; void NEAR ParseErrTokScan(ax:errCode)
; Purpose:
;	Same as ParseErr.  This should be called if the caller wants
;	to flag an error, but continue checking for bad syntax.
;	If a syntax error is found later in the line, it will
;	over-write this error message.  Call PErrMsg_AX if
;	syntax analysis of the line is to stop.
; Entry:
;	ax = errCode is a standard error code from qbimsgs.h or
;	     PSERR_fAsciiMsg with 0 or more of: PSERR_fAlert, PSERR_fRude
;	[pTokScan] = pointer to token where error occurred (used for column
;	     error reporting).
; Exit:
;	Same as ParseErr
;
;********************************************************************/
PUBLIC	ParseErrTokScan
ParseErrTokScan PROC NEAR
	mov	bx,[pTokScan]
	jmp	SHORT ParseErr
ParseErrTokScan ENDP

;*********************************************************************
; void NEAR PErrVarMgr(ax:errCode, bx:pTokErr)
; Purpose:
;	Handle error code returned by MakeVariable
;	Note that this can be an error returned by ScanAndExec as well.
;	If PRS_ER_RE bit is set (Rude edit error)
;	   set PSERR_fRude bit in ParseLine's return value
;	Else If PRS_ER_RP bit is NOT set (passive reparse error)
;	   set PSERR_fAlert bit in ParseLine's return value
;	Else
;	   caller of ParseLine may defer reporting the error until
;	   the user tries to run the program.
; Entry:
;	ax = errCode is an error code as returned by MakeVariable
;	bx = (used for column
;	     error reporting).
;	     bx = 0 if caller doesn't know what token caused the error.
; Exit:
;	psFlags bit PSIF_fBindVars is reset so we don't continue
;	   binding variables in a statement which is bad
;	We will continue to check rest of statement for syntax errors,
;	   since these are stronger (more useful to user) than
;	   variable manager errors.  If any syntax errors are found,
;	   any information recorded in ps.err... by this function
;	   will be overwritten.
;
;********************************************************************/
PUBLIC	PErrVarMgr
PErrVarMgr PROC NEAR
	test	ah,(PRS_ER_RP / 100h) AND 7Fh
	jne	ReparseErr		;brif Reparse Error
	test	ah,(PRS_ER_RE / 100h) AND 7Fh
	.errnz	PSERR_fRude AND 0FFH
	mov	ah,PSERR_fRude / 100h	;set rude edit flag in result
	jne	BindRude		;brif a rude edit
	.errnz	PSERR_fAlert AND 0FFH

⌨️ 快捷键说明

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