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

📄 asm.asm

📁 比dos下的debug更好的debug程序源码
💻 ASM
📖 第 1 页 / 共 3 页
字号:
;The problem here appears to be, immediates have size 0 unless they are
;prefixed with byte ptr, word ptr, etc.  So for example, any size operand
;can be stuck into [44], like AL, AX, or EAX.  Furthermore, it was a
;conscious design decision that mov al,FFFF is allowed as an editing
;function. That is, you can enter as many hex digits as you want, if
; the number is too big then digits on the left are truncated.  This
; allows changing the number without using the backspace key.


chsize:					; collect a size
	mov	al,arg1.asize		;see if first arg size is 0
	or	al,al			;used later, so load into AL
	jnz	szch			;if non0 size, more checking
	mov	al,arg2.asize		;else load up size of 2d arg
	or	al,al			;used again
	jnz	szch			;if non0, keep checking?
	mov	al,arg3.asize		;check size of final arg
	or	al,al
	jnz	szch			;if it has non0 size
	clc				; no size, let it go
	ret
szch:
	test	arg1.asize,0FFh		;if arg1 has a size
	jz	noa1			;
	cmp	al,arg1.asize		;it must match the collected size
	jnz	absx			; or check for special cases
noa1:
	test	arg2.asize,0FFh		; if arg2 has a size
	jz	noa2			
	cmp	al,arg2.asize		; it must match the collected size
	jne	absx  			; or we check for special cases
noa2:	
;Near as I can tell, we get here if:
;1) Both arg1.asize and arg2.asize are 0 
;2) Either or both is nonzero but matches the collected size
;
;We have to check the arg3 byte, this is necessary for example in
; the 386 imul instruction.  If both arg1 and arg2 had no size this
; extra compare makes no difference as there won't be an arg3 and the
; size will have been initialized to zero
	test	arg3.asize,0FFh		; if arg3 has a size
	jz	finalsize
	cmp	al,arg3.asize		; it must match the collect size
	jne	absx			; or we check for special cases
finalsize:
	call	setsize			;set the size we found in all ops
	jmp	chimmsize		;chk immediates and based addressing
;
; get here on size mismatch, must check for special cases
;
absx:
	mov	eax,dword ptr [EnteredMnemonic] ; get ASCII for mnemonic
	and	eax,0ffffffh
	cmp	eax,"tuo"		; out?
	je	vox			; yes, no size error
	cmp	ax,"ni"			; in?
	je	vox			; yes, no size error
	mov	di,offset arg2		; is arg2 cl?
	call	chkcl			;
	jz	vox                     ; yes, no size error
	mov	di,offset arg3		; is arg3 cl?
	call	chkcl
	jz	vox
	call	printAlignedErrorMsg	; otherwise print an error and get out
	db	"Bad size",0
	stc
vox:
	ret
;
; get here if we had an immediate, must check sizing
;
chimmsize:
     	mov	di,offset arg1
	call	immsize			;see if immediate that will fit
	jc	vox			;nope, won't fit
	call	chkbase			;else chk for valid based addressing
	jc	vox			;not valid
     	mov	di,offset arg2		;
	call	immsize			; see if immed that will fit
	jc	vox             	; nope, won't fit
	call	chkbase			; check for valid based mode
	jc	vox			; not valid
     	mov	di,offset arg3
	call	immsize			; see if immed that will fit
	jc	vox			; nope, won't fit
	call	chkbase			; check for valid based mode
	jc	vox			; not valid
	ret
validops	ENDP


;One of the allowed exceptions is a shift or rotate of a register exceeding
;8 bits by CL, which is 8 bits.  Here we check for that CL, and allow the
;exception if we find it
;INPUT: DI points to this structure
;OUTPUT: ZF if we found CL, NZ if we didn't

chkcl	PROC
	cmp	[di+asmop.mode],AM_REG	; check if register involved
	jne	cclerr			; if not, can't be CL
	cmp	arg2.areg1,isECX	; else see if ECX involved at all
	jne	cclerr			; if not, can't be CL
	cmp	arg2.asize,BYTESIZE	; if ECX is byte, must be CL
cclerr:
	ret
chkcl	ENDP


;INPUT: AL is an argument size 1=byte, 2=word, 4=dword
;	EnteredMnemonic is a bucket containing what the user typed
;	PrefixBitmapWord containing a bit for each type of prefix allowed.
;		AS_OPSIZE is for operand size override prefix OS:, which
;		means stick in a 66h
;	arg1,2, and 3 are instances of structure ASMOP. asize is the size
;		of the operand.  An instruction can have up to 3 operands
; What we do here is set the passed size as the size of all 3 operands,
; setting the 66 override if dword size (and not FP), and returning ZF
; if it was a dword, and NZ if it was not

setsize	PROC
	cmp	al,DWORDSIZE			; is it a dword?
	jne	ssnoop				; no, no opsize checking
	cmp	byte ptr [EnteredMnemonic],'f'	; floating point instruction?
	je	ssnoop				; yes, no opsize prefix
	or	[PrefixBitmapWord],AS_OPSIZE	;include 'OS:' prefix
ssnoop:
	mov	arg1.asize,al			;set all sizes the same
	mov	arg2.asize,al
	mov	arg3.asize,al
	cmp	arg1.asize,DWORDSIZE		;rtn NZ if NOT a dword
	clc
	ret
setsize	ENDP
;
; Check the size of an immediate
;
;INPUT: DI points to structure built for this instruction
;	AL contains size of first argument
;If immediate operand, make sure that the size of the argument passed in
;AL is valid. Apparently an immediate dword is always OK, but it is necessary
;in that case to set a bit indicating the operand size prefix, 
;Otherwise, in cases of byte or word, it is necessary to make sure that
;the target offset (or segment if seg:ofs) does not exceed the immediate
;value in size.  This is not nearly well enough understood to draw any
;conclusions yet.
;  My guess is that if we have something like mov eax, immediate, then any
;immediate is OK.  If it is mov ax, immediate, then the value to be moved in
;must be a byte or word. Finally, if mov al, immediate, then the immediate
;value must be a byte
;OUTPUT: NC if immediate operand will fit in target, CY if not.

immsize	PROC
	cmp	[di+asmop.mode],AM_IMM		;see if immediate value
	clc					;assume not
	jne	immok				;and if not, we're OK
	cmp	al,DWORDSIZE			;else chk for dword size
	jae	immokl				;go if AL >=4 (dword)
	cmp	al,WORDSIZE			;else if AL is word size
	clc					;assume it is
	jne	bytech				;if not, go chk byte offset
	test	[di+asmop.addrx],0ffff0000h	;else test for word offset
	jz	immok				;if so, we're ok
	stc					;else error
immok:
	ret
immokl:
	or	[PrefixBitmapWord],AS_OPSIZE	;set this
	ret
bytech:
	test	[di+asmop.addrx],0ffffff00h	;test for byte offset
	jz	immok				;OK if byte
	stc					;else error
	ret
immsize	ENDP

;
; subroutine to verify that a based/indexed mode has a correct
; register combination
;
; INPUT: DI = pointer to operand (asmop) structure
; OUPUT: CY set on error, clear if ok
;
chkbase	PROC
	cmp	[di+asmop.mode],AM_BASED	;is it base+something?
	jne	cbxnb				;if not, get out
	cmp	[di+asmop.msize],BYTEMODE	;see if byte-mode addressing
	je	cberr				;no can do this
	cmp	[di+asmop.msize],DWORDMODE	;how about dword?
	je	cb32				;go check 32-bit addressing
;
; if we get here we have 16-bit addressing.  No scale factors allowed.

	cmp	[di+asmop.ascale],TIMES1	;check scale factor against 1
	jne	cberr				;error if not 1
	cmp	[di+asmop.areg1],isESP		;check for sp
	je	cberr				;error if trying to index off sp

	cmp	[di+asmop.areg1],isEBX		;Carry clear if eax,ecx,edx
	jb	cberr				;error if trying to index off those

;areg2 is any second register (like [bx+si+nnnn]

	cmp	[di+asmop.areg2],0FFh		;any second register

;A table is emerging from the following.  It tells us:
;

	je	cbx				;didn't get to second base
	cmp	[di+asmop.areg2],isESP		;is 2d base ESP
	je	cberr				;if so, illegal
	cmp	[di+asmop.areg2],isEBX		;compare with EBX value
	jb	cberr				;error is ax,cx,dx
	cmp	[di+asmop.areg1],isESI		;compare with ESI
	jae	cbdown				;ok for  si,di
cbup:
	cmp	[di+asmop.areg2],isESI		; check second if si or di
	jz	cbx				; ok if so
	jmp	cberr				;err if anything else

;
; we got here if the first arg is si/di, in which case the second arg
; must be bx or bp

cbdown:
	cmp	[di+asmop.areg2],isESI		;if bx or bp
	jb	cbx				;we're OK

;Errors go here. By implication, these errors are:
;1) using ESP at all for a base register
;2) using EAX, ECX or EDX as a base register
;3) using a register combo other than [si + bx] [si + bp] [di + bx] [di+bp]

cberr:
	call	printAlignedErrorMsg
	db	"Invalid base or index register",0
	stc
	ret

;
; we get here if we have a 32-bit address mode with based addressing
;

cb32:
	test	[Disassemble32Bit],TRUE		;dwords allowed at all?
	jz	cberr				;if not, bomb
	or	[PrefixBitmapWord],AS_ADDRSIZE	;else set addrsize prefix
	cmp	[di+asmop.areg1],isEBP		;see if EBP is first reg
	jne	cb32n2bp			;skip if not
	cmp	[ di+asmop.areg2],isEBP		;else if second is EBP
	je	cberr				;that's an error
cb32n2bp:
	cmp	[di+asmop.areg2],isESP		;check for [exx + esp]
	jne	cbx				; if not, accept it
	cmp	[di+asmop.ascale],TIMES1	; else check for a scale factor
	jne	cberr				; error if not 1
cbx:
	push	ax
	mov	al,[di+asmop.areg1]

;
; now we have to figure out whether DS or SS is the default segment

	and	al,6		; turn ebp into esp
	cmp	al,isESP	; is esp or ebp?
	jne	cbx1		; no
	mov	DefaultSeg,2	; else default to sseg
cbx1:
	mov	al,[di+asmop.areg2]

	and	al,6            ; turn ebp into esp
	cmp	al,isESP	; is esp or ebp?
	jne	cbxnb		; no
	mov	DefaultSeg,2	; else default to sseg
cbxnb:
	pop	ax

	clc
	ret
chkbase	ENDP


; print out error message
; INPUT: The error message is embedded in the code immediately following the
;	call to printAlignedErrorMsg
;
; this allows 32 characters for the input string.  It tabs the error
; message over to 32 columns beyond the first column of input.  If the
; input took more than 32 characters the error message cannot be aligned
; and is just tagged right after the input.

printAlignedErrorMsg	proc
	mov	cx,0FFFFh	;search a segment worth
	mov	di,offset inputbuffer	;in buffer
	mov	al,13		;for a CR
	repne	scasb		;find it
	add	cx,32		; space to line up errs
	jcxz	nospace
	jns	ok
	mov	cx,1		;if can't align, use single space
ok:
	call	printspace
	loop	ok
nospace:
	PRINT_MESSAGE	"??? "
	jmp	PrintFollowingMessage
printAlignedErrorMsg	ENDP
;
; get the opcode and scan the tables for it
;
;
getcode	PROC
	mov	RepPfxBitmap,0	;No Reps/locks found
getcode3:
	mov	di,offset EnteredMnemonic	;point to mnemonic buffer
getcode2:
	lodsb			;get input character
	cmp	al,' '		;see if space or below
	jbe	nomore		;if so, done, don't store
	stosb			;else store it
	cmp	al,':'		;was it a colon?
	je	nomore2		;if so, ignore it and end the name
	jmp	getcode2
nomore:
	dec	si   	       	; all done, backtrack
nomore2:
	mov	ah,[di-1]      	;get last char we stuffed in buffer
	mov	[lastbyte],ah	; last byte is used by some commands
				; string &c
	mov	al,0		; store the trailer
	stosb
	push	si		;save where we left off in input string
	mov	si,offset EnteredMnemonic	;point to buffer we just stuffed
	call	strlen		; length of name in buffer into AX
	inc	ax		; plus trailer
	mov	si,offset EnteredMnemonic	; check for repeats and lock
	mov	di,offset say_repne	;actual string 'repne'
	mov	cx,ax		;length to compare
	repe	cmpsb		;see if a match, lowercase
	mov	bl,AF_REPNE	;this is 2
	jz	reps		;if a match, go to reps to stuff in RepPfxBitmap
	mov	si,offset EnteredMnemonic	;else lets look for repe
	mov	di,offset say_repe
	mov	cx,ax
	repe	cmpsb
	mov	bl,AF_REPE	;this is 4
	jz	reps
	mov	si,offset EnteredMnemonic
	mov	di,offset say_rep	;just look for rep
	mov	cx,ax
	repe	cmpsb
	mov	bl,AF_REP	;this is 1
	jz	reps
	mov	si,offset EnteredMnemonic	
	mov	di,offset say_lock	;look for lock
	mov	cx,ax
	repe	cmpsb
	mov	bl,AF_LOCK	;this is 8
	jz	reps
	cmp	ax,4		;is the length 4 (including 0-terminator?)
	jnz	npf		;if not, go look it up
	cmp	[EnteredMnemonic+2],':'	;else maybe segment override, so check colon
	jne	npf		;not a colon, so go look it up
	mov	ax,word ptr [EnteredMnemonic]	;else, get 1st 2 chars in AX
	mov	di,offset OverridePfxList	;point to string of possible prefixes
	mov	cx,8		;there are 8, 2 of which I've never heard of
	repne	scasw		;see if any match
	jnz	npf		;if not, go look it up the hard way
	bts	[PrefixBitmapWord],cx	;set prefix word bit for this prefix
	pop	si		;back to our input line
	call	WadeSpace	;find next string
	jnz	getcode3	;got one, so start over
	stc			;else we failed???
	ret
npf:
	mov	si,offset EnteredMnemonic	;point to buffer containing instruction
	call	LookupOpName	;and go look it up
	pop	si		;restore SI ptr to next input
	jc	gcx		; get out if nonexistant
	call	WadeSpace	; see if any more...
gcx:
	ret
reps:
	pop	si		;restore pointer to input
	or	RepPfxBitmap,bl	;set bitmap for rep prefix found
	call	WadeSpace	;find next
	jnz	getcode3	;if more, parse that
	stc			;else invalid - something must follow rep
	ret
getcode	ENDP
;
; get an operand
;
; INPUT: DI points to asmop structure for this arg
;	SI points to input buffer past opcode string
; OUTPUT: CY if arg is invalid
; PROCESSING:
;	1) init asmop structure
;
parsearg	PROC
	mov	[di+asmop.asize],NOSIZE
	mov	[di+asmop.areg1],0FFh
	mov	[di+asmop.areg2],0FFh
	mov	[di+asmop.ascale],1
	mov	[di+asmop.addrx],0
	mov	[di+asmop.mode],AM_NONE
	mov	[di+asmop.msize],0
	call	wadespace      		;see if any more???
	jz	gax	 		; comma taken care of by wadespace
	cmp	byte ptr [si],'['	;see if opening an indirect addr
	je	getbrack		;if so, look for contents
	call	parsecontrol		;else chk for control register
	jc	gax			;error, bad ctrl reg
	jz	gaxc			;good ctrol reg, we got it
	call	parsesize		;set width, 1-10
	jc	gax			;bad width, bomb
	jz	getbrack		;else found width, get inside bracket
	call	parseseg		;else check for segment arg
	jc	gax			;bad seg arg
	jz	gaxc			;if good one, find more
	js	getbrack		;if SF, seg is inside brackets
	call	parsereg		;so find register
	jz	gaxc			;got it, find mire
	mov	[di+asmop.mode],AM_NONE	;assume it is just a number
	call	parseval		;look for an immediate
	jc	gax			;nope, bomb
	mov	[di+asmop.mode],AM_IMM	;else say it is an immediate
	mov	[di+asmop.addrx],ebx	;so save that
	call	wadespace  		;find next
	cmp	al,':'			;a colon?
	jnz	gaxc			;if not, done
	inc	si			;else move past colon
	call	parseval		;and get target value
	jc	gax			;sorry, no value found
	mov	[di+asmop.addrx2],ebx	;else stash the value in addrx2

;Aha, I think I dig. This flag indicates that addrx1 contains a segment
;value and addrx2 has the offset.  If this flag is clear, addrx1 has an
;offset and addrx2 is inoperative.

	mov	[di+asmop.mode],AM_SEGOFFS	;set flag
gaxc:
	call	WadeSpace
	clc
gax:
	ret

;Handle the case where we have something in brackets.
;SI points to the opening bracket character


getbrack:

⌨️ 快捷键说明

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