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

📄 lsmain.asm

📁 Microsoft MS-DOS6.0 完整源代码
💻 ASM
📖 第 1 页 / 共 4 页
字号:
	add	cx,ax
					;cx points to column to advance to
	sub	cx,di			;subtract current column
	ja	ListCol1		;brif not already past that column
	mov	cx,1
	or	dx,dx
	js	ListCol1		;always list at least 1 space
	jmp	SHORT J1_Stg2Cont	;return to outer loop

subttl	List a numeric constant

;Table which maps LIT_xxx to runtime library's value types as follows:
;
; If the high bit is set, its a "special" number and:
;    the low 7 bits mean: 00cbbbbb where:
;        c = 0 for 16 bit integer, 1 for 32 bit integer,
;        bbbbb = base value (2, 8 or 16)
; Else the remaining 7 bits are the "runtime" value type
;    The runtime uses the convention that the low 4 bits = length of value
;
OrdConstStart 0
OrdConst LIT_I2		; % suffix
OrdConst LIT_O2		; &O prefix
OrdConst LIT_H2		; &H prefix
OrdConst LIT_I4		; & suffix
OrdConst LIT_O4		; &&O prefix
OrdConst LIT_H4		; &&H prefix
OrdConst LIT_R4		; ! suffix
OrdConst LIT_R8		; # suffix
OrdConst LIT_STR	; "xxx"

SNM_LONG EQU 40H	;indicates LONG special number

mpLtToRt LABEL WORD
	DB	VT_I2,0			;LIT_I2
	DB	084H,'O'		;LIT_O2
	DB	090H,'H'		;LIT_H2
	DB	VT_I4,'&'		;LIT_I4
	DB	0C4H,'O'		;LIT_O4
	DB	0D0H,'H'		;LIT_H4
	DB	VT_R4,'!'		;LIT_R4
	DB	VT_R8,'#'		;LIT_R8


;***************************************************************************
; ListNumNode
; Purpose:
;	List a numeric constant to the output buffer.
;
;***************************************************************************
DbPub ListNumNode
ListNumNode:
	push	si			;preserve node ptr
	GETSEG	es,[txdCur.TXD_bdlText_seg],,<SIZE,LOAD> ;[4]
					; es = seg for current text table
	xor	bh,bh
	mov	bl,[si.LN_val_clNum]	;bx = type of num (LIT_D2...LIT_LINENUM)
	mov	si,[si.LN_val_otxNum]	;es:si points to number
	cmp	bl,LIT_LINENUM
	je	ListUnsigned		;brif linenum


.errnz	LIT_I2
	or	bl,bl			;I2?
	jz	ListSigned
	shl	bx,1
	mov	ax,[mpLtToRt+bx]	;al = runtime's value type
					;ah = explicit type char
	or	al,al
	js	HexNum			;brif hex/octal/binary constant
	push	ds			;swap ds,es
	push	es
	pop	ds			;ds = seg adr of text table
	pop	es			;es = DGROUP
	mov	cx,ax			;cx = runtime's value type
	and	cx,000FH		;cx = # bytes in value
	push	di
	lea	di,[numBuf]		;di points to temp 8 byte buffer
	rep movsb			;copy value from pcode to numBuf
	pop	di			;restore di=ptr to next list byte
	push	es
	pop	ds			;restore ds = es = DGROUP

;al=runtime's value type, ah=explicit type char
CallFout:
	lea	bx,[numBuf]		;bx points to temp 8 byte buffer
	cmp	ah,'&'
	jne	NotLong
	push	ax
	mov	ax,[bx]
	cwd				;dx = 0 if ax <= 7FFF, else FFFF
	sub	dx,[bx+2]		;dx = 0 if number could be represented
					; as a short integer (i.e. '&' required)
	pop	ax
	je	NotLong			;brif '&' is necessary
	sub	ah,ah			;else list no explicit char
NotLong:
	call	far ptr ListNum		;copy ASCII number to di
NumDone:
	pop	si			;restore node ptr
	jmp	Stg2Cont		;return to outer loop

ListSigned:
	mov	si,es:[si]		;Get number to si
;	jmp	short ListUnsigned

DbPub	ListUnsigned
ListUnsigned:
;16-bit integer in si
	push	ds
	pop	es			;es=ds=dgroup
	xchg	ax,si			;put number in ax
	xor	cx,cx			;Initialize count of digits
	mov	bx,10
;While >10, divide by 10, counting digits
NextDig:
	inc	cx			;Count all digits
	cmp	ax,bx			;Less than 10?
	jb	SaveDig
	xor	dx,dx			;Extend to DWord
	div	bx			;Next digit is remainder in dx
	push	dx			;Save digit on stack
	jmp	NextDig

SaveDig:
	add	al,"0"			;Add ASCII bias
	stosb				;List a digit
	pop	ax			;Get next digit from stack
	loop	SaveDig
	xchg	si,ax			;Last thing popped was node pointer
	mov	byte ptr [di],0		;Terminate with zero
	jmp	Stg2Cont


;al & SNM_LONG is non-zero if LONG, ah = 'H', 'O', 'B' for hex,octal,binary
;es = text table's segment
;di = pointer to next byte to be listed (destination)
HexNum:
	push	ax			;save fLong
	xchg	bx,ax			;bl = fLong, bh = base char
	lods	WORD PTR es:[si]	;ax = low word of constant
	xchg	dx,ax			;dx = low word of constant
	sub	ax,ax			;default high word = 0
	test	bl,SNM_LONG
	je	NotLongHex		;branch if I2 constant
	lods	WORD PTR es:[si]	;ax = high word of constant
NotLongHex:
	mov	bl,'&'			;list '&'
	mov	[di],bx			;store &H, &O, or &B
	inc	di
	inc	di
	xchg	ax,dx			;dx:ax = I4 to output
	push	dx			;save high-word
	call	far ptr ListBaseNum
	pop	dx			;restore high-word
	pop	ax			;al = fLong
	or	dx,dx
	jne	NumDone			;brif implicitly long
	test	al,SNM_LONG
	je	NumDone			;brif implicitly short
	mov	BYTE PTR [di],'&'	;list second '&' to indicate long
	inc	di
	jmp	SHORT NumDone		;return to outer loop

;***************************************************************************
; ListBaseNum
; Purpose:
;	Copy the ASCII equivalent of a hex/octal number to a buffer
; NOTE:
;	This function assumes that the following runtime functions
;	cannot result in a runtime error: B$FCONVBASE, B$IFOUT
; Entry:
;	dx:ax = I4 to output
;	ds:di points to destination buffer
;	dh = 'H' or 'O' for hex/octal
; Exit:
;	di points beyond last byte of number (i.e. TO 0-byte terminator)
;	es = ds
;	
;***************************************************************************

cProc	ListBaseNum,<PUBLIC,FAR>,<si>

cBegin
; bh = 'H' for Hex, 'O' for Octal
; dx:ax = I4 to convert
; di points to next free byte in output buffer
;
DoConv:
	mov	cx,0F04h		;ch=mask, cl=shift count
	cmp	bh,'H'
	je	GotHex
	mov	cx,0703h		;ch=mask, cl=shift count
	DbAssertRelB bh,e,'O',LIST,<ListBaseNum called with bad dh>

GotHex:
	lea	bx,[di+12d]		;bx points to end of 12 byte buffer
	call	B$FCONVBASE		;dx points to 1st byte of result
					;bx = number of digits
					;es = ds
	mov	cx,bx			;cx = number of digits
	mov	si,dx			;bx points to 1st digit
	rep movsb			;copy ASCII string to list buffer
LBNExit:
	mov	BYTE PTR [di],0		;0 terminate result
cEnd


;***************************************************************************
; ListNum
; Purpose:
;	Copy the ASCII equivalent of a binary number to a buffer
;	Used by WATCH pcode as well as lister.
; Entry:
;	al = type of number (VT_I2, VT_I4, VT_R4, VT_R8, VT_CY (EB specific))
;	ah = explicit terminating char (i.e. %, !, &, #, @ (EB specific))
;	bx points to 1st byte of binary number (in DS)
;	di points to destination buffer (in DS)
; Exit:
;	di points beyond last byte of number (i.e. TO 0-byte terminator)
;	es = ds
;
;***************************************************************************
cProc	ListNum,<PUBLIC,FAR>,<si>
cBegin
	push	ds
	pop	es			;es = DGROUP
	push	ax			;save ah=explicit type char
					; pass B$IFOUT ptr to value in es:bx
					; pass B$IFOUT valTyp in al
	call	B$IFOUT			;bx = adr of ascii string
					;ax = byte count
	pop	dx			;restore dh = explicit type char
	cmp	BYTE PTR [bx],' '
	jne	NoSpc			;brif no leading space
	inc	bx			;skip leading space
	dec	ax
NoSpc:
	xchg	cx,ax			;cx = # bytes in ASCII string
	mov	si,bx			;si points to start of ASCII string

	;copy ascii string from BIFOUT's static buffer to result buffer
NumLoop:
	lodsb				;al = next byte to transfer
	stosb				;list it
	cmp	al,'E'
	je	Not0to9
	cmp	al,'D'
	je	Not0to9
	cmp	al,'.'
	jne	Its0to9
	cmp	dh,'#'
	je	Its0to9			;. isn't strong enough to not list #
					;else 10.5# would list as 10.5 (R4)
	cmp	dh,'@'
	je	Its0to9			;same goes for @
Not0to9:
	sub	dh,dh			;no explicit type needed, we got
					; a period, E or D
Its0to9:
	loop	NumLoop
	or	dh,dh
	je	LnExit			;brif not explicit type char needed
	mov	al,dh			;al = explicit type char
	stosb				;list it
LnExit:
	mov	BYTE PTR [di],0		;0 terminate result
cEnd

;***************************************************************************
; SetLsCursor				; - function added in this rev.
; Entry:
;	ax = number of bytes in line
;	bx = pbdDst
;	[colLsCursor] = column of interest (equivalent to otxLsCursor)
; Exit:
;	dx = column of interest (equivalent to otxLsCursor)
;
;***************************************************************************
cProc	SetLsCursor,<NEAR>,<si>
cBegin
	mov	cx,UNDEFINED		;for cheaper comparisons below
	mov	dx,[colLsCursor]
	cmp	dx,cx
	jne	NotStmtEnd		;brif colLsCursor already set
	cmp	[ndLsCursor],cx
	je	NoColCursor		;brif otxLsCursor wasn't in line
	xchg	dx,ax			;else, this is it, dx=column

;Make sure that column of interest isn't pointing to a blank,
;If it is, make first token after blank column of interest
NotStmtEnd:
	cmp	dx,cx
	je	NoColCursor		;brif otxLsCursor not in this line
	mov	si,[bx.BD_pb]		;si points to 1st byte of result
	add	si,dx			;si points to column of interest
SkipBlanks:
	lodsb				;al = byte at column of interest
	cmp	al,' '
	je	SkipBlanks
	cmp	al,0
	je	NoColCursor		;brif blanks are at end-of-line
	dec	si			;si points to 1st non blank
	mov	dx,si
	sub	dx,[bx.BD_pb]		;dx = offset to 1st non blank
NoColCursor:
cEnd


;***************************************************************************
; B$FConvBase
; Purpose:
;	Convert an I4 to ASCII Hex/Octal/Binary without causing any
;	Heap Movement.  This is needed by QBI.
; Entry:
;	BX points beyond last byte of 11 byte buffer (32 bytes for _BFBIN)
;	CH = Mask, CL = Shift count, i.e.
;	   0703 for Octal, 0F04 for Hex
;	DX:AX = number to convert
; Exit:
;	DX points to 1st byte of resulting string
;	BX = number of digits in resulting string
;	ES = DS
;
;***************************************************************************
cProc	B$FCONVBASE,<NEAR>,<DI>	
cBegin
	MOV	DI,BX		;DI points beyond destination
	XCHG	AX,BX		;DX:AX = I4 to be converted
	STD			;move from high to low
	PUSH	DS		;set ES=DS
	POP	ES
	XOR	AH,AH		;init char count

; At this point the following conditions exist:
;	AH = Character count
;	CH = Mask
;	CL = Shift count
;	DX:BX = I4 to convert
;	DI = pointer to digit buffer
; Perform the conversion by shifting DX:BX by CL bits and masm out
; unused bits with CH.	Take this number and convert to ascii char
; representing digit. Stuff the char in the buffer, bump the char
; count and continue until no non-zero digits remain.

CONVERT_LOOP:
	MOV	AL,BL		;Bring number to accumulator
	AND	AL,CH		;Mask down to the bits that count
;Trick 6-byte hex conversion
	ADD	AL,90H
	DAA
	ADC	AL,40H
	DAA			;Number in hex now
	STOSB			;Save in string
	INC	AH		;Count the digits
	PUSH	CX		;Save mask/shift count
	XOR	CH,CH		;zero out mask, leaving shift count

SHIFT_LOOP:
	SHR	DX,1		;shift low bit into carry, zero high bit
	RCR	BX,1		;rotate carry into low word
	LOOP	SHIFT_LOOP	;repeat shift count times

	POP	CX		;recover mask/shift count
	PUSH	BX
	OR	BX,DX		;is rest of I4 = 0?
	POP	BX
	JNZ	CONVERT_LOOP	;brif not, convert next digit

	CLD			;Restore direction UP
	INC	DI		;Point to most significant digit
	MOV	DX,DI		;Put string pointer in DX
	MOV	BL,AH		;Digit count in BX (BH already zero)
cEnd
sEnd	LIST

end

⌨️ 快捷键说明

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