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

📄 lsmain.asm

📁 Microsoft MS-DOS6.0 完整源代码
💻 ASM
📖 第 1 页 / 共 4 页
字号:

;======================================================================
; Module: LsMain.asm - main module of 'lister' component
;
; Purpose:
;	The Lister is responsible for converting one logical line
;	of pcode to its ASCII source equivalent.  A logical line
;	may consist of several physical lines, with each physical
;	line terminated by an underscore_remark.  The pcode may
;	be in any scan-state from SS_rude to SS_executable.  The
;	pcode resides in a far (non DS) segment.  The lister's
;	main interface to the rest of BASIC is the entry point
;	ListLine().
;
;
;=======================================================================*/

	include 	version.inc
	LSMAIN_ASM = ON
	includeOnce	architec
	includeOnce	context
	includeOnce	heap
	includeOnce	lister
	includeOnce	lsint
	includeOnce	names
	includeOnce	optables
	includeOnce	parser
	includeOnce	pcode
	includeOnce	prstab
	includeOnce	qblist
	includeOnce	rtps
	includeOnce	scanner
	includeOnce	txtmgr
	includeOnce	util

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


;-----------------------------------------------------------------------
;		NOTE NOTE NOTE NOTE NOTE
;
;  A powerful debugging aid is to set a break point at ListLine
;  just before the line of interest is to be listed.  When in
;  the breakpoint, set fDebugList non-zero.  This will cause
;  the intermediate list-node-tree to be symbolically dumped
;
;-----------------------------------------------------------------------



;-----------------------------------------------------------------------
;   Notation:
;
;   This module deals heavily with lists of nodes.
;
;   The list:
;	(a)->(b)->( )->(f)->(g)
;		   |
;		   +-->(c)->(d)->(e)
;
;   is equivalent to the representation:
;
;	[a b [c d e] f g]
;
;   Where b is a sibling of a, d is a sibling of c, and the entire list [c d e]
;   is a sibling of b.
;
;   Functions which operate on a list of nodes use the notation
;	[oldList] ==> [newList]
;   to indicate how the list is transformed.  For example, a function
;   which inserts 'newNode' into a list would be documented as:
;	[x y z]  ==>  [newNode x y z]
;
;   The way a line of pcode is listed (converted to ASCII text) is by
;   dispatching to a "ListRule" for each opcode.  These ListRules are
;   labeled LrXXX (i.e. LrBos handles opBos and LrBinaryOp handles
;   all binary operators).  These ListRule functions all work together
;   to manipulate to global lists, the "Root" list and the "Temp" list.
;   By the time the end-of-line is reached, the Root list contains
;   a complete description of the text to be listed.  The Temp list is
;   only used for 1 ListRule's temporary needs.  Nothing is passed
;   on the Temp list from one ListRule to another.
;
;   All the nodes which make up these lists physically reside within
;   the buffer bdNodes.  Since this buffer is a heap entry that can move,
;   all nodes are refered to as offsets into the buffer.  The first byte
;   of the buffer is not used, allowing 0 to represent end-of-list.
;   Nodes are of different types and lengths length.  The first field
;   in each node is LN_sib (offset to sibling node), followed by LN_type
;   (type of node).
;
; Algorithm:
;
;   ListLine consists of 2 stages.  Stage1 reads the pcode,
;   building an list-node description of the line.  Stage2
;   traverses this node description and appends ASCII text
;   to the output buffer.  Stage2 dumps the last node in the list
;   first, then the next to last, etc.
;
; Example of how an line of pcode is listed.
;
;   Original ASCII Source: a(x,y)=1+2
;   pcode: opBol opLit(1) opLit(2) opAdd
;	     opId(x) opId(y) opAIdSt(a,2) opBol/opEot
;
;   The following chart represents snapshots in time of the
;   current state of the lister's data structures during Stage1:
;
;	next opcode   oNodeRoot's tree
;	-----------   -----------------
;	opBol	      NULL
;	opLit(1)      NULL
;	opLit(2)      [1]
;	opAdd	      [2 1]
;	opId(x)       [[2 + 1]]
;	opId(y)       [x [2 + 1]]
;	opAIdSt(a,2)  [y x [2 + 1]]
;	opBol/opEot   [[2 + 1] = [) y , x ( a]
;
;  Stage2 then output's 'a', '(', 'x', ',', 'y', ')', '=', '1', '+', '2'
;
;-----------------------------------------------------------------------


sBegin	RT
	EXTRN	B$IFOUT:far		;binary to ASCII numeric conversion
	EXTRN	B$FHEX:far		;binary to ASCII base 16 conversion
	EXTRN	B$FOCT:far		;binary to ASCII base 8 conversion
sEnd	RT

sBegin	DATA
;-----------------------------------+
; Inter-component Global variables: |
;-----------------------------------+
PUBLIC	otxListNext, otxListNextInc, cLeadingSpaces
otxListNext	DW 0	;text offset to opBol for next line to be listed
			; by ListLine().  Set by ListLine at exit.
otxListNextInc	DW 0	;text offset to opBol for next line after current
			; line, even if it is from an included file.
			; Set by ListLine at exit.
cLeadingSpaces	DB 0	;Could of leading spaces in listed line
			; Set by ListLine at exit.

PUBLIC	otxLsCursor			;Public to non-lister components
PUBLIC otxLsCursorTmp, ndLsCursor, colLsCursor ;PUBLIC to modules w/i lister
otxLsCursor	DW 0	;See ListLine header for description
otxLsCursorTmp	DW 0	;See ListLine header for description
ndLsCursor	DW 0	;node equivalent to otxLsCursor
colLsCursor	DW 0	;column equivalent to otxLsCursor
lnTypeFindSave	DB 0

PUBLIC	fLsIncluded
fLsIncluded	DB 0	;set TRUE if this line is from an $INCLUDE file
			; (i.e. opInclude was found in it).  This allows
			; ASCII Save to not send it to the file being saved.

;flags which get reset each beginning of line
PUBLIC	lsBolFlags
lsBolFlags DB 0		;FBOL_xxx masks

;flags which get reset each beginning of stmt
PUBLIC	lsBosFlags, lsBosFlags2, lsBosFlagsWord
lsBosFlagsWord LABEL WORD
lsBosFlags DB 0		;FBOS_xxx masks
lsBosFlags2 DB 0	;FBOS2_xxx masks

;variables used by ChkLineWrap to insert _<CrLf> in lines longer than 255 bytes
;
colLastTok	DW 0
colLastLine	DW 0

PUBLIC	fLsDynArrays
fLsDynArrays DB 0	;Initialized to FALSE by AsciiSave, set TRUE when
			; $DYNAMIC is listed, set FALSE when $STATIC is listed
			; Tested by AsciiSave.

QUOTE	=	022H			;quote char (")

;--------------------------+
; Lister Local variables:  |
;--------------------------+
CB_NODES_MIN	equ	200	;never let node buffer get < 200 free bytes
CB_NODES_GROW	equ	400	;when it does, grow it by 400
				;Note: this isn't because one node can be
				; 200 bytes long, its because one dispatch
				; can produce many nodes, which together
				; can be 200 bytes in length.  For example,
				; CALL x (x1,x2,x3,...,x50)

;bdNodes is a table descriptor for a growable buffer in the table-heap used
; to accumulate the generated listing.	It contains node entries
; which represent current line being listed.

	EVEN
PUBLIC	bdNodes
bdNodes bd	<0,0,0>


PUBLIC	fGotBol
fGotBol DB	0			;non-zero after 1st opBol
					;UNDEFINED if no leading spaces on line
					;else count of leading spaces

;oNodeRoot is an offset (initially NULL) into bdNodes for the node which
; is the root of a tree of nodes used to represent current line being listed.
;
PUBLIC	oNodeRoot
oNodeRoot DW	0

;oNodeTemp is an offset (initially NULL) into bdNodes for the node which
; is the root of a temporary tree of nodes used to construct complex
; nodes which will eventyally be pushed onto oNodeRoot's list.
;
PUBLIC	oNodeTemp
oNodeTemp DW	0

PUBLIC	opList2, opList
opList2 DW	0			;2 * opcode being listed.  Used
					; by individual listers to index
					; tables of opcode related data
opList DW	0			;value of current opcode before 
					;masking with OPCODE_MASK


PUBLIC	cLsArgs
cLsArgs DB	0			;temporary for counting down args


sEnd	DATA

subttl	List Debugging Functions




sBegin	LIST
assumes CS,LIST

;===========================================================================
;		Outer Loop of Lister
;===========================================================================

;***************************************************************************
; ushort FAR ListLine(otx, pbdDst)
;
; Purpose:
;	Converts one line of pcode to its ASCII source equivalent.
;	The pcode may be in any scan-state from SS_rude to SS_executable.
;	The pcode resides in a far (non DS) segment indicated by grsCur.oRsCur.
;	The buffer pointed to by pbdDst is grown if necessary EXCEPT FOR
;	THE SPECIAL CASE when pbdDst->cbLogical < 80, in which case,
;	the output is truncated.  This special case is for listing WATCH
;	expressions, which list to a static buffer that can't be grown.
;	All normal callers call this with pbdDst->cbLogical >= 80.
;
; Entry:
;	parm1: ushort oText - the offset into the current text table for
;		for the 1st opcode of the line to be listed.
;	parm2: char *pbdDst - points to destination buffer to
;		filled with the resulting ASCII source.
;	The global variable otxLsCursor = text offset for stmt to isolate
;	   columns for.  Causes column for otxLsCursor to be returned in dx.
;
; Exit:
;	returns UNDEFINED if out-of-memory-error
;	else returns actual number of bytes listed to pbdDst.
;	Text in pbdDst is 0-byte terminated (0 not included in byte count)
;	The global variable 'otxListNext' = text offset to opBol for next
;	   line to be listed by ListLine.  Set by ListLine at exit to speed
;	   up actions like listing 1 screen full, or ASCII Save.
;	The global variable 'otxListNextInc' is set to text offset to opBol
;	   for next line after current line, even if it is from an included
;	   file.
;	dx is set to UNDEFINED if otxLsCursor is not within this line.
;	   Otherwise, it represents the column offset into the ASCII
;	   output buffer where the opcode for otxLsCursor is.
;	   This is used by the User Interface code so it can
;	   highlight the current statement and position the cursor to errors.
;	The global variable 'fLsIncluded' is set TRUE if this line
;	   is from an $INCLUDE file (i.e. opInclude was found in it).
;	   This allows ASCII Save to not send it to the file being saved.
;	cLeadingSpaces is set to the number of leading spaces 
;	   that were on the line.
;
;***************************************************************************

cProc	ListLine <PUBLIC,NODATA,FAR>,<si,di>
	parmW	otxParm
	parmW	pbdDst

	localV	numBuf,8		;holds number for B$IFOUT
	localW	spSave
	localW	pbDstWarning
	localW  hTxdCurSeg		;handle of current text seg 
cBegin	ListLine
	mov	Word Ptr [lsBosFlagsWord],NULL ; clear any leftover flags
ListLineRestart:
	mov	[spSave],sp		;save for restart-ability
	mov	si,[otxParm]		;si = offset for 1st opcode to list
	sub	di,di			;di = offset to 1st node to output
	inc	di			;1st node must not be 0, because
					; we use NULL to indicate end-of-list.
					; This is much cheaper than using
					; UNDEFINED to indicate end-of-list.

	sub	ax,ax			;ax = 0
	mov	[fGotBol],al		;so we can stop at 2nd opBol
	mov	[fLsIncluded],al	;default to FALSE
	mov	[oNodeRoot],ax		;oNodeRoot = 0
	mov	[oNodeTemp],ax		;temp stack head = 0
	dec	ax			;ax = UNDEFINED
	mov	[ndLsCursor],ax
	mov	[colLsCursor],ax

	mov	dx,[otxLsCursor]
	mov	[otxLsCursorTmp],dx
	cmp	dx,si
	jae	StmtInLine		;brif stmt is in or beyond line to list
					; or if otxLsCursor == UNDEFINED
	mov	[otxLsCursorTmp],ax	;otxLsCursorTmp = UNDEFINED
StmtInLine:

	cmp	[bdNodes.BD_pb],NULL
	jne	GotBuffer		;brif we already have node buffer

;	Always allocate the node buffer if this is for compiler list support.

	;Allocate the buffer which holds nodes
	; BdAlloc(&bdNodes, 0, IT_NO_OWNERS)
	PUSHI	ax,<dataOFFSET bdNodes>
	PUSHI	ax,CB_NODES_GROW	;initial size of nodes buffer
	PUSHI	ax,<IT_NO_OWNERS>;heap type
	call	BdAlloc
	or	ax,ax
	je	J1_ListErrExit		;brif out-of-memory error
GotBuffer:

GetTextSegAddr:
	GETSEG	es,[txdCur.TXD_bdlText_seg],,<SIZE,LOAD> ;[4]
					;es = segment for current text tbl
	jmp	SHORT Stg1Loop

GetRoom:
	call	GrowBdNodes		;grow node buffer
	jne	GotRoom			;branch if not out-of-memory
J1_ListErrExit:
	DJMP	jmp SHORT ListErrExit

;We created node for token of interest, and it is on top of Root stack.
;Replace topNode with [<topNnode> <LNT_CURSOR node>], so Stage2 loop
;will save column of this token.
;
SetNdLsCursor:
	mov	[ndLsCursor],di
	mov	[otxLsCursorTmp],UNDEFINED ;make sure we don't branch here again
	jmp	SHORT SetNdRet

; Stage1:
;   The outer loop of Stage1 fetches the next opcode, maps it
;   to a function, and jumps to the function, which jumps
;   back to  the top of the loop.  The function for the 2nd encountered
;   opBol/opEot terminates this loop by not jumping back to
;   the top of the loop.  If the text is in SS_Executable
;   state, after fetching the executor, it maps to the opcode
;   associated with this executor.  The functions dispatched
;   to by this loop can expect:
;
;	DS -> DGROUP
;	ES -> the segment with the current text table
;	SI -> the next opcode to be fetched,
;	DI -> next free byte in buffer described by bdNodes.
;
;   The current text table is locked in order to avoid the need to continually
;   update es after each FAR call.
;
;THE FOLLOWING IS TRUE FOR QBx but not EB [11]
;   Stage1's outer loop guarentees at least CB_NODES_MIN free bytes

⌨️ 快捷键说明

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