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

📄 lsid.asm

📁 Dos6.0
💻 ASM
📖 第 1 页 / 共 3 页
字号:
TITLE	LSID - Contains functions for listing id related opcodes

;======================================================================
; Module: lsid.asm
;
; Purpose:
;	Contains functions for listing id related opcodes
;
;
;=======================================================================*/

	include		version.inc
	LSID_ASM = ON
	includeOnce architec
	includeOnce context
	includeOnce lister
	includeOnce lsint
	includeOnce names
	includeOnce opmin
	includeOnce pcode
	includeOnce prsorw
	includeOnce prstab
	includeOnce qblist
	includeOnce scanner
	includeOnce txtmgr
	includeOnce types
	includeOnce variable

	PERIOD_ID EQU ON		;record.element, not record->element

	assumes	DS,DGROUP
	assumes	SS,DGROUP
	assumes	ES,NOTHING

FV_ARYELEM EQU 1

sBegin	DATA

orwDecl DW	0			;temporary location used to
					;store the reserved word for the
					;the declaration stmt currently
					;being listed: AUTO,PUBLIC,STATIC,DIM



ET_MAX_NOFIELDS = ET_MaxStr
sEnd	DATA

sBegin	LIST
assumes	CS,LIST

; Code Segment Tables

;Table for mapping ET_xxx to DEFxxx reserved word
tRwDefType LABEL WORD
	DW	ORW_DEFINT		;res word for ET_I2
	DW	ORW_DEFLNG		;res word for ET_I4
	DW	ORW_DEFSNG		;res word for ET_R4
	DW	ORW_DEFDBL		;res word for ET_R8
	DW	ORW_DEFSTR		;res word for ET_SD



subttl	Beginning/End of line/statement opcodes

;------------------------------------------------------------------
;	Beginning/End of line/statement opcodes
;------------------------------------------------------------------

;===========================================================================
;			 List Rules
;
;	Each of these functions takes 0 or more nodes off oNodeRoot's list
;	and adds 0 or more nodes as indicated in its header comment.
;
;	On Entry, each of these routines can expect:
;		SI points to opcode's operand (if any)
;		DI points to node to be created (if any)
;		AX = opcode being listed
;		BX = 2 * opcode being listed
;
;===========================================================================

;	+-------------------------------------------+
;	| Beginning-of-line / End-of-text List Rules|
;	+-------------------------------------------+

;	[...] ==> [linenum ...] or [: label ...]
;
EatLabelDef PROC NEAR
	inc	si			;skip link field
	inc	si
	lods	WORD PTR es:[si]	;ax = label's oNam operand
	call	NewLabelONam		;Create either LNT_ONAM for label
					; or LNT_NUM for line number,
					; ax = offset to newly created node
	or	dl,dl
	jne	GotLineNum		;brif not an alphanumeric label
	call	PushRoot		;push label's oNam node
	mov	al,':'
	call	NewChar			;ax = offset to ":" node
GotLineNum:
	jmp	PushRoot		;push line number node or ':' 
EatLabelDef ENDP

; Emit n spaces. CX = emitted space count on return
Spc	PROC NEAR
	lods	WORD PTR es:[si]	;ax = space count
Spc	ENDP
	;fall into SpcAX
SpcAX	PROC NEAR
	push	ax			;save cSpaces
	call	NewSpaces		;ax = offset to spaces node
	pop	cx			;cx = space count
	jmp	PushRoot		;return to caller
SpcAX	ENDP

LrEotInclude:
	cmp	[fViewInclude],0
	jne	LrEot1			;brif INCLUDEd lines are visible
	dec	si
	dec	si			;si points to the BolInclude[Sp] opcode
	mov	[otxListNextInc],si	;save it for caller of ListLine
	push	es			;preserve seg addr of text table
	push	si
	call	OtxNoInclude		;ax = otx to opBol/opEot for next line
					; which has no $INCLUDE
	pop	es			;restore seg addr of text table
	xchg	si,ax			;si = otx to opBol/opEot for next line
					; which has no $INCLUDE
	jmp	Stage2Inc


ListRule LrEot
 	cmp	[fGotBol],0		
 	jne	LrEot1			;brif we've seen an opBol
 	mov	[ndLsCursor],UNDEFINED	;if called to list beyond eot, don't
 					; highlight it as current stmt
LrEot1:
	dec	si
	dec	si			;si = text offset to terminating opcode
J1_Stage2:
	jmp	Stage2

ListRule LrBolLab
	cmp	[fGotBol],0
	jne	LrEot1			;brif this is 2nd Bol opcode
	;fall into LrLab
ListRule LrLab
	call	EatLabelDef
	call	PushRootSpc		;terminate with a space
	jmp	SHORT LrBol2

ListRule LrBolLabSp
	cmp	[fGotBol],0
	jne	LrEot1			;brif this is 2nd Bol opcode
	;fall into LrLabSp
ListRule LrLabSp
	call	EatLabelDef
	call	Spc			;consume and handle space-count operand
	jmp	SHORT LrBol2

ListRule LrBolInclude
	cmp	[fGotBol],0
	jne	LrEotInclude		;brif this is 2nd Bol opcode
					; seen so far in this line
	lods	WORD PTR es:[si]	;ax = $INCLUDE nesting depth
	mov	[fLsIncluded],al	;tell ListLine's caller this is
	jmp	SHORT LrBol1		; an INCLUDEd line

ListRule LrBolIncludeSp
	cmp	[fGotBol],0
	jne	LrEotInclude		;brif this is 2nd Bol opcode
					; seen so far in this line
	lods	WORD PTR es:[si]	;ax = $INCLUDE nesting depth
	mov	[fLsIncluded],al	;tell ListLine's caller this is
					; an INCLUDEd line
	;fall into LrBolSp
ListRule LrBolSp
	cmp	[fGotBol],0
	jne	LrEot1			;brif this is 2nd Bol opcode
	call	Spc			;consume and handle space-count operand
	jmp	SHORT LrBol3		;cx = space count

ListRule LrBol
	cmp	[fGotBol],0
	jne	LrEot1			;brif this is 2nd Bol opcode
	mov	ax,[opList]		;ax = opcode (as saved by DispLs1)
;ax = opcode and high-bit operands
	.errnz	OPCODE_MASK - 3FFh
	shr	ah,1
	shr	ah,1			;ah = high-bit operand
	je	LrBol1			;brif no leading spaces
	.errnz	opBol
	xchg	ah,al			;ax = high-bit operand
	call	SpcAX
	jmp	SHORT LrBol3

ListRule LrEndProg

ListRule LrWatchExp
ListRule LrWatchStop
	cmp	[fGotBol],0
	jne	LrEot1			;brif this is 2nd Bol opcode
					; seen so far in this line
LrBol1:
	sub	al,al
	call	PushRootChar		;list null node, so Stg2Loop will
					; have something after ndLsCursor
					; in case this is the opcode identified
					; by otxLsCursorTmp
	;fall into LrBol2
LrBol2:
	mov	cl,LOW UNDEFINED	;no leading spaces on line
LrBol3:

;NOTE: the leading space count is used when entabbing leading spaces during
;	 ASCII save.  This won't work if cbLeading > 254, but who cares?

	mov	[fGotBol],cl		;remember we've seen the first BOL
					;also specifies number of leading spaces
	mov	[lsBolFlags],0		;reset beginning of line flags
LrBos1:
	mov	[lsBosFlagsWord],0	;reset beginning of stmt flags
					;sets lsBosFlags & lsBosFlags2
J1_Stg1Loop:
	jmp	Stg1Loop		;return to outer loop

ListRule LrBos
	mov	ax,' :'
	call	PushRootChars		;list ": "
	jmp	SHORT LrBos1

ListRule LrBosSp
	mov	al,':'
	call	PushRootChar
	lods	WORD PTR es:[si]	;ax = column operand
	call	NewCol1			;ax = "advance to column(ax)" node
	call	PushRoot		;list it
	jmp	SHORT LrBos1

subttl Expression related list rules

;------------------------------------------------------------------
;		Expression related list rules
;------------------------------------------------------------------

;***************************************************************************
; LrBinaryOp
; Purpose:
;	List a binary operator opcode like opAdd
;	[expRight expLeft] ==> [[expRight operator expLeft]]
;
;***************************************************************************
ListRule LrBinaryOp
	call	PopRootPushTemp		;move expRightNode from root to temp stk
	call	PushTempSpc		;surround operator with blanks
	call	PushTempOpChars		;list opcode's char(s)
	call	PushTempSpc		;surround operator with blanks
BinaryOp1:
	call	PopRootPushTemp		;move expLeftNode from root to temp stk
PUBLIC	PushRevListStg1
PushRevListStg1:
	call	PushRevList		;move temp stk to root in reverse order
	jmp	Stg1Loop		;return to outer loop

;***************************************************************************
; LrBinaryRw
; Purpose:
;	List a binary reserved-word operator opcode like opXor
;	[expRight expLeft] ==> [[expRight operator expLeft]]
;
; Algorithm:
;	opNode = NewRw(opcode)
;	expRightNode = PopRoot()
;	expLeftNode = PopRoot()
;	PushTemp(expLeftNode)
;	PushTemp(opNode)
;	PushTemp(expRightNode)
;	PushList()
;
;***************************************************************************
ListRule LrBinaryRw
	call	PopRootPushTemp		;move expRightNode from root to temp stk
	call	PushTempSpc		;surround operator with blanks
	call	PushTempOpRwSpc		;push res word node to temp stack
	jmp	SHORT BinaryOp1

;***************************************************************************
; LrLParen
; Purpose:
;	List the opcode (exp)opLParen
;	[exp] ==> [[")" exp "("]]
;
;***************************************************************************
ListRule LrLParen
	call	PushTempLParen		;push '(' onto temp stack
	call	PopRootPushTemp		;move expNode from root to temp stk
	call	PushTempRParen		;push ')' onto temp stack
	jmp	PushListStg1		;push temp list to root as 1 node

subttl Id related opcodes

;------------------------------------------------------------------
;			Id related opcodes
;------------------------------------------------------------------

PUBLIC PushTempONam
PushTempONam PROC NEAR
	call	NewONam 		;ax = offset to new ONam node
	jmp	PushTemp		;push node to temp stack
					; and return to caller
PushTempONam ENDP

;***************************************************************************
; PushTempId
; Purpose:
;	Consume an id opcode and push the following nodes to the temp stack:
;	(typeChar oNam)
;
; Entry:
;	si points to id's operand
;	di = offset to next free byte in bdNodes
;	FBOS_DoIdCommas is set if ", " is to be pushed to the root stack
;	   before this id is pushed to the temp stack
; Exit:
;	si points beyond id's operand
;	di is updated
;	typeChar oNam are pushed to the temp stack
;
;***************************************************************************
PushTempId PROC NEAR
	call	PushTempIdComma		;list ", " if we're in COMMON/SHARED
	call	NewId			;consume id's operand, ax = node
	call	PushTemp
PushTempId ENDP
	;fall into PushEt		;push explicit type (if any)
PushEt	PROC NEAR
.errnz	OPCODE_MASK - 3FFh
	mov	bl,BYTE PTR[opList+1]	;bl = high byte of original opcode
	shr	bl,1			
	shr	bl,1			;shift off low two bits
	jz	J1_Ret			;brif not an explicit type
	xor	bh,bh			;bx = ET_<type>
	mov	al,CS:tcEt[bx - 1]	;al = explicit type char
	call	PushTempChar		;push a char node (al) onto temp stack
	jmp	CharToCharTok		;convert it to a LNT_CHARS_TOK node
					;and return to caller
PushEt	ENDP

;***************************************************************************
; PushTempElem
;	Added as part of revision [14]
; Purpose:
;	Load the next word representing a record element
;	(which is an oNam if we're in rude or an oElem if we're not).
;	Push a "." and then a node containing the oNam of the element
;	onto the Temp stack.
;		[] ==> [ElementName "."]
; Entry:
;	[pIdLdOperand] is a pointer to the operand of the IdLd opcode
;	whose element is referenced.
;
;***************************************************************************
PushTempElem PROC NEAR
	mov	al,'.'
	call	PushTempChar		;push "." onto temp stack
	call	CharToCharTok		;convert it to a LNT_CHARS_TOK node
	lods	WORD PTR es:[si]	;ax = oNam or oElem
	cmp	[txdCur.TXD_scanState],SS_RUDE
	jae	PTEExit 		;brif table is in rude-edit state
	;ax is oElem parm to ONamOElem
	push	es			;preserve seg addr of text table
	cCall	ONamOElem,<ax>		; ax = oNam for element oElem
GotONam:
	pop	es			;restore seg addr of text table
PTEExit:
	call	PushTempONam		;push oNam
	jmp	SHORT PushEt		;push explicit type (if any)
					; and return to caller
PushTempElem ENDP

;***************************************************************************
; PushOffId
; Purpose:
;	Consume an id offset opcode's operand, and an id from the root
;	stack, and push the following nodes to the temp stack:
;	  [id ...]  ==>  [[typeChar oNam '.' id] ...]
; Entry:
;	mpOpLsArg[bx] = explicit type char (0 if none)
;	si points to opOffxxx's operand
;	di = offset to next free byte in bdNodes
; Exit:
;	si points beyond opcode's operand
;	di is updated
;
;***************************************************************************
PUBLIC	PushOffId
PushOffId PROC NEAR
	call	PopRootPushTemp		;move id node from Root to temp stack
	jmp	SHORT PushTempElem	;push "." and "elem_name"
PushOffId ENDP

;***************************************************************************
; PushTempAId
; Purpose:
;	push array id & indicies onto temp stack
;	  [[")" indexN "," ... index1 "(" typeChar oNam]]
; Entry:
;	root stack: [indexN ... index1 ...] ==>

⌨️ 快捷键说明

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