home
***
CD-ROM
|
disk
|
FTP
|
other
***
search
/
Power-Programmierung
/
CD1.mdf
/
forth
/
compiler
/
fpc
/
source
/
dis.seq
< prev
next >
Wrap
Text File
|
1991-02-13
|
17KB
|
476 lines
\ DIS8086.SEQ 8086 Disassembler by Charles Curley
\ Prefix conversion by Bill Muench 9 September 88
\ conversion to TCOM and symbolic additions by Tom Zimmer 03/07/90
\ conversion to 6805 by Andrew McKewan 12/17/90
comment:
A disassembler, for taking apart .COM files built by TCOM. This
program reads a file.COM and its .SYM (symbol) and .LIN (line table)
files, then proceeds to disassemble to the display with symbols and
source. I/O redirection is supported for output, with the normal DOS
">" symbol. Only the CODE portion of the file is disassembled.
USAGE: DIS CLOCK TIK/TOK >CLOCK.LST [Enter]
This will disassemble CLOCK.COM, using CLOCK.SYM and CLOCK.LIN to
provide symbols and source for the disassembly. Disassembly will start
at symbol "TIK/TOK" if it is found in the symbol table file. Output
will be directed to the file CLOCK.LST.
If the .SYM or .LIN file is not available, disassembly continues
without symbols or source. If NON-TCOM files are disassembled, DIS will
not know how much of the file to disassemble, but will proceed anyway
until terminated or until what it thinks is the end of file is reached.
If no symbol is specified, or the specified symbol is not found, then
disassembly starts at HEX 100.
Disassembly with symbols and source is a relatively slow process, so
if you redirect output to a file, be prepared to wait upto several
minutes for the disassembly to complete. The file created by DIS with
I/O redirection are usually fairly large, so make sure you have lots of
disk space. I ran DIS on the SZ editor, and created a file SZ.LST that
was over 600k bytes long. It took six minutes to complete on a 20mhz
80386 machine.
comment;
: COL ( n ) #OUT @ - SPACES ;
VARIABLE DISSEG
: =SEG ( seg ) DISSEG ! ;
: 2/S ( n ct - n'| shift n right ct )
0 ?DO U2/ LOOP ;
: 2*S ( n ct - n' | shift n left ct )
0 ?DO 2* LOOP ;
CODE SEXT ( n - n' | sign extend byte to word )
MOV AX, BX
CBW
MOV BX, AX
RET END-CODE
VARIABLE RELOC \ Relocation factor for dump or dis ???
0 RELOC !
: +RELOC ( a - seg ofs ) RELOC @ + DISSEG @ SWAP ;
: T@ ( a - w ) +RELOC @L FLIP ;
: TC@ ( a - n ) +RELOC C@L ;
: ID.L ( a ) #OUT @ SWAP count type #OUT @ - 6 + SPACES ;
:: SELF.L ( Left Justified Self-doc! )
CREATE DOES> ID.L ;
:: .SELF ( Self-doc! )
CREATE DOES> COUNT TYPE ;
VARIABLE CP
: NEXTB ( - n ) CP @ TC@ 1 CP +! ;
: NEXTW ( - w ) CP @ T@ 2 CP +! ;
\ Display hex object code
: H. SAVE> BASE HEX 0 U.R RESTORE> BASE ;
: ## save> base hex 0 <# # # #> type space restore> base ;
: #### save> base hex 0 <# # # # # #> type space restore> base ;
: bytes ( tadr n -- tadr )
2 spaces over + over do i tc@ ## loop ; \ *** TCOM
\ over #### space over + over do i tc@ ## loop ;
: byte 1 bytes ;
: 2bytes 2 bytes ;
: 3bytes 3 bytes ;
: bit# ( opcode -- bit# ) 2/ 7 and ;
: B>W ( byte -- n ) DUP 128 AND IF 256 - THEN ;
\ disassembly format:
\ AAAA XX XX XX OPC OPR COMMENT
\ : tab #out @ - spaces ;
\ : opcode 20 tab ;
\ : operand 28 tab ;
\ : comment 36 tab ;
: >address 0 col ;
: >object 0 col ;
: >label 0 col ;
: >opcode 0 col ;
: >operand 22 col ;
.self ??? ," ???"
.self NEG ," NEG" .self COM ," COM" .self LSR ," LSR"
.self ROR ," ROR" .self ASR ," ASR" .self LSL ," LSL"
.self ROL ," ROL" .self DEC ," DEC" .self INC ," INC"
.self TST ," TST" .self CLR ," CLR" .self SUB ," SUB"
.self CMP ," CMP" .self SBC ," SBC" .self CPX ," CPX"
.self UND ," AND" .self BIT ," BIT" .self LDA ," LDA"
.self STA ," STA" .self EOR ," EOR" .self ADC ," ADC"
.self ORA ," ORA" .self ADD ," ADD" .self JMP ," JMP"
.self JSR ," JSR" .self LDX ," LDX" .self STX ," STX"
.self BRA ," BRA" .self BRN ," BRN" .self BHI ," BHI"
.self BLS ," BLS" .self BCC ," BCC" .self BCS ," BCS"
.self BNE ," BNE" .self BEQ ," BEQ" .self BHCC ," BHCC"
.self BHCS ," BHCS" .self BPL ," BPL" .self BMI ," BMI"
.self BMC ," BMC" .self BMS ," BMS" .self BIL ," BIL"
.self BIH ," BIH"
defer .symbol ( adr -- ) \ display symbol or hex address
\ address modes:
: dir nextb .symbol ;
: ext nextw .symbol ;
: imm ." #" dir ;
: ix ." ,X" ;
: ix1 dir ." ,X" ;
: ix2 ext ." ,X" ;
: rel nextb b>w cp @ + .symbol ;
: bsc cp @ 1- tc@ bit# 0 .r ." ," dir ;
: btb bsc ." ," rel ;
: inha ." A" ;
: inhx ." X" ;
: .brset ( opcode -- )
dup 1 and if ." BRCLR" else ." BRSET" then
>operand btb ;
: .bset ( opcode -- )
dup 1 and if ." BCLR" else ." BSET" then
>operand bsc ;
: .bop ( opcode -- )
15 and exec: bra brn bhi bls bcc bcs bne beq
bhcc bhcs bpl bmi bmc bms bil bih ;
: .bran ( opcode -- )
.bop >operand rel ;
: op1 ( opcode -- )
15 and exec: sub cmp sbc cpx und bit lda sta
eor adc ora add jmp jsr ldx stx ;
: mode1 ( mode -- )
10 - 5 min exec: imm dir ext ix2 ix1 ix ;
: arith ( opcode mode -- )
over $ad = if drop ." BSR" >operand rel exit then
swap op1 >operand mode1 ;
: op2 ( opcode -- )
15 and exec: neg ??? ??? com lsr ??? ror asr
lsl rol dec ??? inc tst ??? clr ;
: mode2 ( mode -- )
3 - 4 min
dup 1 2 between not if >operand then
exec: dir inha inhx ix1 ix ;
: rmw ( opcode mode -- )
over $42 = if ." MUL " 2drop exit then
swap op2 mode2 ;
: misc ( opcode -- )
case
$80 of ." RTI" endof $81 of ." RTS" endof
$83 of ." SWI" endof $8e of ." STOP" endof
$8f of ." WAIT" endof $97 of ." TAX" endof
$98 of ." CLC" endof $99 of ." SEC" endof
$9a of ." CLI" endof $9b of ." SEI" endof
$9c of ." RSP" endof $9d of ." NOP" endof
$9f of ." TXA" endof
??? drop endcase ;
: .inst ( op -- )
dup 16 /
dup 0= if drop .brset exit then
dup 1 = if drop .bset exit then
dup 2 = if drop .bran exit then
dup 3 7 between if rmw exit then
dup 8 9 between if drop misc exit then
arith ;
: INST \ display opcode at ip advancing as needed
save> base hex
CP @ 0 <# # # # # #> TYPE 4 SPACES
CP @ >R
#OUT @ >R
NEXTB .INST
\ OPS @ CP +!
R> #OUT @ - 28 + 1 max SPACES
R> CP @ SWAP
?DO I TC@ 0 <# # # #> TYPE
LOOP
\ OPS OFF
\ DISP OFF
restore> base ;
15000 constant symmax
0 value symbuf
0 value symcnt
0 value symptr
handle symhndl
0 value comseg
0 value comcnt
: read_sym ( -- )
bl word symhndl $>handle
" SYM" ">$ symhndl $>ext
symhndl hopen
if cr ." Could not open " symhndl count type
." , no symbols available."
off> symcnt symbuf off exit
then cr ." Opened " symhndl count type ." , read "
symbuf symmax symhndl hread dup =: symcnt
U. ." bytes"
symhndl hclose drop ;
: .disusage ( -- )
cr ." Could not open " symhndl count type
cr cr
." Usage: DIS <filename> <starting_symbol> <enter>"
cr ." leaving" abort ;
: read_com ( -- ) \ assumes symbol file has been read
" BIN" ">$ symhndl $>ext
symhndl hopen if .disusage then
$1000 alloc 8 = \ allocate some space for
\ the .COM file.
if cr ." Not enough memory, leaving" abort
then =: comseg drop
cr ." Opened " symhndl count type ." , read "
0 $2000 symhndl comseg exhread dup =: comcnt
u. ." bytes"
symhndl hclose drop ;
: %?symbol ( a1 -- <a2 n1> f1 ) \ given a1 the symbol address, return
\ a2 n1 f1 = true if symbol found
\ else f1 false symbol not found
0 <# # # # # #> drop =: symptr
symbuf symcnt
begin over symptr 4 comp over 0> and
while $0A scan 1 /string
repeat dup
if 2dup $0A scan nip - \ parse line
bl scan bl skip \ remove leading number
1- 0max
over dup c@ $7F and swap c!
true \ remove trailing CR
else 2drop false
then ;
defer ?symbol
: ?.symbol ( a1 -- )
dup ?symbol
if type
else dup 0 U.R ( H. )
then drop ;
: show_symbol ( -- <a2 n1> f1 )
cp @ ?symbol ;
: ?address ( a1 -- <a2> f1 ) \ given a1 the symbol name, return
\ a2 addr, & f1 = true if addr found
\ else f1 false addr not found
?uppercase =: symptr
symptr c@ dup 0= ?exit drop
symptr number? nip \ pass in a number directly
if true exit
then drop
$0D symptr count + c!
symbuf symcnt
begin over 5 + symptr count 1+ caps-comp over 0> and
while $0A scan 1 /string
repeat dup
if 2dup bl scan nip - \ parse line
here place
bl here count + c!
here number? nip
else 2drop false
then ;
0 value linseg
0 value lincnt
0 value linstart
0 value srcline
0 value targaddr
0 value ?src
80 array sline_buf
: read_lin ( -- )
" LIN" ">$ symhndl $>ext
symhndl hopen
if cr ." Could not open " symhndl count type
exit
then
$1000 alloc 8 = \ allocate some space for
\ the .COM file.
if cr ." Not enough memory, leaving" abort
then =: linseg drop
cr ." Opened " symhndl count type ." , read "
$00 $FF00 symhndl linseg exhread dup =: lincnt
u. ." bytes"
symhndl hclose drop ;
: getsline ( -- f1 )
linseg save!> sseg
linstart lincnt 2dup $0A scan
2dup 1 /string =: lincnt =: linstart
nip - 79 min >r linseg swap ?ds: sline_buf 1+ r@ cmovel
r> sline_buf c!
restore> sseg
sline_buf c@ 0= ?dup ?exit \ stop if at end of lines
sline_buf count 2dup bl scan 2dup 2>r nip - here place
bl here count + c!
here number? 2drop =: targaddr
2r> bl skip 2dup $0D scan nip - dup
if here place
bl here count + c!
lreadhndl hclose drop
here lreadhndl $>handle
lreadhndl hopen ( -- f1 )
ibreset
else 2drop false
then ;
: .source_line ( -- )
save> base decimal
loadline @ 5 .r space
lineread count 2- 0max type cr
restore> base ;
: show_source ( -- )
?src 0= ?exit
begin cp @ targaddr u>=
while .source_line
getsline
if -1 =: targaddr
off> ?src
then
?keypause
repeat ;
: skip_source ( -- )
?src 0= ?exit
begin cp @ $10 - targaddr u>=
while lineread drop
getsline
if -1 =: targaddr
off> ?src
then
?keypause
repeat ;
: DIS ( a1 -- ) \ disassemble from address a1
cp ! ?cs: =seg
begin cr
show_symbol
if ." ; " type cr then
8 spaces
INST
?KEYPAUSE
again cr ;
[FORTH] ?DIS 0= [TARGET] \ If we are not just appending disassembler
#IF \ but are actually building a standalone
\ disassembler, then include this
: show-variables
save> base hex
$100 0
do i ?symbol
if cr 8 spaces
i 0 <# # # # # #> type
2 spaces type
then
loop cr
restore> base ;
: .1inst_line ( -- )
CR
show_source
show_symbol
if ." ; " type cr then
8 spaces
INST ;
: .VECTOR ( addr - )
CR DUP 12 .R
4 SPACES ." FDB"
3 SPACES T@ .SYMBOL ;
: SHOW-VECTORS ( -- )
SAVE> BASE HEX
$2000 $1FF4
DO I .VECTOR
2 +LOOP
RESTORE> BASE ;
VARIABLE CPEND
: find-cpend ( -- )
$10ff
begin dup tc@ 0= over $101 u> and
while 1-
repeat cpend ! ;
: DISASSEM ( -- )
CAPS ON
?ds: sseg !
DOSIO_INIT \ init EMIT, TYPE & SPACES
symmax 2+ ds:alloc =: symbuf
$FFF0 SET_MEMORY \ default to 64k code space
DOS_TO_TIB \ move command tail to TIB
DECIMAL
lineread_init
['] ?.symbol is .symbol
['] %?symbol is ?symbol
read_sym \ read symbol table
read_com \ read .COM file
read_lin
getsline dup 0= =: ?src
if cr ." Could not open source file"
then
comseg =SEG
HEX
cr
bl word ?address \ find word following, if found
if cp ! \ set as starting address
skip_source \ walk past previous source lines
else $100 cp ! \ else use $100 for starting
then
\ symcnt \ if symbol file presend,
\ if comseg $0103 @L $10 * \ then assume its a TCOM file
\ else $FF00 \ else just do whole .COM file
\ then comcnt cp @ + umin cpend !
find-cpend
show-variables
BEGIN .1inst_line
?KEYPAUSE
CP @ CPEND @ U>
UNTIL
CR CR
SHOW-VECTORS
cr cr ;
#ENDIF