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

📄 txtfind.asm

📁 [随书类]Dos6.0源代码
💻 ASM
📖 第 1 页 / 共 4 页
字号:
	TITLE	txtfind.asm - Text Table Searching functions

;==========================================================================
;
;Module:  txtfind.asm - Text Table Searching functions
;System:  Quick BASIC Interpreter
;
;=========================================================================*/

	include		version.inc
	TXTFIND_ASM = ON
	includeOnce	architec
	includeOnce	context
	includeOnce	executor	;for EnStaticStructs
	includeOnce	names
	includeOnce	opcontrl
	includeOnce	opid
	includeOnce	opmin
	includeOnce	opstmt
	includeOnce	optables
	includeOnce	pcode
	includeOnce	scanner
	includeOnce	txtint
	includeOnce	txtmgr
	includeOnce	ui

	assumes	DS,DATA
	assumes	SS,DATA
	assumes	ES,NOTHING


;-------------------------------------------------------------------------
;		DATA Segment Declarations
;-------------------------------------------------------------------------

sBegin	DATA

	cbTbSearchOps = (OP_MAX/8)+1	;byte size of TbSearchOps
pOpListLast	DW 0			;cached ptr to table of opcodes from
					;last call to TxtFindOp
tbSearchOps	DB cbTbSearchOps DUP(0) ;bit packed array for TxtFindOp
					;contains a bit for each opcode in
					;the system
lnFindLast	DW UNDEFINED		;used by FindBol to reduce searching
otxFindLast	DW UNDEFINED		;used by FindBol to reduce searching

sEnd	DATA

sBegin CODE

;Table of opcodes which mark the beginning of a line
;
tOpBol	LABEL WORD
	opTabStart	BOL
	opTabEntry	BOL,opBolInclude
	opTabEntry	BOL,opBolIncludeSp
	opTabEntry	BOL,opBol
	opTabEntry	BOL,opBolLab
	opTabEntry	BOL,opBolSp
	opTabEntry	BOL,opBolLabSp
	opTabEntry	BOL,opEndProg
	opTabEntry	BOL,opEot

;Table of opcodes which mark the beginning of a stmt within a line
;
tOpBos	LABEL WORD
	opTabStart	BOS
	opTabEntry	BOS,opBos
	opTabEntry	BOS,opBosSp
	opTabEntry	BOS,opEot

;Table of opcodes which mark the beginning of a stmt or a line
;
tOpBosBol LABEL WORD
	opTabStart	BOSBOL
	opTabEntry	BOSBOL,opBos
	opTabEntry	BOSBOL,opBosSp
	opTabEntry	BOSBOL,opBol
	opTabEntry	BOSBOL,opBolLab
	opTabEntry	BOSBOL,opBolSp
	opTabEntry	BOSBOL,opBolLabSp
	opTabEntry	BOSBOL,opBolInclude
	opTabEntry	BOSBOL,opBolIncludeSp
	opTabEntry	BOSBOL,opEndProg
	opTabEntry	BOSBOL,opEot

;Table of opcodes which mark the beginning of a stmt within a line
; or start of a then/else clause for single line IF RESUME compatability.
;
tOpResume LABEL WORD
	opTabStart	RESUME
	opTabEntry	RESUME,opStIf
	opTabEntry	RESUME,opStElse
		RESUME_opIfElseMax EQU RESUME_opStElse
	opTabEntry	RESUME,opBos
	opTabEntry	RESUME,opBosSp
	opTabEntry	RESUME,opEot

;Table of opcodes which mark the beginning of a stmt or a line
; or start of a then/else clause for single line IF RESUME NEXT compatability.
tOpResumeNext LABEL WORD
	opTabStart	RESUMENEXT
	opTabEntry	RESUMENEXT,opStIf
		RESUMENEXT_opIfMax EQU RESUMENEXT_opStIf
	opTabEntry	RESUMENEXT,opBos
	opTabEntry	RESUMENEXT,opBosSp
	opTabEntry	RESUMENEXT,opBol
	opTabEntry	RESUMENEXT,opBolLab
	opTabEntry	RESUMENEXT,opBolSp
	opTabEntry	RESUMENEXT,opBolLabSp
	opTabEntry	RESUMENEXT,opBolInclude
	opTabEntry	RESUMENEXT,opBolIncludeSp
	opTabEntry	RESUMENEXT,opEndProg
	opTabEntry	RESUMENEXT,opEot

;Table of legal opcodes which may appear between a SELECT CASE and the
;   First CASE item, CASE ELSE, or END SELECT

tOpSelect label   word
	opTabStart	SEL
	opTabEntry	SEL,opBos
	opTabEntry	SEL,opBosSp
	opTabEntry	SEL,opBol
	opTabEntry	SEL,opBolSp
	opTabEntry	SEL,opBolInclude
	opTabEntry	SEL,opBolIncludeSp
	opTabEntry	SEL,opNoType
	opTabEntry	SEL,opQuoteRem
	opTabEntry	SEL,opStRem
	SEL_opValidMax	EQU SEL_opStRem 	;max valid opcode

	opTabEntry	SEL,opBolLab		;labels aren't allowed
	opTabEntry	SEL,opBolLabSp		;between SELECT / 1st item
	opTabEntry	SEL,opEot




sEnd	CODE

;-------------------------------------------------------------------------
;		CP Segment Functions
;-------------------------------------------------------------------------

sBegin	CP
assumes	cs,CP


;***
;InitSearchTable - Initialize search table for TxtFindOpcode
;
;Purpose:
;	Builds a bit packed array for the specified search opcodes.
;	Each opcode in the passed list will have a bit set in
;	the constructed table.	All other opcodes in the table
;	will have their associated bits set to 0.
;Entry:
;	di - ptr to tbSearchOps (in DGROUP) [6]
;	segCode:si - ptr to list of search opcodes.
;		The first word of the table contains the number
;		of opcodes in the table.
;Exit:
;	tbSearchOps - constructed bitpacked array of search opcodes
;
;***************************************************************************
DbPub 	InitSearchTable
cProc	InitSearchTable,<NEAR>,<si>
cBegin
	GetSegAddr CODE			;ax = current address of CODE seg
	mov	ds,ax			;ds:si = pOpcodeList

assumes ds,NOTHING 
	DbSegMoveOff			;can't allow seg movement
	push	ss
	pop	es			;es = DGROUP

	mov	cx,cbTbSearchOps	;get byte size of table

	push	di			;save table base
	sub	ax,ax			;clear previous table
	shr	cx,1			;byte count -> word count
	rep	stosw			;clear table
	jnc	EvenCount		;brif count even

	stosb				;clear the last (odd) byte
EvenCount:
	pop	di			;recover table base


	lodsw				;pick up cwOpcodes
	and	ah,7fH			;mask out Search all opcodes bit
	mov	dx,ax			;dx = count of opcodes in list

ConstructLoop:
	lodsw				;get opcode
	mov	bx,ax
	shr	bx,1			;divide opcode by 8 to get
	shr	bx,1			;table index for specified opcode
	shr	bx,1			;bx = table index for opcode
	and	al,7			;al = bit number to set in byte
	mov	cl,1
	xchg	ax,cx
	shl	al,cl			;generate bit mask for table byte
	or	es:[di+bx],al		;set bit for opcode
	dec	dx
	jne	ConstructLoop		;get next opcode

	push	ss
	pop	ds			;restore ds = DGROUP
	DbSegMoveOn			;OK to move segs again
assumes ds,DGROUP

cEnd


;*************************************************************************
; TxtFindOpcode(al:operation, otxStart, pOpcodeList)
; Purpose:
;	Given an offset into the current text table, and a
;	list of opcodes to search for, perform a search skipping
;	each opcode's operands.  As a FUTURE optimization all opBol
;	opcodes could be linked.  This would eliminate many calls to
;	this routine.
;	Note: this routine was initially a lot smaller, but SS_EXECUTE
;	and Non SS_EXECUTE searches were split for performance.  This
;	routine shows up significantly in ASCII load/Rude Scan/ and
;	CUT/PASTE/COPY operations.
; Entry:
;	[al] = 0 or more TFC_xxx flags indicating what to do
	TFC_FindNext EQU 1  ; skip 1st opcode in buffer before doing search
	TFC_FindInDS EQU 2  ;search in DS segment, not current text table
	TFC_FindExec EQU 4  ;pcode buffer is in EXECUTE scan state
;	parm1: ushort otxStart - offset into buffer to start search.
;	       [14] A value of 0 always means start at StartOtx.
;	parm2: ushort *pOpcodeList - If this parm is NULL,
;	  the current opcode is skipped.
;	  If it is not NULL, it points to a list of opcodes to search for.
;	  The first word in the list is the count of opcodes which follow.
;	  If the high bit of this first word is set, it means the table
;	  is to be searched even for opcodes which don't have the
;	  OPA_fTxtFind attribute flag set (speed optimization).
;	  NOTE: Make sure one of them is opEot to ensure that we don't
;	  search past end-of-text.
;	  NOTE: This table must reside in the CODE segment.
;	grs.fDirect, oMrsCur, oPrsCur identify the text table being
;	  searched.  txdCur describes its text table.
;	txdCur.TXD_scanState indicates text table's scan state
;
; Exit:
;	DL = txtFindIndex (global static ushort variable) = 0 if 1st opcode in
;	   list was found, 1 if 2nd opcode in list was found etc.
;	   (this is only set if parm2 is not NULL on entry)
;	AX = offset within text where one of the opcodes was found
;	pOpListLast - cached ptr to list of search opcodes.
;			(Speed opt to avoid reconstructing tbSearchOps
;			for each call to TxtFindOpcode).
;
;*************************************************************************
PUBLIC	TxtFindOpDS
TxtFindOpDS PROC NEAR
	mov	al,TFC_FindInDS
	jmp	SHORT TxtFindOpcode
TxtFindOpDS ENDP

PUBLIC	TxtFindNextOpDS
TxtFindNextOpDS PROC NEAR
	mov	al,TFC_FindNext + TFC_FindInDS
	jmp	SHORT TxtFindOpcode
TxtFindNextOpDS ENDP

;TxtFindOpExec and TxtFindNextOpExec are called by scanner when it knows
;that pcode is in SS_EXECUTE even though txdCur.scanState = SS_PARSE.
;It does this when it found an error during scan, and is backing out
;of the scan.

cProc	TxtFindOpExec,<PUBLIC,FAR>	
	parmW	otxStart		
	parmW	pOpcodeList		
cBegin	TxtFindOpExec			
	mov	al,TFC_FindExec 	
	cCall	TxtFindOpcode,<otxStart, pOpcodeList>	
cEnd	TxtFindOpExec			

DbPub TxtFindNextOpExec
TxtFindNextOpExec PROC NEAR
	mov	al,TFC_FindNext + TFC_FindExec
	jmp	SHORT TxtFindOpcode
TxtFindNextOpExec ENDP

PUBLIC	TxtFindOp
TxtFindOp PROC NEAR
	mov	al,TFC_FindExec 	
	cmp	[txdCur.TXD_scanState],SS_EXECUTE
	je	TxtFindOpcode		; brif txt tbl in executeable state

	cmp	[grs.GRS_fDirect],FALSE
	jne	TxtFindOpcode		; brif direct mode buffer (This func
					; can assume it is in executable state)
	sub	al,al
	jmp	SHORT TxtFindOpcode	;branch to TxtFindNextOp shared code
TxtFindOp ENDP

PUBLIC	TxtFindNextOp
TxtFindNextOp PROC NEAR
	cmp	[txdCur.TXD_scanState],SS_EXECUTE
	je	TxtFindNextOpExec	;brif txt table is in executable state
	cmp	[grs.GRS_fDirect],FALSE
	jne	TxtFindNextOpExec	;brif direct mode buffer (This func
					; can assume it is in executable state)
	mov	al,TFC_FindNext
TxtFindNextOp ENDP
	;fall into TxtFindOpcode

cProc	TxtFindOpcode,<NEAR>,<si,di>
	parmW	otxStart
	parmW	pOpcodeList
	localB	flags
cBegin	;TxtFindOpcode

	DbChk	ConStatStructs		;ensure static structures, else
					; txdCur structure contains garbage.
	mov	[flags],al		;remember what we need to do
	DbChk	TxdCur			;perform sanity check on txdCur

	mov	si,[pOpcodeList]	;get ptr to opcode list
	mov	di,si			;set up in case its TxtSkipOp

	or	si,si			;was an Opcode list specified
	je	NoInitTable		;brif not - skip one opcode case

	mov	di,offset dgroup:tbSearchOps
	cmp	si,[pOpListLast]	;is table already built?
	je	NoInitTable		;brif so - use it

	mov	[pOpListLast],si	;cache constructed table

	call	InitSearchTable 	;Init opcode search table
					;es:di - ptr to search opcode table
NoInitTable:
	GetSegAddr CODE			;ax = current address of CODE segment
	push	ax			;push addr of code seg.
					;  later popped into es
	DbSegMoveOff			;can't allow seg movement

	test	[flags],TFC_FindInDS
	jne	DoItInDS		;brif entry was TxtFind[Next]OpDS
					; in which case the txt table is the
					; direct mode buffer which is in DGROUP
	GetSegTxtCur			;[24] es = seg adr of current txt tbl
	push	es			; ds = seg of current txt table
	pop	ds			
assumes	ds,NOTHING

DoItInDS:
	pop	es			;es = adr of CODE seg

	;********************************************************
	;NOTE: DS register points to text table until end-of-loop
	;      ES points to CODE, where opcodes in execute state can be accessed
	;      SS still points to DGROUP, so local vars can be accessed

⌨️ 快捷键说明

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