📄 prsmain.asm
字号:
call ScanTok ;pick up 1st token on line
test [ps.PS_flags],PSF_fParseExp
jne ParseExp ;brif called to parse a Watch Expression
call ParseLineNumAndLabel ;consume and emit line number and
; label definition
jc PlErr ;brif some error in label
call NtStatementList0 ;parse a list of statements
; [:] stmt [: stmt [: ...]]
CheckResult:
jl PlErr ;brif bad syntax, ps.bdErr already
; contains ASCII error message,
;PR_NotFound is ok (empty stmt list)
mov ax,IRW_NewLine
call TestScan_AX ;test for end-of-line
jne NoEndOfLine ;brif didn't get expected end-of-line
test [psFlags],PSIF_fLineHasPeriodId
je NoAdotB ;brif line contains no A.B identifiers
mov ax,opNoType ;emit an opEot to terminate pcode
call Emit16_AX
NoAdotB:
mov ax,opEot ;emit an opEot to terminate pcode
call Emit16_AX
cmp [ps.PS_errCode],0
jne PlErr ;brif got some error like out-of-memory
; or variable creation error
clc ;return carry clear (no error)
PlExit:
ret
NoEndOfLine:
mov ax,MSG_ExpStatement ;Error "Expected statement"
test [psFlags],PSIF_fNot1stStmt
je PlReportErr ;brif never got 1st statement on line
;else didn't get expected end-of-line
mov ax,IRW_ELSE
call TestScan_AX
je BadElse ;brif got ELSE
mov ax,IRW_ELSEIF
call TestScan_AX
jne PlExpEos
;Tried to put ELSE or ELSEIF after 1st statement on line,
BadElse:
mov ax,MSG_1stStmt ;Error: "Must be 1st statement on line"
call PErrMsg_AX
jmp SHORT PlErr
PlExpEos:
call PErrState ;generate "Expected A or B or C based
; on parse table state where last
; token was scanned.
mov ax,MSG_eos ;Error "Expected End-of-Statement"
;ax = text for what we expected
PlReportErr:
call PErrExpMsg_AX
;This point is only reached if the line entered had bad syntax,
;or we ran out of memory during some stage,
;or the variable manager detected an error.
PlErr:
;Halt if non-release version, and user entered -TglParseErrs
call far ptr ParseErrInit
DbAssertRel [ps.PS_errCode],ne,0,CP,<prsmain.asm: errcode != 0>
stc ;return with carry set (error)
jmp SHORT PlExit
ParseLine ENDP
;*********************************************************************
; boolean FAR SetPsBufSz(szStmt)
; Purpose:
; Set the content of the parser's source buffer.
; Entry:
; szStmt points to a 0-byte terminated string.
; Exit:
; If out-of-memory,
; returns FALSE
; else
; The line is copied to the global buffer ps.bdpSrc
; returns TRUE (non-zero)
;
;********************************************************************/
cProc SetPsBufSz,<PUBLIC,FAR>
parmW szStmt
cBegin
push [szStmt]
call CbSz ;ax = length of string
xchg dx,ax ;dx = length of string
inc dx ;include room for 0-byte terminator
sub ax,ax ;prepare to return FALSE
cmp dx,[ps.PS_bdpSrc.BDP_cbLogical]
ja SetSzExit ;brif no room for command
;Now copy the block from szStmt to the parser's buffer
push [szStmt]
push [ps.PS_bdpSrc.BDP_pb]
push dx
call CopyBlk
mov ax,sp ;return non-zero (success)
SetSzExit:
cEnd
;*********************************************************************
; SetDstPbCur()
; Purpose:
; Set parser's output pcode buffer's current pointer field
; (ps.bdpDst.pbCur) pointing to the end of the buffer.
; This is called after ps.bdpDst.cbLogical has been altered.
;
; Preserves:
; All registers except ax, flags
;
;*********************************************************************
PUBLIC ResetDstPbCur
ResetDstPbCur PROC NEAR
mov [ps.PS_bdpDst.BDP_cbLogical],0
mov [bdParseUndo.BD_cbLogical],0
ResetDstPbCur ENDP
;fall into SetDstPbCur
PUBLIC SetDstPbCur
SetDstPbCur PROC NEAR
mov ax,[ps.PS_bdpDst.BDP_pb]
add ax,[ps.PS_bdpDst.BDP_cbLogical]
mov [ps.PS_bdpDst.BDP_pbCur],ax
ret
SetDstPbCur ENDP
;*********************************************************************
; void FAR ParseInit()
; Purpose:
; Called once during initialization to initialize the parser
;
;*********************************************************************
AllocBd PROC NEAR
mov dl,IT_NO_OWNERS
sub cx,cx ;byte count = 0
AllocBd ENDP
;fall into AllocBd1
AllocBd1 PROC NEAR
push ax ;pass ptr to buffer
push cx ;pass byte count
push dx ;pass flags
call BdAlloc
or ax,ax
je J1_RtErrorOM_INI ;fatal out-of-memory error
ret
AllocBd1 ENDP
J1_RtErrorOM_INI:
jmp RtErrorOM_INI ;fatal error, never returns
STKCHK_NtParse EQU 400d ;actually 242, add 158 bytes for maintenance/uncertainty
;
;STKCHK_ToNtParse is the number of bytes of stack space needed to get from
; UserInterface (where caller ensures STACK_CHECK bytes exist between sp
; and b$pend) and NtParse().
;
STKCHK_ToNtParse EQU 350d ;actually 228d, add 122 for maintenance/uncertainty
cProc ParseInit,<FAR,PUBLIC>
cBegin ParseInit
;Runtime ensures we never enter the user interface with less
;than STACK_CHECK bytes free. Make sure that STACK_CHECK is big enough
;to satisfy parser's requirements.
DbAssertRel <STKCHK_ToNtParse+STKCHK_NtParse>,b,STACK_CHECK,CP,<ParseInit stk>
;Set static variable which prevents the recursive parser from
;over-running the memory allocated for stack space (b$pend)
mov ax,[b$pend]
add ax,STKCHK_NtParse
mov [stkChkParse],ax
; BdAlloc(&ps.bdpSrc, 0, (char)IT_NO_OWNERS_BDP)
mov ax,dataOFFSET ps.PS_bdpSrc
mov dl,IT_NO_OWNERS_BDP
sub cx,cx ;byte count = 0
call AllocBd1
; BdAlloc(&ps.bdpDst, 0, (char)IT_NO_OWNERS_BDP)
mov ax,dataOFFSET ps.PS_bdpDst
mov dl,IT_NO_OWNERS_BDP
mov cx,CB_PCODE_MIN ;never let bdpDst get smaller than
call AllocBd1 ; CB_PCODE_MIN, so we can always
; execute a SYSTEM, SETMEM, CLEAR stmt
; in direct mode.
; BdAlloc(&bdEMScratch, 0, (char)IT_NO_OWNERS)
mov ax,dataOFFSET bdEMScratch
call AllocBd
; BdAlloc(&ps.bdErr, 0, (char)IT_NO_OWNERS)
mov ax,dataOFFSET ps.PS_bdErr
call AllocBd
; BdAlloc(&bdParseUndo, 0, (char)IT_NO_OWNERS)
mov ax,dataOFFSET bdParseUndo
call AllocBd
jmp SHORT ParseErrInitStart
ParseInit ENDP
;Called during initialization and after errors
cProc ParseErrInit,<FAR>
cBegin ParseErrInit
ParseErrInitStart:
;set all token pointers start of circular token queue
mov ax,dataOFFSET tLookAhead
mov [pTokLast],ax
mov [pTokScan],ax
mov [pTokPeek],ax
mov [pExpTos],dataOFFSET stkExpInit
;reset NtExp's stack
; (for expression parsing)
cEnd ParseErrInit
;*********************************************************************
; void FAR ParseNewInit()
; Purpose:
; Called once during initialization and for NEW statement
; to change size of parser's source buffer to 256.
; ASCII Load can increase the size of the parser's source
; buffer to the length of the longest line loaded.
; Exit:
; ax = zero if out-of-memory
;
;*********************************************************************
cProc ParseNewInit,<PUBLIC,FAR>
cBegin
PUSHI ax,<dataOFFSET ps.PS_bdpSrc>
PUSHI ax,MIN_EDITLINE
call BdRealloc
or ax,ax
jz ParseNew_Exit
PUSHI ax,<dataOFFSET bdEMScratch>
PUSHI ax,MIN_EDITLINE
call BdRealloc
ParseNew_Exit:
cEnd
;*********************************************************************
; RudeIfErr
; Purpose:
; If current line gets any kind of error, we will descan to ss-rude.
; First, ask user if he wants to back out of edit for Edit & Continue.
; This is called before calling MakeVariable for CONST ID=1
; because if the line is never inserted, the variable table
; still contains the now bogus entry for ID.
; Exit:
; If user wants to back out of edit,
; ps.errCode = ER_IER (any error code would do other than ER_CN
; as long as PSERR_fAlert bit is not set, user will
; never see the error. Any non-zero value prevents
; us from calling MakeVariable for rest of this line.
; ps.flags PSF_UndoEdit bit is set, telling caller to back out of edit.
; else
; ps.flags PSF_RudeIfErr is set, telling caller of ParseLine
; to call ModuleRudeEdit if any error occurs before this
; line's pcode gets inserted into the text table.
;
;*********************************************************************
PUBLIC RudeIfErr
RudeIfErr PROC NEAR
call AskCantCont_CP ;see if user wants to back out of edit
jne RiNoBackOut ;brif not
mov ax,ER_IER
call ParseErr0 ;stop's subsequent calls to MakeVariable
or [ps.PS_flags],PSF_UndoEdit
ret
RiNoBackOut:
or [ps.PS_flags],PSF_fRudeIfErr
ret
RudeIfErr ENDP
;*********************************************************************
; void ParseUndoLog()
; Purpose:
; Called to remember something ParseUndo must handle if
; for any reason, this statement's pcode doesn't make it
; into a text table without errors.
; Entry:
; al = entry type (PUNDO_xxx)
; dx = type specific argument (oNam, oPrs, etc.)
; Exit:
; if out-of-memory, ps.errCode = ER_OM, [QB4]
; or MSG_LineTooLong [EB]
; ax = zero if out-of-memory, PSW set accordingly
;
;*********************************************************************
cProc ParseUndoLog,<PUBLIC,NEAR>
cBegin
push ax ;save entry type
push dx ;save entry argument
PUSHI ax,<dataOFFSET bdParseUndo>
PUSHI ax,3 ;size of 1 entry
call BdGrow ;allocate space for entry
pop dx ;pop entry argument
or ax,ax ;test return value from BdGrow()
pop ax ;al = entry type
je PulOm ;brif BdGrow returned out-of-memory
mov bx,[bdParseUndo.BD_pb]
add bx,[bdParseUndo.BD_cbLogical]
mov [bx-2],dx ;store entry argument
mov [bx-3],al ;store entry type
DbAssertRel ax,ne,0,CP,<ParseUndoLog: ax=0>
;ax = return value, condition codes already set
PulExit:
cEnd
PulOm:
call ParseErrOm ;set ps.errCode to ER_OM
sub ax,ax ;return 0 (out-of-memory)
jmp SHORT PulExit
;*********************************************************************
; void ParseUndo()
; Purpose:
; Called when line which was partially parsed by ParseLine is
; found to have an error. It undoes any static actions (like
; setting of name table bits) caused by ParseLine. It scans
; the entries created by ParseUndoLog and takes following actions:
; PUNDO_oNamAs - Call ChkLastAs to see if no other refs to
; oNam AS in pcode. If so, oNam's NM_fAs name table bit is reset.
; PUNDO_oPrsRef - call ChkDelPrs to see if PrsFree should
; be called for this prs, since no other refs to this prs exist.
;
;*********************************************************************
cProc ParseUndo,<PUBLIC,NEAR>,<si>
cBegin
mov si,[bdParseUndo.BD_pb]
PudLoop:
mov ax,[bdParseUndo.BD_pb]
add ax,[bdParseUndo.BD_cbLogical]
cmp si,ax
jae PudDone
lodsb ;al = entry type
dec al
lodsw ;ax = oNam/oPrs (flags unaffected)
jne NotAsType
.errnz PUNDO_oNamAs - 1
call ChkLastAs ;reset NM_fAs bit if appropriate
jmp SHORT PudLoop
NotAsType:
;ax = oPrs if SUB/FUNCTION/DECLARE
.errnz PUNDO_oPrsRef - 2
call UndefPrs ;tell txtmgr we deleted "defining" ref
jmp SHORT PudLoop
PudDone:
mov [bdParseUndo.BD_cbLogical],0
;so if we're called twice for
; the same line, the 2nd call will
; be a nop
cEnd
;*********************************************************************
; VOID NEAR MakeOpReParse()
; Purpose:
; This is called when some parse-time error is encountered.
; Discard current contents of ps.bdpDst and replace it with an
; opReParse token for the current source line.
; Entry:
; ps.bdpSrc contains the current 0-byte terminated source line
; Exit:
; If an out-of-memory error occured,
; ps.errCode = ER_OM
; ps.bdpDst contains garbage
; else
; ps.bdpDst contains opBol, opReParse(cTxt, link, text), opEot
; (the 0-byte terminator is not included in the opReParse)
;
;********************************************************************/
PUBLIC MakeOpReParse
MakeOpReParse PROC NEAR
call ResetDstPbCur ;discard any output produced thus far
.errnz opBol
mov al,[cInclNest] ;al = $INCLUDE nesting depth (0 if none)
and ax,0FFh ;ax=al, can't use cbw--doesn't set flags
je NotIncl ;brif source line isnt from include file
push ax
mov ax,opBolInclude
call Emit16_AX ;emit opBolInclude
pop ax ;ax = $INCLUDE nesting depth (0 if none)
NotIncl:
call Emit16_AX ;emit an opBol (or opBolIncl operand)
mov ax,opReParse
call Emit16_AX ;emit an opReParse
;Copy all of source buffer ps.bdpSrc to pcode buffer ps.bdpDst
PUSHI ax,0 ;EmitSrc(0, cbText)
push [ps.PS_bdpSrc.BDP_pb] ;pass ptr to 1st byte of source line
call CbSz ;ax = length of stmt
push ax ;pass to EmitSrc (below)
inc ax ;include room for link field
inc ax
call Emit16_AX ;emit count
call Emit16_0 ;leave room for link field
call EmitSrc ;parms were pushed several lines above
mov ax,opEot
jmp Emit16_AX ;emit ax and return to caller
MakeOpReParse ENDP
sEnd CP
end
⌨️ 快捷键说明
复制代码
Ctrl + C
搜索代码
Ctrl + F
全屏模式
F11
切换主题
Ctrl + Shift + D
显示快捷键
?
增大字号
Ctrl + =
减小字号
Ctrl + -