1 /* Copyright (C) 2000-2014 Free Software Foundation, Inc.
2    Contributed by Alexandre Oliva <aoliva@cygnus.com>
3 
4    This file is free software; you can redistribute it and/or modify it
5    under the terms of the GNU General Public License as published by
6    the Free Software Foundation; either version 3 of the License, or
7    (at your option) any later version.
8 
9    This program is distributed in the hope that it will be useful, but
10    WITHOUT ANY WARRANTY; without even the implied warranty of
11    MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE.  See the GNU
12    General Public License for more details.
13 
14    You should have received a copy of the GNU General Public License
15    along with this program; if not, write to the Free Software
16    Foundation, Inc., 51 Franklin Street - Fifth Floor, Boston,
17    MA 02110-1301, USA.  */
18 
19 /* Generator of tests for Maverick.
20 
21    See the following file for usage and documentation.  */
22 #include "../all/test-gen.c"
23 
24 /* These are the ARM registers.  Some of them have canonical names
25    other than r##, so we'll use both in the asm input, but only the
26    canonical names in the expected disassembler output.  */
27 char *arm_regs[] =
28   {
29     /* Canonical names.  */
30     "r0", "r1", "r2", "r3", "r4", "r5", "r6", "r7",
31     "r8", "r9", "sl", "fp", "ip", "sp", "lr", "pc",
32     /* Alternate names, i.e., those that can be used in the assembler,
33      * but that will never be emitted by the disassembler.  */
34     "r0", "r1", "r2", "r3", "r4", "r5", "r6", "r7",
35     "r8", "r9", "r10", "r11", "r12", "r13", "r14", "r15"
36   };
37 
38 /* The various types of registers: ARM's registers, Maverick's
39    f/d/fx/dx registers, Maverick's accumulators and Maverick's
40    status register.  */
41 #define armreg(shift) \
42   reg_r (arm_regs, shift, 0xf, mk_get_bits (5u))
43 #define mvreg(prefix, shift) \
44   reg_p ("mv" prefix, shift, mk_get_bits (4u))
45 #define acreg(shift) \
46   reg_p ("mvax", shift, mk_get_bits (2u))
47 #define dspsc \
48   literal ("dspsc"), tick_random
49 
50 /* This outputs the condition flag that may follow each ARM insn.
51    Since the condition 15 is invalid, we use it to check that the
52    assembler recognizes the absence of a condition as `al'.  However,
53    the disassembler won't ever output `al', so, if we emit it in the
54    assembler, expect the condition to be omitted in the disassembler
55    output.  */
56 
57 int
arm_cond(func_arg * arg,insn_data * data)58 arm_cond (func_arg * arg, insn_data * data)
59 #define arm_cond { arm_cond }
60 {
61   static const char conds[16][3] =
62     {
63       "eq", "ne", "cs", "cc",
64       "mi", "pl", "vs", "vc",
65       "hi", "ls", "ge", "lt",
66       "gt", "le", "al", ""
67     };
68   unsigned val = get_bits (4u);
69 
70   data->as_in = data->dis_out = strdup (conds[val]);
71   if (val == 14)
72     data->dis_out = strdup ("");
73   data->bits = (val == 15 ? 14 : val) << 28;
74   return 0;
75 }
76 
77 /* The sign of an offset is actually used to determined whether the
78    absolute value of the offset should be added or subtracted, so we
79    must adjust negative values so that they do not overflow: -1024 is
80    not valid, but -0 is distinct from +0.  */
81 int
off8s(func_arg * arg,insn_data * data)82 off8s (func_arg * arg, insn_data * data)
83 #define off8s { off8s }
84 {
85   int val;
86   char value[9];
87 
88   /* Zero values are problematical.
89      The assembler performs translations on the addressing modes
90      for these values, meaning that we cannot just recreate the
91      disassembler string in the LDST macro without knowing what
92      value had been generated in off8s.  */
93   do
94     {
95       val  = get_bits (9s);
96     }
97   while (val == -1 || val == 0);
98 
99   val <<= 2;
100   if (val < 0)
101     {
102       val = -4 - val;
103       sprintf (value, ", #-%i", val);
104       data->dis_out = strdup (value);
105       sprintf (value, ", #-%i", val);
106       data->as_in = strdup (value);
107       data->bits = val >> 2;
108     }
109   else
110     {
111       sprintf (value, ", #%i", val);
112       data->as_in = data->dis_out = strdup (value);
113       data->bits = (val >> 2) | (1 << 23);
114     }
115 
116   return 0;
117 }
118 
119 /* This function generates a 7-bit signed constant, emitted as
120    follows: the 4 least-significant bits are stored in the 4
121    least-significant bits of the word; the 3 most-significant bits are
122    stored in bits 7:5, i.e., bit 4 is skipped.  */
123 int
imm7(func_arg * arg,insn_data * data)124 imm7 (func_arg *arg, insn_data *data)
125 #define imm7 { imm7 }
126 {
127   int val = get_bits (7s);
128   char value[6];
129 
130   data->bits = (val & 0x0f) | (2 * (val & 0x70));
131   sprintf (value, "#%i", val);
132   data->as_in = data->dis_out = strdup (value);
133   return 0;
134 }
135 
136 /* Convenience wrapper to define_insn, that prefixes every insn with
137    `cf' (so, if you specify command-line arguments, remember that `cf'
138    must *not* be part of the string), and post-fixes a condition code.
139    insname and insnvar specify the main insn name and a variant;
140    they're just concatenated, and insnvar is often empty.  word is the
141    bit pattern that defines the insn, properly shifted, and funcs is a
142    sequence of funcs that define the operands and the syntax of the
143    insn.  */
144 #define mv_insn(insname, insnvar, word, funcs...) \
145   define_insn (insname ## insnvar, \
146 	      literal ("cf"), \
147 	      insn_bits (insname, word), \
148 	      arm_cond, \
149 	      tab, \
150 	      ## funcs)
151 
152 /* Define a single LDC/STC variant.  op is the main insn opcode; ld
153    stands for load (it should be 0 on stores), dword selects 64-bit
154    operations, pre should be enabled for pre-increment, and wb, for
155    write-back.  sep1, sep2 and sep3 are syntactical elements ([]!)
156    that the assembler will use to enable pre and wb.  It would
157    probably have been cleaner to couple the syntactical elements with
158    the pre/wb bits directly, but it would have required the definition
159    of more functions.  */
160 #define LDST(insname, insnvar, op, ld, dword, regname, pre, wb, sep1, sep2, sep3) \
161   mv_insn (insname, insnvar, \
162 	   (12 << 24) | (op << 8) | (ld << 20) | (pre << 24) | (dword << 22) | (wb << 21), \
163 	    mvreg (regname, 12), comma, \
164 	    lsqbkt, armreg (16), sep1, off8s, sep2, sep3, \
165 	    tick_random)
166 
167 /* Define all variants of an LDR or STR instruction, namely,
168    pre-indexed without write-back, pre-indexed with write-back and
169    post-indexed.  */
170 #define LDSTall(insname, op, ld, dword, regname) \
171   LDST (insname, _p, op, ld, dword, regname, 1, 0, nothing, rsqbkt, nothing); \
172   LDST (insname, _pw, op, ld, dword, regname, 1, 1, nothing, rsqbkt, literal ("!")); \
173   LDST (insname, ,op, ld, dword, regname, 0, 1, rsqbkt, nothing, nothing)
174 
175 /* Produce the insn identifiers of all LDST variants of a given insn.
176    To be used in the initialization of an insn group array.  */
177 #define insns_LDSTall(insname) \
178   insn (insname ## _p), insn (insname ## _pw), insn (insname)
179 
180 /* Define a CDP variant that uses two registers, at offsets 12 and 16.
181    The two opcodes and the co-processor number identify the CDP
182    insn.  */
183 #define CDP2(insname, var, cpnum, opcode1, opcode2, reg1name, reg2name) \
184   mv_insn (insname##var, , \
185 	   (14 << 24) | ((opcode1) << 20) | ((cpnum) << 8) | ((opcode2) << 5), \
186 	   mvreg (reg1name, 12), comma, mvreg (reg2name, 16))
187 
188 /* Define a 32-bit integer CDP instruction with two operands.  */
189 #define CDP2fx(insname, opcode1, opcode2) \
190   CDP2 (insname, 32, 5, opcode1, opcode2, "fx", "fx")
191 
192 /* Define a 64-bit integer CDP instruction with two operands.  */
193 #define CDP2dx(insname, opcode1, opcode2) \
194   CDP2 (insname, 64, 5, opcode1, opcode2, "dx", "dx")
195 
196 /* Define a float CDP instruction with two operands.  */
197 #define CDP2f(insname, opcode1, opcode2) \
198   CDP2 (insname, s, 4, opcode1, opcode2, "f", "f")
199 
200 /* Define a double CDP instruction with two operands.  */
201 #define CDP2d(insname, opcode1, opcode2) \
202   CDP2 (insname, d, 4, opcode1, opcode2, "d", "d")
203 
204 /* Define a CDP instruction with two register operands and one 7-bit
205    signed immediate generated with imm7.  */
206 #define CDP2_imm7(insname, cpnum, opcode1, reg1name, reg2name) \
207   mv_insn (insname, , (14 << 24) | ((opcode1) << 20) | ((cpnum) << 8), \
208 	   mvreg (reg1name, 12), comma, mvreg (reg2name, 16), comma, imm7, \
209 	   tick_random)
210 
211 /* Produce the insn identifiers of CDP floating-point or integer insn
212    pairs (i.e., it appends the suffixes for 32-bit and 64-bit
213    insns.  */
214 #define CDPfp_insns(insname) \
215   insn (insname ## s), insn (insname ## d)
216 #define CDPx_insns(insname) \
217   insn (insname ## 32), insn (insname ## 64)
218 
219 /* Define a CDP instruction with 3 operands, at offsets 12, 16, 0.  */
220 #define CDP3(insname, var, cpnum, opcode1, opcode2, reg1name, reg2name, reg3name) \
221   mv_insn (insname##var, , \
222 	   (14 << 24) | ((opcode1) << 20) | ((cpnum) << 8) | ((opcode2) << 5), \
223 	   mvreg (reg1name, 12), comma, mvreg (reg2name, 16), comma, \
224 	   mvreg (reg3name, 0), tick_random)
225 
226 /* Define a 32-bit integer CDP instruction with three operands.  */
227 #define CDP3fx(insname, opcode1, opcode2) \
228   CDP3 (insname, 32, 5, opcode1, opcode2, "fx", "fx", "fx")
229 
230 /* Define a 64-bit integer CDP instruction with three operands.  */
231 #define CDP3dx(insname, opcode1, opcode2) \
232   CDP3 (insname, 64, 5, opcode1, opcode2, "dx", "dx", "dx")
233 
234 /* Define a float CDP instruction with three operands.  */
235 #define CDP3f(insname, opcode1, opcode2) \
236   CDP3 (insname, s, 4, opcode1, opcode2, "f", "f", "f")
237 
238 /* Define a double CDP instruction with three operands.  */
239 #define CDP3d(insname, opcode1, opcode2) \
240   CDP3 (insname, d, 4, opcode1, opcode2, "d", "d", "d")
241 
242 /* Define a CDP instruction with four operands, at offsets 5, 12, 16
243  * and 0.  Used only for ACC instructions.  */
244 #define CDP4(insname, opcode1, reg2spec, reg3name, reg4name) \
245   mv_insn (insname, , (14 << 24) | ((opcode1) << 20) | (6 << 8), \
246 	   acreg (5), comma, reg2spec, comma, \
247 	   mvreg (reg3name, 16), comma, mvreg (reg4name, 0))
248 
249 /* Define a CDP4 instruction with one accumulator operands.  */
250 #define CDP41A(insname, opcode1) \
251   CDP4 (insname, opcode1, mvreg ("fx", 12), "fx", "fx")
252 
253 /* Define a CDP4 instruction with two accumulator operands.  */
254 #define CDP42A(insname, opcode1) \
255   CDP4 (insname, opcode1, acreg (12), "fx", "fx")
256 
257 /* Define a MCR or MRC instruction with two register operands.  */
258 #define MCRC2(insname, cpnum, opcode1, dir, opcode2, reg1spec, reg2spec) \
259   mv_insn (insname, , \
260 	   ((14 << 24) | ((opcode1) << 21) | ((dir) << 20)| \
261 	    ((cpnum) << 8) | ((opcode2) << 5) | (1 << 4)), \
262 	   reg1spec, comma, reg2spec)
263 
264 /* Define a move from a DSP register to an ARM register.  */
265 #define MVDSPARM(insname, cpnum, opcode2, regDSPname) \
266   MCRC2 (mv ## insname, cpnum, 0, 0, opcode2, \
267 	 mvreg (regDSPname, 16), armreg (12))
268 
269 /* Define a move from an ARM register to a DSP register.  */
270 #define MVARMDSP(insname, cpnum, opcode2, regDSPname) \
271   MCRC2 (mv ## insname, cpnum, 0, 1, opcode2, \
272 	 armreg (12), mvreg (regDSPname, 16))
273 
274 /* Move between coprocessor registers. A two operand CDP insn.   */
275 #define MCC2(insname, opcode1, opcode2, reg1spec, reg2spec) \
276   mv_insn (insname, , \
277 	   ((14 << 24) | ((opcode1) << 20) | \
278 	    (4 << 8) | ((opcode2) << 5)), \
279 	   reg1spec, comma, reg2spec)
280 
281 /* Define a move from a DSP register to a DSP accumulator.  */
282 #define MVDSPACC(insname, opcode2, regDSPname) \
283   MCC2 (mv ## insname, 2, opcode2, acreg (12), mvreg (regDSPname, 16))
284 
285 /* Define a move from a DSP accumulator to a DSP register.  */
286 #define MVACCDSP(insname, opcode2, regDSPname) \
287   MCC2 (mv ## insname, 1, opcode2, mvreg (regDSPname, 12), acreg (16))
288 
289 /* Define move insns between a float DSP register and an ARM
290    register.  */
291 #define MVf(nameAD, nameDA, opcode2) \
292   MVDSPARM (nameAD, 4, opcode2, "f"); \
293   MVARMDSP (nameDA, 4, opcode2, "f")
294 
295 /* Define move insns between a double DSP register and an ARM
296    register.  */
297 #define MVd(nameAD, nameDA, opcode2) \
298   MVDSPARM (nameAD, 4, opcode2, "d"); \
299   MVARMDSP (nameDA, 4, opcode2, "d")
300 
301 /* Define move insns between a 32-bit integer DSP register and an ARM
302    register.  */
303 #define MVfx(nameAD, nameDA, opcode2) \
304   MVDSPARM (nameAD, 5, opcode2, "fx"); \
305   MVARMDSP (nameDA, 5, opcode2, "fx")
306 
307 /* Define move insns between a 64-bit integer DSP register and an ARM
308    register.  */
309 #define MVdx(nameAD, nameDA, opcode2) \
310   MVDSPARM (nameAD, 5, opcode2, "dx"); \
311   MVARMDSP (nameDA, 5, opcode2, "dx")
312 
313 /* Define move insns between a 32-bit DSP register and a DSP
314    accumulator.  */
315 #define MVfxa(nameFA, nameAF, opcode2) \
316   MVDSPACC (nameFA, opcode2, "fx"); \
317   MVACCDSP (nameAF, opcode2, "fx")
318 
319 /* Define move insns between a 64-bit DSP register and a DSP
320    accumulator.  */
321 #define MVdxa(nameDA, nameAD, opcode2) \
322   MVDSPACC (nameDA, opcode2, "dx"); \
323   MVACCDSP (nameAD, opcode2, "dx")
324 
325 /* Produce the insn identifiers for a pair of mv insns.  */
326 #define insns_MV(name1, name2) \
327   insn (mv ## name1), insn (mv ## name2)
328 
329 /* Define a MCR or MRC instruction with three register operands.  */
330 #define MCRC3(insname, cpnum, opcode1, dir, opcode2, reg1spec, reg2spec, reg3spec) \
331   mv_insn (insname, , \
332 	   ((14 << 24) | ((opcode1) << 21) | ((dir) << 20)| \
333 	    ((cpnum) << 8) | ((opcode2) << 5) | (1 << 4)), \
334 	   reg1spec, comma, reg2spec, comma, reg3spec, \
335 	   tick_random)
336 
337 /* Define all load_store insns.  */
338 LDSTall (ldrs, 4, 1, 0, "f");
339 LDSTall (ldrd, 4, 1, 1, "d");
340 LDSTall (ldr32, 5, 1, 0, "fx");
341 LDSTall (ldr64, 5, 1, 1, "dx");
342 LDSTall (strs, 4, 0, 0, "f");
343 LDSTall (strd, 4, 0, 1, "d");
344 LDSTall (str32, 5, 0, 0, "fx");
345 LDSTall (str64, 5, 0, 1, "dx");
346 
347 /* Create the load_store insn group.  */
348 func *load_store_insns[] =
349   {
350     insns_LDSTall (ldrs),  insns_LDSTall (ldrd),
351     insns_LDSTall (ldr32), insns_LDSTall (ldr64),
352     insns_LDSTall (strs),  insns_LDSTall (strd),
353     insns_LDSTall (str32), insns_LDSTall (str64),
354     0
355   };
356 
357 /* Define all move insns.  */
358 MVf (sr, rs, 2);
359 MVd (dlr, rdl, 0);
360 MVd (dhr, rdh, 1);
361 MVdx (64lr, r64l, 0);
362 MVdx (64hr, r64h, 1);
363 MVfxa (al32, 32al, 2);
364 MVfxa (am32, 32am, 3);
365 MVfxa (ah32, 32ah, 4);
366 MVfxa (a32, 32a, 5);
367 MVdxa (a64, 64a, 6);
368 MCC2 (mvsc32, 2, 7, dspsc, mvreg ("dx", 12));
369 MCC2 (mv32sc, 1, 7, mvreg ("dx", 12), dspsc);
370 CDP2 (cpys, , 4, 0, 0, "f", "f");
371 CDP2 (cpyd, , 4, 0, 1, "d", "d");
372 
373 /* Create the move insns group.  */
374 func * move_insns[] =
375   {
376     insns_MV (sr, rs), insns_MV (dlr, rdl), insns_MV (dhr, rdh),
377     insns_MV (64lr, r64l), insns_MV (64hr, r64h),
378     insns_MV (al32, 32al), insns_MV (am32, 32am), insns_MV (ah32, 32ah),
379     insns_MV (a32, 32a), insns_MV (a64, 64a),
380     insn (mvsc32), insn (mv32sc), insn (cpys), insn (cpyd),
381     0
382   };
383 
384 /* Define all conversion insns.  */
385 CDP2 (cvtsd, , 4, 0, 3, "d", "f");
386 CDP2 (cvtds, , 4, 0, 2, "f", "d");
387 CDP2 (cvt32s, , 4, 0, 4, "f", "fx");
388 CDP2 (cvt32d, , 4, 0, 5, "d", "fx");
389 CDP2 (cvt64s, , 4, 0, 6, "f", "dx");
390 CDP2 (cvt64d, , 4, 0, 7, "d", "dx");
391 CDP2 (cvts32, , 5, 1, 4, "fx", "f");
392 CDP2 (cvtd32, , 5, 1, 5, "fx", "d");
393 CDP2 (truncs32, , 5, 1, 6, "fx", "f");
394 CDP2 (truncd32, , 5, 1, 7, "fx", "d");
395 
396 /* Create the conv insns group.  */
397 func * conv_insns[] =
398   {
399     insn (cvtsd), insn (cvtds), insn (cvt32s), insn (cvt32d),
400     insn (cvt64s), insn (cvt64d), insn (cvts32), insn (cvtd32),
401     insn (truncs32), insn (truncd32),
402     0
403   };
404 
405 /* Define all shift insns.  */
406 MCRC3 (rshl32, 5, 0, 0, 2, mvreg ("fx", 16), mvreg ("fx", 0), armreg (12));
407 MCRC3 (rshl64, 5, 0, 0, 3, mvreg ("dx", 16), mvreg ("dx", 0), armreg (12));
408 CDP2_imm7 (sh32, 5, 0, "fx", "fx");
409 CDP2_imm7 (sh64, 5, 2, "dx", "dx");
410 
411 /* Create the shift insns group.  */
412 func *shift_insns[] =
413   {
414     insn (rshl32), insn (rshl64),
415     insn (sh32), insn (sh64),
416     0
417   };
418 
419 /* Define all comparison insns.  */
420 MCRC3 (cmps, 4, 0, 1, 4, armreg (12), mvreg ("f", 16), mvreg ("f", 0));
421 MCRC3 (cmpd, 4, 0, 1, 5, armreg (12), mvreg ("d", 16), mvreg ("d", 0));
422 MCRC3 (cmp32, 5, 0, 1, 4, armreg (12), mvreg ("fx", 16), mvreg ("fx", 0));
423 MCRC3 (cmp64, 5, 0, 1, 5, armreg (12), mvreg ("dx", 16), mvreg ("dx", 0));
424 
425 /* Create the comp insns group.  */
426 func *comp_insns[] =
427   {
428     insn (cmps), insn (cmpd),
429     insn (cmp32), insn (cmp64),
430     0
431   };
432 
433 /* Define all floating-point arithmetic insns.  */
434 CDP2f (abs, 3, 0);
435 CDP2d (abs, 3, 1);
436 CDP2f (neg, 3, 2);
437 CDP2d (neg, 3, 3);
438 CDP3f (add, 3, 4);
439 CDP3d (add, 3, 5);
440 CDP3f (sub, 3, 6);
441 CDP3d (sub, 3, 7);
442 CDP3f (mul, 1, 0);
443 CDP3d (mul, 1, 1);
444 
445 /* Create the fp-arith insns group.  */
446 func *fp_arith_insns[] =
447   {
448     CDPfp_insns (abs), CDPfp_insns (neg),
449     CDPfp_insns (add), CDPfp_insns (sub), CDPfp_insns (mul),
450     0
451   };
452 
453 /* Define all integer arithmetic insns.  */
454 CDP2fx (abs, 3, 0);
455 CDP2dx (abs, 3, 1);
456 CDP2fx (neg, 3, 2);
457 CDP2dx (neg, 3, 3);
458 CDP3fx (add, 3, 4);
459 CDP3dx (add, 3, 5);
460 CDP3fx (sub, 3, 6);
461 CDP3dx (sub, 3, 7);
462 CDP3fx (mul, 1, 0);
463 CDP3dx (mul, 1, 1);
464 CDP3fx (mac, 1, 2);
465 CDP3fx (msc, 1, 3);
466 
467 /* Create the int-arith insns group.  */
468 func * int_arith_insns[] =
469   {
470     CDPx_insns (abs), CDPx_insns (neg),
471     CDPx_insns (add), CDPx_insns (sub), CDPx_insns (mul),
472     insn (mac32), insn (msc32),
473     0
474   };
475 
476 /* Define all accumulator arithmetic insns.  */
477 CDP41A (madd32, 0);
478 CDP41A (msub32, 1);
479 CDP42A (madda32, 2);
480 CDP42A (msuba32, 3);
481 
482 /* Create the acc-arith insns group.  */
483 func * acc_arith_insns[] =
484   {
485     insn (madd32), insn (msub32),
486     insn (madda32), insn (msuba32),
487     0
488   };
489 
490 /* Create the set of all groups.  */
491 group_t groups[] =
492   {
493     { "load_store", load_store_insns },
494     { "move", move_insns },
495     { "conv", conv_insns },
496     { "shift", shift_insns },
497     { "comp", comp_insns },
498     { "fp_arith", fp_arith_insns },
499     { "int_arith", int_arith_insns },
500     { "acc_arith", acc_arith_insns },
501     { 0 }
502   };
503 
504 int
main(int argc,char * argv[])505 main (int argc, char *argv[])
506 {
507   FILE *as_in = stdout, *dis_out = stderr;
508 
509   /* Check whether we're filtering insns.  */
510   if (argc > 1)
511     skip_list = argv + 1;
512 
513   /* Output assembler header.  */
514   fputs ("\t.text\n"
515 	 "\t.align\n",
516 	 as_in);
517   /* Output comments for the testsuite-driver and the initial
518      disassembler output.  */
519   fputs ("#objdump: -dr --prefix-address --show-raw-insn\n"
520 	 "#name: Maverick\n"
521 	 "#as: -mcpu=ep9312\n"
522 	 "\n"
523 	 "# Test the instructions of the Cirrus Maverick floating point co-processor\n"
524 	 "\n"
525 	 ".*: +file format.*arm.*\n"
526 	 "\n"
527 	 "Disassembly of section .text:\n",
528 	 dis_out);
529 
530   /* Now emit all (selected) insns.  */
531   output_groups (groups, as_in, dis_out);
532 
533   exit (0);
534 }
535