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

📄 lsutil.asm

📁 [随书类]Dos6.0源代码
💻 ASM
📖 第 1 页 / 共 2 页
字号:
; Purpose:
;	Move 1 node from top of root stack to top of temp stack.
;
;***************************************************************************
PUBLIC PopRootPushTemp
PopRootPushTemp PROC NEAR
	call	PopRoot			;ax = popped node
PopRootPushTemp ENDP
	;fall into PushTemp
PUBLIC	PushTemp
PushTemp PROC NEAR
	mov	bx,ax			;bx = offset for new temp node
	add	bx,[bdNodes.BD_pb]	;convert offset to ptr (new temp)
	xchg	ax,[oNodeTemp]		;save offset for new temp
					;ax = offset for old temp
	mov	LN_sib[bx],ax		;new.sib = old
	ret
PushTemp ENDP

;***************************************************************************
; PushRevList
; Purpose:
;	Push the entire list headed by oNodeTemp as a child-list-node
;	onto oNodeRoot's list, but reverse the order of the temp list first.
;	For example:
;	  before:
;		root: [x y z]  temp: [a b c]
;	  after:
;		root: [[c b a] x y z]  temp: []
; Entry:
;	oNodeTemp = offset to list of nodes to be pushed as a list
;	onto oNodeRoot's stack
;
;***************************************************************************
;***************************************************************************
; PushList
; Purpose:
;	Push the entire list headed by oNodeTemp as a child-list-node
;	onto oNodeRoot's list
;	For example:
;	  before:
;		root: [x y z]  temp: [a b c]
;	  after:
;		root: [[a b c] x y z]  temp: []
; Entry:
;	oNodeTemp = offset to list of nodes to be pushed as a list
;	onto oNodeRoot's stack
;
;***************************************************************************
PUBLIC	PushRevList
PushRevList PROC NEAR
	mov	bx,[oNodeTemp]		;bx = offset to start of temp list
	DbAssertRel bx,ne,0,LIST,<PushRevList: temp stack empty> 
	sub	ax,ax			;prev node = NULL
;bx = offset to current node,
;ax = offset to previous node (if start of list, ax = 0),
;Traverse bx's list to the end, reversing linkage
;
RevListLoop:
	mov	dx,bx			;save cur nodes offset
	add	bx,[bdNodes.BD_pb]	;convert offset to ptr
	mov	cx,LN_sib[bx]		;cx = offset to next node (if any)
	mov	LN_sib[bx],ax		;swap from prev->next to next->prev
	jcxz	RevListDone		;brif we're at the end-of-list
	mov	ax,dx			;ax = offset to prev node
	mov	bx,cx			;bx = offset to current node
	jmp	SHORT RevListLoop

RevListDone:
	mov	[oNodeTemp],dx		;last node is now head of temp list
PushRevList ENDP
	;fall into PushList
PUBLIC	PushList
PushList PROC NEAR
	mov	bx,di			;bx = offset to new node
	add	di,[bdNodes.BD_pb]	;convert offset to ptr
	mov	ax,[oNodeRoot]		;ax = offset for old root
	stosDsWord ax			;store LN_sib field
	stosDsByte LNT_LIST		;set LN_type field
	mov	ax,[oNodeTemp]
	DbAssertRel ax,ne,0,LIST,<PushList: temp stack empty> 
	stosDsWord ax			;store LN_val_list field
	mov	[oNodeTemp],0
	mov	[oNodeRoot],bx		;save offset for new root
	sub	di,[bdNodes.BD_pb]	;convert ptr to offset
	ret
PushList ENDP

;push '(' onto root stack
PUBLIC	PushRootLParen
PushRootLParen PROC NEAR
	mov	al,'('
	jmp	SHORT PushRootChar	;push a char node (al) onto root stack
PushRootLParen ENDP

;push ')' onto root stack
PUBLIC	PushRootRParen
PushRootRParen PROC NEAR
	mov	al,')'
	jmp	SHORT PushRootChar	;push a char node (al) onto root stack
PushRootRParen ENDP

PUBLIC	PushRootSpc
PushRootSpc PROC NEAR
	mov	al,' '
PushRootSpc ENDP
	;fall into PushRootChar
PUBLIC	PushRootChar
PushRootChar PROC NEAR
	sub	ah,ah			;only 1 char in this node
PushRootChar ENDP
	;fall into PushRootChars
;push a char node (ax) onto root stack
PUBLIC	PushRootChars
PushRootChars PROC NEAR
	call	NewChars
	jmp	PushRoot
PushRootChars ENDP

;push '(' onto temp stack
PUBLIC	PushTempLParen
PushTempLParen PROC NEAR
	mov	al,'('
	jmp	SHORT PushTempChar	;push a char node (al) onto temp stack
PushTempLParen ENDP

;push ')' onto temp stack
PUBLIC	PushTempRParen
PushTempRParen PROC NEAR
	mov	al,')'
	jmp	SHORT PushTempChar	;push a char node (al) onto temp stack
PushTempRParen ENDP

PUBLIC	PushTempSpc
PushTempSpc PROC NEAR
	mov	al,' '
PushTempSpc ENDP
	;fall into PushTempChar
;push a char node (al) onto temp stack
PUBLIC	PushTempChar
PushTempChar PROC NEAR
	sub	ah,ah			;only 1 char in this node
PushTempChar ENDP
	;fall into PushTempChars
;push a char node (ax) onto temp stack
PUBLIC	PushTempChars
PushTempChars PROC NEAR
	call	NewChars		;ax = offset to new node
	jmp	PushTemp		;push it onto temp stack
PushTempChars ENDP

;***************************************************************************
;CharToCharTok
;Purpose:
;	Given the last node created by PushRootChar[s], PushTempChar[s]
;	or NewChar[s], convert its node-type from LNT_CHAR to LNT_CHAR_TOK.
;	This is done for nodes which are known to not begin a lexical token.
;	For example, "string" is 3 nodes, char, string, char, but only
;	1 lexical token, so the 2nd char node is converted to LNT_CHAR_TOK.
;	This is so ChkLineWrap in lsmain.asm knows not to split a logical
;	line into 2 physical lines at this node.
;Entry:
;	di = offset to last node created.
;
;***************************************************************************
PUBLIC	CharToCharTok
CharToCharTok PROC NEAR
	mov	bx,di
	add	bx,[bdNodes.BD_pb]	;convert offset to ptr 
DbAssertRelB <[bx + LN_type - CBLNT_CHAR]>,e,LNT_CHAR,LIST,<CharToCharTok err1>
	mov	[bx + LN_type - CBLNT_CHAR],LNT_CHAR_TOK
	ret
CharToCharTok ENDP

;***************************************************************************
; PushRootONam
; Purpose:
;	Create a new oNam list node and push it onto oNodeRoot's stack.
; Entry:
;	ax = oNam
; Exit:
;	none
;
;***************************************************************************
PUBLIC PushRootONam
PushRootONam PROC NEAR
	call	NewONam 		;ax = offset to new ONam node
	jmp	PushRoot		;push node to root stack
					; and return to caller
PushRootONam ENDP

;***************************************************************************
; PushRootLabel
; Purpose:
;	Fetch the next 2 bytes of pcode, which represent a label
;	reference.  If scanState = SS_EXECUTE, convert this 16 bit
;	text offset into a name table offset.  Create a new oNam list
;	node and push it onto oNodeRoot's stack.
; Entry:
;	es:si points to oNam or otx argument
; Exit:
;	si bumped by 2
;	none
;
;***************************************************************************
PUBLIC	PushRootLabel
PushRootLabel PROC NEAR
	call	NewLabel		;ax = new node for this label
	jmp	PushRoot
PushRootLabel ENDP

;push opcode's reserved word node to root's stack
PUBLIC	PushRootOpRw
PushRootOpRw PROC NEAR
	mov	bx,[opList2]		;bx = opcode being listed * 2
	mov	ax,[mpOpLsArg + bx]	;ax = ORW_xxx to be listed
PushRootOpRw ENDP
	;fall into PushRootRw
;Create a reserved-word node for oRw ax and push it to oNodeRoot's stack
PUBLIC	PushRootRw
PushRootRw PROC NEAR
	call	NewRw			;ax = offset to node for "REM"
	jmp	PushRoot
PushRootRw ENDP

;push opcode's reserved word node followed by space node to root's stack
PUBLIC	PushRootOpRwSpc
PushRootOpRwSpc PROC NEAR
	call	PushRootOpRw
	jmp	PushRootSpc
PushRootOpRwSpc ENDP

;Push a reserved word node followed by a space node to root stack
PUBLIC PushRootRwSpc
PushRootRwSpc PROC NEAR
	call	PushRootRw		;list reserved word [ax]
	jmp	PushRootSpc		;list a space and return to caller
PushRootRwSpc ENDP

;Push '"' literal_string_node '"' onto root stack
;	added as part of revision [6]
; ax = length of string; es:si points to text of string
PUBLIC PushRootQStr
PushRootQStr PROC NEAR
	push	ax			;preserve cbText
	mov	al,34			;al = code for double quote "
	call	PushTempChar
	pop	ax			;restore ax = cbText
	call	NewStr			;ax = offset to new node
	call	PushTemp
	mov	al,34			;al = code for double quote "
	call	PushTempChar
	call	CharToCharTok		;convert it to a LNT_CHARS_TOK node
	call	PushList		;convert to single node on Root stack
	ret
PushRootQStr ENDP

;push opcode's reserved word node to temp stack
PUBLIC	PushTempOpRw
PushTempOpRw PROC NEAR
	mov	bx,[opList2]		;bx = opcode being listed * 2
	mov	ax,[mpOpLsArg + bx]	;ax = ORW_xxx to be listed
PushTempOpRw ENDP
	;fall into PushTempRw
;Create a reserved-word node for oRw ax and push it to oNodeTemp's stack
PUBLIC	PushTempRw
PushTempRw PROC NEAR
	call	NewRw			;ax = offset to node for "REM"
	jmp	PushTemp
PushTempRw ENDP

;push opcode's reserved word node followed by space node to temp stack
PUBLIC	PushTempOpRwSpc
PushTempOpRwSpc PROC NEAR
	call	PushTempOpRw
	jmp	PushTempSpc
PushTempOpRwSpc ENDP

;Push a reserved word node followed by a space node to temp stack
PUBLIC PushTempRwSpc
PushTempRwSpc PROC NEAR
	call	PushTempRw		;list reserved word [ax]
	jmp	PushTempSpc		;list a space and return to caller
PushTempRwSpc ENDP

;***************************************************************************
; PushCommaArgs
; Purpose:
;	Copy cLsArgs from root to temp and separate them by commas.
;	Nodes created by opUndef are not listed.
; Entry:
;	cLsArgs = number of args to be transfered from root to temp stack
; Exit:
;	cLsArgs = 0
;
;***************************************************************************
PUBLIC	PushCommaArgs
PushCommaArgs PROC NEAR
	sub	cx,cx			;cx = 0
	mov	cl,[cLsArgs]		;cx = count of args
	jcxz	EndOfArgs		;brif no args
	mov	bx,[oNodeRoot]		;bx = offset to current root node
MoveIndLoop:
	DbAssertRel bx,ne,0,LIST,<PushCommaArgs: root stack underflow> 
	push	bx			;save offset to index node
	add	bx,[bdNodes.BD_pb]	;convert offset to ptr
	cmp	LN_type[bx],LNT_CHAR
	jne	NotUndefNode		;brif couldn't be opUndef node
	cmp	WORD PTR LN_val_char[bx],100h
	jne	NotUndefNode
	pop	ax			;don't list node's created by opUndef
	dec	[cLsArgs]
NotUndefNode:
	mov	bx,LN_sib[bx]		;bx = offset to next index
	loop	MoveIndLoop		;repeat for all args
	mov	[oNodeRoot],bx		;save new root after all args popped
	pop	ax			;ax = offset to next index node
	call	PushTemp		;transfer it to temp stack
XferIndLoop:
	dec	[cLsArgs] 		;countdown # of args left
	je	EndOfArgs		;brif end of args
	call	GrowBdNodes		;grow list buffer if necessary
	je	XferOmErr		;brif out-of-memory - We'll abort
					; ListLine next time through Stg1Loop
	call	PushTempCommaSpc	;push ", " node onto temp stack
	pop	ax			;ax = offset to next index node
	call	PushTemp		;transfer it to temp stack
	jmp	SHORT XferIndLoop

XferOmErr:
	pop	ax			;ax = offset to next index node
	jmp	SHORT XferIndLoop

EndOfArgs:
	ret
PushCommaArgs ENDP

PUBLIC PushTempCharSpc
PushTempCharSpc PROC NEAR
	call	PushTempChar
	jmp	PushTempSpc
PushTempCharSpc ENDP

PUBLIC PushRootCharSpc
PushRootCharSpc PROC NEAR
	call	PushRootChar
	jmp	PushRootSpc
PushRootCharSpc ENDP

PUBLIC PushTempComma
PushTempComma PROC NEAR
	mov	al,','
	jmp	PushTempChar
PushTempComma ENDP

PUBLIC	PopPushCommaSpc
PopPushCommaSpc PROC NEAR
	call	PopRootPushTemp		;move exp from root to temp stk
PopPushCommaSpc ENDP
	;fall into PushTempCommaSpc
PUBLIC PushTempCommaSpc
PushTempCommaSpc PROC NEAR
	mov	ax,' ,'			;list ", "
	jmp	PushTempChars
PushTempCommaSpc ENDP

PUBLIC PushRootCommaSpc
PushRootCommaSpc PROC NEAR
	mov	ax,' ,'			;list ", "
	jmp	PushRootChars
PushRootCommaSpc ENDP

;list ", " if we're in COMMON/SHARED (i.e. if FBOS_DoIdCommas is set)
;
PUBLIC PushTempIdComma
PushTempIdComma PROC NEAR
	test	lsBosFlags,FBOS_DoIdCommas
	je	NoIdComma		;brif not in COMMON/SHARED stmt
	test	lsBosFlags,FBOS_NextIdComma
	je	FirstId			;brif first id in list, no leading comma
	call	PushTempCommaSpc	;output a ', '
FirstId:
	or	lsBosFlags,FBOS_NextIdComma
NoIdComma:
	ret
PushTempIdComma ENDP

;***************************************************************************
; PushTempOpChars
; Entry:
;	mpOpLsArg[opList2] = ASCII codes for 1 or 2 chars (if only 1 char,
;	high byte = 0)
;
;***************************************************************************
PUBLIC PushTempOpChars
PushTempOpChars PROC NEAR
	mov	bx,[opList2]		;bx = opcode being listed
	mov	ax,[mpOpLsArg + bx]	;ax = char(s) to be listed
	jmp	PushTempChars		;push char(s) to be listed
					; and return to caller
PushTempOpChars ENDP

PUBLIC PushRootOpChars
PushRootOpChars PROC NEAR
	mov	bx,[opList2]		;bx = opcode being listed
	mov	ax,[mpOpLsArg + bx]	;ax = char(s) to be listed
	jmp	PushRootChars		;push char(s) to be listed
					; and return to caller
PushRootOpChars ENDP

;***************************************************************************
; PushTempRwOrComma
; Purpose:
;	Used to list opcodes which list as a reserved word the first time
;	they occur in a statement, and as a comma for the 2nd-nth occurence
;	in the statement.
; Entry:
;	lsBosFlags.FBOS_NextStmtComma is 0 if this is the first time this
;	function has been called this statement.
;	ax = ORW_xxx (reserved word table offset) for res word to list
;	   if FBOS_NextStmtComma = 0
; Exit:
;	lsBosFlags.FBOS_NextStmtComma is set to 1
;	the res word or a comma node is pushed to the temp stack
;
;***************************************************************************
PUBLIC PushTempOpRwOrComma
PushTempOpRwOrComma PROC NEAR
	mov	bx,[opList2]		;bx = opcode * 2
	mov	ax,[mpOpLsArg + bx]	;ax = opcode's reserved word
PushTempOpRwOrComma ENDP
	;fall into PushTempRwOrComma
PUBLIC PushTempRwOrComma
PushTempRwOrComma PROC NEAR
	test	lsBosFlags,FBOS_NextStmtComma
	jne	EmitComma		;brif not 1st time called for this stmt
	or	lsBosFlags,FBOS_NextStmtComma
	jmp	PushTempRwSpc		;push reserved word ax
					; and return to caller
EmitComma:
	call	PushTempComma
	jmp	PushTempSpc		;output a space
					; and return to caller
PushTempRwOrComma ENDP

;push res word ax to root stack if 1st time this has been called for this stmt
PUBLIC PushStmtRwIfBos
PushStmtRwIfBos PROC NEAR
	test	lsBosFlags,FBOS_StmtRw
	jne	PushStmtRet		;brif already called for this stmt
	or	lsBosFlags,FBOS_StmtRw
	call	PushRootRwSpc		;push res word ax to root stack
PushStmtRet:
	ret
PushStmtRwIfBos ENDP

sEnd	LIST

end

⌨️ 快捷键说明

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