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

📄 txtdir.asm

📁 [随书类]Dos6.0源代码
💻 ASM
📖 第 1 页 / 共 2 页
字号:
	;type (needed by the execute-scanner) would not have been
	;stored in the prs table entry by the rude scanner yet.
	
	dec	[scanTo]		;scanTo = SS_EXECUTE
.errnz	SS_PARSE - 1
.errnz	SS_EXECUTE
	mov	bx,CPOFFSET ScanTxtTbl
	call	ForEachTxtTbl
	je	SsDone			;brif error
	call	SsTrimCommon		;call scanner to trim back common tbls
	sub	bx,bx			;iWatch = 0
	call	WatchInfo		;can't update WatchInfo when static
					; structures are disabled
SsDone:
	call	StatusMsg0CP		;tell user we're done compiling

	cmp	[txtErr.TXER_errCode],0
	jne	SsExit
	or	[grs.GRS_flags],FG_allSsExecute
SsExit:
cEnd

SsCancel:
	mov	ax,MSG_GoDirect
SsError:
	mov	[txtErr.TXER_errCode],ax
	jmp	short SsDone



;**************************************************************
; ushort FAR TxtDirect()
;
; Purpose:
;	TxtDirect is called by the user interface to parse and
;	scan a direct mode statement.
;	It first parses direct mode statement to SS_RUDE,
;	then if stmt contains any opcodes which require the
;	  program to be scanned, SystemScan is called to scan
;	  all loaded text tables to SS_EXECUTE.
;	then direct mode buffer is scanned to SS_EXECUTE.
;	The reason we parse to SS_RUDE, instead of SS_PARSE,
;	direct mode statements like PRINT A(1) would cause the
;	array A() to be implicitly dimensioned, where the program,
;	which may still be in SS_RUDE, may have defined it AS STRING,
;	resulting in an error.
;	The reason we scan the entire program for statements like
;	A=1 is because the variable table wouldn't exist if the
;	module was in SS_RUDE state.
;
; Entry:
;	ps.bdpSrc contains the 0-terminated source line to be parsed.
;	grs.oMrsCur and grs.oPrsCur identify the scope of the direct
;	   mode statement.
;
; Exit:
;	If no errors were encountered,
;          [txtErr.TXER_errCode]  = return value = 0
;	   grs.bdlDirect contains the executable pcode,
;	   grs.fDirect = TRUE
;	   grs.otxCur = 0
;	If an error was encountered,
;	   return value = txtErr.errCode = an offset into the QBI Message
;	     Table (MSG_xxx) or, if high-bit set, ps.bdpError contains
;	     the parser-built ASCII error message,
;	   If the error was in the direct mode buffer,
;	      txtErr.fDirect is TRUE,
;	      txt.oSrc identifies the column where the error occurred.
;	   Else, the error was encountered in some program text as a result of
;	      ReParsing or Scanning.
;	      txtErr.fDirect is FALSE,
;	      txtErr.oRs identifies the text table with the error,
;	      txtErr.otx is an offset into the text table where the error
;	         was detected.
;	      txtErr.oSrc identifies the column within the source line where
;	         the error was detected.
;	   If direct mode command would have prevented CONT, and user
;	      wants to backout of the command, error code = UNDEFINED.
;
;**************************************************************
cProc	TxtDirect,<PUBLIC,FAR>,<si>
localW	oPrsPreParse
cBegin	TxtDirect

	mov	ax,[grs.GRS_oPrsCur]	;remember oPrs before parseline
	mov	[oPrsPreParse],ax	;in case an error occurs and
					;ParseLine moves us into a new RS.

	;Setting ps.flags.PSF_fBindVars to 0 tells the parser
	;not to bind variable references.  Direct mode statement
	;variable references are bound by rude scanner after entire program
	;has been scanned (and all variables declared).  Otherwise, a stmt
	;like "print a(1)" would cause array a to be implicitly dimensioned
	;when the program has an explicit DIM a(n) statement.
	
TdRetry:
	sub	ax,ax			;ax = 0
	mov	[ps.PS_flags],al
	mov	[txtErr.TXER_errCode],ax;assume no error
	dec	ax			;ax = UNDEFINED
	mov	[ps.PS_otxLine],ax
	SetfDirect al			;tells parser we're parsing a
					; direct mode stmt, if we find an error,
					; it will be in direct mode stmt

	call	ParseLine		;parse the direct mode stmt
	jnc	TdNoErr			;brif parser encountered no error
	jmp	TdParseErr

TdNoErr:
	push	[ps.PS_bdpDst.BDP_pb]
	PUSHI	ax,<CODEOFFSET tOpDirect>
	call	TxtFindOpDS		;ax = adr of 1st interesting opcode
					;dl = index into tOpDirect for opcode

;	*--------------------------------------------------------------------
;	* examine the pcode opcode by opcode:
;	*
;	*  -  Giving an error if any of the opcodes are illegal in direct mode
;	*	 (like opBolLab, opStDefFn, opStCommon etc.)
;	*
;	*  -  Converting any opcodes which are different in direct mode
;	*	 like opGoto->opGotoDirect etc.
;	*
;	*  -  Remembering if the opcode requires a system-scan.
;	*	 ParseLine() helps by setting ps.flags & PSF_fRef TRUE for all
;	*     opcodes which access variables/labels.
;       *
;	*--------------------------------------------------------------------
;
;NOTE: Since otxCur in this loop is an absolute pointer into DS, it is
;      important that no heap movement occur during the loop
;
TdLoop:
	xchg	si,ax			;si = otxCur
	xchg	ax,dx			;al=[txtFindIndex]
.errnz	DIR_opEot AND 0FF00H	;if tOpDirect has > 255 entries, must use ax
	cmp	al,DIR_opEot
	je	TdDone			;brif done with loop (at or beyond eot)

	cmp	al,DIR_ILLEGAL
	ja	TdLegal			;brif opcode is valid in direct mode

	;got opcode which is illegal in direct mode
	mov	ax,ER_ID		;Illegal in direct mode
J1_TdErr:
	jmp	TdErr

TdLegal:
	or	[ps.PS_flags],PSF_fRef	;remember to scan whole program
	cmp	al,DIR_DM_VARIANT
	ja	TdNotDmVar		;brif not a direct mode specific opcode

	;Got an opcode which has a direct mode variant.
	;Convert opStGoto -> opStGotoDirect etc.
	
	inc	WORD PTR [si]		;bump the opcode
	jmp	SHORT TdNext

TdNotDmVar:
	cmp	al,DIR_CANTCONT
	ja	TdNext			;brif opcode doesn't cause CantCont
;Since CantCont can cause movement we must convert si to an offset from
;the start of ps.bdpDst then after calling CantCont reconvert it back to
;a DGROUP offset
	sub	si,[ps.PS_bdpDst.BDP_pb] 
	call	CantCont
	add	si,[ps.PS_bdpDst.BDP_pb] 
TdNext:
	push	si			;pass otxCur (DS pointer)
	PUSHI	ax,<CODEOFFSET tOpDirect>
	call	TxtFindNextOpDS
	jmp	SHORT TdLoop

TdDone:
	test	[grs.GRS_flags],FG_RetDir
	je	TdNoDirRet		;brif no return address to direct
					; mode buffer is on the stack.
	call	AskCantCont_CP		;ask user "Want to back out?"
	jne	TdNoDirRet		;brif user doesn't want to back out
TdUndo:
	mov	ax,UNDEFINED
J2_TdErr:
	jmp	SHORT J1_TdErr

TdNoDirRet:

;If the parser saw a label in the direct mode statement then set the
;FG_OtxInDir grs flag; otherwise, clear it.
	and	[grs.GRS_flags],NOT FG_OtxInDir ;clear the flag
	test	[ps.PS_flags],PSF_fLabelRef	
	jz	@F				;brif no label ref parsed
	or	[grs.GRS_flags],FG_OtxInDir	;set the flag
@@:						

	;Make sure there's enough free space in the direct-mode
	;text table for the pcode we want to execute
	sub	ax,ax
	mov	[grs.GRS_bdlDirect_cbLogical],ax
	dec	ax			;ax = UNDEFINED
	SetfDirect al			;tells TxtFree we're dealing direct
					; mode buffer
	push	[ps.PS_bdpDst.BDP_cbLogical] 
	call	TxtFree
	mov	ax,ER_OM
	je	J1_TdErr		;brif Out-of-memory error
	PUSHI	ax,<dataOFFSET grs.GRS_bdlDirect>
	SetStartOtx ax			
	push	ax
	push	[ps.PS_bdpDst.BDP_pb]
	mov	ax,[ps.PS_bdpDst.BDP_cbLogical]
	push	ax		;pass [ps.PS_bdpDst.BDP_cbLogical]
	mov	[grs.GRS_bdlDirect_cbLogical],ax ;init logical size of dir buff
	call	BdlCopyTo

	test	[ps.PS_flags],PSF_fRef
	je	TdAllScanned

	;If AskCantCont was called above, current module (grs.oMrsCur)
	;may not be current context (grs.oMrsMain).  Make sure current
	;context is active before scanning, giving error if no main
	;module exists.
	
	mov	dx,UNDEFINED
	mov	ax,[grs.GRS_oMrsCur]
	cmp	[grs.GRS_otxCONT],dx
	jne	CanCont			;brif not starting program from scratch
	mov	ax,[grs.GRS_oMrsMain]	;else, activate MAIN module
	xchg	ax,dx			;ax=UNDEFINED, dx=oMrsMain
	cmp	ax,dx
	mov	ax,MSG_NoMainProg
	je	J2_TdErr		;brif no main module
	cCall	RsActivateCP,<dx>	;activate main module
	and	[grs.GRS_flags],NOT FG_allSsExecute ;force scantxttbl
					; invocation so all Data statments get
					; reset, even if all tables are in
					; SS_EXECUTE.
CanCont:

	;This command contains statements which require a system
	;scan to be performed.
	
	call	SystemScan		;scan all text tables to SS_EXECUTE

;  If SystemScan detected an error in the program, we still want to 
;scan the direct-mode-statement, so if the user types something like
;CALL FOO, and FOO is undefined, we will report that error before
;reporting something like Duplicate Definition of an array in the program.
;If there are no errors in the direct mode statement, we will still
;report any errors found by SystemScan, because txtErr.errCode is non-zero.

; If the current module is in SS_RUDE, we can not scan the direct mode 
; statement because there is no variable table.
	cmp	[txdCur.TXD_scanState],SS_RUDE
	je	TdExit

TdAllScanned:
	SetfDirect al,0FFh		;tells scanner we're scanning direct
					; mode buffer
	PUSHI	ax,SS_PARSE		;pass target state to SsRudeScan
	call	SsRudeScan		;scan direct mode stmt to SS_PARSE
	or	ax,ax			
	jz	NotCantCont		; brif no rude scanner error

	cmp	al,ER_CN
	jne	JNE1_TdErr		;brif not a "Cant CONT" type error
					; like creating a new variable when
					; variable tables are locked and can't
					; grow
	call	AskCantCont_CP		;ask user "Want to back out?"
	jne	J1_TdRetry		;brif user doesn't want to back out
J1_TdUndo:
	jmp	TdUndo			;brif user wants to back out
J1_TdRetry:
	jmp	TdRetry			;brif user doesn't want to back out
					; reparse line - we won't get Retry
					; again because AskCantCont called
					; CantCont.

NotCantCont:
	call	SsScan			;static scan direct mode statement
					;ax = scanner error (0 if none)
					;grs.otxCur = location of error
	or	ax,ax			
JNE1_TdErr:
	jne	TdErr			;brif parse->execute scanner got error

	mov	[grs.GRS_otxCur],0	;set otxCur to 0 (for executor)

;If no error occurred, txtErr.errCode = 0
;else
; tErr.errCode, txtErr.fDirect, txtErr.oRs, txtErr.otx, txtErr.oSrc
; must all be set up
;
TdExit:
	mov	ax,[txtErr.TXER_errCode]
cEnd	TxtDirect

;ParseLine encountered an error - handle it
; The parser could have moved us to a new rs for
; two cases. 1). It could have created a prs for
; a SUB/FUNCTION entered in direct mode, or 2)
; a DEF FN could have been active, and a rude
; edit occurred which the prs for the DEF FN to
; be freed, and its mrs to be activated.
;
; If oPrsCur has changed, one of the above cases
; has occured.	If txdCur is for an prs, then it must
; have been case 1.  If txdCur is for an Mrs, then it
; must have been case 2.

TdParseErr:
	mov	ax,[oPrsPreParse]	;get oPrs on entry for TxtParseUndo
	test	[txdCur.TXD_flags],FTX_mrs ;are we at module level?
	je	TdInSubFunc		;brif not
	mov	ax,[grs.GRS_oPrsCur]	;if so, don't reactivate oPrsPreParse,
					; since it could only have been for
					; a DEF FN, which we have freed.
TdInSubFunc:
	call	TxtParseUndo		;back out of the parser changes

	mov	ax,[ps.PS_oSrcErr]
	mov	[txtErr.TXER_oSrc],ax	;save column error occurred in
	test	[ps.PS_flags],PSF_UndoEdit
	jne	J1_TdUndo		;brif user said he wants to back out
					; of the edit while we were in ParseLine
					; (i.e. ParseLine called AskCantCont)

	;See if the parser wants us to try parsing this line again.  This can
	;happen when:
	; We saw something that made us need to ModuleRudeEdit, but part
	;     of the line's pcode had already been emitted in SS_PARSE
	; Variable manager could not add a variable, because variable heap
	;     was locked (because we can CONTinue).  Parser called AskCantCont
	;     and now wants us to try again (much easier than trying to call
	;     varmgr again from within parser).
	
	test	[ps.PS_flags],PSF_fRetry
	jne	J1_TdRetry		;brif ParseLine wants us to try again
	mov	ax,[ps.PS_errCode]
	and	ah,(PSERR_fAsciiMsg + PSERR_errCode) / 100h
					;mask off parser internal flags
	.errnz  PSERR_fAsciiMsg - 8000h	;caller assumes this is high bit
	jmp	SHORT TdErrOSrc

;Error occurred in direct mode statement, position cursor at column 0
;ax = error code
TdErr:
	mov	[txtErr.TXER_oSrc],0
	mov	[txtErr.TXER_otx],0
;ax = error code
TdErrOSrc:
	mov	[txtErr.TXER_errCode],ax
	mov	[txtErr.TXER_fDirect],1
	jmp	SHORT TdExit







;------------------------------------------------------------
;   WATCH Window Text Manager functions
;------------------------------------------------------------

;************************************************************
; OtxEndProg
; Purpose:
;	Return the text offset in the current text table
;	where WATCH pcode begins
; Exit:
;	grs.fDirect = FALSE
;	ax = text offset to opEndProg opcode
;
;************************************************************
PUBLIC	OtxEndProg
OtxEndProg PROC NEAR
	SetfDirect al,0			;don't search direct mode buffer
	mov	ax,[txdCur.TXD_bdlText_cbLogical]
	sub	ax,CB_EMPTY_TEXT-StartOtx ;default oTxEndProg if no watch
					  ; pcode is active is 
					  ; cbLogical - (CB_EMPTY_TEXT-StartOtx)
	test	[flagsTM],FTM_WatchPcode ;is there any watch pcode anywhere?
	je	OtxEndProgExit		;brif not

	sub	ax,ax
	push	ax			;search text offset = 0
	PUSHI	ax,<CODEOFFSET tOpWatch>
	call	TxtFindOp		;ax = text offset to opEndProg
OtxEndProgExit:
	ret
OtxEndProg ENDP


sEnd	CP

end

⌨️ 快捷键说明

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