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

📄 prscg.asm

📁 [随书类]Dos6.0源代码
💻 ASM
📖 第 1 页 / 共 3 页
字号:

;It was INPUT, not LINE INPUT
;insert opStInputPrompt[cbOperands:16,mask:8,types:8]
;don't count string literal in cInputItems (its in cIdArgs)
;count mask in cInputItems (cancels string literal)
;di = bit mask (built by ORing markIds)
;ax = opcode
;
NotLineInput:
	push	ax			;save opcode on stack
	mov	ax,[cIdArgs]
	shr	ax,1			;round down to word count
	mov	cx,ax			;cx = word count
	mov	bx,si			;bx = oDstOpcode (place to insert ops)
	jcxz	InpLoopDone

;emit garbage typelist (scanner will fill in)
InpLoop:
	push	cx			;save word count
	call	InsertOp		;insert word AX at offset BX
					;any value in ax would do, scanner fills
					; (bx is preserved)
	pop	cx			;restore word count
	loop	InpLoop

;now emit mask and space for 1st entry in type list
InpLoopDone:
	mov	ax,di
	and	al,7			;mask off bits > 7
	call	InsertOp		;insert word AX at offset BX
					; (bx is preserved)
	mov	ax,[cIdArgs]
	inc	ax
	call	InsertOp		;insert word AX at offset BX
					; (bx is preserved)
	pop	ax			;ax = opcode (pushed ~25 lines above)
	call	InsertOp		;insert word AX at offset BX
InpExit:
	pop	di			;save caller's di
	pop	si			;save caller's si
	ret
CgInput	ENDP

;*********************************************************************
; CgStmtCnt(opcode)
; Purpose:
;	Called for statements like CLEAR, CLOSE, COLOR, ERASE, FIELD, LOCATE
;	and SCREEN, which take as an operand the number of arguments
;	preceding them.
;
;*********************************************************************
PUBLIC	CgStmtCnt
CgStmtCnt PROC NEAR
	call	Emit16_AX		;emit the opcode
	mov	ax,[cIdArgs]
	jmp	Emit16_AX		;emit the arg count
					;and return to caller
CgStmtCnt	ENDP

;*********************************************************************
; CgCntHigh(opcode)
;
; Purpose:
;
;   Called for the Format$ function.
;
;*********************************************************************

	;Added with [11]


	;End of [11]

;*********************************************************************
; CgLineStmt(opcode)
;
; Purpose:
;	Invoked to generate code for the following bnf:
;	   tkLINE [coordStep] tkMinus coord2Step
;	[tkComma [Exp MARK(1)]
;	  [tkComma [(RwBF MARK(3)) | (RwB (RwF MARK(3)) | MARK(2))]
;	    [tkComma Exp MARK(4)]]]
;	<CgLineStmt(opStLine)>
;
;*********************************************************************
PUBLIC	CgLineStmt
CgLineStmt PROC NEAR
	push	si			;save caller's si
	sub	dx,dx			;operand = 0
	mov	cx,ax			;cx = opcode
	mov	si,[pCurStkMark]
LineLoop:
	cmp	si,MAX_STK_MARK
	je	LineLoopDone
	lodsw				;ax = markId
	inc	si			;skip oDstPcode
	inc	si
	dec	ax
	je	LineMark1		;brif MARK(1)
	dec	ax
	je	LineMark2		;brif MARK(2)
	dec	ax
	je	LineMark3		;brif MARK(3)

;MARK(4) means line style parm was specified
	inc	cx			;convert opStLine, opStLineColor->
					; opStLineStyle, opStLineColorStyle
	;fall into case 1
;MARK(1) means color parm was specified
LineMark1:
	inc	cx			;convert opStLine to opStLineColor
	jmp	SHORT LineLoop

;MARK(2) means B parm was specified
LineMark2:
	mov	dl,1			;operand = 1
	jmp	SHORT LineLoop

LineMark3:
;MARK(3) means BF parm was specified
	mov	dl,2			;operand = 2
	jmp	SHORT LineLoop

LineLoopDone:
	push	dx			;pass operand to Emit16 below
	xchg	ax,cx			;ax=opcode for Emit16_AX
	call	Emit16_AX		;emit the opcode
	call	Emit16			;emit the operand
	pop	si			;restore caller's si
	ret
CgLineStmt ENDP

;*********************************************************************
; CgOpen(opcode)
;
; Purpose:
;	Invoked to generate code for the following bnf:
;  tkOPEN Exp
;   ([(tkFOR ((tkAPPEND  MARK(1)) |
;             (tkINPUT   MARK(2)) | 
;             (tkOUTPUT  MARK(3)) |
;             (tkRANDOM  MARK(4)) |
;             (tkBINARY  MARK(5))))]
;    [tkACCESS ((tkREAD  MARK(6) [tkWRITE MARK(8)]) | (tkWRITE MARK(7)))]
;    [(tkLOCK ((tkREAD ((tkWRITE MARK(11)) | MARK(9))) |
;              (tkWRITE MARK(10)))) |
;     (tkSHARED MARK(12))]
;    tkAS optFilenum [tkLEN tkEQ Exp MARK(13)])  |
;   (tkComma optFilenum exp12 MARK(14))
;     <CgOpen(opStOpen2)>
;
;*********************************************************************
tModeMask LABEL WORD
	DW MD_APP		; MARK(1) means APPEND was specified
	DW MD_SQI		; MARK(2) means INPUT was specified
	DW MD_SQO		; MARK(3) means OUTPUT was specified
	DW MD_RND		; MARK(4) means RANDOM (or default) was speced
	DW MD_BIN		; MARK(5) means BINARY was specified
	DW ACCESS_READ * 256	; MARK(6) means READ was specified
	DW ACCESS_WRITE * 256	; MARK(7) means WRITE was specified
	DW ACCESS_BOTH * 256	; MARK(8) means READ WRITE was specified
	DW LOCK_READ * 256	; MARK(9) means LOCK READ was specified
	DW LOCK_WRITE * 256	; MARK(10) means LOCK WRITE was specified
	DW LOCK_BOTH * 256	; MARK(11) means LOCK READ WRITE was specified
	DW LOCK_SHARED * 256	; MARK(12) means SHARED was specified

PUBLIC	CgOpen
CgOpen	PROC NEAR
	push	si			;save caller's si
	mov	cx,ax			;cx = opcode
	sub	dx,dx			;mode = 0
	mov	si,[pCurStkMark]
OpenLoop:
	cmp	si,MAX_STK_MARK
	je	OpenLoopDone
	lodsw				;ax = markId
	inc	si			;skip pcode offset
	inc	si
	cmp	al,14
	je	OpenMark14
	cmp	al,13
	je	OpenMark13
	;mode |= tModeMask[markId - 1]
	xchg	bx,ax			;bx = markId
	shl	bx,1			;convert to word index
	mov	ax,tModeMask - 2[bx]	;ax = mask
	or	dx,ax			;or mask into mode
	jmp	SHORT OpenLoop

;MARK(13) means LEN=nnn was specified
OpenMark13:
	inc	cx			;convert opStOpen2 to opStOpen3
	jmp	SHORT OpenLoop

OpenLoopDone:
	push	dx			;save mode
	xchg	ax,cx			;emit opcode
	call	Emit16_AX
	pop	ax			;ax = open mode
	test	al,MD_APP OR MD_SQI OR MD_SQO OR MD_RND OR MD_BIN
	jne	OpenEmitExit		;brif open mode was specified
	or	al,MD_DEFAULT		;default open mode
OpenEmitExit:
	call	Emit16_AX		;emit open mode
	pop	si			;restore caller's si
	ret

;MARK(14) means old open syntax
OpenMark14:
	mov	ax,[cIdArgs]
	add	ax,opStOpenOld3 - 3	;ax = old open opcode
	jmp	SHORT OpenEmitExit

CgOpen	ENDP

;*********************************************************************
; CgLock(opcode)
;
; Purpose:
;	Invoked to generate code for the following bnf:
;	tkLOCK optFileNum
;	 (tkComma (Exp MARK(1) [tkTO MARK(2) Exp]) | (tkTO MARK(3) Exp]))
;	   <CgLock(opStLock)>
;	tkUNLOCK optFileNum
;	 (tkComma (Exp MARK(1) [tkTO MARK(2) Exp]) | (tkTO MARK(3) Exp]))
;	   <CgLock(opStLock)>
;
;*********************************************************************
PUBLIC	CgLock
CgLock	PROC NEAR
	push	si			;save caller's si
	push	di			;save caller's di
	mov	di,ax			;di = opcode
	sub	dx,dx			;mode = markId = 0
	cmp	ax,opStUnLock
	jne	NotUnlock
	mov	dl,LOCK_UNLOCK		;mode = LOCK_UNLOCK
NotUnlock:
	mov	si,[pCurStkMark]
LockLoop:
	cmp	si,MAX_STK_MARK
	je	LockLoopDone		;brif done with MARK directives
	lodsw				;al = markId
	xchg	cx,ax			;cl = markId
	lodsw				;ax = oDstOpcode
	cmp	cl,1
	jne	NotMark1		;brif not MARK(1)
	test	dl,LOCK_1stToLast
	jne	NotMark1		;brif MARK(2) was seen
	or	dh,LOCK_DefLastArg/256	;tell executor to default last record
NotMark1:
	cmp	cl,3
	jne	NotMark3		;brif not MARK(3)
	xchg	bx,ax			;bx = oDstOpcode
	;Emit default 1st record before the 2nd Exp
	push	dx			;save dx
	.erre	opLitI2Max GE 1 	; Assure 1 is allowed
	mov	ax,opLitI2+OPCODE_MASK+1; pass opLitI2 with value of 1
	call	InsertOp		;insert word AX at offset BX
					; (bx is preserved)
	pop	dx			;restore dx = mode & markId
	or	dh,LOCK_Def1stArg/256	;tell lister to default 1st record
NotMark3:
	or	dl,LOCK_1stToLast
	jmp	SHORT LockLoop

LockLoopDone:
	push	dx			;pass mode to 2nd call of Emit16
	xchg	ax,di			;pass opcode to Emit16_AX
	call	Emit16_AX		;emit the opcode
	call	Emit16			;emit the mode operand
	pop	di			;restore caller's di
	pop	si			;restore caller's si
	ret
CgLock	ENDP

PUBLIC	Cg0or1Args, Cg1or2Args, Cg2or3Args, Cg3or4Args
Cg3or4Args PROC NEAR
	dec	ax
Cg3or4Args ENDP				;fall into Cg2or3Args
Cg2or3Args PROC NEAR
	dec	ax
Cg2or3Args ENDP				;fall into Cg1or2Args
Cg1or2Args PROC NEAR
	dec	ax
Cg1or2Args ENDP				;fall into Cg0or1Args
Cg0or1Args PROC NEAR
	mov	dx,ax			;save base opcode in dx
	add	ax,[cIdArgs]		;ax = opcode + cIdArgs
	cmp	dx,opStMid_2 - 3
	je	CgMoveOpsToEnd		;brif MID$ statement
J1_Emit16_AX:
	jmp	Emit16_AX		;emit ax and return to caller
Cg0or1Args ENDP


;*********************************************************************
; CgMoveOpsToEnd(opcode)
;
; Purpose:
;	Invoked to generate code for the following bnf:
;	  tkLSET MARK(1) idAryElemRef MARK(2) tkEQ Exp
;	    CgMoveOpsToEnd(opStLset)
;	  tkRSET MARK(1) idAryElemRef MARK(2) tkEQ Exp
;	    CgMoveOpsToEnd(opStRset)
;	  tkMID_ tkLParen MARK(1) idAryElemRef MARK(2) exp12 tkRParen tkEQ Exp
;	    Cg3or4Args(opStMid_2)
;	Moves the pcode for idAryElemRef to the end of the buffer
;
;*********************************************************************
cProc	CgMoveOpsToEnd,<PUBLIC,NEAR,NODATA>,<si,di>
cBegin
	push	ax			;pass opcode to Emit16 (at end of proc)
	mov	si,[pCurStkMark]
	lodsw				;al = markId (2)
	lodsw				;ax = text offset for MARK(2)
	xchg	di,ax			;bx = text offset for MARK(2)
	lodsw				;al = markId (1)
	lodsw				;ax = text offset for MARK(1)
	xchg	si,ax			;si = text offset for MARK(1)

	;setup for BdShiftLeft((bd *)&ps.bdpDst, oDstCur, cbMoved)
	
	PUSHI	ax,<dataOFFSET ps.PS_bdpDst>
	push	si
	mov	ax,di
	sub	ax,si
	push	ax			;pass cbMoved
					;call to BdShiftLeft is after loop
MoveLoop:
	cmp	si,di
	je	MoveDone
	add	si,[ps.PS_bdpDst.BDP_pb] ;si = ptr to next word to be moved
	lodsw				;ax = next word to be moved
	sub	si,[ps.PS_bdpDst.BDP_pb] ;si = offset to next word to be moved
	call	Emit16_AX		;copy word to end of buffer
	jmp	SHORT MoveLoop

MoveDone:
	;delete the source of copied words - parms pushed several lines above
	call	BdShiftLeft		;grow buf, can cause heap movement
	call	SetDstPbCur		;update ps.bdpDst.pbCur for BdShiftLeft
	;emit opcode - parm pushed several lines above
	call	Emit16
cEnd

PUBLIC	CgCircle
CgCircle PROC NEAR
	mov	dx,MAX_STK_MARK
	cmp	[pCurStkMark],dx
	je	NoCircleMark
	inc	ax			;got a MARK(1), color parm included
					;map opStCircle to opStCircleColor
NoCircleMark:
	jmp	Emit16_AX		;emit ax and return to caller
CgCircle ENDP


sEnd	CP
end

⌨️ 快捷键说明

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