📄 prsnt.asm
字号:
call NtEndStatement
mov al,PR_GoodSyntax
je NtComExit ;branch if not end-of-statement
jmp PErrExpExpr ;Error: expected expression
; return al = PR_BadSyntax
NoComma:
sub al,al ;return PR_NotFound
NtComExit:
cEnd
;**********************************************************************
; PARSE_RESULT NEAR NtEndPrint()
;
; Purpose:
; Called during a PRINT expression list.
;
; Exit:
; Always returns PR_NotFound.
;
;******************************************************************
cProc NtEndPrint <PUBLIC,NEAR>
cBegin NtEndPrint
mov ax,IRW_ELSE
call TestScan_AX
je GotPrintEos ;branch if current token is ELSE
call NtEndStatement ;check for end-of-statement
je NotPrintEos ;branch if not end-of-statement
GotPrintEos:
cmp [fNeedPrintEos],FALSE
je NotPrintEos ;branch if we don't need to emit
mov ax,opPrintEos ; opPrintEos to terminate the PRINT
call Emit16_AX
NotPrintEos:
mov [fNeedPrintEos],0FFh ;set flag to TRUE (non-zero)
sub al,al ;return(PR_NotFound)
cEnd NtEndPrint
;**********************************************************************
; PARSE_RESULT NEAR NtEndPrintExp()
;
; Purpose:
; Called during a PRINT expression list after an expression has been
; parsed.
;
; Exit:
; Always returns PR_GoodSyntax.
;
;******************************************************************
cProc NtEndPrintExp <PUBLIC,NEAR>
cBegin NtEndPrintExp
mov ax,IRW_ELSE
call TestScan_AX ;see if current token is ELSE
je GotPrExpEos ;branch if it is
call NtEndStatement ;see if current token is end-of-stmt
je NotPrExpEos ;branch if not
GotPrExpEos:
mov ax,opPrintItemEos
call Emit16_AX ;emit end-of-stmt print terminator
mov [fNeedPrintEos],FALSE ;so NtEndPrint() won't terminate
jmp SHORT NtEndPrGoodSyntax ; print item list with opPrintEos
NotPrExpEos:
mov ax,opPrintItemSemi
call Emit16_AX
NtEndPrGoodSyntax:
mov al,PR_GoodSyntax
cEnd NtEndPrintExp
;**********************************************************************
; STATICF(uchar) TestLet()
;
; Purpose:
; Test to see if 'pTokScan' is a 1 letter identifier from 'A' - 'Z'
;
; Exit:
; al = 0..25 for A-Z and a-z.
; 26 if its not an ID from A-Z.
;
;******************************************************************
cProc TestLet <PUBLIC,NEAR>
cBegin TestLet
mov bx,[pTokScan] ;bx points to current token
mov ax,26D ;prepare for FALSE return
cmp [bx.TOK_class],CL_id
jne TestLetExit ;branch if not an id token
mov al,[bx.TOK_id_charFirst]
;al = id's 1st char
TestLetExit:
cEnd TestLet
;**********************************************************************
; PARSE_RESULT NEAR NtDeflistXX()
;
; Purpose:
; Parse a letter range like "A-F,X" for statements like DEFINT.
; If it is not recognized at all, return value is PR_NotFound.
; If it is only partially found, like "A-", return value is PR_BadSyntax.
; If it is found, a 32 bit mask is emitted, the tokens are consumed
; and the return value is PR_GoodSyntax.
;
; Exit:
; Emits <opStDefType><link field><low-word><high-word>
; where
; <high-word> has 1 bit set for each letter from A..P
; <low-word> has 1 bit set for each letter from Q..Z in the
; high bits, and type (ET_I2..ET_SD) in the low 3 bits.
; Updates ps.tEtCur[]
; It never returns PR_NotFound because the bnf guarentees that
; nothing else can follow DEFINT.
;
;******************************************************************
SKIP2_BX MACRO
db 0BBH ;mov bx,<immediate word>
ENDM
PUBLIC NtDefListR4
NtDefListR4 PROC NEAR
mov al,ET_R4
SKIP2_BX ;load next 2 bytes to bx (fall through)
NtDefListR4 ENDP
;fall through
PUBLIC NtDefListI2
NtDefListI2 PROC NEAR
mov al,ET_I2
SKIP2_BX ;load next 2 bytes to bx (fall through)
NtDefListI2 ENDP
;fall through
PUBLIC NtDefListI4
NtDefListI4 PROC NEAR
mov al,ET_I4
SKIP2_BX ;load next 2 bytes to bx (fall through)
NtDefListI4 ENDP
;fall through
PUBLIC NtDefListR8
NtDefListR8 PROC NEAR
mov al,ET_R8
SKIP2_BX ;load next 2 bytes to bx (fall through)
NtDefListR8 ENDP
;fall through
PUBLIC NtDefListSD
NtDefListSD PROC NEAR
mov al,ET_SD
NtDefListSD ENDP
;fall through
;register conventions:
; bl = 1st char of A-Z pair
; bh = 2nd char of A-Z pair
; si points to maskCur
;
cProc NtDeflist <PUBLIC,NEAR>,<si,di>
localW maskSumLOW
localW maskSumHIGH
localB oTyp
cBegin NtDeflist
mov [oTyp],al ;save input parm
sub ax,ax
lea si,[maskSumHIGH] ;si doesn't change for rest of NtDeflist
mov [si],ax ;maskSumHIGH = 0
mov [si+2],ax ;maskSumLOW = 0
DefListLoop:
call TestLet ;al = 1st letter of current token
cmp al,26D
jne GotValidLetter ;branch if got a valid letter
DefExpLetter:
;Got something like DEFINT <end-of-stmt> or DEFINT A-B,
mov ax,MSG_Letter ;Error: expected letter
call PErrExpMsg_AX ; al = PR_BadSyntax
jmp short DefListExit
GotValidLetter:
mov bl,al ;bl = 1st char
mov bh,al ;default bh 2nd char to 1st char
mov di,bx ;save letters in di
call ScanTok ;skip 1st letter
mov ax,IRW_Minus ;check for '-'
call TestScan_AX
jne NoDefDash ;branch if no '-'
call ScanTok ;skip '-'
call TestLet ;al = 1st letter of current token
cmp al,26D
je DefExpLetter
mov bx,di ;restore bl = 1st char
mov bh,al ;bh = 2nd char of A-Z pair
mov di,bx
call ScanTok ;skip 2nd letter
NoDefDash:
mov bx,di ;restore bl,bh = 1st,2nd chars
cmp bl,bh
jbe SetTheBits ;branch if 1st char <= 2nd char
xchg bl,bh ;Treat DEFINT S-A same as DEFINT A-S
;bl = 1st char to set, bh = last char to set (0..25)
;cl = current letter (0..25)
;ax:dx = maskCur
;
SetTheBits:
mov ax,08000H
sub dx,dx ;maskCur = 0x80000000
mov cl,dl ;current letter = 0
BitSetLoop:
cmp cl,bh ;compare current with final
ja BitSetEnd ;branch if end of loop
cmp cl,bl
jb DontSetThisOne
or [si],ax ;or ax:dx bits into maskSum
or [si+2],dx
DontSetThisOne:
shr ax,1 ;shift ax:dx right by 1
rcr dx,1
inc cl ;bump current char
jmp SHORT BitSetLoop
BitSetEnd:
mov ax,IRW_Comma
call TestScan_AX
jne DefEndOfList ;branch if no comma
call ScanTok ;skip comma
jmp DefListLoop
DefEndOfList:
mov ax,opStDefType
call Emit16_AX
call Emit16_0 ;leave room for link field
mov ax,[si+2] ;ax = low word
or al,[oTyp] ;or oTyp into low 6 bits
call Emit16_AX ;emit low word first
mov ax,[si] ;emit high word second
call Emit16_AX
;update ps.tEtCur[] for source lines like DEFINT A-Z:b=1
lodsw ;ax = maskSumHIGH
push ax
push [si] ; maskSumLOW
mov bl,[oTyp] ;bl = ET_xxx to set
push bx
call far ptr SetDefBits ; update ps.tEtCur table
mov al,PR_GoodSyntax
DefListExit:
cEnd NtDeflist
;**********************************************************************
; SetDefBits
; Purpose:
; Update the current default-type array as a result of scanning
; a DEFINT..DEFSTR statement
; This is used by both the Parser and Static Scanner
; Entry:
; maskSumHIGH:maskSumLOW = DEFTYPE bit mask, as would appear in
; opStDefType's operand
; defET = ET_xxx to store in si for each bit set in ax:dx
; ps.tEtCur filled with current default types (one ET_xxx for each letter)
; Exit:
; ps.tEtCur is updated according to mask
;
;**********************************************************************
cProc SetDefBits,<PUBLIC,FAR>,<SI>
parmW maskSumLOW
parmW maskSumHIGH
parmB defET
cBegin
mov si,dataOFFSET ps.PS_tEtCur
;si points to table to be updated
mov cx,26D ;cx = repeat count (1 for each letter)
mov dx,[maskSumHIGH]
mov ax,[maskSumLOW]
mov bl,[defET]
BitTestLoop:
shl dx,1 ;shift ax:dx left 1
rcl ax,1
jnc BitNotSet ;branch if this bit is not set
mov [si],bl ;store new type in type table
BitNotSet:
inc si ;advance to next byte
loop BitTestLoop
cEnd
;======================================================================
; Ambiguous Statement resolving functions.
;
; These functions are needed where the BNF specifies 2 or more
; statements which begin with the same keyword. These functions
; look ahead in the pcode to decide which of the statements we're
; really looking at.
;
;==================================================================
OSTMT1 EQU 0 ; offset from current position in reserved word table
; for the first (as ordered in bnf.prs)
; of the possible statements.
OSTMT2 EQU 6 ; offset for the second possible statement
;*******************************************************************************
; ushort NEAR AmDEF()
;
; Purpose:
; Determine if statement is a DEF FN or a DEF SEG statement.
; Exit:
; ax = offset into reserved word entry for correct statement
;
;***************************************************************************
PUBLIC AmDef
AmDef PROC NEAR
mov ax,IRW_SEG
jmp SHORT AmCommon
AmDef ENDP
;*******************************************************************************
; ushort NEAR AmGET(), AmPut()
;
; Purpose:
; Determine if statement is a graphics or I/O GET/PUT.
;
; Method:
; If GET/PUT is followed by a left paren or STEP, this must be
; a graphics GET/PUT.
;
;***************************************************************************
PUBLIC AmGet
AmGet PROC NEAR
AmGet ENDP
;fall into AmPut
PUBLIC AmPut
AmPut PROC NEAR
call Peek1Tok
mov ax,IRW_STEP
call TestPeek_AX
je AmGotExpected ;brif followed by STEP
mov ax,IRW_LParen
jmp SHORT AmTestPeek ;see if followed by '('
AmPut ENDP
;*******************************************************************************
; ushort NEAR AmLINE()
;
; Purpose:
; Determine whether statement is a LINE INPUT or a graphics
; LINE statement.
;
; Method:
; We just look at the next token in the input stream. If it is INPUT, then
; we know it's a LINE INPUT, else it's a graphics line command.
;
;***************************************************************************
PUBLIC AmLine
AmLine PROC NEAR
mov ax,IRW_INPUT
AmLine ENDP
;fall into AmCommon
; Entry:
; ax = reserved word id (IRW_xxx) for token for 2nd stmt in list
; Exit:
; ax = OSTMT2 if reserved word found, OSTMT1 (0) if not
;
AmCommon PROC NEAR
push ax
call Peek1Tok ;peek at next token
pop ax ;ax = token we're looking for
AmTestPeek:
call TestPeek_AX
AmGotExpected:
mov ax,OSTMT2 ;assume next token is [ax]
je AmExit ;branch if next token is [ax]
sub ax,ax ;ax = 0
AmExit:
ret
AmCommon ENDP
;*******************************************************************************
; ushort NEAR AmPLAY()
;
; Purpose:
; Determine if we're starting a PLAY event switch statement,
; or the standard PLAY statement.
;
;***************************************************************************
PLAY_STMT EQU 0
PLAY_EVENT EQU 6
PUBLIC AmPlay
AmPlay PROC NEAR
call Peek1Tok ;peek at next token
mov ax,IRW_ON
call TestPeek_AX
je AmPlayEvent ;branch if next token is ON
mov ax,IRW_OFF
call TestPeek_AX
je AmPlayEvent ;branch if next token is OFF
mov ax,IRW_STOP
call TestPeek_AX
je AmPlayEvent ;branch if next token is STOP
sub ax,ax ;ax = PLAY_STMT
jmp SHORT AmPlayExit
AmPlayEvent:
mov ax,PLAY_EVENT
AmPlayExit:
ret
AmPlay ENDP
CP ENDS
end
⌨️ 快捷键说明
复制代码
Ctrl + C
搜索代码
Ctrl + F
全屏模式
F11
切换主题
Ctrl + Shift + D
显示快捷键
?
增大字号
Ctrl + =
减小字号
Ctrl + -