home *** CD-ROM | disk | FTP | other *** search
- ;
- ; GRDB
- ;
- ; Copyright(c) LADsoft
- ;
- ; David Lindauer, camille@bluegrass.net
- ;
- ;
- ; dis.asm
- ;
- ; Function: patch the dissassembly code together, display the output
- ; handle disassembler commands
- ;
- ;MASM MODE
- .model small
- .386
-
- include eprints.inc
- include ioperand.inc
- include eoperand.inc
- include iopcodes.inc
- include eopcodes.inc
- include emtrap.inc
- include einput.inc
- include eoptions.inc
-
- PUBLIC diss,DisOneLine
-
- DEFAULTBYTES = 32 ; max number of bytes/line (should be 16)
-
- .data
-
- startingDisAddr dw 0 ;current disassembly address
- endningDisAddr dw ? ;end of disassembly
- extraBytes dw 0 ;number of overflow bytes, e.g. if instruction
- ;was more than five bytes we need more lines
- DisassemblySeg dw 0 ;disassembly segment
-
- .code
- oldposition EQU bp - 4 ;beginning of bytes for line
- put EQU bp -6 ;unused
- bytestomove EQU bp - 8 ;number of bytes to put in hex dump portion
- ;of line
- ; .code
-
- isNewLine EQU [bp-2] ;set to true if we are doing an overflow line
- oldposition EQU [bp-4] ;beginning of bytes for line
- put EQU [bp-6] ;unused
- bytestomove EQU [bp-8] ;number of bytes to put in hex dump portion
- ;of line
-
- ;
- ; Get a dissassembled line of code
- ; INPUT: DI points to 256-byte buffer in caller's stack frame
- ; Remember that DS=SS during this process
- ; SI appears to point to the code to disassemble
- ;
- GetCodeLine PROC
- ENTER 8,0 ;8 bytes of automatic space
- mov WORD PTR isNewLine,TRUE ; Assume it has an opcode
- mov BYTE PTR [di],0 ; Clear output buffer
- mov oldposition,si ; Current position
- test extrabytes,0FFh ; See if still printing bytes
- jz short notextra ; from last instruction
-
- ;Only 5 code bytes fit on a line before the mnemonics, so if this instruction
- ;had >5 bytes, we need to stick them on another line by themselves. In this
- ;case, we already snagged them, and I guess DI points to them. So we add
- ;the number of additional bytes to our pointer to the input, then exchange
- ;this with the buffer pointer
- ; The implication here is that the entire opcode has been disassembled
- ;and converted to mnemonics, but defninitely not clear yet just exactly
- ;where the extra opcode bytes get displayed. Right here, we tab over to
- ;a new position and zero out the buffer beyond those bytes.
-
- add si,extrabytes ; New position to edi
- xchg si,di ;
-
- ;Now, SI points into the buffer at a location just past the extra bytes. We
- ;put a 0 into the buffer for reasons unknown right now, then call TabTo.
- ;AHA, TabTo calls strlen, which will return a string length of 0 since SI
- ;points to a 0, and therefore we get a full tab. TabTo stuffed the
- ;intervening positions with spaces, and terminated them with 0. But we
- ;overwrite that and the next 15 buffer positions with 0 anyway.
-
- mov BYTE PTR [si],0 ; Clear buffer
- mov al,10 ; Tab to pos 14
- call TabTo ; by stuffing spaces into the buffer
- xchg si,di ; edi = buffer again now
- push di ;save buffer position
- mov cx,4 ; next four DWORDS = 0;
- sub ax,ax ;
- rep stosd ; Store the dwords
- pop di ;and point at 16 0's
- mov WORD PTR isNewLine,False; Doesn't have an opcode
- jmp btm
-
- ;OK, we aren't doing leftover stuff from the prior call.
-
- notextra:
- mov ax,code_address ; Get code address
- cmp ax,endningDisAddr ; See if done
- jnc endcodeline ; Quit if nothing left
- xchg si,di ; esi = buffer now
- push esi ;save buffer address
- mov ax,fs ;get segment
- call putword ;build that into buffer
- mov BYTE PTR [si],':' ; Print ':' in buffer
- inc si ;go past the colon
- mov ax,code_Address ; Get code address
- call putword ; Print it out in buffer
- mov BYTE PTR [si],' ' ; Put a space
- inc si ;go past the space
- mov BYTE PTR [si],0 ; Put an end-of-buffer
- pop eax ;restore the buffer address into EAX
- xchg esi,eax ;now put it into ESI, EAX has new ptr
- push eax ;save new pointer
- mov al,25 ; Tab to pos 29
- call TabTo ;stuff with spaces
-
- ;XCHG always gives me headaches. Lets see... TabTo bumped SI up, while EAX
- ;still holds the buffer position before the spaces TabTo put in there.
- ;More important, the prior position is on the stack, since we are about to
- ;blow EAX at ReadOverrides. This old position (just after the offset) will
- ;eventually be popped into EDI.
- ; Now DI points to the post-spaces position, and SI points to whatever DI
- ;pointed to. This requires a careful trace, so:
- ;1) DI entered this routine pointing to the 256-byte buffer on the stack
- ;2) Then, it was exchanged, so DI pointed to the code to disassemble
- ;3) Now, di points back into the buffer and SI points to the code to dis
-
- xchg si,di ; edi = buffer beyond spaces
- call ReadOverrides ; Read any overrides
- call FindOpcode ; Find the opcode table
-
- ;The prior two calls moved SI past this opcode, which was consumed and
- ;translated. NOW we point SI back into the buffer and DI at the code
- ;to disassemble.
-
- xchg si,di ; esi = buffer, di=code
- jnc short gotopcode ; Got opcode, go format the text
-
- ;If the opcode was unrecognised, we need to just DB this byte and try again
- ;to find the start of an opcode on the next byte until we are back into
- ;some kind of sync again.
-
- push si ; Else just put a DB
- mov ax,"db" ;opcode not in table, could be new
- call put2 ; CPU type
- pop si ;restore position before 'db'
- mov al,TAB_ARGPOS ; Tab to the arguments=12+4?
- call TabTo ;stuff with spaces
- mov al,fs:[di] ;Get next code byte into AL
- inc di ;bump code pointer
- call putbyte ;cvt to ASCII and stick in bufer
- mov BYTE PTR [si],0 ; End the buffer
- xchg si,di ;DI=buffer, SI=code
- pop edi ;address just past offset of address
- jmp short btm ; Go do the byte dump
-
- ;If we got here, the opcode was recognized. Right here:
- ;SI=buffer pointer, DI=code pointer
-
- gotopcode:
- push si ;save buffer pointer
- mov si,di ;point SI at the code
- sub ax,ax ; assume 16-bit disassembly
- call DispatchOperands ;this probably bumps SI past them
- mov di,si ;so DI is now the code pointer
- pop si ;restore the buffer pointer
- push di ;save the code pointer
- call FormatDisassembly ;Use the operand parse to format output
- pop di ;restore code pointer
- xchg si,di ;SI now code, DI now bufer
-
- ;EAX, pushed far above, contained a pointer into the buffer just past the
- ;offset part of the address plus 1 space, and points at the 0 following
- ;that space.
-
- pop edi ;but so what, since DI now restored
- btm:
-
- ;We already put a 0 in this location way up above, but I guess it won't
- ;hurt to do it twice, just to make sure...
-
- mov BYTE PTR [di],0 ; End the buffer
-
- ;Ouch. Let's see... SI points to the code we are disassembling whether we
- ;found a valid opcode or not. Probably coincidence.
-
- mov ax,si ; Calculate number of bytes to dump
- sub ax,oldposition ;by subtracting old from new offset
- mov bytestomove,ax ;and set variable with result
- mov extrabytes,0 ; Bytes for next round = 0
- cmp WORD PTR bytestomove,5 ; See if > 5
- jbe short notmultiline ; No, not multiline
- mov ax,bytestomove ; Else calculate bytes left
- sub al,5 ;and save result for next time
- mov extrabytes,ax
- mov WORD PTR bytestomove,5 ; Dumping 5 bytes - our max
- notmultiline:
-
- ;Ouch again. Lets see... SI points to the code, and DI to the buffer, so
- ;we switch them, DI=code and SI=buffer
-
- xchg si,di ; esi = buffer
- push di ; Save code pointer
- mov di,oldposition ; Get original code position
- mov cx,bytestomove ; Get bytes to move
- putlp:
- mov al,fs:[di] ; Get a byte
- call putbyte ; Expand to ASCII
- mov BYTE PTR [si],' ' ; Put in a space
- inc si ; Next buffer pos
- inc di ; Next code pos
- LOOP putlp ; Loop till done
- xchg si,di ; Restore regs DI=buf, SI=code
- mov ax,bytestomove ; Codeaddress+=bytes dumped
- add code_address,ax
- endcodeline:
- mov ax,isNewLine ; Return new line flag
- LEAVE
- ret
- GetCodeLine ENDP
- ;
- ; Main disassembler
- ; The user pressed the U command key, followed by ???, then CR. We are going
- ; to disassemble from either where we are, or from the address provided.
- ; My guess is that SI points to the input line at the character
- ; following the U.
- ;
- ;
- diss PROC
- ENTER 256,0 ; Buffer = 256 bytes long
- call crlf ; start on new line
- call WadeSpace ; See if any parms
- jz short atindex ; No disassemble at index
- call ReadAddress ; Else read start address into BX
- jc badargs ; Get out bad args
- mov ax,DEFAULTBYTES ; Number of bytes to disassemble=32
- add ax,bx ; Find end of disassembly
- jnc okadd ; Seems to be a segment limit
- mov ax,0FFFFh ; goto end of segment?
- okadd:
- mov endningDisAddr,ax ; Save count? as default
- call WadeSpace ; See if any more args
- jz short gotargs ; No, got args
- call ReadNumber ; Read the end address
- jc short badargs ; Out if bad args
- mov endningDisAddr,ax ; Save end
- jmp short gotargs ; We have args
- badargs:
- stc ; Error
- LEAVE
- ret
- atindex:
- mov bx,startingDisAddr ; Get the next address to disassemble
- mov dx,DisassemblySeg ;
- mov ax,DEFAULTBYTES ; Default bytes to disassemble
- add ax,bx ;
- mov endningDisAddr,ax ; Set up end
- gotargs:
- call defCS ; get CS segment
- mov code_address,bx ; Save code address for printout
- mov si,bx ;
- mov fs,dx ; ES = the seg
- mov DisassemblySeg,fs
- gcloop:
- call scankey
- jnz dusetadr
- lea di,[bp - 256] ; Get the buffer
- call GetCodeLine ; Get a line of text
- lea bx,[bp - 256] ; Print out the text
- call dgroupMessage
- call crlf
- cmp si,0fff0h
- jnc dusetadr2
- cmp si,endningDisAddr
- jc gcloop ; Loop if not
- test extrabytes,0FFFFh ; Loop if not done with dump
- jnz gcloop
- dusetadr:
- mov si,code_address
- mov startingDisAddr,si
- clc
- LEAVE
- ret
- dusetadr2:
- sub si,si
- mov code_address,si
- jmp dusetadr
- diss ENDP
- ;
- ; Disassemble one line. Used by the Reg display command
- ; INPUT: DX holds segment value (CS)
- ; BS holds offset value (IP)
- ;
- DisOneLine PROC
- ENTER 256,0 ; Space for buffer
- push bx ;save logical IP
- push dx ;and logical CS
- call crlf ;so CRLF won't blow them
- pop dx
- pop bx
- mov ax,1 ;move to next position
- add ax,bx ; One byte to disassemble
- mov endningDisAddr,ax ;(will disassemble entire instruction)
- mov code_address,bx ;save this disassembly address
- mov fs,dx ;save segment in FS
- mov si,bx ;point to code to disassemble in SI
- mov startingDisAddr,si ; Save new starting index
- mov DisassemblySeg,fs ;set disassembly segment
- dol_loop:
- lea di,[bp - 256] ;Point DI at buffer to dis into
- call GetCodeLine ; Get a line of code
- lea bx,[bp -256] ;point BX at line we created
- call dgroupMessage ;and put it on the screen
- call crlf ;down to the next line
- test extrabytes,0FFFFh ; See if >5 opcode bytes
- jnz dol_loop ; Loop if so
- clc ; No errors
- leave
- ret
- DisOneLine ENDP
- END