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

📄 prscg.asm

📁 [随书类]Dos6.0源代码
💻 ASM
📖 第 1 页 / 共 3 页
字号:
	TITLE	prscg.asm - Parser Code Generation Functions

;==========================================================================
;
;  Module:  prscg.asm - Parser Code Generation Functions
;  Subsystem:  Parser
;  System:  Quick BASIC Interpreter
;
;==========================================================================

	include		version.inc
	PRSCG_ASM = ON
	includeOnce	architec
	includeOnce	context
	includeOnce	heap
	includeOnce	opmin
	includeOnce	opcontrl
	includeOnce	opstmt
	includeOnce	opintrsc
	includeOnce	parser
	includeOnce	pcode
	includeOnce	prstab
	includeOnce	psint
	includeOnce	qbimsgs
	includeOnce	rtps
	includeOnce	scanner
	includeOnce	txtmgr
	includeOnce	ui
	includeOnce	util
	includeOnce	variable


;--------------------------------------------------------------------------
;			Code Generation Overview
;
; During the course of interpreting the parse state tables, NtParse()
; encounters MARK(nnn) directives.  These cause NtParse to push
; the current pcode offset and the constant nnn onto a stack as follows:
;
; Given BNF of
;     exp MARK(1) exp MARK(2) exp
;
; Before parsing the statement, the marker stack looks like:
;    high memory:
;	maxStkMark-->        <--pCurStkMark
;           :
;	minStkMark-->
;    low memory:
;
; After parsing the statement, but before calling the code generation
; function for the statement, the marker stack looks like:
;    high memory:
;	maxStkMark-->[oDstPcode]
;
;                    [oDstPcode]
; <--pCurStkMark
;           :
;	minStkMark-->
;    low memory:
;
; Code generation functions use the information on the marker stack to
; decide how to alter pcode already emitted to the pcode buffer during
; parsing.
; An Argument may be passed to a code generation function in ax.
;
;--------------------------------------------------------------------------

assumes	ds,DATA
assumes	ss,DATA
assumes	es,NOTHING

sBegin	DATA
sEnd	DATA

sBegin	CP
assumes	cs,CP

;*********************************************************************
; VOID InsertOp(ax:opcode, bx:oDst)
;
; Purpose:
;	Insert an opcode at a given offset into the pcode buffer
;	If out-of-memory, ps.errCode = ER_OM on exit
;
; Entry:
;	bx = offset into ps.bdpDst where word is to be inserted
;	ax = word to be inserted
; Exit:
;	Caller's can depend on bx being preserved
;	If an out-of-memory error occurs, ps.errCode = ER_OM
;
;*********************************************************************
InsertOp PROC NEAR
	;make room for 2 bytes in pcode buffer before oDst
	; BdShiftRight((bd *)&ps.bdpDst, oDst, (ushort)2))
	
	push	bx			;save caller's bx
	push	ax			;save opcode
	push	bx			;save oDst

	PUSHI	ax,<dataOFFSET ps.PS_bdpDst>
	push	bx			;pass oDst
	PUSHI	ax,2
	call	BdShiftRight		;grow buf, can cause heap movement
	or	ax,ax
	je	InsOpOmErr		;brif out-of-memory
	call	SetDstPbCur		;update ps.bdpDst.pbCur,

	pop	bx			;restore bx = oDst
	add	bx,[ps.PS_bdpDst.BDP_pb]
	pop	[bx]			;pop and store opcode
InsOpExit:
	pop	bx			;restore caller's bx
	ret

InsOpOmErr:
	call	ParseErrOm		;Error "Out of memory"
	pop	bx
	pop	ax
	jmp	SHORT InsOpExit
InsertOp ENDP

;*********************************************************************
; VOID NEAR CgOn(ax:opcode)
;
; Purpose:
;	Called after the RESTORE/RETURN statement has been parsed.
;	It generates code for the statement.
;
; Entry:
;	The top of the MARK stack (*pCurStkMark) is 1 or 2 for
;	   1 for RESTORE
;	   2 for RESTORE <label>
;	opcode = the opcode to emit if top of MARK stack = 1
;	   This can be opStRestore0 or opStReturn0
;
;	The bnf which causes this to occur is:
;	  tkON (event (tkGOSUB ((Lit0 EMIT(opEvGosub) EMIT(UNDEFINED)) |
;			(EMIT(opEvGosub) LabLn)))) |
;	    (tkERROR tkGOTO ((Lit0 EMIT(opStOnError) EMIT(UNDEFINED)) |
;			(EMIT(opStOnError) LabLn))) |
;	    (Exp (tkGOTO MARK(1) | tkGOSUB MARK(2)) LabLn {tkComma LabLn})
;	<CgOn()>
;
;*********************************************************************
PUBLIC	CgOn
CgOn	PROC NEAR
	mov	bx,[pCurStkMark]
	cmp	bx,MAX_STK_MARK
	je	OnExit			;brif no MARK directives from BNF
	push	[bx]			;save markId

	mov	bx,[bx+2]		;bx = offset into pcode which preceeded
					; markId
	mov	ax,[ps.PS_bdpDst.BDP_cbLogical]
	sub	ax,bx			;ax = byte count of operands
	call	InsertOp		;insert word AX at offset BX
					; (bx is preserved)
	pop	ax			;restore ax = markId
	cmp	al,1			;markId
	mov	ax,opStOnGoto
	je	GotGoto			;brif if MARK(1) directive (GOTO)
	mov	ax,opStOnGosub		;else it must be MARK(2) (GOSUB)
GotGoto:
	call	InsertOp		;insert word AX at offset BX
OnExit:
	ret
CgOn	ENDP

;*********************************************************************
; VOID NEAR CgInsert0or1(opcode)
;
; Purpose:
;	Called after the RESTORE/RETURN statement has been parsed.
;	It generates code for the statement.
;	If out-of-memory, ps.errCode = ER_OM on exit
;
; Entry:
;	The top of the MARK stack (*pCurStkMark) is 1 or 2 for
;	   1 for RESTORE/RETURN/RESUME
;	(generated pcode = opStRestore0/opStReturn0/opStResume0)
;	   2 for RESTORE/RETURN/RESUME <label>
;	(generated pcode = opStRestore1/opStReturn1/opStResume <label>)
;	   3 for RESUME 0
;	(generated pcode = opStResume <UNDEFINED>)
;	   4 for RESUME NEXT
;	(generated pcode = opStResumeNext)
;
;	opcode = the opcode to emit if top of MARK stack = 1
;	   This can be opStRestore0, opStReturn0, or opStResume0
;
;	The bnf which causes this to occur is:
;	   tkRESTORE MARK(1) [LabLn MARK(2)]
;	 <CgInsert0or1(opStRestore0)>
;	   tkRETURN MARK(1) [LabLn MARK(2)]
;	 <CgInsert0or1(opStReturn0)>
;	   tkRESUME MARK(1) [(LabLn MARK(2)) | (Lit0 MARK(3)) |
;	                     (tkNEXT MARK(4))]
;	<CgResume(opStResume0)>
;
;*********************************************************************
PUBLIC	CgInsert0or1
CgInsert0or1 PROC NEAR
	xchg	dx,ax			;save opcode in dx
	mov	bx,[pCurStkMark]
	mov	al,[bx]			;al = markId
	cmp	al,1
	je	InsMark1		;brif got RESUME or RETURN or RESTORE
					; with no parameter
	cmp	al,2
	je	InsMark2
	cmp	al,3
	je	InsMark3		;brif got RESUME 0

;else it must be MARK(4) RESUME NEXT
	mov	ax,opStResumeNext
	jmp	SHORT InsEmit

;got RESUME or RETURN or RESTORE with no parameter
InsMark1:
	xchg	ax,dx			;ax = opcode
InsEmit:
	call	Emit16_AX
	jmp	SHORT InsExit

InsMark2:
	push	dx			;save opcode

	;make room for 2 more bytes at end of pcode buffer
	PUSHI	ax,<dataOFFSET ps.PS_bdpDst>
	PUSHI	ax,2
	call	BdGrow			;grow buf, can cause heap movement
	or	ax,ax
	je	InsOmErr
	;move label's oNam forward in buffer by 2 bytes
	mov	bx,[ps.PS_bdpDst.BDP_pbCur]
	mov	ax,[bx-2]
	mov	[bx],ax

	;Insert opcode before label's oNam
	pop	ax			;ax = opcode
	inc	ax			;map to opcode variant with no parm
					; opStResumeLab opStRestoreLab or
					; opStReturnLab
	mov	[bx-2],ax		;store opcode
	call	SetDstPbCur		;update ps.bdpDst.pbCur
	jmp	SHORT InsExit

;map RESUME 0 to opStResume(UNDEFINED)
InsMark3:
	mov	ax,opStResume
	call	Emit16_AX
	mov	ax,UNDEFINED
	call	Emit16_AX
InsExit:
	ret

InsOmErr:
	jmp	ParseErrOm		;Error "Out of memory"
					; and return to caller
CgInsert0or1 ENDP

;*********************************************************************
; ErrIfPrsHasTxtTbl()
; Purpose:
;	If the current prs (prsCur) has a text table, generate an error.
;	This is called by functions which are about to do something which
;	can only be done to a "compiled" (external) procedure, not a
;	pcoded procedure.
;
; Exit:
;	returns FALSE if prsCur has a text table (condition codes set)
;
;*********************************************************************
ErrIfPrsHasTxtTbl PROC NEAR
	sub	ax,ax			;prepare to return FALSE
	test	[txdCur.TXD_flags],FTX_mrs
	jne	ErrNoText		;brif prs has no text table
	mov	ax,MSG_InvDecl OR PSERR_fAlert
	call	ParseErr0
	mov	ax,sp			;return TRUE (non-zero)
ErrNoText:
	or	ax,ax			;set condition codes for caller
	ret	
ErrIfPrsHasTxtTbl ENDP

;*********************************************************************
; VOID NEAR CgDeclare(opcode)
;
; Purpose:
;	Called after the DECLARE, SUB, FUNCTION or DEF FN statement has
;	been parsed.  It generates code for the statement.
;	The prs has already been created (by MakeProc in prsid.asm),
;	and is active for all statements except DECLARE.
;
; Entry:
;	Structure pdcl is filled in by parser terminal recognizers like
;	   NtIdSubDecl, NtIdFn [QB4], etc. to describe to prs being declared/defined
;	The MARK stack (*pCurStkMark) contains entries built by the bnf:
;	   MARK 1    indicates CDECL was present
;	   MARK 2 -> ALIAS's string literal
;	   MARK 3 -> start of formal parm list
;	   MARK 4    indicates STATIC was found
;	   MARK 5 -> single line DEF FN's definition expression
;	   MARK 6    indicates ([parmlist]) was seen
;	   MARK 7 -> LIB's string literal	[EB specific] [07]
;	   MARK 8    indicates AUTO was found	[EB specific] [07]
;
;	BNF which builds entry pcode:
;	   tkDECLARE
;	      (tkFUNCTION IdFuncDecl [tkCDECL MARK(1)]
;	         [tkALIAS MARK(2) LitString] MARK(3) parms) |
;	      (tkSUB IdSubDecl [tkCDECL MARK(1)] 
;	         [tkALIAS MARK(2) LitString] MARK(3) parms)
;	     <CgDeclare(opStDeclare)>
;	   tkDEF IdFn MARK(3) parms [tkEQ MARK(5) Exp]
;	     <CgDeclare(opStDefFn)>
;	   tkFUNCTION IdFuncDef MARK(3) parms [tkSTATIC MARK(4)]
;	     <CgDeclare(opStFunction)>
;	   tkSUB IdSubDef MARK(3) parms [tkSTATIC MARK(4)]
;	     <CgDeclare(opStSub)>
;
;	For the statement DECLARE SUB X CDECL ALIAS "abc" (BYVAL A(), B, ...)
;	The pcode buffer contains:
;	              <"abc"> <idA> <idB> ...
;	MARK(1)MARK(2)^MARK(3)^
;
;	For the statement SUB X (BYVAL A(), B, ...) STATIC
;	The pcode buffer contains:
;	       <idA> <idB> ...
;	MARK(3)^MARK(8)
;
;	Where <idX> is 3 16 bit words:  oPrs, oNamProc, oTypProc
;
;*********************************************************************
cProc	CgDeclare,<PUBLIC,NEAR,NODATA>,<si,di>
	localW	opcode
	localW	oDstParms
	localW	oDstAlias
	localW	oDstEndDef
	localW	cbLibInfo
	localW	procAtr
	procAtr_LO EQU  BYTE PTR (procAtr)
	procAtr_HI EQU  BYTE PTR (procAtr+1)
cBegin
	mov	[opcode],ax
	mov	ax,[ps.PS_bdpDst.BDP_cbLogical]
	mov	[oDstEndDef],ax		;save current size of output

	sub	ax,ax
	mov	[procAtr],ax
	mov	[oDstAlias],ax
	mov	[cbLibInfo],ax
	mov	al,[pdcl.PDCL_procType]
	.errnz	DCLA_procType - 0300h
	or	[procAtr_HI],al		;save procType in pcode field
	mov	al,[pdcl.PDCL_oTyp]	;al = value for low byte of ProcAtr
					;  word which DCLA_Explicit,
					;  DCLA_AsClause, and DCLA_oTyp
	mov	[procAtr_LO],al		;save oTyp in pcode field
	sub	ax,ax
	cmp	[pdcl.PDCL_fDeclare],al
	je	NotDeclare		;brif not DECLARE stmt

⌨️ 快捷键说明

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