Annotation of gforth/arch/mips/disasm.fs, revision 1.7
1.1 anton 1: \ disasm.fs disassembler file (for MIPS R3000)
2: \
3: \ Copyright (C) 1995-97 Martin Anton Ertl, Christian Pirker
4: \
5: \ This file is part of RAFTS.
6: \
7: \ RAFTS is free software; you can redistribute it and/or
8: \ modify it under the terms of the GNU General Public License
9: \ as published by the Free Software Foundation; either version 2
10: \ of the License, or (at your option) any later version.
11: \
12: \ This program is distributed in the hope that it will be useful,
13: \ but WITHOUT ANY WARRANTY; without even the implied warranty of
14: \ MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the
15: \ GNU General Public License for more details.
16: \
17: \ You should have received a copy of the GNU General Public License
18: \ along with this program; if not, write to the Free Software
19: \ Foundation, Inc., 675 Mass Ave, Cambridge, MA 02139, USA.
20:
1.4 anton 21: \ this disassembler is based on data from the R4400 manual
22: \ http://www.mips.com/Documentation/R4400_Uman_book_Ed2.pdf, in
1.6 anton 23: \ particular pages A3, A181, A182 (p. 471, 649, 650 in xpdf).
1.4 anton 24: \ it is limited to the R3000 (MIPS-I) architecture, though.
1.2 anton 25:
1.7 ! anton 26: \ test this with
! 27: \ gforth arch/mips/disasm.fs -e "here" arch/mips/testdisasm.fs -e "here over - disasm-dump bye" |sed 's/([^)]*) //'|diff -u - arch/mips/testasm.fs
! 28:
1.4 anton 29: \ instruction fields
1.3 anton 30:
31: : disasm-op ( w -- u )
32: 26 rshift ;
33:
34: : disasm-rs ( w -- u )
35: 21 rshift $1F and ;
36:
37: : disasm-rt ( w -- u )
38: 16 rshift $1f and ;
39:
40: : disasm-rd ( w -- u )
41: 11 rshift $1f and ;
42:
43: : disasm-shamt ( w -- u )
44: \ shift amount field
45: 6 rshift $1f and ;
46:
47: : disasm-funct ( w -- u )
48: $3f and ;
49:
50: : disasm-copz ( w -- u )
51: disasm-op 3 and ;
52:
1.5 anton 53: : disasm-uimm ( w -- u )
54: $ffff and ;
55:
1.3 anton 56: : disasm-imm ( w -- n )
1.5 anton 57: disasm-uimm dup 15 rshift negate 15 lshift or ;
1.3 anton 58:
59: : disasm-relative ( addr n -- w )
60: \ compute printable form of relative address n relative to addr
1.6 anton 61: 2 lshift nip ( + ) ;
1.3 anton 62:
1.4 anton 63: \ decode tables
64:
65: : disasm-illegal ( addr w -- )
66: \ disassemble illegal/unknown instruction w at addr
67: hex. ." , ( illegal inst ) " drop ;
68:
69: : disasm-table ( n "name" -- )
70: \ initialize table with n entries with disasm-illegal
71: create 0 ?do
72: ['] disasm-illegal ,
73: loop
74: does> ( u -- addr )
75: swap cells + ;
76:
77: $40 disasm-table opc-tab-entry \ top-level decode table
78: $40 disasm-table funct-tab-entry \ special function table
79: $20 disasm-table regimm-tab-entry \ regim instructions rt table
80: $20 disasm-table copz-rs-tab-entry \ COPz instructions rs table
81: $20 disasm-table copz-rt-tab-entry \ COPz BC instructions rt table
82: $40 disasm-table cp0-tab-entry \ COP0 CO instructions funct table
83:
1.3 anton 84: \ disassembler central decode cascade
85:
86: : disasm-inst ( addr w -- )
87: \G disassemble instruction w at addr (addr is used for computing
88: \G branch targets)
1.4 anton 89: dup disasm-op opc-tab-entry @ execute ;
1.3 anton 90:
91: : disasm-dump ( addr u -- ) \ gforth
92: \G disassemble u aus starting at addr
93: bounds u+do
94: cr ." ( " i hex. ." ) " i i @ disasm-inst
95: 1 cells +loop ;
96:
97: : disasm-special ( addr w -- )
98: \ disassemble inst with opcode special
1.4 anton 99: dup disasm-funct funct-tab-entry @ execute ;
100: ' disasm-special 0 opc-tab-entry ! \ enter it for opcode special
1.3 anton 101:
102: : disasm-regimm ( addr w -- )
103: \ disassemble regimm inst
1.4 anton 104: dup disasm-rt regimm-tab-entry @ execute ;
105: ' disasm-regimm 1 opc-tab-entry ! \ enter it for opcode regimm
1.3 anton 106:
107: : disasm-copz-rs ( addr w -- )
108: \ disassemble inst with opcode COPz
1.4 anton 109: dup disasm-rs copz-rs-tab-entry @ execute ;
110: ' disasm-copz-rs $10 opc-tab-entry ! \ enter it for opcodes COPz
111: ' disasm-copz-rs $11 opc-tab-entry !
112: ' disasm-copz-rs $12 opc-tab-entry !
1.3 anton 113:
114: : disasm-copz-rt ( addr w -- )
115: \ disassemble inst with opcode COPz, rs=BC
1.4 anton 116: dup disasm-rt copz-rt-tab-entry @ execute ;
117: ' disasm-copz-rt $08 copz-rs-tab-entry ! \ into COPz-table for rs=BC
1.3 anton 118:
119: : disasm-cp0 ( addr w -- )
120: \ disassemble inst with opcode COPz, rs=CO
1.4 anton 121: dup disasm-funct cp0-tab-entry @ execute ;
122: ' disasm-cp0 $10 copz-rs-tab-entry ! \ into COPz-table for rs=CO
1.3 anton 123:
1.4 anton 124: \ dummy words for insts.fs (words with these names are needed by asm.fs)
1.3 anton 125:
126: : asm-op ( -- ) ;
1.4 anton 127: : asm-rs ( -- ) ;
128: : asm-rt ( -- ) ;
129:
130: \ disassemble various formats
1.3 anton 131:
132: : disasm-J-target ( addr w -- )
133: \ print jump target
1.7 ! anton 134: 2 lshift $0fffffff and swap $f0000000 and or hex. ;
1.3 anton 135:
136: : disasm-I-rs,rt,imm ( addr w -- )
137: dup disasm-rs .
138: dup disasm-rt .
139: disasm-imm disasm-relative . ;
140:
141: : disasm-I-rs,imm ( addr w -- )
142: dup disasm-rs .
143: disasm-imm disasm-relative . ;
144:
145: : disasm-rt,rs,imm ( addr w -- )
146: dup disasm-rt .
147: dup disasm-rs .
148: disasm-imm .
149: drop ;
1.1 anton 150:
1.5 anton 151: : disasm-rt,rs,uimm ( addr w -- )
1.3 anton 152: dup disasm-rt .
1.5 anton 153: dup disasm-rs .
154: disasm-uimm hex.
155: drop ;
156:
157: : disasm-rt,uimm ( addr w -- )
158: dup disasm-rt .
159: disasm-uimm hex.
1.1 anton 160: drop ;
161:
1.3 anton 162: : disasm-rt,imm,rs ( addr w -- )
163: dup disasm-rt .
164: dup disasm-imm .
165: dup disasm-rs .
166: 2drop ;
167:
168: : disasm-rd,rt,sa ( addr w -- )
169: dup disasm-rd .
170: dup disasm-rt .
171: dup disasm-shamt .
172: 2drop ;
173:
174: : disasm-rd,rt,rs ( addr w -- )
175: dup disasm-rd .
176: dup disasm-rt .
177: dup disasm-rs .
178: 2drop ;
179:
180: : disasm-rs. ( addr w -- )
181: dup disasm-rs .
182: 2drop ;
183:
184: : disasm-rd,rs ( addr w -- )
185: dup disasm-rd .
186: dup disasm-rs .
187: 2drop ;
188:
189: : disasm-rd. ( addr w -- )
190: dup disasm-rd .
191: 2drop ;
192:
193: : disasm-rs,rt ( addr w -- )
194: dup disasm-rs .
195: dup disasm-rt .
196: 2drop ;
197:
198: : disasm-rd,rs,rt ( addr w -- )
199: dup disasm-rd .
200: dup disasm-rs .
201: dup disasm-rt .
202: 2drop ;
203:
204: : disasm-rt,rd,z ( addr w -- )
205: dup disasm-rt .
206: dup disasm-rd .
207: dup disasm-copz .
208: 2drop ;
209:
1.5 anton 210: : disasm-I-imm,z ( addr w -- )
211: tuck disasm-imm disasm-relative .
212: disasm-copz . ;
1.4 anton 213:
214: \ meta-defining word for instruction format disassembling definitions
215:
216: \ The following word defines instruction-format words, which in turn
217: \ define anonymous words for disassembling specific instructions and
218: \ put them in the appropriate decode table.
219:
220: : define-format ( disasm-xt table-xt -- )
221: \ define an instruction format that uses disasm-xt for
222: \ disassembling and enters the defined instructions into table
223: \ table-xt
224: create 2,
225: does> ( u "inst" -- )
226: \ defines an anonymous word for disassembling instruction inst,
227: \ and enters it as u-th entry into table-xt
228: 2@ swap here name string, ( u table-xt disasm-xt c-addr ) \ remember string
229: noname create 2, \ define anonymous word
230: execute lastxt swap ! \ enter xt of defined word into table-xt
231: does> ( addr w -- )
232: \ disassemble instruction w at addr
233: 2@ >r ( addr w disasm-xt R: c-addr )
234: execute ( R: c-addr ) \ disassemble operands
235: r> count type ; \ print name
236:
237: \ all the following words have the stack effect ( u "name" )
238: ' disasm-J-target ' opc-tab-entry define-format asm-J-target
239: ' disasm-I-rs,rt,imm ' opc-tab-entry define-format asm-I-rs,rt,imm
240: ' disasm-I-rs,imm ' opc-tab-entry define-format asm-I-rs,imm1
241: ' disasm-rt,rs,imm ' opc-tab-entry define-format asm-I-rt,rs,imm
1.5 anton 242: ' disasm-rt,rs,uimm ' opc-tab-entry define-format asm-I-rt,rs,uimm
243: ' disasm-rt,uimm ' opc-tab-entry define-format asm-I-rt,uimm
1.4 anton 244: ' disasm-rt,imm,rs ' opc-tab-entry define-format asm-I-rt,offset,rs
245: ' disasm-rd,rt,sa ' funct-tab-entry define-format asm-special-rd,rt,sa
246: ' disasm-rd,rt,rs ' funct-tab-entry define-format asm-special-rd,rt,rs
247: ' disasm-rs. ' funct-tab-entry define-format asm-special-rs
248: ' disasm-rd,rs ' funct-tab-entry define-format asm-special-rd,rs
249: ' 2drop ' funct-tab-entry define-format asm-special-nothing
250: ' disasm-rd. ' funct-tab-entry define-format asm-special-rd
251: ' disasm-rs,rt ' funct-tab-entry define-format asm-special-rs,rt
252: ' disasm-rd,rs,rt ' funct-tab-entry define-format asm-special-rd,rs,rt
253: ' disasm-I-rs,imm ' regimm-tab-entry define-format asm-regimm-rs,imm
254: ' 2drop ' cp0-tab-entry define-format asm-copz0
255: ' disasm-rt,rd,z ' copz-rs-tab-entry define-format asm-copz-rt,rd1
1.5 anton 256: ' disasm-I-imm,z ' copz-rt-tab-entry define-format asm-copz-imm1
1.4 anton 257:
258: : asm-I-rs,imm ( u1 u2 "name" -- ; compiled code: addr w -- )
259: nip asm-I-rs,imm1 ;
260:
1.3 anton 261: : asm-copz-rt,rd ( u1 u2 "name" -- )
1.4 anton 262: drop asm-copz-rt,rd1 ;
1.3 anton 263:
1.4 anton 264: : asm-copz-rt,offset,rs ( u "name" -- )
265: \ ignore these insts, we disassemble using asm-I-rt,offset,rs
266: drop name 2drop ;
1.3 anton 267:
268: : asm-copz-imm ( u1 u2 u3 "name" -- )
1.4 anton 269: drop nip asm-copz-imm1 ;
1.1 anton 270:
1.3 anton 271: include ./insts.fs
FreeBSD-CVSweb <freebsd-cvsweb@FreeBSD.org>