1*3d8817e4Smiod /* Disassembly routines for TMS320C30 architecture
2*3d8817e4Smiod Copyright 1998, 1999, 2000, 2002, 2005 Free Software Foundation, Inc.
3*3d8817e4Smiod Contributed by Steven Haworth (steve@pm.cse.rmit.edu.au)
4*3d8817e4Smiod
5*3d8817e4Smiod This program is free software; you can redistribute it and/or modify
6*3d8817e4Smiod it under the terms of the GNU General Public License as published by
7*3d8817e4Smiod the Free Software Foundation; either version 2 of the License, or
8*3d8817e4Smiod (at your option) any later version.
9*3d8817e4Smiod
10*3d8817e4Smiod This program is distributed in the hope that it will be useful,
11*3d8817e4Smiod but WITHOUT ANY WARRANTY; without even the implied warranty of
12*3d8817e4Smiod MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the
13*3d8817e4Smiod GNU General Public License for more details.
14*3d8817e4Smiod
15*3d8817e4Smiod You should have received a copy of the GNU General Public License
16*3d8817e4Smiod along with this program; if not, write to the Free Software
17*3d8817e4Smiod Foundation, Inc., 51 Franklin Street - Fifth Floor, Boston, MA
18*3d8817e4Smiod 02110-1301, USA. */
19*3d8817e4Smiod
20*3d8817e4Smiod #include <errno.h>
21*3d8817e4Smiod #include <math.h>
22*3d8817e4Smiod #include "sysdep.h"
23*3d8817e4Smiod #include "dis-asm.h"
24*3d8817e4Smiod #include "opcode/tic30.h"
25*3d8817e4Smiod
26*3d8817e4Smiod #define NORMAL_INSN 1
27*3d8817e4Smiod #define PARALLEL_INSN 2
28*3d8817e4Smiod
29*3d8817e4Smiod /* Gets the type of instruction based on the top 2 or 3 bits of the
30*3d8817e4Smiod instruction word. */
31*3d8817e4Smiod #define GET_TYPE(insn) (insn & 0x80000000 ? insn & 0xC0000000 : insn & 0xE0000000)
32*3d8817e4Smiod
33*3d8817e4Smiod /* Instruction types. */
34*3d8817e4Smiod #define TWO_OPERAND_1 0x00000000
35*3d8817e4Smiod #define TWO_OPERAND_2 0x40000000
36*3d8817e4Smiod #define THREE_OPERAND 0x20000000
37*3d8817e4Smiod #define PAR_STORE 0xC0000000
38*3d8817e4Smiod #define MUL_ADDS 0x80000000
39*3d8817e4Smiod #define BRANCHES 0x60000000
40*3d8817e4Smiod
41*3d8817e4Smiod /* Specific instruction id bits. */
42*3d8817e4Smiod #define NORMAL_IDEN 0x1F800000
43*3d8817e4Smiod #define PAR_STORE_IDEN 0x3E000000
44*3d8817e4Smiod #define MUL_ADD_IDEN 0x2C000000
45*3d8817e4Smiod #define BR_IMM_IDEN 0x1F000000
46*3d8817e4Smiod #define BR_COND_IDEN 0x1C3F0000
47*3d8817e4Smiod
48*3d8817e4Smiod /* Addressing modes. */
49*3d8817e4Smiod #define AM_REGISTER 0x00000000
50*3d8817e4Smiod #define AM_DIRECT 0x00200000
51*3d8817e4Smiod #define AM_INDIRECT 0x00400000
52*3d8817e4Smiod #define AM_IMM 0x00600000
53*3d8817e4Smiod
54*3d8817e4Smiod #define P_FIELD 0x03000000
55*3d8817e4Smiod
56*3d8817e4Smiod #define REG_AR0 0x08
57*3d8817e4Smiod #define LDP_INSN 0x08700000
58*3d8817e4Smiod
59*3d8817e4Smiod /* TMS320C30 program counter for current instruction. */
60*3d8817e4Smiod static unsigned int _pc;
61*3d8817e4Smiod
62*3d8817e4Smiod struct instruction
63*3d8817e4Smiod {
64*3d8817e4Smiod int type;
65*3d8817e4Smiod template *tm;
66*3d8817e4Smiod partemplate *ptm;
67*3d8817e4Smiod };
68*3d8817e4Smiod
69*3d8817e4Smiod static int
get_tic30_instruction(unsigned long insn_word,struct instruction * insn)70*3d8817e4Smiod get_tic30_instruction (unsigned long insn_word, struct instruction *insn)
71*3d8817e4Smiod {
72*3d8817e4Smiod switch (GET_TYPE (insn_word))
73*3d8817e4Smiod {
74*3d8817e4Smiod case TWO_OPERAND_1:
75*3d8817e4Smiod case TWO_OPERAND_2:
76*3d8817e4Smiod case THREE_OPERAND:
77*3d8817e4Smiod insn->type = NORMAL_INSN;
78*3d8817e4Smiod {
79*3d8817e4Smiod template *current_optab = (template *) tic30_optab;
80*3d8817e4Smiod
81*3d8817e4Smiod for (; current_optab < tic30_optab_end; current_optab++)
82*3d8817e4Smiod {
83*3d8817e4Smiod if (GET_TYPE (current_optab->base_opcode) == GET_TYPE (insn_word))
84*3d8817e4Smiod {
85*3d8817e4Smiod if (current_optab->operands == 0)
86*3d8817e4Smiod {
87*3d8817e4Smiod if (current_optab->base_opcode == insn_word)
88*3d8817e4Smiod {
89*3d8817e4Smiod insn->tm = current_optab;
90*3d8817e4Smiod break;
91*3d8817e4Smiod }
92*3d8817e4Smiod }
93*3d8817e4Smiod else if ((current_optab->base_opcode & NORMAL_IDEN) == (insn_word & NORMAL_IDEN))
94*3d8817e4Smiod {
95*3d8817e4Smiod insn->tm = current_optab;
96*3d8817e4Smiod break;
97*3d8817e4Smiod }
98*3d8817e4Smiod }
99*3d8817e4Smiod }
100*3d8817e4Smiod }
101*3d8817e4Smiod break;
102*3d8817e4Smiod
103*3d8817e4Smiod case PAR_STORE:
104*3d8817e4Smiod insn->type = PARALLEL_INSN;
105*3d8817e4Smiod {
106*3d8817e4Smiod partemplate *current_optab = (partemplate *) tic30_paroptab;
107*3d8817e4Smiod
108*3d8817e4Smiod for (; current_optab < tic30_paroptab_end; current_optab++)
109*3d8817e4Smiod {
110*3d8817e4Smiod if (GET_TYPE (current_optab->base_opcode) == GET_TYPE (insn_word))
111*3d8817e4Smiod {
112*3d8817e4Smiod if ((current_optab->base_opcode & PAR_STORE_IDEN)
113*3d8817e4Smiod == (insn_word & PAR_STORE_IDEN))
114*3d8817e4Smiod {
115*3d8817e4Smiod insn->ptm = current_optab;
116*3d8817e4Smiod break;
117*3d8817e4Smiod }
118*3d8817e4Smiod }
119*3d8817e4Smiod }
120*3d8817e4Smiod }
121*3d8817e4Smiod break;
122*3d8817e4Smiod
123*3d8817e4Smiod case MUL_ADDS:
124*3d8817e4Smiod insn->type = PARALLEL_INSN;
125*3d8817e4Smiod {
126*3d8817e4Smiod partemplate *current_optab = (partemplate *) tic30_paroptab;
127*3d8817e4Smiod
128*3d8817e4Smiod for (; current_optab < tic30_paroptab_end; current_optab++)
129*3d8817e4Smiod {
130*3d8817e4Smiod if (GET_TYPE (current_optab->base_opcode) == GET_TYPE (insn_word))
131*3d8817e4Smiod {
132*3d8817e4Smiod if ((current_optab->base_opcode & MUL_ADD_IDEN)
133*3d8817e4Smiod == (insn_word & MUL_ADD_IDEN))
134*3d8817e4Smiod {
135*3d8817e4Smiod insn->ptm = current_optab;
136*3d8817e4Smiod break;
137*3d8817e4Smiod }
138*3d8817e4Smiod }
139*3d8817e4Smiod }
140*3d8817e4Smiod }
141*3d8817e4Smiod break;
142*3d8817e4Smiod
143*3d8817e4Smiod case BRANCHES:
144*3d8817e4Smiod insn->type = NORMAL_INSN;
145*3d8817e4Smiod {
146*3d8817e4Smiod template *current_optab = (template *) tic30_optab;
147*3d8817e4Smiod
148*3d8817e4Smiod for (; current_optab < tic30_optab_end; current_optab++)
149*3d8817e4Smiod {
150*3d8817e4Smiod if (GET_TYPE (current_optab->base_opcode) == GET_TYPE (insn_word))
151*3d8817e4Smiod {
152*3d8817e4Smiod if (current_optab->operand_types[0] & Imm24)
153*3d8817e4Smiod {
154*3d8817e4Smiod if ((current_optab->base_opcode & BR_IMM_IDEN)
155*3d8817e4Smiod == (insn_word & BR_IMM_IDEN))
156*3d8817e4Smiod {
157*3d8817e4Smiod insn->tm = current_optab;
158*3d8817e4Smiod break;
159*3d8817e4Smiod }
160*3d8817e4Smiod }
161*3d8817e4Smiod else if (current_optab->operands > 0)
162*3d8817e4Smiod {
163*3d8817e4Smiod if ((current_optab->base_opcode & BR_COND_IDEN)
164*3d8817e4Smiod == (insn_word & BR_COND_IDEN))
165*3d8817e4Smiod {
166*3d8817e4Smiod insn->tm = current_optab;
167*3d8817e4Smiod break;
168*3d8817e4Smiod }
169*3d8817e4Smiod }
170*3d8817e4Smiod else
171*3d8817e4Smiod {
172*3d8817e4Smiod if ((current_optab->base_opcode & (BR_COND_IDEN | 0x00800000))
173*3d8817e4Smiod == (insn_word & (BR_COND_IDEN | 0x00800000)))
174*3d8817e4Smiod {
175*3d8817e4Smiod insn->tm = current_optab;
176*3d8817e4Smiod break;
177*3d8817e4Smiod }
178*3d8817e4Smiod }
179*3d8817e4Smiod }
180*3d8817e4Smiod }
181*3d8817e4Smiod }
182*3d8817e4Smiod break;
183*3d8817e4Smiod default:
184*3d8817e4Smiod return 0;
185*3d8817e4Smiod }
186*3d8817e4Smiod return 1;
187*3d8817e4Smiod }
188*3d8817e4Smiod
189*3d8817e4Smiod static int
get_register_operand(unsigned char fragment,char * buffer)190*3d8817e4Smiod get_register_operand (unsigned char fragment, char *buffer)
191*3d8817e4Smiod {
192*3d8817e4Smiod const reg *current_reg = tic30_regtab;
193*3d8817e4Smiod
194*3d8817e4Smiod if (buffer == NULL)
195*3d8817e4Smiod return 0;
196*3d8817e4Smiod for (; current_reg < tic30_regtab_end; current_reg++)
197*3d8817e4Smiod {
198*3d8817e4Smiod if ((fragment & 0x1F) == current_reg->opcode)
199*3d8817e4Smiod {
200*3d8817e4Smiod strcpy (buffer, current_reg->name);
201*3d8817e4Smiod return 1;
202*3d8817e4Smiod }
203*3d8817e4Smiod }
204*3d8817e4Smiod return 0;
205*3d8817e4Smiod }
206*3d8817e4Smiod
207*3d8817e4Smiod static int
get_indirect_operand(unsigned short fragment,int size,char * buffer)208*3d8817e4Smiod get_indirect_operand (unsigned short fragment,
209*3d8817e4Smiod int size,
210*3d8817e4Smiod char *buffer)
211*3d8817e4Smiod {
212*3d8817e4Smiod unsigned char mod;
213*3d8817e4Smiod unsigned arnum;
214*3d8817e4Smiod unsigned char disp;
215*3d8817e4Smiod
216*3d8817e4Smiod if (buffer == NULL)
217*3d8817e4Smiod return 0;
218*3d8817e4Smiod /* Determine which bits identify the sections of the indirect
219*3d8817e4Smiod operand based on the size in bytes. */
220*3d8817e4Smiod switch (size)
221*3d8817e4Smiod {
222*3d8817e4Smiod case 1:
223*3d8817e4Smiod mod = (fragment & 0x00F8) >> 3;
224*3d8817e4Smiod arnum = (fragment & 0x0007);
225*3d8817e4Smiod disp = 0;
226*3d8817e4Smiod break;
227*3d8817e4Smiod case 2:
228*3d8817e4Smiod mod = (fragment & 0xF800) >> 11;
229*3d8817e4Smiod arnum = (fragment & 0x0700) >> 8;
230*3d8817e4Smiod disp = (fragment & 0x00FF);
231*3d8817e4Smiod break;
232*3d8817e4Smiod default:
233*3d8817e4Smiod return 0;
234*3d8817e4Smiod }
235*3d8817e4Smiod {
236*3d8817e4Smiod const ind_addr_type *current_ind = tic30_indaddr_tab;
237*3d8817e4Smiod
238*3d8817e4Smiod for (; current_ind < tic30_indaddrtab_end; current_ind++)
239*3d8817e4Smiod {
240*3d8817e4Smiod if (current_ind->modfield == mod)
241*3d8817e4Smiod {
242*3d8817e4Smiod if (current_ind->displacement == IMPLIED_DISP && size == 2)
243*3d8817e4Smiod continue;
244*3d8817e4Smiod
245*3d8817e4Smiod else
246*3d8817e4Smiod {
247*3d8817e4Smiod size_t i, len;
248*3d8817e4Smiod int bufcnt;
249*3d8817e4Smiod
250*3d8817e4Smiod len = strlen (current_ind->syntax);
251*3d8817e4Smiod for (i = 0, bufcnt = 0; i < len; i++, bufcnt++)
252*3d8817e4Smiod {
253*3d8817e4Smiod buffer[bufcnt] = current_ind->syntax[i];
254*3d8817e4Smiod if (buffer[bufcnt - 1] == 'a' && buffer[bufcnt] == 'r')
255*3d8817e4Smiod buffer[++bufcnt] = arnum + '0';
256*3d8817e4Smiod if (buffer[bufcnt] == '('
257*3d8817e4Smiod && current_ind->displacement == DISP_REQUIRED)
258*3d8817e4Smiod {
259*3d8817e4Smiod sprintf (&buffer[bufcnt + 1], "%u", disp);
260*3d8817e4Smiod bufcnt += strlen (&buffer[bufcnt + 1]);
261*3d8817e4Smiod }
262*3d8817e4Smiod }
263*3d8817e4Smiod buffer[bufcnt + 1] = '\0';
264*3d8817e4Smiod break;
265*3d8817e4Smiod }
266*3d8817e4Smiod }
267*3d8817e4Smiod }
268*3d8817e4Smiod }
269*3d8817e4Smiod return 1;
270*3d8817e4Smiod }
271*3d8817e4Smiod
272*3d8817e4Smiod static int
cnvt_tmsfloat_ieee(unsigned long tmsfloat,int size,float * ieeefloat)273*3d8817e4Smiod cnvt_tmsfloat_ieee (unsigned long tmsfloat, int size, float *ieeefloat)
274*3d8817e4Smiod {
275*3d8817e4Smiod unsigned long exp, sign, mant;
276*3d8817e4Smiod union
277*3d8817e4Smiod {
278*3d8817e4Smiod unsigned long l;
279*3d8817e4Smiod float f;
280*3d8817e4Smiod } val;
281*3d8817e4Smiod
282*3d8817e4Smiod if (size == 2)
283*3d8817e4Smiod {
284*3d8817e4Smiod if ((tmsfloat & 0x0000F000) == 0x00008000)
285*3d8817e4Smiod tmsfloat = 0x80000000;
286*3d8817e4Smiod else
287*3d8817e4Smiod {
288*3d8817e4Smiod tmsfloat <<= 16;
289*3d8817e4Smiod tmsfloat = (long) tmsfloat >> 4;
290*3d8817e4Smiod }
291*3d8817e4Smiod }
292*3d8817e4Smiod exp = tmsfloat & 0xFF000000;
293*3d8817e4Smiod if (exp == 0x80000000)
294*3d8817e4Smiod {
295*3d8817e4Smiod *ieeefloat = 0.0;
296*3d8817e4Smiod return 1;
297*3d8817e4Smiod }
298*3d8817e4Smiod exp += 0x7F000000;
299*3d8817e4Smiod sign = (tmsfloat & 0x00800000) << 8;
300*3d8817e4Smiod mant = tmsfloat & 0x007FFFFF;
301*3d8817e4Smiod if (exp == 0xFF000000)
302*3d8817e4Smiod {
303*3d8817e4Smiod if (mant == 0)
304*3d8817e4Smiod *ieeefloat = ERANGE;
305*3d8817e4Smiod #ifdef HUGE_VALF
306*3d8817e4Smiod if (sign == 0)
307*3d8817e4Smiod *ieeefloat = HUGE_VALF;
308*3d8817e4Smiod else
309*3d8817e4Smiod *ieeefloat = -HUGE_VALF;
310*3d8817e4Smiod #else
311*3d8817e4Smiod if (sign == 0)
312*3d8817e4Smiod *ieeefloat = 1.0 / 0.0;
313*3d8817e4Smiod else
314*3d8817e4Smiod *ieeefloat = -1.0 / 0.0;
315*3d8817e4Smiod #endif
316*3d8817e4Smiod return 1;
317*3d8817e4Smiod }
318*3d8817e4Smiod exp >>= 1;
319*3d8817e4Smiod if (sign)
320*3d8817e4Smiod {
321*3d8817e4Smiod mant = (~mant) & 0x007FFFFF;
322*3d8817e4Smiod mant += 1;
323*3d8817e4Smiod exp += mant & 0x00800000;
324*3d8817e4Smiod exp &= 0x7F800000;
325*3d8817e4Smiod mant &= 0x007FFFFF;
326*3d8817e4Smiod }
327*3d8817e4Smiod if (tmsfloat == 0x80000000)
328*3d8817e4Smiod sign = mant = exp = 0;
329*3d8817e4Smiod tmsfloat = sign | exp | mant;
330*3d8817e4Smiod val.l = tmsfloat;
331*3d8817e4Smiod *ieeefloat = val.f;
332*3d8817e4Smiod return 1;
333*3d8817e4Smiod }
334*3d8817e4Smiod
335*3d8817e4Smiod static int
print_two_operand(disassemble_info * info,unsigned long insn_word,struct instruction * insn)336*3d8817e4Smiod print_two_operand (disassemble_info *info,
337*3d8817e4Smiod unsigned long insn_word,
338*3d8817e4Smiod struct instruction *insn)
339*3d8817e4Smiod {
340*3d8817e4Smiod char name[12];
341*3d8817e4Smiod char operand[2][13] =
342*3d8817e4Smiod {
343*3d8817e4Smiod {0},
344*3d8817e4Smiod {0}
345*3d8817e4Smiod };
346*3d8817e4Smiod float f_number;
347*3d8817e4Smiod
348*3d8817e4Smiod if (insn->tm == NULL)
349*3d8817e4Smiod return 0;
350*3d8817e4Smiod strcpy (name, insn->tm->name);
351*3d8817e4Smiod if (insn->tm->opcode_modifier == AddressMode)
352*3d8817e4Smiod {
353*3d8817e4Smiod int src_op, dest_op;
354*3d8817e4Smiod /* Determine whether instruction is a store or a normal instruction. */
355*3d8817e4Smiod if ((insn->tm->operand_types[1] & (Direct | Indirect))
356*3d8817e4Smiod == (Direct | Indirect))
357*3d8817e4Smiod {
358*3d8817e4Smiod src_op = 1;
359*3d8817e4Smiod dest_op = 0;
360*3d8817e4Smiod }
361*3d8817e4Smiod else
362*3d8817e4Smiod {
363*3d8817e4Smiod src_op = 0;
364*3d8817e4Smiod dest_op = 1;
365*3d8817e4Smiod }
366*3d8817e4Smiod /* Get the destination register. */
367*3d8817e4Smiod if (insn->tm->operands == 2)
368*3d8817e4Smiod get_register_operand ((insn_word & 0x001F0000) >> 16, operand[dest_op]);
369*3d8817e4Smiod /* Get the source operand based on addressing mode. */
370*3d8817e4Smiod switch (insn_word & AddressMode)
371*3d8817e4Smiod {
372*3d8817e4Smiod case AM_REGISTER:
373*3d8817e4Smiod /* Check for the NOP instruction before getting the operand. */
374*3d8817e4Smiod if ((insn->tm->operand_types[0] & NotReq) == 0)
375*3d8817e4Smiod get_register_operand ((insn_word & 0x0000001F), operand[src_op]);
376*3d8817e4Smiod break;
377*3d8817e4Smiod case AM_DIRECT:
378*3d8817e4Smiod sprintf (operand[src_op], "@0x%lX", (insn_word & 0x0000FFFF));
379*3d8817e4Smiod break;
380*3d8817e4Smiod case AM_INDIRECT:
381*3d8817e4Smiod get_indirect_operand ((insn_word & 0x0000FFFF), 2, operand[src_op]);
382*3d8817e4Smiod break;
383*3d8817e4Smiod case AM_IMM:
384*3d8817e4Smiod /* Get the value of the immediate operand based on variable type. */
385*3d8817e4Smiod switch (insn->tm->imm_arg_type)
386*3d8817e4Smiod {
387*3d8817e4Smiod case Imm_Float:
388*3d8817e4Smiod cnvt_tmsfloat_ieee ((insn_word & 0x0000FFFF), 2, &f_number);
389*3d8817e4Smiod sprintf (operand[src_op], "%2.2f", f_number);
390*3d8817e4Smiod break;
391*3d8817e4Smiod case Imm_SInt:
392*3d8817e4Smiod sprintf (operand[src_op], "%d", (short) (insn_word & 0x0000FFFF));
393*3d8817e4Smiod break;
394*3d8817e4Smiod case Imm_UInt:
395*3d8817e4Smiod sprintf (operand[src_op], "%lu", (insn_word & 0x0000FFFF));
396*3d8817e4Smiod break;
397*3d8817e4Smiod default:
398*3d8817e4Smiod return 0;
399*3d8817e4Smiod }
400*3d8817e4Smiod /* Handle special case for LDP instruction. */
401*3d8817e4Smiod if ((insn_word & 0xFFFFFF00) == LDP_INSN)
402*3d8817e4Smiod {
403*3d8817e4Smiod strcpy (name, "ldp");
404*3d8817e4Smiod sprintf (operand[0], "0x%06lX", (insn_word & 0x000000FF) << 16);
405*3d8817e4Smiod operand[1][0] = '\0';
406*3d8817e4Smiod }
407*3d8817e4Smiod }
408*3d8817e4Smiod }
409*3d8817e4Smiod /* Handle case for stack and rotate instructions. */
410*3d8817e4Smiod else if (insn->tm->operands == 1)
411*3d8817e4Smiod {
412*3d8817e4Smiod if (insn->tm->opcode_modifier == StackOp)
413*3d8817e4Smiod get_register_operand ((insn_word & 0x001F0000) >> 16, operand[0]);
414*3d8817e4Smiod }
415*3d8817e4Smiod /* Output instruction to stream. */
416*3d8817e4Smiod info->fprintf_func (info->stream, " %s %s%c%s", name,
417*3d8817e4Smiod operand[0][0] ? operand[0] : "",
418*3d8817e4Smiod operand[1][0] ? ',' : ' ',
419*3d8817e4Smiod operand[1][0] ? operand[1] : "");
420*3d8817e4Smiod return 1;
421*3d8817e4Smiod }
422*3d8817e4Smiod
423*3d8817e4Smiod static int
print_three_operand(disassemble_info * info,unsigned long insn_word,struct instruction * insn)424*3d8817e4Smiod print_three_operand (disassemble_info *info,
425*3d8817e4Smiod unsigned long insn_word,
426*3d8817e4Smiod struct instruction *insn)
427*3d8817e4Smiod {
428*3d8817e4Smiod char operand[3][13] =
429*3d8817e4Smiod {
430*3d8817e4Smiod {0},
431*3d8817e4Smiod {0},
432*3d8817e4Smiod {0}
433*3d8817e4Smiod };
434*3d8817e4Smiod
435*3d8817e4Smiod if (insn->tm == NULL)
436*3d8817e4Smiod return 0;
437*3d8817e4Smiod switch (insn_word & AddressMode)
438*3d8817e4Smiod {
439*3d8817e4Smiod case AM_REGISTER:
440*3d8817e4Smiod get_register_operand ((insn_word & 0x000000FF), operand[0]);
441*3d8817e4Smiod get_register_operand ((insn_word & 0x0000FF00) >> 8, operand[1]);
442*3d8817e4Smiod break;
443*3d8817e4Smiod case AM_DIRECT:
444*3d8817e4Smiod get_register_operand ((insn_word & 0x000000FF), operand[0]);
445*3d8817e4Smiod get_indirect_operand ((insn_word & 0x0000FF00) >> 8, 1, operand[1]);
446*3d8817e4Smiod break;
447*3d8817e4Smiod case AM_INDIRECT:
448*3d8817e4Smiod get_indirect_operand ((insn_word & 0x000000FF), 1, operand[0]);
449*3d8817e4Smiod get_register_operand ((insn_word & 0x0000FF00) >> 8, operand[1]);
450*3d8817e4Smiod break;
451*3d8817e4Smiod case AM_IMM:
452*3d8817e4Smiod get_indirect_operand ((insn_word & 0x000000FF), 1, operand[0]);
453*3d8817e4Smiod get_indirect_operand ((insn_word & 0x0000FF00) >> 8, 1, operand[1]);
454*3d8817e4Smiod break;
455*3d8817e4Smiod default:
456*3d8817e4Smiod return 0;
457*3d8817e4Smiod }
458*3d8817e4Smiod if (insn->tm->operands == 3)
459*3d8817e4Smiod get_register_operand ((insn_word & 0x001F0000) >> 16, operand[2]);
460*3d8817e4Smiod info->fprintf_func (info->stream, " %s %s,%s%c%s", insn->tm->name,
461*3d8817e4Smiod operand[0], operand[1],
462*3d8817e4Smiod operand[2][0] ? ',' : ' ',
463*3d8817e4Smiod operand[2][0] ? operand[2] : "");
464*3d8817e4Smiod return 1;
465*3d8817e4Smiod }
466*3d8817e4Smiod
467*3d8817e4Smiod static int
print_par_insn(disassemble_info * info,unsigned long insn_word,struct instruction * insn)468*3d8817e4Smiod print_par_insn (disassemble_info *info,
469*3d8817e4Smiod unsigned long insn_word,
470*3d8817e4Smiod struct instruction *insn)
471*3d8817e4Smiod {
472*3d8817e4Smiod size_t i, len;
473*3d8817e4Smiod char *name1, *name2;
474*3d8817e4Smiod char operand[2][3][13] =
475*3d8817e4Smiod {
476*3d8817e4Smiod {
477*3d8817e4Smiod {0},
478*3d8817e4Smiod {0},
479*3d8817e4Smiod {0}
480*3d8817e4Smiod },
481*3d8817e4Smiod {
482*3d8817e4Smiod {0},
483*3d8817e4Smiod {0},
484*3d8817e4Smiod {0}
485*3d8817e4Smiod }
486*3d8817e4Smiod };
487*3d8817e4Smiod
488*3d8817e4Smiod if (insn->ptm == NULL)
489*3d8817e4Smiod return 0;
490*3d8817e4Smiod /* Parse out the names of each of the parallel instructions from the
491*3d8817e4Smiod q_insn1_insn2 format. */
492*3d8817e4Smiod name1 = (char *) strdup (insn->ptm->name + 2);
493*3d8817e4Smiod name2 = "";
494*3d8817e4Smiod len = strlen (name1);
495*3d8817e4Smiod for (i = 0; i < len; i++)
496*3d8817e4Smiod {
497*3d8817e4Smiod if (name1[i] == '_')
498*3d8817e4Smiod {
499*3d8817e4Smiod name2 = &name1[i + 1];
500*3d8817e4Smiod name1[i] = '\0';
501*3d8817e4Smiod break;
502*3d8817e4Smiod }
503*3d8817e4Smiod }
504*3d8817e4Smiod /* Get the operands of the instruction based on the operand order. */
505*3d8817e4Smiod switch (insn->ptm->oporder)
506*3d8817e4Smiod {
507*3d8817e4Smiod case OO_4op1:
508*3d8817e4Smiod get_indirect_operand ((insn_word & 0x000000FF), 1, operand[0][0]);
509*3d8817e4Smiod get_indirect_operand ((insn_word & 0x0000FF00) >> 8, 1, operand[1][1]);
510*3d8817e4Smiod get_register_operand ((insn_word >> 16) & 0x07, operand[1][0]);
511*3d8817e4Smiod get_register_operand ((insn_word >> 22) & 0x07, operand[0][1]);
512*3d8817e4Smiod break;
513*3d8817e4Smiod case OO_4op2:
514*3d8817e4Smiod get_indirect_operand ((insn_word & 0x000000FF), 1, operand[0][0]);
515*3d8817e4Smiod get_indirect_operand ((insn_word & 0x0000FF00) >> 8, 1, operand[1][0]);
516*3d8817e4Smiod get_register_operand ((insn_word >> 19) & 0x07, operand[1][1]);
517*3d8817e4Smiod get_register_operand ((insn_word >> 22) & 0x07, operand[0][1]);
518*3d8817e4Smiod break;
519*3d8817e4Smiod case OO_4op3:
520*3d8817e4Smiod get_indirect_operand ((insn_word & 0x000000FF), 1, operand[0][1]);
521*3d8817e4Smiod get_indirect_operand ((insn_word & 0x0000FF00) >> 8, 1, operand[1][1]);
522*3d8817e4Smiod get_register_operand ((insn_word >> 16) & 0x07, operand[1][0]);
523*3d8817e4Smiod get_register_operand ((insn_word >> 22) & 0x07, operand[0][0]);
524*3d8817e4Smiod break;
525*3d8817e4Smiod case OO_5op1:
526*3d8817e4Smiod get_indirect_operand ((insn_word & 0x000000FF), 1, operand[0][0]);
527*3d8817e4Smiod get_indirect_operand ((insn_word & 0x0000FF00) >> 8, 1, operand[1][1]);
528*3d8817e4Smiod get_register_operand ((insn_word >> 16) & 0x07, operand[1][0]);
529*3d8817e4Smiod get_register_operand ((insn_word >> 19) & 0x07, operand[0][1]);
530*3d8817e4Smiod get_register_operand ((insn_word >> 22) & 0x07, operand[0][2]);
531*3d8817e4Smiod break;
532*3d8817e4Smiod case OO_5op2:
533*3d8817e4Smiod get_indirect_operand ((insn_word & 0x000000FF), 1, operand[0][1]);
534*3d8817e4Smiod get_indirect_operand ((insn_word & 0x0000FF00) >> 8, 1, operand[1][1]);
535*3d8817e4Smiod get_register_operand ((insn_word >> 16) & 0x07, operand[1][0]);
536*3d8817e4Smiod get_register_operand ((insn_word >> 19) & 0x07, operand[0][0]);
537*3d8817e4Smiod get_register_operand ((insn_word >> 22) & 0x07, operand[0][2]);
538*3d8817e4Smiod break;
539*3d8817e4Smiod case OO_PField:
540*3d8817e4Smiod if (insn_word & 0x00800000)
541*3d8817e4Smiod get_register_operand (0x01, operand[0][2]);
542*3d8817e4Smiod else
543*3d8817e4Smiod get_register_operand (0x00, operand[0][2]);
544*3d8817e4Smiod if (insn_word & 0x00400000)
545*3d8817e4Smiod get_register_operand (0x03, operand[1][2]);
546*3d8817e4Smiod else
547*3d8817e4Smiod get_register_operand (0x02, operand[1][2]);
548*3d8817e4Smiod switch (insn_word & P_FIELD)
549*3d8817e4Smiod {
550*3d8817e4Smiod case 0x00000000:
551*3d8817e4Smiod get_indirect_operand ((insn_word & 0x000000FF), 1, operand[0][1]);
552*3d8817e4Smiod get_indirect_operand ((insn_word & 0x0000FF00) >> 8, 1, operand[0][0]);
553*3d8817e4Smiod get_register_operand ((insn_word >> 16) & 0x07, operand[1][1]);
554*3d8817e4Smiod get_register_operand ((insn_word >> 19) & 0x07, operand[1][0]);
555*3d8817e4Smiod break;
556*3d8817e4Smiod case 0x01000000:
557*3d8817e4Smiod get_indirect_operand ((insn_word & 0x000000FF), 1, operand[1][0]);
558*3d8817e4Smiod get_indirect_operand ((insn_word & 0x0000FF00) >> 8, 1, operand[0][0]);
559*3d8817e4Smiod get_register_operand ((insn_word >> 16) & 0x07, operand[1][1]);
560*3d8817e4Smiod get_register_operand ((insn_word >> 19) & 0x07, operand[0][1]);
561*3d8817e4Smiod break;
562*3d8817e4Smiod case 0x02000000:
563*3d8817e4Smiod get_indirect_operand ((insn_word & 0x000000FF), 1, operand[1][1]);
564*3d8817e4Smiod get_indirect_operand ((insn_word & 0x0000FF00) >> 8, 1, operand[1][0]);
565*3d8817e4Smiod get_register_operand ((insn_word >> 16) & 0x07, operand[0][1]);
566*3d8817e4Smiod get_register_operand ((insn_word >> 19) & 0x07, operand[0][0]);
567*3d8817e4Smiod break;
568*3d8817e4Smiod case 0x03000000:
569*3d8817e4Smiod get_indirect_operand ((insn_word & 0x000000FF), 1, operand[1][1]);
570*3d8817e4Smiod get_indirect_operand ((insn_word & 0x0000FF00) >> 8, 1, operand[0][0]);
571*3d8817e4Smiod get_register_operand ((insn_word >> 16) & 0x07, operand[1][0]);
572*3d8817e4Smiod get_register_operand ((insn_word >> 19) & 0x07, operand[0][1]);
573*3d8817e4Smiod break;
574*3d8817e4Smiod }
575*3d8817e4Smiod break;
576*3d8817e4Smiod default:
577*3d8817e4Smiod return 0;
578*3d8817e4Smiod }
579*3d8817e4Smiod info->fprintf_func (info->stream, " %s %s,%s%c%s", name1,
580*3d8817e4Smiod operand[0][0], operand[0][1],
581*3d8817e4Smiod operand[0][2][0] ? ',' : ' ',
582*3d8817e4Smiod operand[0][2][0] ? operand[0][2] : "");
583*3d8817e4Smiod info->fprintf_func (info->stream, "\n\t\t\t|| %s %s,%s%c%s", name2,
584*3d8817e4Smiod operand[1][0], operand[1][1],
585*3d8817e4Smiod operand[1][2][0] ? ',' : ' ',
586*3d8817e4Smiod operand[1][2][0] ? operand[1][2] : "");
587*3d8817e4Smiod free (name1);
588*3d8817e4Smiod return 1;
589*3d8817e4Smiod }
590*3d8817e4Smiod
591*3d8817e4Smiod static int
print_branch(disassemble_info * info,unsigned long insn_word,struct instruction * insn)592*3d8817e4Smiod print_branch (disassemble_info *info,
593*3d8817e4Smiod unsigned long insn_word,
594*3d8817e4Smiod struct instruction *insn)
595*3d8817e4Smiod {
596*3d8817e4Smiod char operand[2][13] =
597*3d8817e4Smiod {
598*3d8817e4Smiod {0},
599*3d8817e4Smiod {0}
600*3d8817e4Smiod };
601*3d8817e4Smiod unsigned long address;
602*3d8817e4Smiod int print_label = 0;
603*3d8817e4Smiod
604*3d8817e4Smiod if (insn->tm == NULL)
605*3d8817e4Smiod return 0;
606*3d8817e4Smiod /* Get the operands for 24-bit immediate jumps. */
607*3d8817e4Smiod if (insn->tm->operand_types[0] & Imm24)
608*3d8817e4Smiod {
609*3d8817e4Smiod address = insn_word & 0x00FFFFFF;
610*3d8817e4Smiod sprintf (operand[0], "0x%lX", address);
611*3d8817e4Smiod print_label = 1;
612*3d8817e4Smiod }
613*3d8817e4Smiod /* Get the operand for the trap instruction. */
614*3d8817e4Smiod else if (insn->tm->operand_types[0] & IVector)
615*3d8817e4Smiod {
616*3d8817e4Smiod address = insn_word & 0x0000001F;
617*3d8817e4Smiod sprintf (operand[0], "0x%lX", address);
618*3d8817e4Smiod }
619*3d8817e4Smiod else
620*3d8817e4Smiod {
621*3d8817e4Smiod address = insn_word & 0x0000FFFF;
622*3d8817e4Smiod /* Get the operands for the DB instructions. */
623*3d8817e4Smiod if (insn->tm->operands == 2)
624*3d8817e4Smiod {
625*3d8817e4Smiod get_register_operand (((insn_word & 0x01C00000) >> 22) + REG_AR0, operand[0]);
626*3d8817e4Smiod if (insn_word & PCRel)
627*3d8817e4Smiod {
628*3d8817e4Smiod sprintf (operand[1], "%d", (short) address);
629*3d8817e4Smiod print_label = 1;
630*3d8817e4Smiod }
631*3d8817e4Smiod else
632*3d8817e4Smiod get_register_operand (insn_word & 0x0000001F, operand[1]);
633*3d8817e4Smiod }
634*3d8817e4Smiod /* Get the operands for the standard branches. */
635*3d8817e4Smiod else if (insn->tm->operands == 1)
636*3d8817e4Smiod {
637*3d8817e4Smiod if (insn_word & PCRel)
638*3d8817e4Smiod {
639*3d8817e4Smiod address = (short) address;
640*3d8817e4Smiod sprintf (operand[0], "%ld", address);
641*3d8817e4Smiod print_label = 1;
642*3d8817e4Smiod }
643*3d8817e4Smiod else
644*3d8817e4Smiod get_register_operand (insn_word & 0x0000001F, operand[0]);
645*3d8817e4Smiod }
646*3d8817e4Smiod }
647*3d8817e4Smiod info->fprintf_func (info->stream, " %s %s%c%s", insn->tm->name,
648*3d8817e4Smiod operand[0][0] ? operand[0] : "",
649*3d8817e4Smiod operand[1][0] ? ',' : ' ',
650*3d8817e4Smiod operand[1][0] ? operand[1] : "");
651*3d8817e4Smiod /* Print destination of branch in relation to current symbol. */
652*3d8817e4Smiod if (print_label && info->symbols)
653*3d8817e4Smiod {
654*3d8817e4Smiod asymbol *sym = *info->symbols;
655*3d8817e4Smiod
656*3d8817e4Smiod if ((insn->tm->opcode_modifier == PCRel) && (insn_word & PCRel))
657*3d8817e4Smiod {
658*3d8817e4Smiod address = (_pc + 1 + (short) address) - ((sym->section->vma + sym->value) / 4);
659*3d8817e4Smiod /* Check for delayed instruction, if so adjust destination. */
660*3d8817e4Smiod if (insn_word & 0x00200000)
661*3d8817e4Smiod address += 2;
662*3d8817e4Smiod }
663*3d8817e4Smiod else
664*3d8817e4Smiod {
665*3d8817e4Smiod address -= ((sym->section->vma + sym->value) / 4);
666*3d8817e4Smiod }
667*3d8817e4Smiod if (address == 0)
668*3d8817e4Smiod info->fprintf_func (info->stream, " <%s>", sym->name);
669*3d8817e4Smiod else
670*3d8817e4Smiod info->fprintf_func (info->stream, " <%s %c %d>", sym->name,
671*3d8817e4Smiod ((short) address < 0) ? '-' : '+',
672*3d8817e4Smiod abs (address));
673*3d8817e4Smiod }
674*3d8817e4Smiod return 1;
675*3d8817e4Smiod }
676*3d8817e4Smiod
677*3d8817e4Smiod int
print_insn_tic30(bfd_vma pc,disassemble_info * info)678*3d8817e4Smiod print_insn_tic30 (bfd_vma pc, disassemble_info *info)
679*3d8817e4Smiod {
680*3d8817e4Smiod unsigned long insn_word;
681*3d8817e4Smiod struct instruction insn = { 0, NULL, NULL };
682*3d8817e4Smiod bfd_vma bufaddr = pc - info->buffer_vma;
683*3d8817e4Smiod
684*3d8817e4Smiod /* Obtain the current instruction word from the buffer. */
685*3d8817e4Smiod insn_word = (*(info->buffer + bufaddr) << 24) | (*(info->buffer + bufaddr + 1) << 16) |
686*3d8817e4Smiod (*(info->buffer + bufaddr + 2) << 8) | *(info->buffer + bufaddr + 3);
687*3d8817e4Smiod _pc = pc / 4;
688*3d8817e4Smiod /* Get the instruction refered to by the current instruction word
689*3d8817e4Smiod and print it out based on its type. */
690*3d8817e4Smiod if (!get_tic30_instruction (insn_word, &insn))
691*3d8817e4Smiod return -1;
692*3d8817e4Smiod switch (GET_TYPE (insn_word))
693*3d8817e4Smiod {
694*3d8817e4Smiod case TWO_OPERAND_1:
695*3d8817e4Smiod case TWO_OPERAND_2:
696*3d8817e4Smiod if (!print_two_operand (info, insn_word, &insn))
697*3d8817e4Smiod return -1;
698*3d8817e4Smiod break;
699*3d8817e4Smiod case THREE_OPERAND:
700*3d8817e4Smiod if (!print_three_operand (info, insn_word, &insn))
701*3d8817e4Smiod return -1;
702*3d8817e4Smiod break;
703*3d8817e4Smiod case PAR_STORE:
704*3d8817e4Smiod case MUL_ADDS:
705*3d8817e4Smiod if (!print_par_insn (info, insn_word, &insn))
706*3d8817e4Smiod return -1;
707*3d8817e4Smiod break;
708*3d8817e4Smiod case BRANCHES:
709*3d8817e4Smiod if (!print_branch (info, insn_word, &insn))
710*3d8817e4Smiod return -1;
711*3d8817e4Smiod break;
712*3d8817e4Smiod }
713*3d8817e4Smiod return 4;
714*3d8817e4Smiod }
715