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