📄 prsmain.asm
字号:
TITLE prsmain.asm - Parser Main Module
;==========================================================================
;
; Module: prsmain.asm - Parser Main Module
; Subsystem: Parser
; System: Quick BASIC Interpreter
;
;==========================================================================
include version.inc
PRSMAIN_ASM = ON
includeOnce architec
includeOnce context
includeOnce heap
includeOnce names
includeOnce opcontrl
includeOnce opid
includeOnce opmin
includeOnce parser
includeOnce pcode
includeOnce prsirw
includeOnce prstab
includeOnce psint
includeOnce qbimsgs
includeOnce rtinterp
includeOnce rtps
includeOnce scanner
includeOnce txtmgr
includeOnce ui
includeOnce util
includeOnce stack2
;--------------------------------------------------------------------------
;
; The BIC Parser is a table driven recursive descent parser.
; Because it is used by the Interpreter, it can make no assumptions
; about the order in which it sees statements. This means it has
; to consider each statement as an atomic unit. Checking syntax
; which spans multiple statements, like matching FOR NEXT statements,
; is left to the static scanner, a separate BIC component.
;
; The parser receives tokens from FetchToken(). For the interpreter,
; it produces an infix pcode stream. For the compiler, it returns
; the top node of a syntax tree.
;
; The fundamental Control hierarchy of the parser component is as follows:
;
; (ParseLine)
; |
; +-----------------------------+
; | |
; (ParseLabelOrLineNum) (Parse)
; | | |
; +----+ | +--------+----------|
; | | | | |
; (ScanTok) (Peek1Tok) |
; | | |
; +-------+--+ |
; | (NtXXXX)
; (FetTok)
; |
; (FetchToken)
; | | |
; | | |
; +-----------+ | |
; | | |
; [ONamOfPbCb] ($i8input) |
; |
; (FindRw)
;
;=========================================================================*
;
; The tables which this module uses to perform its parsing are produced
; by the utility program 'buildprs' (a recursive descent parser generator).
; See 'parser.doc' for a definition of how these parse tables are built.
; The following is an example of how they are used.
; The lexical analyzer recognizes all reserved words. When it encounters
; one, it returns a pointer to a structure which shows all the opcodes
; which map to this reserved word, as well as whether or not it is
; a legal keyword to start a statement or intrinsic function.
; If it can start a statement or intrinsic function, this list also contains
; an offset into the parser state table which describes the syntax for
; the statement/function. The following is an example of how CALL would
; be parsed.
;
; Reserved-Word-Table Syntax-State-Table
; CALL---------+
; |
; +-----> s24: [id->s27] [error]
; s27: ["("->s31] [empty->accept]
; s31: [svar->s36] [exp->s43] [error]
; s36: ["("->s40] [empty->s43]
; s40: [")"->s43] [error]
; s43: [","->s31] [")"->accept] [error]
;
; This state table represents the following state transition graph:
;
; ID ( svar ( ) )
; CALL (s24)---->[s27]---->(s31)---->(s36)---->(s40)---->(s43)---->[]
; +--> | +------------+--> |
; | | exp | |
; | +----------------------+ |
; | , |
; +------------------------------------+
;
;
;
; Where [sn] is a "final" or "accepting" state, and (sn) is not.
;
;--------------------------------------------------------------------
assumes ds,DATA
assumes ss,DATA
assumes es,NOTHING
sBegin DATA
PUBLIC stkChkParse, psFlags
stkChkParse DW 0
psFlags DB 0 ;general purpose parser internal flags
bdParseUndo DB SIZE bd DUP(0) ;buffer used by ParseUndo()
sEnd DATA
sBegin CP
assumes cs,CP
;--------------------------------------------------------------------
; P A R S E - A - L I N E F U N C T I O N S
;--------------------------------------------------------------------
;*********************************************************************
;EmitLabel
; Emit a label definition (i.e. opBol, opBolSp, opBolLabSp etc.)
; Entry:
; di = 0 for line number, 1 for alpha label:
; si = name table offset for label/line number
;Exit:
; appropriate label opcode is emitted
; carry set if duplicate label error
;Uses: di
;
;*********************************************************************
EmitLabel PROC NEAR
push si ;pass label to FlagOfONam
call FlagOfONam ;ax = name's flags
test al,NM_fLineNumLabel
jne DupLabel ;brif linenum already declared
mov ax,[ps.PS_bdpSrc.BDP_pbCur]
sub ax,[ps.PS_bdpSrc.BDP_pb] ;ax = number of leading blanks
push ax
call ScanTok ;skip label
dec di
jnz LineNum ;brif not alpha label
call ScanTok ;skip ':'
LineNum:
pop ax ;ax = number of leading blanks
mov bx,[pTokScan]
mov di,[bx.TOK_oSrc]
sub di,ax ;di = updated # of leading blanks
cmp di,1
jbe NoLeadingBlanks ;brif not 2 or more leading blanks
cmp [ps.PS_bdpDst.BDP_cbLogical],0
mov ax,opBolLabSp
je Bol1 ;brif we're at beginning of line
; i.e. no pcode has been emitted yet
mov ax,opLabSp
Bol1:
call Emit16_AX ;emit the opcode
call Emit16_0 ;leave room for link field
push si
call Emit16 ;emit oNam field
push di ;emit count of leading blanks
jmp SHORT ElEmit
NoLeadingBlanks:
cmp [ps.PS_bdpDst.BDP_cbLogical],0
mov ax,opBolLab
je Bol2 ;brif we're at beginning of line
mov ax,opLab
Bol2:
call Emit16_AX ;emit the opcode
call Emit16_0 ;leave room for link field
push si
ElEmit:
call Emit16 ;emit oNam field
clc
ElExit:
ret
DupLabel:
mov ax,ER_DL OR PSERR_fAlert ;report duplicate label
call ParseErrTokScan ;ParseErr(ax)
stc ;set carry to indicate error
jmp SHORT ElExit
EmitLabel ENDP
;*********************************************************************
;EmitBol
;Purpose:
; Emit an opBol, opBolSp, opBolInclude, or opBolIncludeSp
;Entry:
; ax = opBolInclude or opBol
;
;*********************************************************************
EmitBol PROC NEAR
mov bx,[pTokScan]
mov cx,[bx.TOK_oSrc] ;ax = #bytes leading spaces
jcxz NoSpc ;brif no leading blanks
.errnz opBol
or ax,ax
jne NotOpBol ;brif not opBol
cmp cx,24d
ja NotOpBol ;brif too many spaces
.errnz OPCODE_MASK - 3FFh
mov ah,cl ;ax = 256 * cSpaces
shl ax,1 ;ax = 512 * cSpaces
shl ax,1 ;ax = 1024 * cSpaces
jmp SHORT NoSpc
NotOpBol:
push cx ;pass cb to Emit16 (below)
inc ax ;map opBol->opBolSp
; opBolInclude->opBolIncludeSp
call Emit16_AX
mov al,[cInclNest] ;al = $INCLUDE nesting depth (0 if none)
and ax,0FFh ;ax=al, can't use cbw--doesn't set flags
je NotIncl1 ;brif not an included line
call Emit16_AX ;emit $INCLUDE nesting depth
NotIncl1:
pop ax ;ax = #leading blanks
jmp Emit16_AX ;emit the #leading blanks pushed above
; and return to caller
NoSpc:
call Emit16_AX ;emit opcode
mov al,[cInclNest] ;al = $INCLUDE nesting depth (0 if none)
and ax,0FFh ;ax=al, can't use cbw--doesn't set flags
je NotIncl2 ;brif not an included line
call Emit16_AX ;emit $INCLUDE nesting depth
NotIncl2:
ret
EmitBol ENDP
;*********************************************************************
; STATICF(VOID) ParseLineNumAndLabel()
;
; Purpose:
; Parse an optional line number and/or label definition and emit
; pcode for them. If no label, emit an opBol.
;
; Exit:
; appropriate opBolXXX opcode(s) are emitted
; if error occurred, ps.errCode = error code, carry set
; else carry is clear on exit
;
;*********************************************************************
ParseLineNumAndLabel PROC NEAR
push si
push di
cmp [cInclNest],0
je NoInclude ;brif source line isnt from include file
mov ax,opBolInclude
call EmitBol
NoInclude:
call TestLn ;ax = oNam for line number or 0
jc PlabExit ;brif error (Overflow, out-of-memory)
je NoLineNum ;brif no line number
xchg si,ax ;save oNam in si
sub di,di ;tell EmitLabel its a line number label
call EmitLabel ;emit label
jc PlabExit ;brif duplicate label
NoLineNum:
call IdTokPeriodImp ;next token can have "." in it
; but must have no explicit type char
je NoLabel1 ;branch if PR_NotFound
call Peek1Tok ;pTokPeek -> token after pTokScan
mov ax,IRW_Colon
call TestPeek_AX
jne NoLabel1 ;brif not ':'
mov bx,[pTokScan]
mov si,[bx.TOK_id_oNam]
mov di,1 ;tell EmitLabel its an alpha label
call EmitLabel ;emit the label definition
NoLabel:
cmp [ps.PS_bdpDst.BDP_cbLogical],0
jne PlabExit ;brif a label or linenum was emitted
.errnz opBol
sub ax,ax ;mov ax,opBol
call EmitBol ;emit an opBol or opBolSp
jmp SHORT PlabGood
NoLabel1:
call LexReset ;rescan pTokScan ("." is terminator)
jmp SHORT NoLabel
PlabNoSpc:
.errnz opBol
call Emit16_0 ;emit an opBol
PlabGood:
clc ;indicate no error
PlabExit:
pop di
pop si
ret
ParseLineNumAndLabel ENDP
;*********************************************************************
; boolean NEAR ParseLine()
; Purpose:
; Parse a line of BASIC source, producing pcode and or
; error message text.
; Entry:
; ps.bdpSrc contains the zero-byte terminated ASCII source line to
; be parsed.
; grs.fDirect is true if we're parsing a direct mode statement.
; if grs.fDirect is FALSE, grs.oMrsCur and grs.oPrsCur identify
; the module/procedure being edited.
; ps.bdpDst describes destination buffer to receive generated pcode.
; ps.bdErr describes destination buffer for error message text.
; ps.PS_flags & PSF_fParseExp is non-zero if parser is to parse just
; an expression, zero if it is to parse a source line
; other ps.PS_flags must be 0
; Exit:
; condition codes set based on value in ax
; If no errors were encountered,
; PSW.C is not set,
; ps.errCode=0
; ps.bdpDst contains generated pcode.
; If any labels or variables were referenced, on output,
; ps.flags & PWF_fRef is set true, so the text manager knows
; to scan the whole program if the parsed statement was in
; direct mode.
; grs.oPrs is updated if a SUB/FUNCTION/DEF statement for an
; as yet undefined procedure is parsed (during ASCII Load), in which
; case, the text manager inserts the text at the beginning of the
; new module.
;
; If any error was encountered,
; PSW.C is set,
; ps.flags PSF_UndoEdit is set if caller should back out of
; current edit.
; ps.flags PSF_fRetry is set if caller should call ParseLine
; again for the current edit.
; ps.flags PSF_fRudeIfErr is non-zero if ModuleRudeEdit is to be called
; if for any reason, this line's pcode is stored as opReParse,
; or not inserted at all.
; ps.oSrcErr contains the offset into ps.bdpSrc to the offending text.
; ps.bdpDst contains garbage.
; If a syntax error was encountered,
; ps.errCode & PSERR_fAsciiMsg is set non-zero and ps.bdErr contains
; a parser-built ASCII error message
; Else
; ps.errCode & PSERR_errCode contains an offset into the
; QBI Message Table (MSG_xxx or ER_xxx)
; If the variable manager returns an error code which
; means a RudeEdit is being performed, ps.errCode & PSERR_fRude
; is non-zero. If the user wants to go through with the edit,
; TxtChange() will cause the module's value table to be destroyed
; and the module to be de-scanned to SS_RUDE
; If the error was a serious error, i.e. the kind of error which
; we want to flag as soon as the user enters it,
; ps.errCode & PSERR_fAlert is set non-zero. An example of
; when this wouldn't be set is if the user referenced an as-yet
; undefined TYPE, causing the variable manager to return a
; 'ReParse' error code. This allows the text mgr to remember
; the pcode in an opReParse, but not report the error to the user.
; The reason this is not reported as an error is because
; the user may define the TYPE before a RUN is attempted. If
; it is still an error when TxtDirect() is going through
; its ReParse list before a RUN, the error is reported to the
; user at that time.
;
;********************************************************************/
ParseExp:
or [psFlags],PSIF_fNot1stStmt
;so we give "expected end-of-statement
; error" instead of "expected statement"
; if expression isn't terminated
; by end-of-line
call NtConsumeExp ;parse expression (error if not found)
jmp short CheckResult ;check result in al
PUBLIC ParseLine
ParseLine PROC NEAR
;Static variable stkChkParse assumes b$pend never moves.
;If this ever becomes invalid, just move code from ParseInit to ParseLine.
DbAssertRel [b$pend],e,[initBpEnd],CP,<ParseLine: b$pend moved>
sub ax,ax ;ax = 0
mov [ps.PS_errCode],ax
mov [psFlags],al
mov [pStateCur],ax
mov [pStateLastScan],ax
mov [pStateLastGood],ax
cmp [grs.GRS_fDirect],al
jne PlNoBind ;brif we're in direct mode
cmp [txdCur.TXD_scanState],SS_RUDE
je PlNoBind
or [psFlags],PSIF_fBindVars ;bind var refs
PlNoBind:
;reset all parser buffers to their start
mov ax,[ps.PS_bdpSrc.BDP_pb]
mov [ps.PS_bdpSrc.BDP_pbCur],ax
call ResetDstPbCur ;discard anything in this buffer
⌨️ 快捷键说明
复制代码
Ctrl + C
搜索代码
Ctrl + F
全屏模式
F11
切换主题
Ctrl + Shift + D
显示快捷键
?
增大字号
Ctrl + =
减小字号
Ctrl + -