rx-parse.y revision 1.1.1.3
1/* rx-parse.y  Renesas RX parser
2   Copyright (C) 2008-2015 Free Software Foundation, Inc.
3
4   This file is part of GAS, the GNU Assembler.
5
6   GAS is free software; you can redistribute it and/or modify
7   it under the terms of the GNU General Public License as published by
8   the Free Software Foundation; either version 3, or (at your option)
9   any later version.
10
11   GAS is distributed in the hope that it will be useful,
12   but WITHOUT ANY WARRANTY; without even the implied warranty of
13   MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE.  See the
14   GNU General Public License for more details.
15
16   You should have received a copy of the GNU General Public License
17   along with GAS; see the file COPYING.  If not, write to the Free
18   Software Foundation, 51 Franklin Street - Fifth Floor, Boston, MA
19   02110-1301, USA.  */
20%{
21
22#include "as.h"
23#include "safe-ctype.h"
24#include "rx-defs.h"
25
26static int rx_lex (void);
27
28#define COND_EQ	0
29#define COND_NE	1
30
31#define MEMEX 0x06
32
33#define BSIZE 0
34#define WSIZE 1
35#define LSIZE 2
36
37/*                       .sb    .sw    .l     .uw   */
38static int sizemap[] = { BSIZE, WSIZE, LSIZE, WSIZE };
39
40/* Ok, here are the rules for using these macros...
41
42   B*() is used to specify the base opcode bytes.  Fields to be filled
43        in later, leave zero.  Call this first.
44
45   F() and FE() are used to fill in fields within the base opcode bytes.  You MUST
46        call B*() before any F() or FE().
47
48   [UN]*O*(), PC*() appends operands to the end of the opcode.  You
49        must call P() and B*() before any of these, so that the fixups
50        have the right byte location.
51        O = signed, UO = unsigned, NO = negated, PC = pcrel
52
53   IMM() adds an immediate and fills in the field for it.
54   NIMM() same, but negates the immediate.
55   NBIMM() same, but negates the immediate, for sbb.
56   DSP() adds a displacement, and fills in the field for it.
57
58   Note that order is significant for the O, IMM, and DSP macros, as
59   they append their data to the operand buffer in the order that you
60   call them.
61
62   Use "disp" for displacements whenever possible; this handles the
63   "0" case properly.  */
64
65#define B1(b1)             rx_base1 (b1)
66#define B2(b1, b2)         rx_base2 (b1, b2)
67#define B3(b1, b2, b3)     rx_base3 (b1, b2, b3)
68#define B4(b1, b2, b3, b4) rx_base4 (b1, b2, b3, b4)
69
70/* POS is bits from the MSB of the first byte to the LSB of the last byte.  */
71#define F(val,pos,sz)      rx_field (val, pos, sz)
72#define FE(exp,pos,sz)	   rx_field (exp_val (exp), pos, sz);
73
74#define O1(v)              rx_op (v, 1, RXREL_SIGNED); rx_range (v, -128, 255)
75#define O2(v)              rx_op (v, 2, RXREL_SIGNED); rx_range (v, -32768, 65536)
76#define O3(v)              rx_op (v, 3, RXREL_SIGNED); rx_range (v, -8388608, 16777216)
77#define O4(v)              rx_op (v, 4, RXREL_SIGNED)
78
79#define UO1(v)             rx_op (v, 1, RXREL_UNSIGNED); rx_range (v, 0, 255)
80#define UO2(v)             rx_op (v, 2, RXREL_UNSIGNED); rx_range (v, 0, 65536)
81#define UO3(v)             rx_op (v, 3, RXREL_UNSIGNED); rx_range (v, 0, 16777216)
82#define UO4(v)             rx_op (v, 4, RXREL_UNSIGNED)
83
84#define NO1(v)             rx_op (v, 1, RXREL_NEGATIVE)
85#define NO2(v)             rx_op (v, 2, RXREL_NEGATIVE)
86#define NO3(v)             rx_op (v, 3, RXREL_NEGATIVE)
87#define NO4(v)             rx_op (v, 4, RXREL_NEGATIVE)
88
89#define PC1(v)             rx_op (v, 1, RXREL_PCREL)
90#define PC2(v)             rx_op (v, 2, RXREL_PCREL)
91#define PC3(v)             rx_op (v, 3, RXREL_PCREL)
92
93#define IMM_(v,pos,size)   F (immediate (v, RXREL_SIGNED, pos, size), pos, 2); \
94			   if (v.X_op != O_constant && v.X_op != O_big) rx_linkrelax_imm (pos)
95#define IMM(v,pos)	   IMM_ (v, pos, 32)
96#define IMMW(v,pos)	   IMM_ (v, pos, 16); rx_range (v, -32768, 65536)
97#define IMMB(v,pos)	   IMM_ (v, pos, 8); rx_range (v, -128, 255)
98#define NIMM(v,pos)	   F (immediate (v, RXREL_NEGATIVE, pos, 32), pos, 2)
99#define NBIMM(v,pos)	   F (immediate (v, RXREL_NEGATIVE_BORROW, pos, 32), pos, 2)
100#define DSP(v,pos,msz)	   if (!v.X_md) rx_relax (RX_RELAX_DISP, pos); \
101			   else rx_linkrelax_dsp (pos); \
102			   F (displacement (v, msz), pos, 2)
103
104#define id24(a,b2,b3)	   B3 (0xfb+a, b2, b3)
105
106static void	   rx_check_float_support (void);
107static int         rx_intop (expressionS, int, int);
108static int         rx_uintop (expressionS, int);
109static int         rx_disp3op (expressionS);
110static int         rx_disp5op (expressionS *, int);
111static int         rx_disp5op0 (expressionS *, int);
112static int         exp_val (expressionS exp);
113static expressionS zero_expr (void);
114static int         immediate (expressionS, int, int, int);
115static int         displacement (expressionS, int);
116static void        rtsd_immediate (expressionS);
117static void	   rx_range (expressionS, int, int);
118
119static int    need_flag = 0;
120static int    rx_in_brackets = 0;
121static int    rx_last_token = 0;
122static char * rx_init_start;
123static char * rx_last_exp_start = 0;
124static int    sub_op;
125static int    sub_op2;
126
127#define YYDEBUG 1
128#define YYERROR_VERBOSE 1
129
130%}
131
132%name-prefix="rx_"
133
134%union {
135  int regno;
136  expressionS exp;
137}
138
139%type <regno> REG FLAG CREG BCND BMCND SCCND
140%type <regno> flag bwl bw memex
141%type <exp> EXPR disp
142
143%token REG FLAG CREG
144
145%token EXPR UNKNOWN_OPCODE IS_OPCODE
146
147%token DOT_S DOT_B DOT_W DOT_L DOT_A DOT_UB DOT_UW
148
149%token ABS ADC ADD AND_
150%token BCLR BCND BMCND BNOT BRA BRK BSET BSR BTST
151%token CLRPSW CMP
152%token DBT DIV DIVU
153%token EDIV EDIVU EMUL EMULU
154%token FADD FCMP FDIV FMUL FREIT FSUB FTOI
155%token INT ITOF
156%token JMP JSR
157%token MACHI MACLO MAX MIN MOV MOVU MUL MULHI MULLO MULU MVFACHI MVFACMI MVFACLO
158%token   MVFC MVTACHI MVTACLO MVTC MVTIPL
159%token NEG NOP NOT
160%token OR
161%token POP POPC POPM PUSH PUSHA PUSHC PUSHM
162%token RACW REIT REVL REVW RMPA ROLC RORC ROTL ROTR ROUND RTE RTFI RTS RTSD
163%token SAT SATR SBB SCCND SCMPU SETPSW SHAR SHLL SHLR SMOVB SMOVF
164%token   SMOVU SSTR STNZ STOP STZ SUB SUNTIL SWHILE
165%token TST
166%token WAIT
167%token XCHG XOR
168
169%%
170/* ====================================================================== */
171
172statement :
173
174	  UNKNOWN_OPCODE
175	  { as_bad (_("Unknown opcode: %s"), rx_init_start); }
176
177/* ---------------------------------------------------------------------- */
178
179	| BRK
180	  { B1 (0x00); }
181
182	| DBT
183	  { B1 (0x01); }
184
185	| RTS
186	  { B1 (0x02); }
187
188	| NOP
189	  { B1 (0x03); }
190
191/* ---------------------------------------------------------------------- */
192
193	| BRA EXPR
194	  { if (rx_disp3op ($2))
195	      { B1 (0x08); rx_disp3 ($2, 5); }
196	    else if (rx_intop ($2, 8, 8))
197	      { B1 (0x2e); PC1 ($2); }
198	    else if (rx_intop ($2, 16, 16))
199	      { B1 (0x38); PC2 ($2); }
200	    else if (rx_intop ($2, 24, 24))
201	      { B1 (0x04); PC3 ($2); }
202	    else
203	      { rx_relax (RX_RELAX_BRANCH, 0);
204		rx_linkrelax_branch ();
205		/* We'll convert this to a longer one later if needed.  */
206		B1 (0x08); rx_disp3 ($2, 5); } }
207
208	| BRA DOT_A EXPR
209	  { B1 (0x04); PC3 ($3); }
210
211	| BRA DOT_S EXPR
212	  { B1 (0x08); rx_disp3 ($3, 5); }
213
214/* ---------------------------------------------------------------------- */
215
216	| BSR EXPR
217	  { if (rx_intop ($2, 16, 16))
218	      { B1 (0x39); PC2 ($2); }
219	    else if (rx_intop ($2, 24, 24))
220	      { B1 (0x05); PC3 ($2); }
221	    else
222	      { rx_relax (RX_RELAX_BRANCH, 0);
223		rx_linkrelax_branch ();
224		B1 (0x39); PC2 ($2); } }
225	| BSR DOT_A EXPR
226	  { B1 (0x05), PC3 ($3); }
227
228/* ---------------------------------------------------------------------- */
229
230	| BCND DOT_S EXPR
231	  { if ($1 == COND_EQ || $1 == COND_NE)
232	      { B1 ($1 == COND_EQ ? 0x10 : 0x18); rx_disp3 ($3, 5); }
233	    else
234	      as_bad (_("Only BEQ and BNE may have .S")); }
235
236/* ---------------------------------------------------------------------- */
237
238	| BCND DOT_B EXPR
239	  { B1 (0x20); F ($1, 4, 4); PC1 ($3); }
240
241	| BRA DOT_B EXPR
242	  { B1 (0x2e), PC1 ($3); }
243
244/* ---------------------------------------------------------------------- */
245
246	| BRA DOT_W EXPR
247	  { B1 (0x38), PC2 ($3); }
248	| BSR DOT_W EXPR
249	  { B1 (0x39), PC2 ($3); }
250	| BCND DOT_W EXPR
251	  { if ($1 == COND_EQ || $1 == COND_NE)
252	      { B1 ($1 == COND_EQ ? 0x3a : 0x3b); PC2 ($3); }
253	    else
254	      as_bad (_("Only BEQ and BNE may have .W")); }
255	| BCND EXPR
256	  { if ($1 == COND_EQ || $1 == COND_NE)
257	      {
258		rx_relax (RX_RELAX_BRANCH, 0);
259		rx_linkrelax_branch ();
260		B1 ($1 == COND_EQ ? 0x10 : 0x18); rx_disp3 ($2, 5);
261	      }
262	    else
263	      {
264		rx_relax (RX_RELAX_BRANCH, 0);
265		/* This is because we might turn it into a
266		   jump-over-jump long branch.  */
267		rx_linkrelax_branch ();
268	        B1 (0x20); F ($1, 4, 4); PC1 ($2);
269	      } }
270
271/* ---------------------------------------------------------------------- */
272
273	| MOV DOT_B '#' EXPR ',' disp '[' REG ']'
274	  /* rx_disp5op changes the value if it succeeds, so keep it last.  */
275	  { if ($8 <= 7 && rx_uintop ($4, 8) && rx_disp5op0 (&$6, BSIZE))
276	      { B2 (0x3c, 0); rx_field5s2 ($6); F ($8, 9, 3); O1 ($4); }
277	    else
278	      { B2 (0xf8, 0x04); F ($8, 8, 4); DSP ($6, 6, BSIZE); O1 ($4);
279	      if ($4.X_op != O_constant && $4.X_op != O_big) rx_linkrelax_imm (12); } }
280
281	| MOV DOT_W '#' EXPR ',' disp '[' REG ']'
282	  { if ($8 <= 7 && rx_uintop ($4, 8) && rx_disp5op0 (&$6, WSIZE))
283	      { B2 (0x3d, 0); rx_field5s2 ($6); F ($8, 9, 3); O1 ($4); }
284	    else
285	      { B2 (0xf8, 0x01); F ($8, 8, 4); DSP ($6, 6, WSIZE); IMMW ($4, 12); } }
286
287	| MOV DOT_L '#' EXPR ',' disp '[' REG ']'
288	  { if ($8 <= 7 && rx_uintop ($4, 8) && rx_disp5op0 (&$6, LSIZE))
289	      { B2 (0x3e, 0); rx_field5s2 ($6); F ($8, 9, 3); O1 ($4); }
290	    else
291	      { B2 (0xf8, 0x02); F ($8, 8, 4); DSP ($6, 6, LSIZE); IMM ($4, 12); } }
292
293/* ---------------------------------------------------------------------- */
294
295	| RTSD '#' EXPR ',' REG '-' REG
296	  { B2 (0x3f, 0); F ($5, 8, 4); F ($7, 12, 4); rtsd_immediate ($3);
297	    if ($5 == 0)
298	      rx_error (_("RTSD cannot pop R0"));
299	    if ($5 > $7)
300	      rx_error (_("RTSD first reg must be <= second reg")); }
301
302/* ---------------------------------------------------------------------- */
303
304	| CMP REG ',' REG
305	  { B2 (0x47, 0); F ($2, 8, 4); F ($4, 12, 4); }
306
307/* ---------------------------------------------------------------------- */
308
309	| CMP disp '[' REG ']' DOT_UB ',' REG
310	  { B2 (0x44, 0); F ($4, 8, 4); F ($8, 12, 4); DSP ($2, 6, BSIZE); }
311
312	| CMP disp '[' REG ']' memex ',' REG
313	  { B3 (MEMEX, 0x04, 0); F ($6, 8, 2);  F ($4, 16, 4); F ($8, 20, 4); DSP ($2, 14, sizemap[$6]); }
314
315/* ---------------------------------------------------------------------- */
316
317	| MOVU bw REG ',' REG
318	  { B2 (0x5b, 0x00); F ($2, 5, 1); F ($3, 8, 4); F ($5, 12, 4); }
319
320/* ---------------------------------------------------------------------- */
321
322	| MOVU bw '[' REG ']' ',' REG
323	  { B2 (0x58, 0x00); F ($2, 5, 1); F ($4, 8, 4); F ($7, 12, 4); }
324
325	| MOVU bw EXPR '[' REG ']' ',' REG
326	  { if ($5 <= 7 && $8 <= 7 && rx_disp5op (&$3, $2))
327	      { B2 (0xb0, 0); F ($2, 4, 1); F ($5, 9, 3); F ($8, 13, 3); rx_field5s ($3); }
328	    else
329	      { B2 (0x58, 0x00); F ($2, 5, 1); F ($5, 8, 4); F ($8, 12, 4); DSP ($3, 6, $2); } }
330
331/* ---------------------------------------------------------------------- */
332
333	| SUB '#' EXPR ',' REG
334	  { if (rx_uintop ($3, 4))
335	      { B2 (0x60, 0); FE ($3, 8, 4); F ($5, 12, 4); }
336	    else
337	      /* This is really an add, but we negate the immediate.  */
338	      { B2 (0x70, 0); F ($5, 8, 4); F ($5, 12, 4); NIMM ($3, 6); } }
339
340	| CMP '#' EXPR ',' REG
341	  { if (rx_uintop ($3, 4))
342	      { B2 (0x61, 0); FE ($3, 8, 4); F ($5, 12, 4); }
343	    else if (rx_uintop ($3, 8))
344	      { B2 (0x75, 0x50); F ($5, 12, 4); UO1 ($3); }
345	    else
346	      { B2 (0x74, 0x00); F ($5, 12, 4); IMM ($3, 6); } }
347
348	| ADD '#' EXPR ',' REG
349	  { if (rx_uintop ($3, 4))
350	      { B2 (0x62, 0); FE ($3, 8, 4); F ($5, 12, 4); }
351	    else
352	      { B2 (0x70, 0); F ($5, 8, 4); F ($5, 12, 4); IMM ($3, 6); } }
353
354	| MUL '#' EXPR ',' REG
355	  { if (rx_uintop ($3, 4))
356	      { B2 (0x63, 0); FE ($3, 8, 4); F ($5, 12, 4); }
357	    else
358	      { B2 (0x74, 0x10); F ($5, 12, 4); IMM ($3, 6); } }
359
360	| AND_ '#' EXPR ',' REG
361	  { if (rx_uintop ($3, 4))
362	      { B2 (0x64, 0); FE ($3, 8, 4); F ($5, 12, 4); }
363	    else
364	      { B2 (0x74, 0x20); F ($5, 12, 4); IMM ($3, 6); } }
365
366	| OR '#' EXPR ',' REG
367	  { if (rx_uintop ($3, 4))
368	      { B2 (0x65, 0); FE ($3, 8, 4); F ($5, 12, 4); }
369	    else
370	      { B2 (0x74, 0x30); F ($5, 12, 4); IMM ($3, 6); } }
371
372	| MOV DOT_L '#' EXPR ',' REG
373	  { if (rx_uintop ($4, 4))
374	      { B2 (0x66, 0); FE ($4, 8, 4); F ($6, 12, 4); }
375	    else if (rx_uintop ($4, 8))
376	      { B2 (0x75, 0x40); F ($6, 12, 4); UO1 ($4); }
377	    else
378	      { B2 (0xfb, 0x02); F ($6, 8, 4); IMM ($4, 12); } }
379
380	| MOV '#' EXPR ',' REG
381	  { if (rx_uintop ($3, 4))
382	      { B2 (0x66, 0); FE ($3, 8, 4); F ($5, 12, 4); }
383	    else if (rx_uintop ($3, 8))
384	      { B2 (0x75, 0x40); F ($5, 12, 4); UO1 ($3); }
385	    else
386	      { B2 (0xfb, 0x02); F ($5, 8, 4); IMM ($3, 12); } }
387
388/* ---------------------------------------------------------------------- */
389
390	| RTSD '#' EXPR
391	  { B1 (0x67); rtsd_immediate ($3); }
392
393/* ---------------------------------------------------------------------- */
394
395	| SHLR { sub_op = 0; } op_shift
396	| SHAR { sub_op = 1; } op_shift
397	| SHLL { sub_op = 2; } op_shift
398
399/* ---------------------------------------------------------------------- */
400
401	| PUSHM REG '-' REG
402	  {
403	    if ($2 == $4)
404	      { B2 (0x7e, 0x80); F (LSIZE, 10, 2); F ($2, 12, 4); }
405	    else
406	     { B2 (0x6e, 0); F ($2, 8, 4); F ($4, 12, 4); }
407	    if ($2 == 0)
408	      rx_error (_("PUSHM cannot push R0"));
409	    if ($2 > $4)
410	      rx_error (_("PUSHM first reg must be <= second reg")); }
411
412/* ---------------------------------------------------------------------- */
413
414	| POPM REG '-' REG
415	  {
416	    if ($2 == $4)
417	      { B2 (0x7e, 0xb0); F ($2, 12, 4); }
418	    else
419	      { B2 (0x6f, 0); F ($2, 8, 4); F ($4, 12, 4); }
420	    if ($2 == 0)
421	      rx_error (_("POPM cannot pop R0"));
422	    if ($2 > $4)
423	      rx_error (_("POPM first reg must be <= second reg")); }
424
425/* ---------------------------------------------------------------------- */
426
427	| ADD '#' EXPR ',' REG ',' REG
428	  { B2 (0x70, 0x00); F ($5, 8, 4); F ($7, 12, 4); IMM ($3, 6); }
429
430/* ---------------------------------------------------------------------- */
431
432	| INT '#' EXPR
433	  { B2(0x75, 0x60), UO1 ($3); }
434
435/* ---------------------------------------------------------------------- */
436
437	| BSET '#' EXPR ',' REG
438	  { B2 (0x78, 0); FE ($3, 7, 5); F ($5, 12, 4); }
439	| BCLR '#' EXPR ',' REG
440	  { B2 (0x7a, 0); FE ($3, 7, 5); F ($5, 12, 4); }
441
442/* ---------------------------------------------------------------------- */
443
444	| BTST '#' EXPR ',' REG
445	  { B2 (0x7c, 0x00); FE ($3, 7, 5); F ($5, 12, 4); }
446
447/* ---------------------------------------------------------------------- */
448
449	| SAT REG
450	  { B2 (0x7e, 0x30); F ($2, 12, 4); }
451	| RORC REG
452	  { B2 (0x7e, 0x40); F ($2, 12, 4); }
453	| ROLC REG
454	  { B2 (0x7e, 0x50); F ($2, 12, 4); }
455
456/* ---------------------------------------------------------------------- */
457
458	| PUSH bwl REG
459	  { B2 (0x7e, 0x80); F ($2, 10, 2); F ($3, 12, 4); }
460
461/* ---------------------------------------------------------------------- */
462
463	| POP REG
464	  { B2 (0x7e, 0xb0); F ($2, 12, 4); }
465
466/* ---------------------------------------------------------------------- */
467
468	| PUSHC CREG
469	  { if ($2 < 16)
470	      { B2 (0x7e, 0xc0); F ($2, 12, 4); }
471	    else
472	      as_bad (_("PUSHC can only push the first 16 control registers")); }
473
474/* ---------------------------------------------------------------------- */
475
476	| POPC CREG
477	  { if ($2 < 16)
478	      { B2 (0x7e, 0xe0); F ($2, 12, 4); }
479	    else
480	      as_bad (_("POPC can only pop the first 16 control registers")); }
481
482/* ---------------------------------------------------------------------- */
483
484	| SETPSW flag
485	  { B2 (0x7f, 0xa0); F ($2, 12, 4); }
486	| CLRPSW flag
487	  { B2 (0x7f, 0xb0); F ($2, 12, 4); }
488
489/* ---------------------------------------------------------------------- */
490
491	| JMP REG
492	  { B2 (0x7f, 0x00); F ($2, 12, 4); }
493	| JSR REG
494	  { B2 (0x7f, 0x10); F ($2, 12, 4); }
495	| BRA opt_l REG
496	  { B2 (0x7f, 0x40); F ($3, 12, 4); }
497	| BSR opt_l REG
498	  { B2 (0x7f, 0x50); F ($3, 12, 4); }
499
500/* ---------------------------------------------------------------------- */
501
502	| SCMPU
503	  { B2 (0x7f, 0x83); rx_note_string_insn_use (); }
504	| SMOVU
505	  { B2 (0x7f, 0x87); rx_note_string_insn_use (); }
506	| SMOVB
507	  { B2 (0x7f, 0x8b); rx_note_string_insn_use (); }
508	| SMOVF
509	  { B2 (0x7f, 0x8f); rx_note_string_insn_use (); }
510
511/* ---------------------------------------------------------------------- */
512
513	| SUNTIL bwl
514	  { B2 (0x7f, 0x80); F ($2, 14, 2); rx_note_string_insn_use (); }
515	| SWHILE bwl
516	  { B2 (0x7f, 0x84); F ($2, 14, 2); rx_note_string_insn_use (); }
517	| SSTR bwl
518	  { B2 (0x7f, 0x88); F ($2, 14, 2); }
519
520/* ---------------------------------------------------------------------- */
521
522	| RMPA bwl
523	  { B2 (0x7f, 0x8c); F ($2, 14, 2); rx_note_string_insn_use (); }
524
525/* ---------------------------------------------------------------------- */
526
527	| RTFI
528	  { B2 (0x7f, 0x94); }
529	| RTE
530	  { B2 (0x7f, 0x95); }
531	| WAIT
532	  { B2 (0x7f, 0x96); }
533	| SATR
534	  { B2 (0x7f, 0x93); }
535
536/* ---------------------------------------------------------------------- */
537
538	| MVTIPL '#' EXPR
539	  { B3 (0x75, 0x70, 0x00); FE ($3, 20, 4); }
540
541/* ---------------------------------------------------------------------- */
542
543	/* rx_disp5op changes the value if it succeeds, so keep it last.  */
544	| MOV bwl REG ',' EXPR '[' REG ']'
545	  { if ($3 <= 7 && $7 <= 7 && rx_disp5op (&$5, $2))
546	      { B2 (0x80, 0); F ($2, 2, 2); F ($7, 9, 3); F ($3, 13, 3); rx_field5s ($5); }
547	    else
548	      { B2 (0xc3, 0x00); F ($2, 2, 2); F ($7, 8, 4); F ($3, 12, 4); DSP ($5, 4, $2); }}
549
550/* ---------------------------------------------------------------------- */
551
552	| MOV bwl EXPR '[' REG ']' ',' REG
553	  { if ($5 <= 7 && $8 <= 7 && rx_disp5op (&$3, $2))
554	      { B2 (0x88, 0); F ($2, 2, 2); F ($5, 9, 3); F ($8, 13, 3); rx_field5s ($3); }
555	    else
556	      { B2 (0xcc, 0x00); F ($2, 2, 2); F ($5, 8, 4); F ($8, 12, 4); DSP ($3, 6, $2); } }
557
558/* ---------------------------------------------------------------------- */
559
560	/* MOV a,b - if a is a reg and b is mem, src and dest are
561	   swapped.  */
562
563	/* We don't use "disp" here because it causes a shift/reduce
564	   conflict with the other displacement-less patterns.  */
565
566	| MOV bwl REG ',' '[' REG ']'
567	  { B2 (0xc3, 0x00); F ($2, 2, 2); F ($6, 8, 4); F ($3, 12, 4); }
568
569/* ---------------------------------------------------------------------- */
570
571	| MOV bwl '[' REG ']' ',' disp '[' REG ']'
572	  { B2 (0xc0, 0); F ($2, 2, 2); F ($4, 8, 4); F ($9, 12, 4); DSP ($7, 4, $2); }
573
574/* ---------------------------------------------------------------------- */
575
576	| MOV bwl EXPR '[' REG ']' ',' disp '[' REG ']'
577	  { B2 (0xc0, 0x00); F ($2, 2, 2); F ($5, 8, 4); F ($10, 12, 4); DSP ($3, 6, $2); DSP ($8, 4, $2); }
578
579/* ---------------------------------------------------------------------- */
580
581	| MOV bwl REG ',' REG
582	  { B2 (0xcf, 0x00); F ($2, 2, 2); F ($3, 8, 4); F ($5, 12, 4); }
583
584/* ---------------------------------------------------------------------- */
585
586	| MOV bwl '[' REG ']' ',' REG
587	  { B2 (0xcc, 0x00); F ($2, 2, 2); F ($4, 8, 4); F ($7, 12, 4); }
588
589/* ---------------------------------------------------------------------- */
590
591	| BSET '#' EXPR ',' disp '[' REG ']' DOT_B
592	  { B2 (0xf0, 0x00); F ($7, 8, 4); FE ($3, 13, 3); DSP ($5, 6, BSIZE); }
593	| BCLR '#' EXPR ',' disp '[' REG ']' DOT_B
594	  { B2 (0xf0, 0x08); F ($7, 8, 4); FE ($3, 13, 3); DSP ($5, 6, BSIZE); }
595	| BTST '#' EXPR ',' disp '[' REG ']' DOT_B
596	  { B2 (0xf4, 0x00); F ($7, 8, 4); FE ($3, 13, 3); DSP ($5, 6, BSIZE); }
597
598/* ---------------------------------------------------------------------- */
599
600	| PUSH bwl disp '[' REG ']'
601	  { B2 (0xf4, 0x08); F ($2, 14, 2); F ($5, 8, 4); DSP ($3, 6, $2); }
602
603/* ---------------------------------------------------------------------- */
604
605	| SBB   { sub_op = 0; } op_dp20_rm_l
606	| NEG   { sub_op = 1; sub_op2 = 1; } op_dp20_rr
607	| ADC   { sub_op = 2; } op_dp20_rim_l
608	| ABS   { sub_op = 3; sub_op2 = 2; } op_dp20_rr
609	| MAX   { sub_op = 4; } op_dp20_rim
610	| MIN   { sub_op = 5; } op_dp20_rim
611	| EMUL  { sub_op = 6; } op_dp20_i
612	| EMULU { sub_op = 7; } op_dp20_i
613	| DIV   { sub_op = 8; } op_dp20_rim
614	| DIVU  { sub_op = 9; } op_dp20_rim
615	| TST   { sub_op = 12; } op_dp20_rim
616	| XOR   { sub_op = 13; } op_dp20_rim
617	| NOT   { sub_op = 14; sub_op2 = 0; } op_dp20_rr
618	| STZ   { sub_op = 14; } op_dp20_i
619	| STNZ  { sub_op = 15; } op_dp20_i
620
621/* ---------------------------------------------------------------------- */
622
623	| EMUL  { sub_op = 6; } op_xchg
624	| EMULU { sub_op = 7; } op_xchg
625	| XCHG  { sub_op = 16; } op_xchg
626	| ITOF  { sub_op = 17; } op_xchg
627
628/* ---------------------------------------------------------------------- */
629
630	| BSET REG ',' REG
631	  { id24 (1, 0x63, 0x00); F ($4, 16, 4); F ($2, 20, 4); }
632	| BCLR REG ',' REG
633	  { id24 (1, 0x67, 0x00); F ($4, 16, 4); F ($2, 20, 4); }
634	| BTST REG ',' REG
635	  { id24 (1, 0x6b, 0x00); F ($4, 16, 4); F ($2, 20, 4); }
636	| BNOT REG ',' REG
637	  { id24 (1, 0x6f, 0x00); F ($4, 16, 4); F ($2, 20, 4); }
638
639	| BSET REG ',' disp '[' REG ']' opt_b
640	  { id24 (1, 0x60, 0x00); F ($6, 16, 4); F ($2, 20, 4); DSP ($4, 14, BSIZE); }
641	| BCLR REG ',' disp '[' REG ']' opt_b
642	  { id24 (1, 0x64, 0x00); F ($6, 16, 4); F ($2, 20, 4); DSP ($4, 14, BSIZE); }
643	| BTST REG ',' disp '[' REG ']' opt_b
644	  { id24 (1, 0x68, 0x00); F ($6, 16, 4); F ($2, 20, 4); DSP ($4, 14, BSIZE); }
645	| BNOT REG ',' disp '[' REG ']' opt_b
646	  { id24 (1, 0x6c, 0x00); F ($6, 16, 4); F ($2, 20, 4); DSP ($4, 14, BSIZE); }
647
648/* ---------------------------------------------------------------------- */
649
650	| FSUB  { sub_op = 0; } float2_op
651	| FCMP  { sub_op = 1; } float2_op
652	| FADD  { sub_op = 2; } float2_op
653	| FMUL  { sub_op = 3; } float2_op
654	| FDIV  { sub_op = 4; } float2_op
655	| FTOI  { sub_op = 5; } float2_op_ni
656	| ROUND { sub_op = 6; } float2_op_ni
657
658/* ---------------------------------------------------------------------- */
659
660	| SCCND DOT_L REG
661	  { id24 (1, 0xdb, 0x00); F ($1, 20, 4); F ($3, 16, 4); }
662	| SCCND bwl disp '[' REG ']'
663	  { id24 (1, 0xd0, 0x00); F ($1, 20, 4); F ($2, 12, 2); F ($5, 16, 4); DSP ($3, 14, $2); }
664
665/* ---------------------------------------------------------------------- */
666
667	| BMCND '#' EXPR ',' disp '[' REG ']' opt_b
668	  { id24 (1, 0xe0, 0x00); F ($1, 20, 4); FE ($3, 11, 3);
669	      F ($7, 16, 4); DSP ($5, 14, BSIZE); }
670
671/* ---------------------------------------------------------------------- */
672
673	| BNOT '#' EXPR ',' disp '[' REG ']' opt_b
674	  { id24 (1, 0xe0, 0x0f); FE ($3, 11, 3); F ($7, 16, 4);
675	      DSP ($5, 14, BSIZE); }
676
677/* ---------------------------------------------------------------------- */
678
679	| MULHI REG ',' REG
680	  { id24 (2, 0x00, 0x00); F ($2, 16, 4); F ($4, 20, 4); }
681	| MULLO REG ',' REG
682	  { id24 (2, 0x01, 0x00); F ($2, 16, 4); F ($4, 20, 4); }
683	| MACHI REG ',' REG
684	  { id24 (2, 0x04, 0x00); F ($2, 16, 4); F ($4, 20, 4); }
685	| MACLO REG ',' REG
686	  { id24 (2, 0x05, 0x00); F ($2, 16, 4); F ($4, 20, 4); }
687
688/* ---------------------------------------------------------------------- */
689
690	/* We don't have syntax for these yet.  */
691	| MVTACHI REG
692	  { id24 (2, 0x17, 0x00); F ($2, 20, 4); }
693	| MVTACLO REG
694	  { id24 (2, 0x17, 0x10); F ($2, 20, 4); }
695	| MVFACHI REG
696	  { id24 (2, 0x1f, 0x00); F ($2, 20, 4); }
697	| MVFACMI REG
698	  { id24 (2, 0x1f, 0x20); F ($2, 20, 4); }
699	| MVFACLO REG
700	  { id24 (2, 0x1f, 0x10); F ($2, 20, 4); }
701
702	| RACW '#' EXPR
703	  { id24 (2, 0x18, 0x00);
704	    if (rx_uintop ($3, 4) && $3.X_add_number == 1)
705	      ;
706	    else if (rx_uintop ($3, 4) && $3.X_add_number == 2)
707	      F (1, 19, 1);
708	    else
709	      as_bad (_("RACW expects #1 or #2"));}
710
711/* ---------------------------------------------------------------------- */
712
713	| MOV bwl REG ',' '[' REG '+' ']'
714	  { id24 (2, 0x20, 0); F ($2, 14, 2); F ($6, 16, 4); F ($3, 20, 4); }
715	| MOV bwl REG ',' '[' '-' REG ']'
716	  { id24 (2, 0x24, 0); F ($2, 14, 2); F ($7, 16, 4); F ($3, 20, 4); }
717
718/* ---------------------------------------------------------------------- */
719
720	| MOV bwl '[' REG '+' ']' ',' REG
721	  { id24 (2, 0x28, 0); F ($2, 14, 2); F ($4, 16, 4); F ($8, 20, 4); }
722	| MOV bwl '[' '-' REG ']' ',' REG
723	  { id24 (2, 0x2c, 0); F ($2, 14, 2); F ($5, 16, 4); F ($8, 20, 4); }
724
725/* ---------------------------------------------------------------------- */
726
727	| MOVU bw '[' REG '+' ']' ','  REG
728	  { id24 (2, 0x38, 0); F ($2, 15, 1); F ($4, 16, 4); F ($8, 20, 4); }
729	| MOVU bw '[' '-' REG ']' ',' REG
730	  { id24 (2, 0x3c, 0); F ($2, 15, 1); F ($5, 16, 4); F ($8, 20, 4); }
731
732/* ---------------------------------------------------------------------- */
733
734	| ROTL { sub_op = 6; } op_shift_rot
735	| ROTR { sub_op = 4; } op_shift_rot
736	| REVW { sub_op = 5; } op_shift_rot
737	| REVL { sub_op = 7; } op_shift_rot
738
739/* ---------------------------------------------------------------------- */
740
741	| MVTC REG ',' CREG
742	  { id24 (2, 0x68, 0x00); F ($4 % 16, 20, 4); F ($4 / 16, 15, 1);
743	    F ($2, 16, 4); }
744
745/* ---------------------------------------------------------------------- */
746
747	| MVFC CREG ',' REG
748	  { id24 (2, 0x6a, 0); F ($2, 15, 5); F ($4, 20, 4); }
749
750/* ---------------------------------------------------------------------- */
751
752	| ROTL '#' EXPR ',' REG
753	  { id24 (2, 0x6e, 0); FE ($3, 15, 5); F ($5, 20, 4); }
754	| ROTR '#' EXPR ',' REG
755	  { id24 (2, 0x6c, 0); FE ($3, 15, 5); F ($5, 20, 4); }
756
757/* ---------------------------------------------------------------------- */
758
759	| MVTC '#' EXPR ',' CREG
760	  { id24 (2, 0x73, 0x00); F ($5, 19, 5); IMM ($3, 12); }
761
762/* ---------------------------------------------------------------------- */
763
764	| BMCND '#' EXPR ',' REG
765	  { id24 (2, 0xe0, 0x00); F ($1, 16, 4); FE ($3, 11, 5);
766	      F ($5, 20, 4); }
767
768/* ---------------------------------------------------------------------- */
769
770	| BNOT '#' EXPR ',' REG
771	  { id24 (2, 0xe0, 0xf0); FE ($3, 11, 5); F ($5, 20, 4); }
772
773/* ---------------------------------------------------------------------- */
774
775	| MOV bwl REG ',' '[' REG ',' REG ']'
776	  { id24 (3, 0x00, 0); F ($2, 10, 2); F ($6, 12, 4); F ($8, 16, 4); F ($3, 20, 4); }
777
778	| MOV bwl '[' REG ',' REG ']' ',' REG
779	  { id24 (3, 0x40, 0); F ($2, 10, 2); F ($4, 12, 4); F ($6, 16, 4); F ($9, 20, 4); }
780
781	| MOVU bw '[' REG ',' REG ']' ',' REG
782	  { id24 (3, 0xc0, 0); F ($2, 10, 2); F ($4, 12, 4); F ($6, 16, 4); F ($9, 20, 4); }
783
784/* ---------------------------------------------------------------------- */
785
786	| SUB { sub_op = 0; } op_subadd
787	| ADD { sub_op = 2; } op_subadd
788	| MUL { sub_op = 3; } op_subadd
789	| AND_ { sub_op = 4; } op_subadd
790	| OR  { sub_op = 5; } op_subadd
791
792/* ---------------------------------------------------------------------- */
793/* There is no SBB #imm so we fake it with ADC.  */
794
795	| SBB '#' EXPR ',' REG
796	  { id24 (2, 0x70, 0x20); F ($5, 20, 4); NBIMM ($3, 12); }
797
798/* ---------------------------------------------------------------------- */
799
800	;
801
802/* ====================================================================== */
803
804op_subadd
805	: REG ',' REG
806	  { B2 (0x43 + (sub_op<<2), 0); F ($1, 8, 4); F ($3, 12, 4); }
807	| disp '[' REG ']' DOT_UB ',' REG
808	  { B2 (0x40 + (sub_op<<2), 0); F ($3, 8, 4); F ($7, 12, 4); DSP ($1, 6, BSIZE); }
809	| disp '[' REG ']' memex ',' REG
810	  { B3 (MEMEX, sub_op<<2, 0); F ($5, 8, 2); F ($3, 16, 4); F ($7, 20, 4); DSP ($1, 14, sizemap[$5]); }
811	| REG ',' REG ',' REG
812	  { id24 (4, sub_op<<4, 0), F ($5, 12, 4), F ($1, 16, 4), F ($3, 20, 4); }
813	;
814
815/* sbb, neg, adc, abs, max, min, div, divu, tst, not, xor, stz, stnz, emul, emulu */
816
817op_dp20_rm_l
818	: REG ',' REG
819	  { id24 (1, 0x03 + (sub_op<<2), 0x00); F ($1, 16, 4); F ($3, 20, 4); }
820	| disp '[' REG ']' opt_l ',' REG
821	  { B4 (MEMEX, 0xa0, 0x00 + sub_op, 0x00);
822	  F ($3, 24, 4); F ($7, 28, 4); DSP ($1, 14, LSIZE); }
823	;
824
825/* neg, adc, abs, max, min, div, divu, tst, not, xor, stz, stnz, emul, emulu */
826
827op_dp20_rm
828	: REG ',' REG
829	  { id24 (1, 0x03 + (sub_op<<2), 0x00); F ($1, 16, 4); F ($3, 20, 4); }
830	| disp '[' REG ']' DOT_UB ',' REG
831	  { id24 (1, 0x00 + (sub_op<<2), 0x00); F ($3, 16, 4); F ($7, 20, 4); DSP ($1, 14, BSIZE); }
832	| disp '[' REG ']' memex ',' REG
833	  { B4 (MEMEX, 0x20 + ($5 << 6), 0x00 + sub_op, 0x00);
834	  F ($3, 24, 4); F ($7, 28, 4); DSP ($1, 14, sizemap[$5]); }
835	;
836
837op_dp20_i
838	: '#' EXPR ',' REG
839	  { id24 (2, 0x70, sub_op<<4); F ($4, 20, 4); IMM ($2, 12); }
840	;
841
842op_dp20_rim
843	: op_dp20_rm
844	| op_dp20_i
845	;
846
847op_dp20_rim_l
848	: op_dp20_rm_l
849	| op_dp20_i
850	;
851
852op_dp20_rr
853	: REG ',' REG
854	  { id24 (1, 0x03 + (sub_op<<2), 0x00); F ($1, 16, 4); F ($3, 20, 4); }
855	| REG
856	  { B2 (0x7e, sub_op2 << 4); F ($1, 12, 4); }
857	;
858
859/* xchg, itof, emul, emulu */
860op_xchg
861	: REG ',' REG
862	  { id24 (1, 0x03 + (sub_op<<2), 0); F ($1, 16, 4); F ($3, 20, 4); }
863	| disp '[' REG ']' DOT_UB ',' REG
864	  { id24 (1, 0x00 + (sub_op<<2), 0); F ($3, 16, 4); F ($7, 20, 4); DSP ($1, 14, BSIZE); }
865	| disp '[' REG ']' memex ',' REG
866	  { B4 (MEMEX, 0x20, 0x00 + sub_op, 0); F ($5, 8, 2); F ($3, 24, 4); F ($7, 28, 4);
867	    DSP ($1, 14, sizemap[$5]); }
868	;
869
870/* 000:SHLR, 001:SHAR, 010:SHLL, 011:-, 100:ROTR, 101:REVW, 110:ROTL, 111:REVL */
871op_shift_rot
872	: REG ',' REG
873	  { id24 (2, 0x60 + sub_op, 0); F ($1, 16, 4); F ($3, 20, 4); }
874	;
875op_shift
876	: '#' EXPR ',' REG
877	  { B2 (0x68 + (sub_op<<1), 0); FE ($2, 7, 5); F ($4, 12, 4); }
878	| '#' EXPR ',' REG ',' REG
879	  { id24 (2, 0x80 + (sub_op << 5), 0); FE ($2, 11, 5); F ($4, 16, 4); F ($6, 20, 4); }
880	| op_shift_rot
881	;
882
883
884float2_op
885	: { rx_check_float_support (); }
886	  '#' EXPR ',' REG
887	  { id24 (2, 0x72, sub_op << 4); F ($5, 20, 4); O4 ($3); }
888	| float2_op_ni
889	;
890
891float2_op_ni
892	: { rx_check_float_support (); }
893	  REG ',' REG
894	  { id24 (1, 0x83 + (sub_op << 2), 0); F ($2, 16, 4); F ($4, 20, 4); }
895	| { rx_check_float_support (); }
896	  disp '[' REG ']' opt_l ',' REG
897	  { id24 (1, 0x80 + (sub_op << 2), 0); F ($4, 16, 4); F ($8, 20, 4); DSP ($2, 14, LSIZE); }
898	;
899
900/* ====================================================================== */
901
902disp	:      { $$ = zero_expr (); }
903	| EXPR { $$ = $1; }
904	;
905
906flag	: { need_flag = 1; } FLAG { need_flag = 0; $$ = $2; }
907	;
908
909/* DOT_UB is not listed here, it's handled with a separate pattern.  */
910/* Use sizemap[$n] to get LSIZE etc.  */
911memex	: DOT_B  { $$ = 0; }
912	| DOT_W  { $$ = 1; }
913	|        { $$ = 2; }
914	| DOT_L  { $$ = 2; }
915	| DOT_UW { $$ = 3; }
916	;
917
918bwl	:       { $$ = LSIZE; }
919	| DOT_B { $$ = BSIZE; }
920	| DOT_W { $$ = WSIZE; }
921	| DOT_L { $$ = LSIZE; }
922	;
923
924bw	:       { $$ = 1; }
925	| DOT_B { $$ = 0; }
926	| DOT_W { $$ = 1; }
927	;
928
929opt_l	: 	{}
930	| DOT_L {}
931	;
932
933opt_b	: 	{}
934	| DOT_B {}
935	;
936
937%%
938/* ====================================================================== */
939
940static struct
941{
942  const char * string;
943  int          token;
944  int          val;
945}
946token_table[] =
947{
948  { "r0", REG, 0 },
949  { "r1", REG, 1 },
950  { "r2", REG, 2 },
951  { "r3", REG, 3 },
952  { "r4", REG, 4 },
953  { "r5", REG, 5 },
954  { "r6", REG, 6 },
955  { "r7", REG, 7 },
956  { "r8", REG, 8 },
957  { "r9", REG, 9 },
958  { "r10", REG, 10 },
959  { "r11", REG, 11 },
960  { "r12", REG, 12 },
961  { "r13", REG, 13 },
962  { "r14", REG, 14 },
963  { "r15", REG, 15 },
964
965  { "psw", CREG, 0 },
966  { "pc", CREG, 1 },
967  { "usp", CREG, 2 },
968  { "fpsw", CREG, 3 },
969  /* reserved */
970  /* reserved */
971  /* reserved */
972  { "wr", CREG, 7 },
973
974  { "bpsw", CREG, 8 },
975  { "bpc", CREG, 9 },
976  { "isp", CREG, 10 },
977  { "fintv", CREG, 11 },
978  { "intb", CREG, 12 },
979
980  { "pbp", CREG, 16 },
981  { "pben", CREG, 17 },
982
983  { "bbpsw", CREG, 24 },
984  { "bbpc", CREG, 25 },
985
986  { ".s", DOT_S, 0 },
987  { ".b", DOT_B, 0 },
988  { ".w", DOT_W, 0 },
989  { ".l", DOT_L, 0 },
990  { ".a", DOT_A , 0},
991  { ".ub", DOT_UB, 0 },
992  { ".uw", DOT_UW , 0},
993
994  { "c", FLAG, 0 },
995  { "z", FLAG, 1 },
996  { "s", FLAG, 2 },
997  { "o", FLAG, 3 },
998  { "i", FLAG, 8 },
999  { "u", FLAG, 9 },
1000
1001#define OPC(x) { #x, x, IS_OPCODE }
1002  OPC(ABS),
1003  OPC(ADC),
1004  OPC(ADD),
1005  { "and", AND_, IS_OPCODE },
1006  OPC(BCLR),
1007  OPC(BCND),
1008  OPC(BMCND),
1009  OPC(BNOT),
1010  OPC(BRA),
1011  OPC(BRK),
1012  OPC(BSET),
1013  OPC(BSR),
1014  OPC(BTST),
1015  OPC(CLRPSW),
1016  OPC(CMP),
1017  OPC(DBT),
1018  OPC(DIV),
1019  OPC(DIVU),
1020  OPC(EDIV),
1021  OPC(EDIVU),
1022  OPC(EMUL),
1023  OPC(EMULU),
1024  OPC(FADD),
1025  OPC(FCMP),
1026  OPC(FDIV),
1027  OPC(FMUL),
1028  OPC(FREIT),
1029  OPC(FSUB),
1030  OPC(FTOI),
1031  OPC(INT),
1032  OPC(ITOF),
1033  OPC(JMP),
1034  OPC(JSR),
1035  OPC(MVFACHI),
1036  OPC(MVFACMI),
1037  OPC(MVFACLO),
1038  OPC(MVFC),
1039  OPC(MVTACHI),
1040  OPC(MVTACLO),
1041  OPC(MVTC),
1042  OPC(MVTIPL),
1043  OPC(MACHI),
1044  OPC(MACLO),
1045  OPC(MAX),
1046  OPC(MIN),
1047  OPC(MOV),
1048  OPC(MOVU),
1049  OPC(MUL),
1050  OPC(MULHI),
1051  OPC(MULLO),
1052  OPC(MULU),
1053  OPC(NEG),
1054  OPC(NOP),
1055  OPC(NOT),
1056  OPC(OR),
1057  OPC(POP),
1058  OPC(POPC),
1059  OPC(POPM),
1060  OPC(PUSH),
1061  OPC(PUSHA),
1062  OPC(PUSHC),
1063  OPC(PUSHM),
1064  OPC(RACW),
1065  OPC(REIT),
1066  OPC(REVL),
1067  OPC(REVW),
1068  OPC(RMPA),
1069  OPC(ROLC),
1070  OPC(RORC),
1071  OPC(ROTL),
1072  OPC(ROTR),
1073  OPC(ROUND),
1074  OPC(RTE),
1075  OPC(RTFI),
1076  OPC(RTS),
1077  OPC(RTSD),
1078  OPC(SAT),
1079  OPC(SATR),
1080  OPC(SBB),
1081  OPC(SCCND),
1082  OPC(SCMPU),
1083  OPC(SETPSW),
1084  OPC(SHAR),
1085  OPC(SHLL),
1086  OPC(SHLR),
1087  OPC(SMOVB),
1088  OPC(SMOVF),
1089  OPC(SMOVU),
1090  OPC(SSTR),
1091  OPC(STNZ),
1092  OPC(STOP),
1093  OPC(STZ),
1094  OPC(SUB),
1095  OPC(SUNTIL),
1096  OPC(SWHILE),
1097  OPC(TST),
1098  OPC(WAIT),
1099  OPC(XCHG),
1100  OPC(XOR),
1101};
1102
1103#define NUM_TOKENS (sizeof (token_table) / sizeof (token_table[0]))
1104
1105static struct
1106{
1107  char * string;
1108  int    token;
1109}
1110condition_opcode_table[] =
1111{
1112  { "b", BCND },
1113  { "bm", BMCND },
1114  { "sc", SCCND },
1115};
1116
1117#define NUM_CONDITION_OPCODES (sizeof (condition_opcode_table) / sizeof (condition_opcode_table[0]))
1118
1119static struct
1120{
1121  char * string;
1122  int    val;
1123}
1124condition_table[] =
1125{
1126  { "z", 0 },
1127  { "eq", 0 },
1128  { "geu",  2 },
1129  { "c",  2 },
1130  { "gtu", 4 },
1131  { "pz", 6 },
1132  { "ge", 8 },
1133  { "gt", 10 },
1134  { "o",  12},
1135  /* always = 14 */
1136  { "nz", 1 },
1137  { "ne", 1 },
1138  { "ltu", 3 },
1139  { "nc", 3 },
1140  { "leu", 5 },
1141  { "n", 7 },
1142  { "lt", 9 },
1143  { "le", 11 },
1144  { "no", 13 }
1145  /* never = 15 */
1146};
1147
1148#define NUM_CONDITIONS (sizeof (condition_table) / sizeof (condition_table[0]))
1149
1150void
1151rx_lex_init (char * beginning, char * ending)
1152{
1153  rx_init_start = beginning;
1154  rx_lex_start = beginning;
1155  rx_lex_end = ending;
1156  rx_in_brackets = 0;
1157  rx_last_token = 0;
1158
1159  setbuf (stdout, 0);
1160}
1161
1162static int
1163check_condition (char * base)
1164{
1165  char * cp;
1166  unsigned int i;
1167
1168  if ((unsigned) (rx_lex_end - rx_lex_start) < strlen (base) + 1)
1169    return 0;
1170  if (memcmp (rx_lex_start, base, strlen (base)))
1171    return 0;
1172  cp = rx_lex_start + strlen (base);
1173  for (i = 0; i < NUM_CONDITIONS; i ++)
1174    {
1175      if (strcasecmp (cp, condition_table[i].string) == 0)
1176	{
1177	  rx_lval.regno = condition_table[i].val;
1178	  return 1;
1179	}
1180    }
1181  return 0;
1182}
1183
1184static int
1185rx_lex (void)
1186{
1187  unsigned int ci;
1188  char * save_input_pointer;
1189
1190  while (ISSPACE (*rx_lex_start)
1191	 && rx_lex_start != rx_lex_end)
1192    rx_lex_start ++;
1193
1194  rx_last_exp_start = rx_lex_start;
1195
1196  if (rx_lex_start == rx_lex_end)
1197    return 0;
1198
1199  if (ISALPHA (*rx_lex_start)
1200      || (rx_pid_register != -1 && memcmp (rx_lex_start, "%pidreg", 7) == 0)
1201      || (rx_gp_register != -1 && memcmp (rx_lex_start, "%gpreg", 6) == 0)
1202      || (*rx_lex_start == '.' && ISALPHA (rx_lex_start[1])))
1203    {
1204      unsigned int i;
1205      char * e;
1206      char save;
1207
1208      for (e = rx_lex_start + 1;
1209	   e < rx_lex_end && ISALNUM (*e);
1210	   e ++)
1211	;
1212      save = *e;
1213      *e = 0;
1214
1215      if (strcmp (rx_lex_start, "%pidreg") == 0)
1216	{
1217	  {
1218	    rx_lval.regno = rx_pid_register;
1219	    *e = save;
1220	    rx_lex_start = e;
1221	    rx_last_token = REG;
1222	    return REG;
1223	  }
1224	}
1225
1226      if (strcmp (rx_lex_start, "%gpreg") == 0)
1227	{
1228	  {
1229	    rx_lval.regno = rx_gp_register;
1230	    *e = save;
1231	    rx_lex_start = e;
1232	    rx_last_token = REG;
1233	    return REG;
1234	  }
1235	}
1236
1237      if (rx_last_token == 0)
1238	for (ci = 0; ci < NUM_CONDITION_OPCODES; ci ++)
1239	  if (check_condition (condition_opcode_table[ci].string))
1240	    {
1241	      *e = save;
1242	      rx_lex_start = e;
1243	      rx_last_token = condition_opcode_table[ci].token;
1244	      return condition_opcode_table[ci].token;
1245	    }
1246
1247      for (i = 0; i < NUM_TOKENS; i++)
1248	if (strcasecmp (rx_lex_start, token_table[i].string) == 0
1249	    && !(token_table[i].val == IS_OPCODE && rx_last_token != 0)
1250	    && !(token_table[i].token == FLAG && !need_flag))
1251	  {
1252	    rx_lval.regno = token_table[i].val;
1253	    *e = save;
1254	    rx_lex_start = e;
1255	    rx_last_token = token_table[i].token;
1256	    return token_table[i].token;
1257	  }
1258      *e = save;
1259    }
1260
1261  if (rx_last_token == 0)
1262    {
1263      rx_last_token = UNKNOWN_OPCODE;
1264      return UNKNOWN_OPCODE;
1265    }
1266
1267  if (rx_last_token == UNKNOWN_OPCODE)
1268    return 0;
1269
1270  if (*rx_lex_start == '[')
1271    rx_in_brackets = 1;
1272  if (*rx_lex_start == ']')
1273    rx_in_brackets = 0;
1274
1275  if (rx_in_brackets
1276      || rx_last_token == REG
1277      || strchr ("[],#", *rx_lex_start))
1278    {
1279      rx_last_token = *rx_lex_start;
1280      return *rx_lex_start ++;
1281    }
1282
1283  save_input_pointer = input_line_pointer;
1284  input_line_pointer = rx_lex_start;
1285  rx_lval.exp.X_md = 0;
1286  expression (&rx_lval.exp);
1287
1288  /* We parse but ignore any :<size> modifier on expressions.  */
1289  if (*input_line_pointer == ':')
1290    {
1291      char *cp;
1292
1293      for (cp  = input_line_pointer + 1; *cp && cp < rx_lex_end; cp++)
1294	if (!ISDIGIT (*cp))
1295	  break;
1296      if (cp > input_line_pointer+1)
1297	input_line_pointer = cp;
1298    }
1299
1300  rx_lex_start = input_line_pointer;
1301  input_line_pointer = save_input_pointer;
1302  rx_last_token = EXPR;
1303  return EXPR;
1304}
1305
1306int
1307rx_error (const char * str)
1308{
1309  int len;
1310
1311  len = rx_last_exp_start - rx_init_start;
1312
1313  as_bad ("%s", rx_init_start);
1314  as_bad ("%*s^ %s", len, "", str);
1315  return 0;
1316}
1317
1318static int
1319rx_intop (expressionS exp, int nbits, int opbits)
1320{
1321  long v;
1322  long mask, msb;
1323
1324  if (exp.X_op == O_big && nbits == 32)
1325      return 1;
1326  if (exp.X_op != O_constant)
1327    return 0;
1328  v = exp.X_add_number;
1329
1330  msb = 1UL << (opbits - 1);
1331  mask = (1UL << opbits) - 1;
1332
1333  if ((v & msb) && ! (v & ~mask))
1334    v -= 1UL << opbits;
1335
1336  switch (nbits)
1337    {
1338    case 4:
1339      return -0x8 <= v && v <= 0x7;
1340    case 5:
1341      return -0x10 <= v && v <= 0x17;
1342    case 8:
1343      return -0x80 <= v && v <= 0x7f;
1344    case 16:
1345      return -0x8000 <= v && v <= 0x7fff;
1346    case 24:
1347      return -0x800000 <= v && v <= 0x7fffff;
1348    case 32:
1349      return 1;
1350    default:
1351      printf ("rx_intop passed %d\n", nbits);
1352      abort ();
1353    }
1354  return 1;
1355}
1356
1357static int
1358rx_uintop (expressionS exp, int nbits)
1359{
1360  unsigned long v;
1361
1362  if (exp.X_op != O_constant)
1363    return 0;
1364  v = exp.X_add_number;
1365
1366  switch (nbits)
1367    {
1368    case 4:
1369      return v <= 0xf;
1370    case 8:
1371      return v <= 0xff;
1372    case 16:
1373      return v <= 0xffff;
1374    case 24:
1375      return v <= 0xffffff;
1376    default:
1377      printf ("rx_uintop passed %d\n", nbits);
1378      abort ();
1379    }
1380  return 1;
1381}
1382
1383static int
1384rx_disp3op (expressionS exp)
1385{
1386  unsigned long v;
1387
1388  if (exp.X_op != O_constant)
1389    return 0;
1390  v = exp.X_add_number;
1391  if (v < 3 || v > 10)
1392    return 0;
1393  return 1;
1394}
1395
1396static int
1397rx_disp5op (expressionS * exp, int msize)
1398{
1399  long v;
1400
1401  if (exp->X_op != O_constant)
1402    return 0;
1403  v = exp->X_add_number;
1404
1405  switch (msize)
1406    {
1407    case BSIZE:
1408      if (0 <= v && v <= 31)
1409	return 1;
1410      break;
1411    case WSIZE:
1412      if (v & 1)
1413	return 0;
1414      if (0 <= v && v <= 63)
1415	{
1416	  exp->X_add_number >>= 1;
1417	  return 1;
1418	}
1419      break;
1420    case LSIZE:
1421      if (v & 3)
1422	return 0;
1423      if (0 <= v && v <= 127)
1424	{
1425	  exp->X_add_number >>= 2;
1426	  return 1;
1427	}
1428      break;
1429    }
1430  return 0;
1431}
1432
1433/* Just like the above, but allows a zero displacement.  */
1434
1435static int
1436rx_disp5op0 (expressionS * exp, int msize)
1437{
1438  if (exp->X_op != O_constant)
1439    return 0;
1440  if (exp->X_add_number == 0)
1441    return 1;
1442  return rx_disp5op (exp, msize);
1443}
1444
1445static int
1446exp_val (expressionS exp)
1447{
1448  if (exp.X_op != O_constant)
1449  {
1450    rx_error (_("constant expected"));
1451    return 0;
1452  }
1453  return exp.X_add_number;
1454}
1455
1456static expressionS
1457zero_expr (void)
1458{
1459  /* Static, so program load sets it to all zeros, which is what we want.  */
1460  static expressionS zero;
1461  zero.X_op = O_constant;
1462  return zero;
1463}
1464
1465static int
1466immediate (expressionS exp, int type, int pos, int bits)
1467{
1468  /* We will emit constants ourself here, so negate them.  */
1469  if (type == RXREL_NEGATIVE && exp.X_op == O_constant)
1470    exp.X_add_number = - exp.X_add_number;
1471  if (type == RXREL_NEGATIVE_BORROW)
1472    {
1473      if (exp.X_op == O_constant)
1474	exp.X_add_number = - exp.X_add_number - 1;
1475      else
1476	rx_error (_("sbb cannot use symbolic immediates"));
1477    }
1478
1479  if (rx_intop (exp, 8, bits))
1480    {
1481      rx_op (exp, 1, type);
1482      return 1;
1483    }
1484  else if (rx_intop (exp, 16, bits))
1485    {
1486      rx_op (exp, 2, type);
1487      return 2;
1488    }
1489  else if (rx_uintop (exp, 16) && bits == 16)
1490    {
1491      rx_op (exp, 2, type);
1492      return 2;
1493    }
1494  else if (rx_intop (exp, 24, bits))
1495    {
1496      rx_op (exp, 3, type);
1497      return 3;
1498    }
1499  else if (rx_intop (exp, 32, bits))
1500    {
1501      rx_op (exp, 4, type);
1502      return 0;
1503    }
1504  else if (type == RXREL_SIGNED)
1505    {
1506      /* This is a symbolic immediate, we will relax it later.  */
1507      rx_relax (RX_RELAX_IMM, pos);
1508      rx_op (exp, linkrelax ? 4 : 1, type);
1509      return 1;
1510    }
1511  else
1512    {
1513      /* Let the linker deal with it.  */
1514      rx_op (exp, 4, type);
1515      return 0;
1516    }
1517}
1518
1519static int
1520displacement (expressionS exp, int msize)
1521{
1522  int val;
1523  int vshift = 0;
1524
1525  if (exp.X_op == O_symbol
1526      && exp.X_md)
1527    {
1528      switch (exp.X_md)
1529	{
1530	case BFD_RELOC_GPREL16:
1531	  switch (msize)
1532	    {
1533	    case BSIZE:
1534	      exp.X_md = BFD_RELOC_RX_GPRELB;
1535	      break;
1536	    case WSIZE:
1537	      exp.X_md = BFD_RELOC_RX_GPRELW;
1538	      break;
1539	    case LSIZE:
1540	      exp.X_md = BFD_RELOC_RX_GPRELL;
1541	      break;
1542	    }
1543	  O2 (exp);
1544	  return 2;
1545	}
1546    }
1547
1548  if (exp.X_op == O_subtract)
1549    {
1550      exp.X_md = BFD_RELOC_RX_DIFF;
1551      O2 (exp);
1552      return 2;
1553    }
1554
1555  if (exp.X_op != O_constant)
1556    {
1557      rx_error (_("displacements must be constants"));
1558      return -1;
1559    }
1560  val = exp.X_add_number;
1561
1562  if (val == 0)
1563    return 0;
1564
1565  switch (msize)
1566    {
1567    case BSIZE:
1568      break;
1569    case WSIZE:
1570      if (val & 1)
1571	rx_error (_("word displacement not word-aligned"));
1572      vshift = 1;
1573      break;
1574    case LSIZE:
1575      if (val & 3)
1576	rx_error (_("long displacement not long-aligned"));
1577      vshift = 2;
1578      break;
1579    default:
1580      as_bad (_("displacement with unknown size (internal bug?)\n"));
1581      break;
1582    }
1583
1584  val >>= vshift;
1585  exp.X_add_number = val;
1586
1587  if (0 <= val && val <= 255 )
1588    {
1589      O1 (exp);
1590      return 1;
1591    }
1592
1593  if (0 <= val && val <= 65535)
1594    {
1595      O2 (exp);
1596      return 2;
1597    }
1598  if (val < 0)
1599    rx_error (_("negative displacements not allowed"));
1600  else
1601    rx_error (_("displacement too large"));
1602  return -1;
1603}
1604
1605static void
1606rtsd_immediate (expressionS exp)
1607{
1608  int val;
1609
1610  if (exp.X_op != O_constant)
1611    {
1612      rx_error (_("rtsd size must be constant"));
1613      return;
1614    }
1615  val = exp.X_add_number;
1616  if (val & 3)
1617    rx_error (_("rtsd size must be multiple of 4"));
1618
1619  if (val < 0 || val > 1020)
1620    rx_error (_("rtsd size must be 0..1020"));
1621
1622  val >>= 2;
1623  exp.X_add_number = val;
1624  O1 (exp);
1625}
1626
1627static void
1628rx_range (expressionS exp, int minv, int maxv)
1629{
1630  int val;
1631
1632  if (exp.X_op != O_constant)
1633    return;
1634
1635  val = exp.X_add_number;
1636  if (val < minv || val > maxv)
1637    as_warn (_("Value %d out of range %d..%d"), val, minv, maxv);
1638}
1639
1640static void
1641rx_check_float_support (void)
1642{
1643  if (rx_cpu == RX100 || rx_cpu == RX200)
1644    rx_error (_("target CPU type does not support floating point instructions"));
1645}
1646