1440a403fSchristos /* rx-parse.y  Renesas RX parser
2*b88e3e88Schristos    Copyright (C) 2008-2020 Free Software Foundation, Inc.
3440a403fSchristos 
4440a403fSchristos    This file is part of GAS, the GNU Assembler.
5440a403fSchristos 
6440a403fSchristos    GAS is free software; you can redistribute it and/or modify
7440a403fSchristos    it under the terms of the GNU General Public License as published by
8440a403fSchristos    the Free Software Foundation; either version 3, or (at your option)
9440a403fSchristos    any later version.
10440a403fSchristos 
11440a403fSchristos    GAS is distributed in the hope that it will be useful,
12440a403fSchristos    but WITHOUT ANY WARRANTY; without even the implied warranty of
13440a403fSchristos    MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE.  See the
14440a403fSchristos    GNU General Public License for more details.
15440a403fSchristos 
16440a403fSchristos    You should have received a copy of the GNU General Public License
17440a403fSchristos    along with GAS; see the file COPYING.  If not, write to the Free
18440a403fSchristos    Software Foundation, 51 Franklin Street - Fifth Floor, Boston, MA
19440a403fSchristos    02110-1301, USA.  */
20440a403fSchristos %{
21440a403fSchristos 
22440a403fSchristos #include "as.h"
23440a403fSchristos #include "safe-ctype.h"
24440a403fSchristos #include "rx-defs.h"
25440a403fSchristos 
26440a403fSchristos static int rx_lex (void);
27440a403fSchristos 
28440a403fSchristos #define COND_EQ	0
29440a403fSchristos #define COND_NE	1
30440a403fSchristos 
31440a403fSchristos #define MEMEX 0x06
32440a403fSchristos 
33440a403fSchristos #define BSIZE 0
34440a403fSchristos #define WSIZE 1
35440a403fSchristos #define LSIZE 2
36*b88e3e88Schristos #define DSIZE 3
37440a403fSchristos 
38440a403fSchristos /*                       .sb    .sw    .l     .uw   */
39440a403fSchristos static int sizemap[] = { BSIZE, WSIZE, LSIZE, WSIZE };
40440a403fSchristos 
41440a403fSchristos /* Ok, here are the rules for using these macros...
42440a403fSchristos 
43440a403fSchristos    B*() is used to specify the base opcode bytes.  Fields to be filled
44440a403fSchristos         in later, leave zero.  Call this first.
45440a403fSchristos 
46440a403fSchristos    F() and FE() are used to fill in fields within the base opcode bytes.  You MUST
47440a403fSchristos         call B*() before any F() or FE().
48440a403fSchristos 
49440a403fSchristos    [UN]*O*(), PC*() appends operands to the end of the opcode.  You
50440a403fSchristos         must call P() and B*() before any of these, so that the fixups
51440a403fSchristos         have the right byte location.
52440a403fSchristos         O = signed, UO = unsigned, NO = negated, PC = pcrel
53440a403fSchristos 
54440a403fSchristos    IMM() adds an immediate and fills in the field for it.
55440a403fSchristos    NIMM() same, but negates the immediate.
56440a403fSchristos    NBIMM() same, but negates the immediate, for sbb.
57440a403fSchristos    DSP() adds a displacement, and fills in the field for it.
58440a403fSchristos 
59440a403fSchristos    Note that order is significant for the O, IMM, and DSP macros, as
60440a403fSchristos    they append their data to the operand buffer in the order that you
61440a403fSchristos    call them.
62440a403fSchristos 
63440a403fSchristos    Use "disp" for displacements whenever possible; this handles the
64440a403fSchristos    "0" case properly.  */
65440a403fSchristos 
66440a403fSchristos #define B1(b1)             rx_base1 (b1)
67440a403fSchristos #define B2(b1, b2)         rx_base2 (b1, b2)
68440a403fSchristos #define B3(b1, b2, b3)     rx_base3 (b1, b2, b3)
69440a403fSchristos #define B4(b1, b2, b3, b4) rx_base4 (b1, b2, b3, b4)
70440a403fSchristos 
71440a403fSchristos /* POS is bits from the MSB of the first byte to the LSB of the last byte.  */
72440a403fSchristos #define F(val,pos,sz)      rx_field (val, pos, sz)
73440a403fSchristos #define FE(exp,pos,sz)	   rx_field (exp_val (exp), pos, sz);
74440a403fSchristos 
75440a403fSchristos #define O1(v)              rx_op (v, 1, RXREL_SIGNED); rx_range (v, -128, 255)
76440a403fSchristos #define O2(v)              rx_op (v, 2, RXREL_SIGNED); rx_range (v, -32768, 65536)
77440a403fSchristos #define O3(v)              rx_op (v, 3, RXREL_SIGNED); rx_range (v, -8388608, 16777216)
78440a403fSchristos #define O4(v)              rx_op (v, 4, RXREL_SIGNED)
79440a403fSchristos 
80440a403fSchristos #define UO1(v)             rx_op (v, 1, RXREL_UNSIGNED); rx_range (v, 0, 255)
81440a403fSchristos #define UO2(v)             rx_op (v, 2, RXREL_UNSIGNED); rx_range (v, 0, 65536)
82440a403fSchristos #define UO3(v)             rx_op (v, 3, RXREL_UNSIGNED); rx_range (v, 0, 16777216)
83440a403fSchristos #define UO4(v)             rx_op (v, 4, RXREL_UNSIGNED)
84440a403fSchristos 
85440a403fSchristos #define NO1(v)             rx_op (v, 1, RXREL_NEGATIVE)
86440a403fSchristos #define NO2(v)             rx_op (v, 2, RXREL_NEGATIVE)
87440a403fSchristos #define NO3(v)             rx_op (v, 3, RXREL_NEGATIVE)
88440a403fSchristos #define NO4(v)             rx_op (v, 4, RXREL_NEGATIVE)
89440a403fSchristos 
90440a403fSchristos #define PC1(v)             rx_op (v, 1, RXREL_PCREL)
91440a403fSchristos #define PC2(v)             rx_op (v, 2, RXREL_PCREL)
92440a403fSchristos #define PC3(v)             rx_op (v, 3, RXREL_PCREL)
93440a403fSchristos 
94*b88e3e88Schristos #define POST(v)            rx_post (v)
95*b88e3e88Schristos 
96440a403fSchristos #define IMM_(v,pos,size)   F (immediate (v, RXREL_SIGNED, pos, size), pos, 2); \
97440a403fSchristos 			   if (v.X_op != O_constant && v.X_op != O_big) rx_linkrelax_imm (pos)
98440a403fSchristos #define IMM(v,pos)	   IMM_ (v, pos, 32)
99440a403fSchristos #define IMMW(v,pos)	   IMM_ (v, pos, 16); rx_range (v, -32768, 65536)
100440a403fSchristos #define IMMB(v,pos)	   IMM_ (v, pos, 8); rx_range (v, -128, 255)
101440a403fSchristos #define NIMM(v,pos)	   F (immediate (v, RXREL_NEGATIVE, pos, 32), pos, 2)
102440a403fSchristos #define NBIMM(v,pos)	   F (immediate (v, RXREL_NEGATIVE_BORROW, pos, 32), pos, 2)
103440a403fSchristos #define DSP(v,pos,msz)	   if (!v.X_md) rx_relax (RX_RELAX_DISP, pos); \
104440a403fSchristos 			   else rx_linkrelax_dsp (pos); \
105440a403fSchristos 			   F (displacement (v, msz), pos, 2)
106440a403fSchristos 
107440a403fSchristos #define id24(a,b2,b3)	   B3 (0xfb + a, b2, b3)
108440a403fSchristos 
109440a403fSchristos static void	   rx_check_float_support (void);
110440a403fSchristos static int         rx_intop (expressionS, int, int);
111440a403fSchristos static int         rx_uintop (expressionS, int);
112440a403fSchristos static int         rx_disp3op (expressionS);
113440a403fSchristos static int         rx_disp5op (expressionS *, int);
114440a403fSchristos static int         rx_disp5op0 (expressionS *, int);
115440a403fSchristos static int         exp_val (expressionS exp);
116440a403fSchristos static expressionS zero_expr (void);
117440a403fSchristos static int         immediate (expressionS, int, int, int);
118440a403fSchristos static int         displacement (expressionS, int);
119440a403fSchristos static void        rtsd_immediate (expressionS);
120440a403fSchristos static void	   rx_range (expressionS, int, int);
121440a403fSchristos static void        rx_check_v2 (void);
122*b88e3e88Schristos static void        rx_check_v3 (void);
123*b88e3e88Schristos static void        rx_check_dfpu (void);
124440a403fSchristos 
125440a403fSchristos static int    need_flag = 0;
126440a403fSchristos static int    rx_in_brackets = 0;
127440a403fSchristos static int    rx_last_token = 0;
128440a403fSchristos static char * rx_init_start;
129440a403fSchristos static char * rx_last_exp_start = 0;
130440a403fSchristos static int    sub_op;
131440a403fSchristos static int    sub_op2;
132440a403fSchristos 
133440a403fSchristos #define YYDEBUG 1
134440a403fSchristos #define YYERROR_VERBOSE 1
135440a403fSchristos 
136440a403fSchristos %}
137440a403fSchristos 
138440a403fSchristos %name-prefix="rx_"
139440a403fSchristos 
140440a403fSchristos %union {
141440a403fSchristos   int regno;
142440a403fSchristos   expressionS exp;
143440a403fSchristos }
144440a403fSchristos 
145*b88e3e88Schristos %type <regno> REG FLAG CREG BCND BMCND SCCND ACC DREG DREGH DREGL DCREG DCMP
146440a403fSchristos %type <regno> flag bwl bw memex
147440a403fSchristos %type <exp> EXPR disp
148440a403fSchristos 
149*b88e3e88Schristos %token REG FLAG CREG ACC DREG DREGH DREGL DCREG
150440a403fSchristos 
151440a403fSchristos %token EXPR UNKNOWN_OPCODE IS_OPCODE
152440a403fSchristos 
153*b88e3e88Schristos %token DOT_S DOT_B DOT_W DOT_L DOT_A DOT_UB DOT_UW DOT_D
154440a403fSchristos 
155440a403fSchristos %token ABS ADC ADD AND_
156*b88e3e88Schristos %token BCLR BCND BFMOV BFMOVZ BMCND BNOT BRA BRK BSET BSR BTST
157440a403fSchristos %token CLRPSW CMP
158*b88e3e88Schristos %token DABS DADD DBT DCMP DDIV DIV DIVU DMOV DMUL DNEG
159*b88e3e88Schristos %token   DPOPM DPUSHM DROUND DSQRT DSUB DTOF DTOI DTOU
160440a403fSchristos %token EDIV EDIVU EMACA EMSBA EMUL EMULA EMULU
161*b88e3e88Schristos %token FADD FCMP FDIV FMUL FREIT FSUB FSQRT FTOD FTOI FTOU
162*b88e3e88Schristos %token INT ITOD ITOF
163440a403fSchristos %token JMP JSR
164440a403fSchristos %token MACHI MACLH MACLO MAX MIN MOV MOVCO MOVLI MOVU MSBHI MSBLH MSBLO MUL
165*b88e3e88Schristos %token   MULHI MULLH MULLO MULU MVFACHI MVFACGU MVFACMI MVFACLO MVFC MVFDC
166*b88e3e88Schristos %token     MVFDR MVTACGU MVTACHI MVTACLO MVTC MVTDC MVTIPL
167440a403fSchristos %token NEG NOP NOT
168440a403fSchristos %token OR
169440a403fSchristos %token POP POPC POPM PUSH PUSHA PUSHC PUSHM
170440a403fSchristos %token RACL RACW RDACL RDACW REIT REVL REVW RMPA ROLC RORC ROTL ROTR ROUND
171*b88e3e88Schristos %token   RSTR RTE RTFI RTS RTSD
172*b88e3e88Schristos %token SAT SATR SAVE SBB SCCND SCMPU SETPSW SHAR SHLL SHLR SMOVB SMOVF
173440a403fSchristos %token   SMOVU SSTR STNZ STOP STZ SUB SUNTIL SWHILE
174440a403fSchristos %token TST
175*b88e3e88Schristos %token UTOD UTOF
176440a403fSchristos %token WAIT
177440a403fSchristos %token XCHG XOR
178440a403fSchristos 
179440a403fSchristos %%
180440a403fSchristos /* ====================================================================== */
181440a403fSchristos 
182440a403fSchristos statement :
183440a403fSchristos 
184440a403fSchristos 	  UNKNOWN_OPCODE
185440a403fSchristos 	  { as_bad (_("Unknown opcode: %s"), rx_init_start); }
186440a403fSchristos 
187440a403fSchristos /* ---------------------------------------------------------------------- */
188440a403fSchristos 
189440a403fSchristos 	| BRK
190440a403fSchristos 	  { B1 (0x00); }
191440a403fSchristos 
192440a403fSchristos 	| DBT
193440a403fSchristos 	  { B1 (0x01); }
194440a403fSchristos 
195440a403fSchristos 	| RTS
196440a403fSchristos 	  { B1 (0x02); }
197440a403fSchristos 
198440a403fSchristos 	| NOP
199440a403fSchristos 	  { B1 (0x03); }
200440a403fSchristos 
201440a403fSchristos /* ---------------------------------------------------------------------- */
202440a403fSchristos 
203440a403fSchristos 	| BRA EXPR
204440a403fSchristos 	  { if (rx_disp3op ($2))
205440a403fSchristos 	      { B1 (0x08); rx_disp3 ($2, 5); }
206440a403fSchristos 	    else if (rx_intop ($2, 8, 8))
207440a403fSchristos 	      { B1 (0x2e); PC1 ($2); }
208440a403fSchristos 	    else if (rx_intop ($2, 16, 16))
209440a403fSchristos 	      { B1 (0x38); PC2 ($2); }
210440a403fSchristos 	    else if (rx_intop ($2, 24, 24))
211440a403fSchristos 	      { B1 (0x04); PC3 ($2); }
212440a403fSchristos 	    else
213440a403fSchristos 	      { rx_relax (RX_RELAX_BRANCH, 0);
214440a403fSchristos 		rx_linkrelax_branch ();
215440a403fSchristos 		/* We'll convert this to a longer one later if needed.  */
216440a403fSchristos 		B1 (0x08); rx_disp3 ($2, 5); } }
217440a403fSchristos 
218440a403fSchristos 	| BRA DOT_A EXPR
219440a403fSchristos 	  { B1 (0x04); PC3 ($3); }
220440a403fSchristos 
221440a403fSchristos 	| BRA DOT_S EXPR
222440a403fSchristos 	  { B1 (0x08); rx_disp3 ($3, 5); }
223440a403fSchristos 
224440a403fSchristos /* ---------------------------------------------------------------------- */
225440a403fSchristos 
226440a403fSchristos 	| BSR EXPR
227440a403fSchristos 	  { if (rx_intop ($2, 16, 16))
228440a403fSchristos 	      { B1 (0x39); PC2 ($2); }
229440a403fSchristos 	    else if (rx_intop ($2, 24, 24))
230440a403fSchristos 	      { B1 (0x05); PC3 ($2); }
231440a403fSchristos 	    else
232440a403fSchristos 	      { rx_relax (RX_RELAX_BRANCH, 0);
233440a403fSchristos 		rx_linkrelax_branch ();
234440a403fSchristos 		B1 (0x39); PC2 ($2); } }
235440a403fSchristos 	| BSR DOT_A EXPR
236440a403fSchristos 	  { B1 (0x05), PC3 ($3); }
237440a403fSchristos 
238440a403fSchristos /* ---------------------------------------------------------------------- */
239440a403fSchristos 
240440a403fSchristos 	| BCND DOT_S EXPR
241440a403fSchristos 	  { if ($1 == COND_EQ || $1 == COND_NE)
242440a403fSchristos 	      { B1 ($1 == COND_EQ ? 0x10 : 0x18); rx_disp3 ($3, 5); }
243440a403fSchristos 	    else
244440a403fSchristos 	      as_bad (_("Only BEQ and BNE may have .S")); }
245440a403fSchristos 
246440a403fSchristos /* ---------------------------------------------------------------------- */
247440a403fSchristos 
248440a403fSchristos 	| BCND DOT_B EXPR
249440a403fSchristos 	  { B1 (0x20); F ($1, 4, 4); PC1 ($3); }
250440a403fSchristos 
251440a403fSchristos 	| BRA DOT_B EXPR
252440a403fSchristos 	  { B1 (0x2e), PC1 ($3); }
253440a403fSchristos 
254440a403fSchristos /* ---------------------------------------------------------------------- */
255440a403fSchristos 
256440a403fSchristos 	| BRA DOT_W EXPR
257440a403fSchristos 	  { B1 (0x38), PC2 ($3); }
258440a403fSchristos 	| BSR DOT_W EXPR
259440a403fSchristos 	  { B1 (0x39), PC2 ($3); }
260440a403fSchristos 	| BCND DOT_W EXPR
261440a403fSchristos 	  { if ($1 == COND_EQ || $1 == COND_NE)
262440a403fSchristos 	      { B1 ($1 == COND_EQ ? 0x3a : 0x3b); PC2 ($3); }
263440a403fSchristos 	    else
264440a403fSchristos 	      as_bad (_("Only BEQ and BNE may have .W")); }
265440a403fSchristos 	| BCND EXPR
266440a403fSchristos 	  { if ($1 == COND_EQ || $1 == COND_NE)
267440a403fSchristos 	      {
268440a403fSchristos 		rx_relax (RX_RELAX_BRANCH, 0);
269440a403fSchristos 		rx_linkrelax_branch ();
270440a403fSchristos 		B1 ($1 == COND_EQ ? 0x10 : 0x18); rx_disp3 ($2, 5);
271440a403fSchristos 	      }
272440a403fSchristos 	    else
273440a403fSchristos 	      {
274440a403fSchristos 		rx_relax (RX_RELAX_BRANCH, 0);
275440a403fSchristos 		/* This is because we might turn it into a
276440a403fSchristos 		   jump-over-jump long branch.  */
277440a403fSchristos 		rx_linkrelax_branch ();
278440a403fSchristos 	        B1 (0x20); F ($1, 4, 4); PC1 ($2);
279440a403fSchristos 	      } }
280440a403fSchristos 
281440a403fSchristos /* ---------------------------------------------------------------------- */
282440a403fSchristos 
283440a403fSchristos 	| MOV DOT_B '#' EXPR ',' '[' REG ']'
284440a403fSchristos 	  { B2 (0xf8, 0x04); F ($7, 8, 4); IMMB ($4, 12);}
285440a403fSchristos 
286440a403fSchristos 	| MOV DOT_W '#' EXPR ',' '[' REG ']'
287440a403fSchristos           { B2 (0xf8, 0x01); F ($7, 8, 4); IMMW ($4, 12);}
288440a403fSchristos 
289440a403fSchristos 	| MOV DOT_L '#' EXPR ',' '[' REG ']'
290440a403fSchristos 	  { B2 (0xf8, 0x02); F ($7, 8, 4); IMM ($4, 12);}
291440a403fSchristos 
292440a403fSchristos 	| MOV DOT_B '#' EXPR ',' disp '[' REG ']'
293440a403fSchristos 	  /* rx_disp5op changes the value if it succeeds, so keep it last.  */
294440a403fSchristos 	  { if ($8 <= 7 && rx_uintop ($4, 8) && rx_disp5op0 (&$6, BSIZE))
295440a403fSchristos 	      { B2 (0x3c, 0); rx_field5s2 ($6); F ($8, 9, 3); O1 ($4); }
296440a403fSchristos 	    else
297440a403fSchristos 	      { B2 (0xf8, 0x04); F ($8, 8, 4); DSP ($6, 6, BSIZE); O1 ($4);
298440a403fSchristos 	      if ($4.X_op != O_constant && $4.X_op != O_big) rx_linkrelax_imm (12); } }
299440a403fSchristos 
300440a403fSchristos 	| MOV DOT_W '#' EXPR ',' disp '[' REG ']'
301440a403fSchristos 	  { if ($8 <= 7 && rx_uintop ($4, 8) && rx_disp5op0 (&$6, WSIZE))
302440a403fSchristos 	      { B2 (0x3d, 0); rx_field5s2 ($6); F ($8, 9, 3); O1 ($4); }
303440a403fSchristos 	    else
304440a403fSchristos 	      { B2 (0xf8, 0x01); F ($8, 8, 4); DSP ($6, 6, WSIZE); IMMW ($4, 12); } }
305440a403fSchristos 
306440a403fSchristos 	| MOV DOT_L '#' EXPR ',' disp '[' REG ']'
307440a403fSchristos 	  { if ($8 <= 7 && rx_uintop ($4, 8) && rx_disp5op0 (&$6, LSIZE))
308440a403fSchristos 	      { B2 (0x3e, 0); rx_field5s2 ($6); F ($8, 9, 3); O1 ($4); }
309440a403fSchristos 	    else
310440a403fSchristos 	      { B2 (0xf8, 0x02); F ($8, 8, 4); DSP ($6, 6, LSIZE); IMM ($4, 12); } }
311440a403fSchristos 
312440a403fSchristos /* ---------------------------------------------------------------------- */
313440a403fSchristos 
314440a403fSchristos 	| RTSD '#' EXPR ',' REG '-' REG
315440a403fSchristos 	  { B2 (0x3f, 0); F ($5, 8, 4); F ($7, 12, 4); rtsd_immediate ($3);
316440a403fSchristos 	    if ($5 == 0)
317440a403fSchristos 	      rx_error (_("RTSD cannot pop R0"));
318440a403fSchristos 	    if ($5 > $7)
319440a403fSchristos 	      rx_error (_("RTSD first reg must be <= second reg")); }
320440a403fSchristos 
321440a403fSchristos /* ---------------------------------------------------------------------- */
322440a403fSchristos 
323440a403fSchristos 	| CMP REG ',' REG
324440a403fSchristos 	  { B2 (0x47, 0); F ($2, 8, 4); F ($4, 12, 4); }
325440a403fSchristos 
326440a403fSchristos /* ---------------------------------------------------------------------- */
327440a403fSchristos 
328440a403fSchristos 	| CMP disp '[' REG ']' DOT_UB ',' REG
329440a403fSchristos 	  { B2 (0x44, 0); F ($4, 8, 4); F ($8, 12, 4); DSP ($2, 6, BSIZE); }
330440a403fSchristos 
331440a403fSchristos 	| CMP disp '[' REG ']' memex ',' REG
332440a403fSchristos 	  { B3 (MEMEX, 0x04, 0); F ($6, 8, 2);  F ($4, 16, 4); F ($8, 20, 4); DSP ($2, 14, sizemap[$6]); }
333440a403fSchristos 
334440a403fSchristos /* ---------------------------------------------------------------------- */
335440a403fSchristos 
336440a403fSchristos 	| MOVU bw REG ',' REG
337440a403fSchristos 	  { B2 (0x5b, 0x00); F ($2, 5, 1); F ($3, 8, 4); F ($5, 12, 4); }
338440a403fSchristos 
339440a403fSchristos /* ---------------------------------------------------------------------- */
340440a403fSchristos 
341440a403fSchristos 	| MOVU bw '[' REG ']' ',' REG
342440a403fSchristos 	  { B2 (0x58, 0x00); F ($2, 5, 1); F ($4, 8, 4); F ($7, 12, 4); }
343440a403fSchristos 
344440a403fSchristos 	| MOVU bw EXPR '[' REG ']' ',' REG
345440a403fSchristos 	  { if ($5 <= 7 && $8 <= 7 && rx_disp5op (&$3, $2))
346440a403fSchristos 	      { B2 (0xb0, 0); F ($2, 4, 1); F ($5, 9, 3); F ($8, 13, 3); rx_field5s ($3); }
347440a403fSchristos 	    else
348440a403fSchristos 	      { B2 (0x58, 0x00); F ($2, 5, 1); F ($5, 8, 4); F ($8, 12, 4); DSP ($3, 6, $2); } }
349440a403fSchristos 
350440a403fSchristos /* ---------------------------------------------------------------------- */
351440a403fSchristos 
352440a403fSchristos 	| SUB '#' EXPR ',' REG
353440a403fSchristos 	  { if (rx_uintop ($3, 4))
354440a403fSchristos 	      { B2 (0x60, 0); FE ($3, 8, 4); F ($5, 12, 4); }
355440a403fSchristos 	    else
356440a403fSchristos 	      /* This is really an add, but we negate the immediate.  */
357440a403fSchristos 	      { B2 (0x70, 0); F ($5, 8, 4); F ($5, 12, 4); NIMM ($3, 6); } }
358440a403fSchristos 
359440a403fSchristos 	| CMP '#' EXPR ',' REG
360440a403fSchristos 	  { if (rx_uintop ($3, 4))
361440a403fSchristos 	      { B2 (0x61, 0); FE ($3, 8, 4); F ($5, 12, 4); }
362440a403fSchristos 	    else if (rx_uintop ($3, 8))
363440a403fSchristos 	      { B2 (0x75, 0x50); F ($5, 12, 4); UO1 ($3); }
364440a403fSchristos 	    else
365440a403fSchristos 	      { B2 (0x74, 0x00); F ($5, 12, 4); IMM ($3, 6); } }
366440a403fSchristos 
367440a403fSchristos 	| ADD '#' EXPR ',' REG
368440a403fSchristos 	  { if (rx_uintop ($3, 4))
369440a403fSchristos 	      { B2 (0x62, 0); FE ($3, 8, 4); F ($5, 12, 4); }
370440a403fSchristos 	    else
371440a403fSchristos 	      { B2 (0x70, 0); F ($5, 8, 4); F ($5, 12, 4); IMM ($3, 6); } }
372440a403fSchristos 
373440a403fSchristos 	| MUL '#' EXPR ',' REG
374440a403fSchristos 	  { if (rx_uintop ($3, 4))
375440a403fSchristos 	      { B2 (0x63, 0); FE ($3, 8, 4); F ($5, 12, 4); }
376440a403fSchristos 	    else
377440a403fSchristos 	      { B2 (0x74, 0x10); F ($5, 12, 4); IMM ($3, 6); } }
378440a403fSchristos 
379440a403fSchristos 	| AND_ '#' EXPR ',' REG
380440a403fSchristos 	  { if (rx_uintop ($3, 4))
381440a403fSchristos 	      { B2 (0x64, 0); FE ($3, 8, 4); F ($5, 12, 4); }
382440a403fSchristos 	    else
383440a403fSchristos 	      { B2 (0x74, 0x20); F ($5, 12, 4); IMM ($3, 6); } }
384440a403fSchristos 
385440a403fSchristos 	| OR '#' EXPR ',' REG
386440a403fSchristos 	  { if (rx_uintop ($3, 4))
387440a403fSchristos 	      { B2 (0x65, 0); FE ($3, 8, 4); F ($5, 12, 4); }
388440a403fSchristos 	    else
389440a403fSchristos 	      { B2 (0x74, 0x30); F ($5, 12, 4); IMM ($3, 6); } }
390440a403fSchristos 
391440a403fSchristos 	| MOV DOT_L '#' EXPR ',' REG
392440a403fSchristos 	  { if (rx_uintop ($4, 4))
393440a403fSchristos 	      { B2 (0x66, 0); FE ($4, 8, 4); F ($6, 12, 4); }
394440a403fSchristos 	    else if (rx_uintop ($4, 8))
395440a403fSchristos 	      { B2 (0x75, 0x40); F ($6, 12, 4); UO1 ($4); }
396440a403fSchristos 	    else
397440a403fSchristos 	      { B2 (0xfb, 0x02); F ($6, 8, 4); IMM ($4, 12); } }
398440a403fSchristos 
399440a403fSchristos 	| MOV '#' EXPR ',' REG
400440a403fSchristos 	  { if (rx_uintop ($3, 4))
401440a403fSchristos 	      { B2 (0x66, 0); FE ($3, 8, 4); F ($5, 12, 4); }
402440a403fSchristos 	    else if (rx_uintop ($3, 8))
403440a403fSchristos 	      { B2 (0x75, 0x40); F ($5, 12, 4); UO1 ($3); }
404440a403fSchristos 	    else
405440a403fSchristos 	      { B2 (0xfb, 0x02); F ($5, 8, 4); IMM ($3, 12); } }
406440a403fSchristos 
407440a403fSchristos /* ---------------------------------------------------------------------- */
408440a403fSchristos 
409440a403fSchristos 	| RTSD '#' EXPR
410440a403fSchristos 	  { B1 (0x67); rtsd_immediate ($3); }
411440a403fSchristos 
412440a403fSchristos /* ---------------------------------------------------------------------- */
413440a403fSchristos 
414440a403fSchristos 	| SHLR { sub_op = 0; } op_shift
415440a403fSchristos 	| SHAR { sub_op = 1; } op_shift
416440a403fSchristos 	| SHLL { sub_op = 2; } op_shift
417440a403fSchristos 
418440a403fSchristos /* ---------------------------------------------------------------------- */
419440a403fSchristos 
420440a403fSchristos 	| PUSHM REG '-' REG
421440a403fSchristos 	  {
422440a403fSchristos 	    if ($2 == $4)
423440a403fSchristos 	      { B2 (0x7e, 0x80); F (LSIZE, 10, 2); F ($2, 12, 4); }
424440a403fSchristos 	    else
425440a403fSchristos 	     { B2 (0x6e, 0); F ($2, 8, 4); F ($4, 12, 4); }
426440a403fSchristos 	    if ($2 == 0)
427440a403fSchristos 	      rx_error (_("PUSHM cannot push R0"));
428440a403fSchristos 	    if ($2 > $4)
429440a403fSchristos 	      rx_error (_("PUSHM first reg must be <= second reg")); }
430440a403fSchristos 
431440a403fSchristos /* ---------------------------------------------------------------------- */
432440a403fSchristos 
433440a403fSchristos 	| POPM REG '-' REG
434440a403fSchristos 	  {
435440a403fSchristos 	    if ($2 == $4)
436440a403fSchristos 	      { B2 (0x7e, 0xb0); F ($2, 12, 4); }
437440a403fSchristos 	    else
438440a403fSchristos 	      { B2 (0x6f, 0); F ($2, 8, 4); F ($4, 12, 4); }
439440a403fSchristos 	    if ($2 == 0)
440440a403fSchristos 	      rx_error (_("POPM cannot pop R0"));
441440a403fSchristos 	    if ($2 > $4)
442440a403fSchristos 	      rx_error (_("POPM first reg must be <= second reg")); }
443440a403fSchristos 
444440a403fSchristos /* ---------------------------------------------------------------------- */
445440a403fSchristos 
446440a403fSchristos 	| ADD '#' EXPR ',' REG ',' REG
447440a403fSchristos 	  { B2 (0x70, 0x00); F ($5, 8, 4); F ($7, 12, 4); IMM ($3, 6); }
448440a403fSchristos 
449440a403fSchristos /* ---------------------------------------------------------------------- */
450440a403fSchristos 
451440a403fSchristos 	| INT '#' EXPR
452440a403fSchristos 	  { B2(0x75, 0x60), UO1 ($3); }
453440a403fSchristos 
454440a403fSchristos /* ---------------------------------------------------------------------- */
455440a403fSchristos 
456440a403fSchristos 	| BSET '#' EXPR ',' REG
457440a403fSchristos 	  { B2 (0x78, 0); FE ($3, 7, 5); F ($5, 12, 4); }
458440a403fSchristos 	| BCLR '#' EXPR ',' REG
459440a403fSchristos 	  { B2 (0x7a, 0); FE ($3, 7, 5); F ($5, 12, 4); }
460440a403fSchristos 
461440a403fSchristos /* ---------------------------------------------------------------------- */
462440a403fSchristos 
463440a403fSchristos 	| BTST '#' EXPR ',' REG
464440a403fSchristos 	  { B2 (0x7c, 0x00); FE ($3, 7, 5); F ($5, 12, 4); }
465440a403fSchristos 
466440a403fSchristos /* ---------------------------------------------------------------------- */
467440a403fSchristos 
468440a403fSchristos 	| SAT REG
469440a403fSchristos 	  { B2 (0x7e, 0x30); F ($2, 12, 4); }
470440a403fSchristos 	| RORC REG
471440a403fSchristos 	  { B2 (0x7e, 0x40); F ($2, 12, 4); }
472440a403fSchristos 	| ROLC REG
473440a403fSchristos 	  { B2 (0x7e, 0x50); F ($2, 12, 4); }
474440a403fSchristos 
475440a403fSchristos /* ---------------------------------------------------------------------- */
476440a403fSchristos 
477440a403fSchristos 	| PUSH bwl REG
478440a403fSchristos 	  { B2 (0x7e, 0x80); F ($2, 10, 2); F ($3, 12, 4); }
479440a403fSchristos 
480440a403fSchristos /* ---------------------------------------------------------------------- */
481440a403fSchristos 
482440a403fSchristos 	| POP REG
483440a403fSchristos 	  { B2 (0x7e, 0xb0); F ($2, 12, 4); }
484440a403fSchristos 
485440a403fSchristos /* ---------------------------------------------------------------------- */
486440a403fSchristos 
487440a403fSchristos 	| PUSHC CREG
488440a403fSchristos 	  { if ($2 == 13)
489440a403fSchristos 	      { rx_check_v2 (); }
490440a403fSchristos 	    if ($2 < 16)
491440a403fSchristos 	      { B2 (0x7e, 0xc0); F ($2, 12, 4); }
492440a403fSchristos 	    else
493440a403fSchristos 	      as_bad (_("PUSHC can only push the first 16 control registers")); }
494440a403fSchristos 
495440a403fSchristos /* ---------------------------------------------------------------------- */
496440a403fSchristos 
497440a403fSchristos 	| POPC CREG
498440a403fSchristos 	  { if ($2 == 13)
499440a403fSchristos 	    { rx_check_v2 (); }
500440a403fSchristos 	    if ($2 < 16)
501440a403fSchristos 	      { B2 (0x7e, 0xe0); F ($2, 12, 4); }
502440a403fSchristos 	    else
503440a403fSchristos 	      as_bad (_("POPC can only pop the first 16 control registers")); }
504440a403fSchristos 
505440a403fSchristos /* ---------------------------------------------------------------------- */
506440a403fSchristos 
507440a403fSchristos 	| SETPSW flag
508440a403fSchristos 	  { B2 (0x7f, 0xa0); F ($2, 12, 4); }
509440a403fSchristos 	| CLRPSW flag
510440a403fSchristos 	  { B2 (0x7f, 0xb0); F ($2, 12, 4); }
511440a403fSchristos 
512440a403fSchristos /* ---------------------------------------------------------------------- */
513440a403fSchristos 
514440a403fSchristos 	| JMP REG
515440a403fSchristos 	  { B2 (0x7f, 0x00); F ($2, 12, 4); }
516440a403fSchristos 	| JSR REG
517440a403fSchristos 	  { B2 (0x7f, 0x10); F ($2, 12, 4); }
518440a403fSchristos 	| BRA opt_l REG
519440a403fSchristos 	  { B2 (0x7f, 0x40); F ($3, 12, 4); }
520440a403fSchristos 	| BSR opt_l REG
521440a403fSchristos 	  { B2 (0x7f, 0x50); F ($3, 12, 4); }
522440a403fSchristos 
523440a403fSchristos /* ---------------------------------------------------------------------- */
524440a403fSchristos 
525440a403fSchristos 	| SCMPU
526440a403fSchristos 	  { B2 (0x7f, 0x83); rx_note_string_insn_use (); }
527440a403fSchristos 	| SMOVU
528440a403fSchristos 	  { B2 (0x7f, 0x87); rx_note_string_insn_use (); }
529440a403fSchristos 	| SMOVB
530440a403fSchristos 	  { B2 (0x7f, 0x8b); rx_note_string_insn_use (); }
531440a403fSchristos 	| SMOVF
532440a403fSchristos 	  { B2 (0x7f, 0x8f); rx_note_string_insn_use (); }
533440a403fSchristos 
534440a403fSchristos /* ---------------------------------------------------------------------- */
535440a403fSchristos 
536440a403fSchristos 	| SUNTIL bwl
537440a403fSchristos 	  { B2 (0x7f, 0x80); F ($2, 14, 2); rx_note_string_insn_use (); }
538440a403fSchristos 	| SWHILE bwl
539440a403fSchristos 	  { B2 (0x7f, 0x84); F ($2, 14, 2); rx_note_string_insn_use (); }
540440a403fSchristos 	| SSTR bwl
541440a403fSchristos 	  { B2 (0x7f, 0x88); F ($2, 14, 2); }
542440a403fSchristos 
543440a403fSchristos /* ---------------------------------------------------------------------- */
544440a403fSchristos 
545440a403fSchristos 	| RMPA bwl
546440a403fSchristos 	  { B2 (0x7f, 0x8c); F ($2, 14, 2); rx_note_string_insn_use (); }
547440a403fSchristos 
548440a403fSchristos /* ---------------------------------------------------------------------- */
549440a403fSchristos 
550440a403fSchristos 	| RTFI
551440a403fSchristos 	  { B2 (0x7f, 0x94); }
552440a403fSchristos 	| RTE
553440a403fSchristos 	  { B2 (0x7f, 0x95); }
554440a403fSchristos 	| WAIT
555440a403fSchristos 	  { B2 (0x7f, 0x96); }
556440a403fSchristos 	| SATR
557440a403fSchristos 	  { B2 (0x7f, 0x93); }
558440a403fSchristos 
559440a403fSchristos /* ---------------------------------------------------------------------- */
560440a403fSchristos 
561440a403fSchristos 	| MVTIPL '#' EXPR
562440a403fSchristos 	  { B3 (0x75, 0x70, 0x00); FE ($3, 20, 4); }
563440a403fSchristos 
564440a403fSchristos /* ---------------------------------------------------------------------- */
565440a403fSchristos 
566440a403fSchristos 	/* rx_disp5op changes the value if it succeeds, so keep it last.  */
567440a403fSchristos 	| MOV bwl REG ',' EXPR '[' REG ']'
568440a403fSchristos 	  { if ($3 <= 7 && $7 <= 7 && rx_disp5op (&$5, $2))
569440a403fSchristos 	      { B2 (0x80, 0); F ($2, 2, 2); F ($7, 9, 3); F ($3, 13, 3); rx_field5s ($5); }
570440a403fSchristos 	    else
571440a403fSchristos 	      { B2 (0xc3, 0x00); F ($2, 2, 2); F ($7, 8, 4); F ($3, 12, 4); DSP ($5, 4, $2); }}
572440a403fSchristos 
573440a403fSchristos /* ---------------------------------------------------------------------- */
574440a403fSchristos 
575440a403fSchristos 	| MOV bwl EXPR '[' REG ']' ',' REG
576440a403fSchristos 	  { if ($5 <= 7 && $8 <= 7 && rx_disp5op (&$3, $2))
577440a403fSchristos 	      { B2 (0x88, 0); F ($2, 2, 2); F ($5, 9, 3); F ($8, 13, 3); rx_field5s ($3); }
578440a403fSchristos 	    else
579440a403fSchristos 	      { B2 (0xcc, 0x00); F ($2, 2, 2); F ($5, 8, 4); F ($8, 12, 4); DSP ($3, 6, $2); } }
580440a403fSchristos 
581440a403fSchristos /* ---------------------------------------------------------------------- */
582440a403fSchristos 
583440a403fSchristos 	/* MOV a,b - if a is a reg and b is mem, src and dest are
584440a403fSchristos 	   swapped.  */
585440a403fSchristos 
586440a403fSchristos 	/* We don't use "disp" here because it causes a shift/reduce
587440a403fSchristos 	   conflict with the other displacement-less patterns.  */
588440a403fSchristos 
589440a403fSchristos 	| MOV bwl REG ',' '[' REG ']'
590440a403fSchristos 	  { B2 (0xc3, 0x00); F ($2, 2, 2); F ($6, 8, 4); F ($3, 12, 4); }
591440a403fSchristos 
592440a403fSchristos /* ---------------------------------------------------------------------- */
593440a403fSchristos 
594440a403fSchristos 	| MOV bwl '[' REG ']' ',' disp '[' REG ']'
595440a403fSchristos 	  { B2 (0xc0, 0); F ($2, 2, 2); F ($4, 8, 4); F ($9, 12, 4); DSP ($7, 4, $2); }
596440a403fSchristos 
597440a403fSchristos /* ---------------------------------------------------------------------- */
598440a403fSchristos 
599440a403fSchristos 	| MOV bwl EXPR '[' REG ']' ',' disp '[' REG ']'
600440a403fSchristos 	  { B2 (0xc0, 0x00); F ($2, 2, 2); F ($5, 8, 4); F ($10, 12, 4); DSP ($3, 6, $2); DSP ($8, 4, $2); }
601440a403fSchristos 
602440a403fSchristos /* ---------------------------------------------------------------------- */
603440a403fSchristos 
604440a403fSchristos 	| MOV bwl REG ',' REG
605440a403fSchristos 	  { B2 (0xcf, 0x00); F ($2, 2, 2); F ($3, 8, 4); F ($5, 12, 4); }
606440a403fSchristos 
607440a403fSchristos /* ---------------------------------------------------------------------- */
608440a403fSchristos 
609440a403fSchristos 	| MOV bwl '[' REG ']' ',' REG
610440a403fSchristos 	  { B2 (0xcc, 0x00); F ($2, 2, 2); F ($4, 8, 4); F ($7, 12, 4); }
611440a403fSchristos 
612440a403fSchristos /* ---------------------------------------------------------------------- */
613440a403fSchristos 
614440a403fSchristos 	| BSET '#' EXPR ',' disp '[' REG ']' DOT_B
615440a403fSchristos 	  { B2 (0xf0, 0x00); F ($7, 8, 4); FE ($3, 13, 3); DSP ($5, 6, BSIZE); }
616440a403fSchristos 	| BCLR '#' EXPR ',' disp '[' REG ']' DOT_B
617440a403fSchristos 	  { B2 (0xf0, 0x08); F ($7, 8, 4); FE ($3, 13, 3); DSP ($5, 6, BSIZE); }
618440a403fSchristos 	| BTST '#' EXPR ',' disp '[' REG ']' DOT_B
619440a403fSchristos 	  { B2 (0xf4, 0x00); F ($7, 8, 4); FE ($3, 13, 3); DSP ($5, 6, BSIZE); }
620440a403fSchristos 
621440a403fSchristos /* ---------------------------------------------------------------------- */
622440a403fSchristos 
623440a403fSchristos 	| PUSH bwl disp '[' REG ']'
624440a403fSchristos 	  { B2 (0xf4, 0x08); F ($2, 14, 2); F ($5, 8, 4); DSP ($3, 6, $2); }
625440a403fSchristos 
626440a403fSchristos /* ---------------------------------------------------------------------- */
627440a403fSchristos 
628440a403fSchristos 	| SBB   { sub_op = 0; } op_dp20_rm_l
629440a403fSchristos 	| NEG   { sub_op = 1; sub_op2 = 1; } op_dp20_rr
630440a403fSchristos 	| ADC   { sub_op = 2; } op_dp20_rim_l
631440a403fSchristos 	| ABS   { sub_op = 3; sub_op2 = 2; } op_dp20_rr
632440a403fSchristos 	| MAX   { sub_op = 4; } op_dp20_rim
633440a403fSchristos 	| MIN   { sub_op = 5; } op_dp20_rim
634440a403fSchristos 	| EMUL  { sub_op = 6; } op_dp20_i
635440a403fSchristos 	| EMULU { sub_op = 7; } op_dp20_i
636440a403fSchristos 	| DIV   { sub_op = 8; } op_dp20_rim
637440a403fSchristos 	| DIVU  { sub_op = 9; } op_dp20_rim
638440a403fSchristos 	| TST   { sub_op = 12; } op_dp20_rim
639*b88e3e88Schristos 	| XOR   { sub_op = 13; } op_xor
640440a403fSchristos 	| NOT   { sub_op = 14; sub_op2 = 0; } op_dp20_rr
641440a403fSchristos 	| STZ   { sub_op = 14; sub_op2 = 0; } op_dp20_ri
642440a403fSchristos 	| STNZ  { sub_op = 15; sub_op2 = 1; } op_dp20_ri
643440a403fSchristos 
644440a403fSchristos /* ---------------------------------------------------------------------- */
645440a403fSchristos 
646440a403fSchristos 	| EMUL  { sub_op = 6; } op_xchg
647440a403fSchristos 	| EMULU { sub_op = 7; } op_xchg
648440a403fSchristos 	| XCHG  { sub_op = 16; } op_xchg
649440a403fSchristos 	| ITOF  { sub_op = 17; } op_xchg
650440a403fSchristos 	| UTOF  { sub_op = 21; } op_xchg
651440a403fSchristos 
652440a403fSchristos /* ---------------------------------------------------------------------- */
653440a403fSchristos 
654440a403fSchristos 	| BSET REG ',' REG
655440a403fSchristos 	  { id24 (1, 0x63, 0x00); F ($4, 16, 4); F ($2, 20, 4); }
656440a403fSchristos 	| BCLR REG ',' REG
657440a403fSchristos 	  { id24 (1, 0x67, 0x00); F ($4, 16, 4); F ($2, 20, 4); }
658440a403fSchristos 	| BTST REG ',' REG
659440a403fSchristos 	  { id24 (1, 0x6b, 0x00); F ($4, 16, 4); F ($2, 20, 4); }
660440a403fSchristos 	| BNOT REG ',' REG
661440a403fSchristos 	  { id24 (1, 0x6f, 0x00); F ($4, 16, 4); F ($2, 20, 4); }
662440a403fSchristos 
663440a403fSchristos 	| BSET REG ',' disp '[' REG ']' opt_b
664440a403fSchristos 	  { id24 (1, 0x60, 0x00); F ($6, 16, 4); F ($2, 20, 4); DSP ($4, 14, BSIZE); }
665440a403fSchristos 	| BCLR REG ',' disp '[' REG ']' opt_b
666440a403fSchristos 	  { id24 (1, 0x64, 0x00); F ($6, 16, 4); F ($2, 20, 4); DSP ($4, 14, BSIZE); }
667440a403fSchristos 	| BTST REG ',' disp '[' REG ']' opt_b
668440a403fSchristos 	  { id24 (1, 0x68, 0x00); F ($6, 16, 4); F ($2, 20, 4); DSP ($4, 14, BSIZE); }
669440a403fSchristos 	| BNOT REG ',' disp '[' REG ']' opt_b
670440a403fSchristos 	  { id24 (1, 0x6c, 0x00); F ($6, 16, 4); F ($2, 20, 4); DSP ($4, 14, BSIZE); }
671440a403fSchristos 
672440a403fSchristos /* ---------------------------------------------------------------------- */
673440a403fSchristos 
674440a403fSchristos 	| FSUB  { sub_op = 0; } float3_op
675440a403fSchristos 	| FCMP  { sub_op = 1; } float2_op
676440a403fSchristos 	| FADD  { sub_op = 2; } float3_op
677440a403fSchristos 	| FMUL  { sub_op = 3; } float3_op
678440a403fSchristos 	| FDIV  { sub_op = 4; } float2_op
679440a403fSchristos 	| FSQRT { sub_op = 8; } float2_op_ni
680440a403fSchristos 	| FTOI  { sub_op = 5; } float2_op_ni
681440a403fSchristos 	| FTOU  { sub_op = 9; } float2_op_ni
682440a403fSchristos 	| ROUND { sub_op = 6; } float2_op_ni
683440a403fSchristos 
684440a403fSchristos /* ---------------------------------------------------------------------- */
685440a403fSchristos 
686440a403fSchristos 
687440a403fSchristos /* ---------------------------------------------------------------------- */
688440a403fSchristos 
689440a403fSchristos 	| SCCND DOT_L REG
690440a403fSchristos 	  { id24 (1, 0xdb, 0x00); F ($1, 20, 4); F ($3, 16, 4); }
691440a403fSchristos 	| SCCND bwl disp '[' REG ']'
692440a403fSchristos 	  { id24 (1, 0xd0, 0x00); F ($1, 20, 4); F ($2, 12, 2); F ($5, 16, 4); DSP ($3, 14, $2); }
693440a403fSchristos 
694440a403fSchristos /* ---------------------------------------------------------------------- */
695440a403fSchristos 
696440a403fSchristos 	| BMCND '#' EXPR ',' disp '[' REG ']' opt_b
697440a403fSchristos 	  { id24 (1, 0xe0, 0x00); F ($1, 20, 4); FE ($3, 11, 3);
698440a403fSchristos 	      F ($7, 16, 4); DSP ($5, 14, BSIZE); }
699440a403fSchristos 
700440a403fSchristos /* ---------------------------------------------------------------------- */
701440a403fSchristos 
702440a403fSchristos 	| BNOT '#' EXPR ',' disp '[' REG ']' opt_b
703440a403fSchristos 	  { id24 (1, 0xe0, 0x0f); FE ($3, 11, 3); F ($7, 16, 4);
704440a403fSchristos 	      DSP ($5, 14, BSIZE); }
705440a403fSchristos 
706440a403fSchristos /* ---------------------------------------------------------------------- */
707440a403fSchristos 
708440a403fSchristos 	| MULHI REG ',' REG
709440a403fSchristos 	  { id24 (2, 0x00, 0x00); F ($2, 16, 4); F ($4, 20, 4); }
710440a403fSchristos 	| MULHI REG ',' REG ',' ACC
711440a403fSchristos 	  { rx_check_v2 (); id24 (2, 0x00, 0x00); F ($2, 16, 4); F ($4, 20, 4); F ($6, 12, 1); }
712440a403fSchristos 	| MULLO REG ',' REG
713440a403fSchristos 	  { id24 (2, 0x01, 0x00); F ($2, 16, 4); F ($4, 20, 4); }
714440a403fSchristos 	| MULLO REG ',' REG ',' ACC
715440a403fSchristos 	  { rx_check_v2 (); id24 (2, 0x01, 0x00); F ($2, 16, 4); F ($4, 20, 4); F ($6, 12, 1); }
716440a403fSchristos 	| MACHI REG ',' REG
717440a403fSchristos 	  { id24 (2, 0x04, 0x00); F ($2, 16, 4); F ($4, 20, 4); }
718440a403fSchristos 	| MACHI REG ',' REG ',' ACC
719440a403fSchristos 	  { rx_check_v2 (); id24 (2, 0x04, 0x00); F ($2, 16, 4); F ($4, 20, 4); F ($6, 12, 1); }
720440a403fSchristos 	| MACLO REG ',' REG
721440a403fSchristos 	  { id24 (2, 0x05, 0x00); F ($2, 16, 4); F ($4, 20, 4); }
722440a403fSchristos 	|  MACLO REG ',' REG ',' ACC
723440a403fSchristos 	  { rx_check_v2 (); id24 (2, 0x05, 0x00); F ($2, 16, 4); F ($4, 20, 4); F ($6, 12, 1); }
724440a403fSchristos 
725440a403fSchristos /* ---------------------------------------------------------------------- */
726440a403fSchristos 
727440a403fSchristos 	/* We don't have syntax for these yet.  */
728440a403fSchristos 	| MVTACHI REG
729440a403fSchristos 	  { id24 (2, 0x17, 0x00); F ($2, 20, 4); }
730440a403fSchristos 	|  MVTACHI REG ',' ACC
731440a403fSchristos 	  { rx_check_v2 (); id24 (2, 0x17, 0x00); F ($2, 20, 4); F ($4, 16, 1); }
732440a403fSchristos 	| MVTACLO REG
733440a403fSchristos 	  { id24 (2, 0x17, 0x10); F ($2, 20, 4); }
734440a403fSchristos 	| MVTACLO REG ',' ACC
735440a403fSchristos 	  { rx_check_v2 (); id24 (2, 0x17, 0x10); F ($2, 20, 4); F ($4, 16, 1); }
736440a403fSchristos 	| MVFACHI REG
737440a403fSchristos 	  { id24 (2, 0x1f, 0x00); F ($2, 20, 4); }
738440a403fSchristos 	| MVFACHI { sub_op = 0; } mvfa_op
739440a403fSchristos 	| MVFACMI REG
740440a403fSchristos 	  { id24 (2, 0x1f, 0x20); F ($2, 20, 4); }
741440a403fSchristos 	| MVFACMI { sub_op = 2; } mvfa_op
742440a403fSchristos 	| MVFACLO REG
743440a403fSchristos 	  { id24 (2, 0x1f, 0x10); F ($2, 20, 4); }
744440a403fSchristos 	| MVFACLO { sub_op = 1; } mvfa_op
745440a403fSchristos 	| RACW '#' EXPR
746440a403fSchristos 	  { id24 (2, 0x18, 0x00);
747*b88e3e88Schristos 	    if (rx_uintop ($3, 4) && exp_val($3) == 1)
748440a403fSchristos 	      ;
749*b88e3e88Schristos 	    else if (rx_uintop ($3, 4) && exp_val($3) == 2)
750440a403fSchristos 	      F (1, 19, 1);
751440a403fSchristos 	    else
752440a403fSchristos 	      as_bad (_("RACW expects #1 or #2"));}
753440a403fSchristos 	| RACW '#' EXPR ',' ACC
754440a403fSchristos 	    { rx_check_v2 (); id24 (2, 0x18, 0x00); F ($5, 16, 1);
755*b88e3e88Schristos 	    if (rx_uintop ($3, 4) && exp_val($3) == 1)
756440a403fSchristos 	      ;
757*b88e3e88Schristos 	    else if (rx_uintop ($3, 4) && exp_val($3) == 2)
758440a403fSchristos 	      F (1, 19, 1);
759440a403fSchristos 	    else
760440a403fSchristos 	      as_bad (_("RACW expects #1 or #2"));}
761440a403fSchristos 
762440a403fSchristos /* ---------------------------------------------------------------------- */
763440a403fSchristos 
764440a403fSchristos 	| MOV bwl REG ',' '[' REG '+' ']'
765440a403fSchristos 	  { id24 (2, 0x20, 0); F ($2, 14, 2); F ($6, 16, 4); F ($3, 20, 4); }
766440a403fSchristos 	| MOV bwl REG ',' '[' '-' REG ']'
767440a403fSchristos 	  { id24 (2, 0x24, 0); F ($2, 14, 2); F ($7, 16, 4); F ($3, 20, 4); }
768440a403fSchristos 
769440a403fSchristos /* ---------------------------------------------------------------------- */
770440a403fSchristos 
771440a403fSchristos 	| MOV bwl '[' REG '+' ']' ',' REG
772440a403fSchristos 	  { id24 (2, 0x28, 0); F ($2, 14, 2); F ($4, 16, 4); F ($8, 20, 4); }
773440a403fSchristos 	| MOV bwl '[' '-' REG ']' ',' REG
774440a403fSchristos 	  { id24 (2, 0x2c, 0); F ($2, 14, 2); F ($5, 16, 4); F ($8, 20, 4); }
775440a403fSchristos 
776440a403fSchristos /* ---------------------------------------------------------------------- */
777440a403fSchristos 
778440a403fSchristos 	| MOVU bw '[' REG '+' ']' ','  REG
779440a403fSchristos 	  { id24 (2, 0x38, 0); F ($2, 15, 1); F ($4, 16, 4); F ($8, 20, 4); }
780440a403fSchristos 	| MOVU bw '[' '-' REG ']' ',' REG
781440a403fSchristos 	  { id24 (2, 0x3c, 0); F ($2, 15, 1); F ($5, 16, 4); F ($8, 20, 4); }
782440a403fSchristos 
783440a403fSchristos /* ---------------------------------------------------------------------- */
784440a403fSchristos 
785440a403fSchristos 	| ROTL { sub_op = 6; } op_shift_rot
786440a403fSchristos 	| ROTR { sub_op = 4; } op_shift_rot
787440a403fSchristos 	| REVW { sub_op = 5; } op_shift_rot
788440a403fSchristos 	| REVL { sub_op = 7; } op_shift_rot
789440a403fSchristos 
790440a403fSchristos /* ---------------------------------------------------------------------- */
791440a403fSchristos 
792440a403fSchristos 	| MVTC REG ',' CREG
793440a403fSchristos 	  { if ($4 == 13)
794440a403fSchristos 	      rx_check_v2 ();
795440a403fSchristos 	  id24 (2, 0x68, 0x00); F ($4 % 16, 20, 4); F ($4 / 16, 15, 1);
796440a403fSchristos 	    F ($2, 16, 4); }
797440a403fSchristos 
798440a403fSchristos /* ---------------------------------------------------------------------- */
799440a403fSchristos 
800440a403fSchristos 	| MVFC CREG ',' REG
801440a403fSchristos 	  { if ($2 == 13)
802440a403fSchristos 	    rx_check_v2 ();
803440a403fSchristos 	  id24 (2, 0x6a, 0); F ($2, 15, 5); F ($4, 20, 4); }
804440a403fSchristos 
805440a403fSchristos /* ---------------------------------------------------------------------- */
806440a403fSchristos 
807440a403fSchristos 	| ROTL '#' EXPR ',' REG
808440a403fSchristos 	  { id24 (2, 0x6e, 0); FE ($3, 15, 5); F ($5, 20, 4); }
809440a403fSchristos 	| ROTR '#' EXPR ',' REG
810440a403fSchristos 	  { id24 (2, 0x6c, 0); FE ($3, 15, 5); F ($5, 20, 4); }
811440a403fSchristos 
812440a403fSchristos /* ---------------------------------------------------------------------- */
813440a403fSchristos 
814440a403fSchristos 	| MVTC '#' EXPR ',' CREG
815440a403fSchristos 	  { if ($5 == 13)
816440a403fSchristos 	      rx_check_v2 ();
817440a403fSchristos 	    id24 (2, 0x73, 0x00); F ($5, 19, 5); IMM ($3, 12); }
818440a403fSchristos 
819440a403fSchristos /* ---------------------------------------------------------------------- */
820440a403fSchristos 
821440a403fSchristos 	| BMCND '#' EXPR ',' REG
822440a403fSchristos 	  { id24 (2, 0xe0, 0x00); F ($1, 16, 4); FE ($3, 11, 5);
823440a403fSchristos 	      F ($5, 20, 4); }
824440a403fSchristos 
825440a403fSchristos /* ---------------------------------------------------------------------- */
826440a403fSchristos 
827440a403fSchristos 	| BNOT '#' EXPR ',' REG
828440a403fSchristos 	  { id24 (2, 0xe0, 0xf0); FE ($3, 11, 5); F ($5, 20, 4); }
829440a403fSchristos 
830440a403fSchristos /* ---------------------------------------------------------------------- */
831440a403fSchristos 
832440a403fSchristos 	| MOV bwl REG ',' '[' REG ',' REG ']'
833440a403fSchristos 	  { id24 (3, 0x00, 0); F ($2, 10, 2); F ($6, 12, 4); F ($8, 16, 4); F ($3, 20, 4); }
834440a403fSchristos 
835440a403fSchristos 	| MOV bwl '[' REG ',' REG ']' ',' REG
836440a403fSchristos 	  { id24 (3, 0x40, 0); F ($2, 10, 2); F ($4, 12, 4); F ($6, 16, 4); F ($9, 20, 4); }
837440a403fSchristos 
838440a403fSchristos 	| MOVU bw '[' REG ',' REG ']' ',' REG
839440a403fSchristos 	  { id24 (3, 0xc0, 0); F ($2, 10, 2); F ($4, 12, 4); F ($6, 16, 4); F ($9, 20, 4); }
840440a403fSchristos 
841440a403fSchristos /* ---------------------------------------------------------------------- */
842440a403fSchristos 
843440a403fSchristos 	| SUB { sub_op = 0; } op_subadd
844440a403fSchristos 	| ADD { sub_op = 2; } op_subadd
845440a403fSchristos 	| MUL { sub_op = 3; } op_subadd
846440a403fSchristos 	| AND_ { sub_op = 4; } op_subadd
847440a403fSchristos 	| OR  { sub_op = 5; } op_subadd
848440a403fSchristos 
849440a403fSchristos /* ---------------------------------------------------------------------- */
850440a403fSchristos /* There is no SBB #imm so we fake it with ADC.  */
851440a403fSchristos 
852440a403fSchristos 	| SBB '#' EXPR ',' REG
853440a403fSchristos 	  { id24 (2, 0x70, 0x20); F ($5, 20, 4); NBIMM ($3, 12); }
854440a403fSchristos 
855440a403fSchristos /* ---------------------------------------------------------------------- */
856440a403fSchristos 
857440a403fSchristos 	| MOVCO REG ',' '[' REG ']'
858440a403fSchristos 	  { rx_check_v2 (); B3 (0xfd, 0x27, 0x00); F ($5, 16, 4); F ($2, 20, 4); }
859440a403fSchristos 
860440a403fSchristos /* ---------------------------------------------------------------------- */
861440a403fSchristos 
862440a403fSchristos 	| MOVLI '[' REG ']' ',' REG
863440a403fSchristos 	  { rx_check_v2 (); B3 (0xfd, 0x2f, 0x00); F ($3, 16, 4); F ($6, 20, 4); }
864440a403fSchristos 
865440a403fSchristos /* ---------------------------------------------------------------------- */
866440a403fSchristos 
867440a403fSchristos 	| EMACA REG ',' REG ',' ACC
868440a403fSchristos 	  { rx_check_v2 (); id24 (2, 0x07, 0x00); F ($2, 16, 4); F ($4, 20, 4); F ($6, 12, 1); }
869440a403fSchristos 	| EMSBA REG ',' REG ',' ACC
870440a403fSchristos 	  { rx_check_v2 (); id24 (2, 0x47, 0x00); F ($2, 16, 4); F ($4, 20, 4); F ($6, 12, 1); }
871440a403fSchristos 	| EMULA REG ',' REG ',' ACC
872440a403fSchristos 	  { rx_check_v2 (); id24 (2, 0x03, 0x00); F ($2, 16, 4); F ($4, 20, 4); F ($6, 12, 1); }
873440a403fSchristos 	| MACLH REG ',' REG ',' ACC
874440a403fSchristos 	  { rx_check_v2 (); id24 (2, 0x06, 0x00); F ($2, 16, 4); F ($4, 20, 4); F ($6, 12, 1); }
875440a403fSchristos 	| MSBHI REG ',' REG ',' ACC
876440a403fSchristos 	  { rx_check_v2 (); id24 (2, 0x44, 0x00); F ($2, 16, 4); F ($4, 20, 4); F ($6, 12, 1); }
877440a403fSchristos 	| MSBLH REG ',' REG ',' ACC
878440a403fSchristos 	  { rx_check_v2 (); id24 (2, 0x46, 0x00); F ($2, 16, 4); F ($4, 20, 4); F ($6, 12, 1); }
879440a403fSchristos 	| MSBLO REG ',' REG ',' ACC
880440a403fSchristos 	  { rx_check_v2 (); id24 (2, 0x45, 0x00); F ($2, 16, 4); F ($4, 20, 4); F ($6, 12, 1); }
881440a403fSchristos 	| MULLH REG ',' REG ',' ACC
882440a403fSchristos 	  { rx_check_v2 (); id24 (2, 0x02, 0x00); F ($2, 16, 4); F ($4, 20, 4); F ($6, 12, 1); }
883440a403fSchristos 	| MVFACGU { sub_op = 3; } mvfa_op
884440a403fSchristos 	| MVTACGU REG ',' ACC
885440a403fSchristos 	  { rx_check_v2 (); id24 (2, 0x17, 0x30); F ($4, 16, 1); F ($2, 20, 4); }
886440a403fSchristos 	| RACL '#' EXPR ',' ACC
887440a403fSchristos 	{ rx_check_v2 (); id24 (2, 0x19, 0x00); F ($5, 16, 1);
888440a403fSchristos 	    if (rx_uintop ($3, 4) && $3.X_add_number == 1)
889440a403fSchristos 	      ;
890440a403fSchristos 	    else if (rx_uintop ($3, 4) && $3.X_add_number == 2)
891440a403fSchristos 	      F (1, 19, 1);
892440a403fSchristos 	    else
893440a403fSchristos 	      as_bad (_("RACL expects #1 or #2"));}
894440a403fSchristos 	| RDACL '#' EXPR ',' ACC
895440a403fSchristos 	{ rx_check_v2 (); id24 (2, 0x19, 0x40); F ($5, 16, 1);
896440a403fSchristos 	    if (rx_uintop ($3, 4) && $3.X_add_number == 1)
897440a403fSchristos 	      ;
898440a403fSchristos 	    else if (rx_uintop ($3, 4) && $3.X_add_number == 2)
899440a403fSchristos 	      F (1, 19, 1);
900440a403fSchristos 	    else
901440a403fSchristos 	      as_bad (_("RDACL expects #1 or #2"));}
902440a403fSchristos 	| RDACW '#' EXPR ',' ACC
903440a403fSchristos 	{ rx_check_v2 (); id24 (2, 0x18, 0x40); F ($5, 16, 1);
904440a403fSchristos 	    if (rx_uintop ($3, 4) && $3.X_add_number == 1)
905440a403fSchristos 	      ;
906440a403fSchristos 	    else if (rx_uintop ($3, 4) && $3.X_add_number == 2)
907440a403fSchristos 	      F (1, 19, 1);
908440a403fSchristos 	    else
909440a403fSchristos 	      as_bad (_("RDACW expects #1 or #2"));}
910440a403fSchristos 
911440a403fSchristos /* ---------------------------------------------------------------------- */
912*b88e3e88Schristos 	| BFMOV { rx_check_v3(); sub_op = 1; } op_bfield
913*b88e3e88Schristos 	| BFMOVZ { rx_check_v3(); sub_op = 0; } op_bfield
914*b88e3e88Schristos 
915*b88e3e88Schristos /* ---------------------------------------------------------------------- */
916*b88e3e88Schristos 	| RSTR { rx_check_v3(); sub_op = 1; } op_save_rstr
917*b88e3e88Schristos 	| SAVE { rx_check_v3(); sub_op = 0; } op_save_rstr
918*b88e3e88Schristos 
919*b88e3e88Schristos /* ---------------------------------------------------------------------- */
920*b88e3e88Schristos 	| DABS { rx_check_dfpu(); sub_op = 0x0c; sub_op2 = 0x01; } double2_op
921*b88e3e88Schristos 	| DNEG { rx_check_dfpu(); sub_op = 0x0c; sub_op2 = 0x02; } double2_op
922*b88e3e88Schristos 	| DROUND { rx_check_dfpu(); sub_op = 0x0d; sub_op2 = 0x0d; } double2_op
923*b88e3e88Schristos 	| DSQRT { rx_check_dfpu(); sub_op = 0x0d; sub_op2 = 0x00; } double2_op
924*b88e3e88Schristos 	| DTOF { rx_check_dfpu(); sub_op = 0x0d; sub_op2 = 0x0c; } double2_op
925*b88e3e88Schristos 	| DTOI { rx_check_dfpu(); sub_op = 0x0d; sub_op2 = 0x08;} double2_op
926*b88e3e88Schristos 	| DTOU { rx_check_dfpu(); sub_op = 0x0d; sub_op2 = 0x09; } double2_op
927*b88e3e88Schristos 	| DADD { rx_check_dfpu(); sub_op = 0x00; } double3_op
928*b88e3e88Schristos 	| DDIV { rx_check_dfpu(); sub_op = 0x05; } double3_op
929*b88e3e88Schristos 	| DMUL { rx_check_dfpu(); sub_op = 0x02; } double3_op
930*b88e3e88Schristos 	| DSUB { rx_check_dfpu(); sub_op = 0x01; } double3_op
931*b88e3e88Schristos 	| DCMP DREG ',' DREG { rx_check_dfpu();
932*b88e3e88Schristos 	    B4(0x76, 0x90, 0x08, 0x00); F($1, 24, 4); F($2, 28, 4); F($4, 16, 4); }
933*b88e3e88Schristos 	| DMOV DOT_D REG ',' DREGH
934*b88e3e88Schristos 	{ rx_check_dfpu();
935*b88e3e88Schristos 	  B4(0xfd, 0x77, 0x80, 0x03); F($3, 20, 4); F($5, 24, 4); }
936*b88e3e88Schristos 	| DMOV DOT_L REG ',' DREGH
937*b88e3e88Schristos 	{ rx_check_dfpu();
938*b88e3e88Schristos 	  B4(0xfd, 0x77, 0x80, 0x02); F($3, 20, 4); F($5, 24, 4); }
939*b88e3e88Schristos 	| DMOV DOT_L REG ',' DREGL
940*b88e3e88Schristos 	{ rx_check_dfpu();
941*b88e3e88Schristos 	  B4(0xfd, 0x77, 0x80, 0x00); F($3, 20, 4); F($5, 24, 4); }
942*b88e3e88Schristos 	| DMOV DOT_L DREGH ',' REG
943*b88e3e88Schristos 	{ rx_check_dfpu();
944*b88e3e88Schristos 	  B4(0xfd, 0x75, 0x80, 0x02); F($3, 24, 4); F($5, 20, 4); }
945*b88e3e88Schristos 	| DMOV DOT_L DREGL ',' REG
946*b88e3e88Schristos 	{ rx_check_dfpu();
947*b88e3e88Schristos 	  B4(0xfd, 0x75, 0x80, 0x00); F($3, 24, 4); F($5, 20, 4); }
948*b88e3e88Schristos 	| DMOV DOT_D DREG ',' DREG
949*b88e3e88Schristos 	{ rx_check_dfpu();
950*b88e3e88Schristos 	  B4(0x76, 0x90, 0x0c, 0x00); F($3, 16, 4); F($5, 24, 4); }
951*b88e3e88Schristos 	| DMOV DOT_D DREG ',' '[' REG ']'
952*b88e3e88Schristos 	{ rx_check_dfpu();
953*b88e3e88Schristos 	  B4(0xfc, 0x78, 0x08, 0x00); F($6, 16, 4); F($3, 24, 4); }
954*b88e3e88Schristos 	| DMOV DOT_D DREG ',' disp '[' REG ']'
955*b88e3e88Schristos 	{ rx_check_dfpu();
956*b88e3e88Schristos 	  B3(0xfc, 0x78, 0x08); F($7, 16, 4); DSP($5, 14, DSIZE);
957*b88e3e88Schristos 	  POST($3 << 4); }
958*b88e3e88Schristos 	| DMOV DOT_D '[' REG ']' ',' DREG
959*b88e3e88Schristos 	{ rx_check_dfpu();
960*b88e3e88Schristos 	  B4(0xfc, 0xc8, 0x08, 0x00); F($4, 16, 4); F($7, 24, 4); }
961*b88e3e88Schristos 	| DMOV DOT_D disp '[' REG ']' ',' DREG
962*b88e3e88Schristos 	{ rx_check_dfpu();
963*b88e3e88Schristos 	  B3(0xfc, 0xc8, 0x08); F($5, 16, 4); DSP($3, 14, DSIZE);
964*b88e3e88Schristos 	  POST($8 << 4); }
965*b88e3e88Schristos 	| DMOV DOT_D '#' EXPR ',' DREGH
966*b88e3e88Schristos 	{ rx_check_dfpu();
967*b88e3e88Schristos 	  B3(0xf9, 0x03, 0x03); F($6, 16, 4); IMM($4, -1); }
968*b88e3e88Schristos 	| DMOV DOT_L '#' EXPR ',' DREGH
969*b88e3e88Schristos 	{ rx_check_dfpu();
970*b88e3e88Schristos 	  B3(0xf9, 0x03, 0x02); F($6, 16, 4); IMM($4, -1); }
971*b88e3e88Schristos 	| DMOV DOT_L '#' EXPR ',' DREGL
972*b88e3e88Schristos 	{ rx_check_dfpu();
973*b88e3e88Schristos 	  B3(0xf9, 0x03, 0x00); F($6, 16, 4); IMM($4, -1); }
974*b88e3e88Schristos 	| DPOPM DOT_D DREG '-' DREG
975*b88e3e88Schristos 	{ rx_check_dfpu();
976*b88e3e88Schristos 	  B3(0x75, 0xb8, 0x00); F($3, 16, 4); F($5 - $3, 20, 4); }
977*b88e3e88Schristos 	| DPOPM DOT_L DCREG '-' DCREG
978*b88e3e88Schristos 	{ rx_check_dfpu();
979*b88e3e88Schristos 	  B3(0x75, 0xa8, 0x00); F($3, 16, 4); F($5 - $3, 20, 4); }
980*b88e3e88Schristos 	| DPUSHM DOT_D DREG '-' DREG
981*b88e3e88Schristos 	{ rx_check_dfpu();
982*b88e3e88Schristos 	  B3(0x75, 0xb0, 0x00); F($3, 16, 4); F($5 - $3, 20, 4); }
983*b88e3e88Schristos 	| DPUSHM DOT_L DCREG '-' DCREG
984*b88e3e88Schristos 	{ rx_check_dfpu();
985*b88e3e88Schristos 	  B3(0x75, 0xa0, 0x00); F($3, 16, 4); F($5 - $3, 20, 4); }
986*b88e3e88Schristos 	| MVFDC DCREG ',' REG
987*b88e3e88Schristos 	{ rx_check_dfpu();
988*b88e3e88Schristos 	  B4(0xfd, 0x75, 0x80, 0x04); F($2, 24, 4); F($4, 20, 4); }
989*b88e3e88Schristos 	| MVFDR
990*b88e3e88Schristos 	{ rx_check_dfpu(); B3(0x75, 0x90, 0x1b); }
991*b88e3e88Schristos 	| MVTDC REG ',' DCREG
992*b88e3e88Schristos 	{ rx_check_dfpu();
993*b88e3e88Schristos 	  B4(0xfd, 0x77, 0x80, 0x04); F($2, 24, 4); F($4, 20, 4); }
994*b88e3e88Schristos 	| FTOD REG ',' DREG
995*b88e3e88Schristos 	{ rx_check_dfpu();
996*b88e3e88Schristos 	  B4(0xfd, 0x77, 0x80, 0x0a); F($2, 24, 4); F($4, 20, 4); }
997*b88e3e88Schristos 	| ITOD REG ',' DREG
998*b88e3e88Schristos 	{ rx_check_dfpu();
999*b88e3e88Schristos 	  B4(0xfd, 0x77, 0x80, 0x09); F($2, 24, 4); F($4, 20, 4); }
1000*b88e3e88Schristos 	| UTOD REG ',' DREG
1001*b88e3e88Schristos 	{ rx_check_dfpu();
1002*b88e3e88Schristos 	  B4(0xfd, 0x77, 0x80, 0x0d); F($2, 24, 4); F($4, 20, 4); }
1003*b88e3e88Schristos 
1004*b88e3e88Schristos /* ---------------------------------------------------------------------- */
1005440a403fSchristos 
1006440a403fSchristos 	;
1007440a403fSchristos 
1008440a403fSchristos /* ====================================================================== */
1009440a403fSchristos 
1010440a403fSchristos op_subadd
1011440a403fSchristos 	: REG ',' REG
1012440a403fSchristos 	  { B2 (0x43 + (sub_op<<2), 0); F ($1, 8, 4); F ($3, 12, 4); }
1013440a403fSchristos 	| disp '[' REG ']' DOT_UB ',' REG
1014440a403fSchristos 	  { B2 (0x40 + (sub_op<<2), 0); F ($3, 8, 4); F ($7, 12, 4); DSP ($1, 6, BSIZE); }
1015440a403fSchristos 	| disp '[' REG ']' memex ',' REG
1016440a403fSchristos 	  { B3 (MEMEX, sub_op<<2, 0); F ($5, 8, 2); F ($3, 16, 4); F ($7, 20, 4); DSP ($1, 14, sizemap[$5]); }
1017440a403fSchristos 	| REG ',' REG ',' REG
1018440a403fSchristos 	  { id24 (4, sub_op<<4, 0), F ($5, 12, 4), F ($1, 16, 4), F ($3, 20, 4); }
1019440a403fSchristos 	;
1020440a403fSchristos 
1021440a403fSchristos /* sbb, neg, adc, abs, max, min, div, divu, tst, not, xor, stz, stnz, emul, emulu */
1022440a403fSchristos 
1023440a403fSchristos op_dp20_rm_l
1024440a403fSchristos 	: REG ',' REG
1025440a403fSchristos 	  { id24 (1, 0x03 + (sub_op<<2), 0x00); F ($1, 16, 4); F ($3, 20, 4); }
1026440a403fSchristos 	| disp '[' REG ']' opt_l ',' REG
1027440a403fSchristos 	  { B4 (MEMEX, 0xa0, 0x00 + sub_op, 0x00);
1028440a403fSchristos 	  F ($3, 24, 4); F ($7, 28, 4); DSP ($1, 14, LSIZE); }
1029440a403fSchristos 	;
1030440a403fSchristos 
1031440a403fSchristos /* neg, adc, abs, max, min, div, divu, tst, not, xor, stz, stnz, emul, emulu */
1032440a403fSchristos 
1033440a403fSchristos op_dp20_rm
1034440a403fSchristos 	: REG ',' REG
1035440a403fSchristos 	  { id24 (1, 0x03 + (sub_op<<2), 0x00); F ($1, 16, 4); F ($3, 20, 4); }
1036440a403fSchristos 	| disp '[' REG ']' DOT_UB ',' REG
1037440a403fSchristos 	  { id24 (1, 0x00 + (sub_op<<2), 0x00); F ($3, 16, 4); F ($7, 20, 4); DSP ($1, 14, BSIZE); }
1038440a403fSchristos 	| disp '[' REG ']' memex ',' REG
1039440a403fSchristos 	  { B4 (MEMEX, 0x20 + ($5 << 6), 0x00 + sub_op, 0x00);
1040440a403fSchristos 	  F ($3, 24, 4); F ($7, 28, 4); DSP ($1, 14, sizemap[$5]); }
1041440a403fSchristos 	;
1042440a403fSchristos 
1043440a403fSchristos op_dp20_i
1044440a403fSchristos 	: '#' EXPR ',' REG
1045440a403fSchristos 	  { id24 (2, 0x70, sub_op<<4); F ($4, 20, 4); IMM ($2, 12); }
1046440a403fSchristos 	;
1047440a403fSchristos 
1048440a403fSchristos op_dp20_rim
1049440a403fSchristos 	: op_dp20_rm
1050440a403fSchristos 	| op_dp20_i
1051440a403fSchristos 	;
1052440a403fSchristos 
1053440a403fSchristos op_dp20_rim_l
1054440a403fSchristos 	: op_dp20_rm_l
1055440a403fSchristos 	| op_dp20_i
1056440a403fSchristos 	;
1057440a403fSchristos 
1058440a403fSchristos op_dp20_rr
1059440a403fSchristos 	: REG ',' REG
1060440a403fSchristos 	  { id24 (1, 0x03 + (sub_op<<2), 0x00); F ($1, 16, 4); F ($3, 20, 4); }
1061440a403fSchristos 	| REG
1062440a403fSchristos 	  { B2 (0x7e, sub_op2 << 4); F ($1, 12, 4); }
1063440a403fSchristos 	;
1064440a403fSchristos 
1065440a403fSchristos op_dp20_r
1066440a403fSchristos 	: REG ',' REG
1067440a403fSchristos 	  { id24 (1, 0x4b + (sub_op2<<2), 0x00); F ($1, 16, 4); F ($3, 20, 4); }
1068440a403fSchristos 	;
1069440a403fSchristos 
1070440a403fSchristos op_dp20_ri
1071440a403fSchristos 	: { rx_check_v2 (); }
1072440a403fSchristos 	  op_dp20_r
1073440a403fSchristos 	| op_dp20_i
1074440a403fSchristos 	;
1075440a403fSchristos 
1076440a403fSchristos /* xchg, utof, itof, emul, emulu */
1077440a403fSchristos op_xchg
1078440a403fSchristos 	: REG ',' REG
1079440a403fSchristos 	  { id24 (1, 0x03 + (sub_op<<2), 0); F ($1, 16, 4); F ($3, 20, 4); }
1080440a403fSchristos 	| disp '[' REG ']' DOT_UB ',' REG
1081440a403fSchristos 	  { id24 (1, 0x00 + (sub_op<<2), 0); F ($3, 16, 4); F ($7, 20, 4); DSP ($1, 14, BSIZE); }
1082440a403fSchristos 	| disp '[' REG ']' memex ',' REG
1083440a403fSchristos 	  { B4 (MEMEX, 0x20, 0x00 + sub_op, 0); F ($5, 8, 2); F ($3, 24, 4); F ($7, 28, 4);
1084440a403fSchristos 	    DSP ($1, 14, sizemap[$5]); }
1085440a403fSchristos 	;
1086440a403fSchristos 
1087440a403fSchristos /* 000:SHLR, 001:SHAR, 010:SHLL, 011:-, 100:ROTR, 101:REVW, 110:ROTL, 111:REVL */
1088440a403fSchristos op_shift_rot
1089440a403fSchristos 	: REG ',' REG
1090440a403fSchristos 	  { id24 (2, 0x60 + sub_op, 0); F ($1, 16, 4); F ($3, 20, 4); }
1091440a403fSchristos 	;
1092440a403fSchristos op_shift
1093440a403fSchristos 	: '#' EXPR ',' REG
1094440a403fSchristos 	  { B2 (0x68 + (sub_op<<1), 0); FE ($2, 7, 5); F ($4, 12, 4); }
1095440a403fSchristos 	| '#' EXPR ',' REG ',' REG
1096440a403fSchristos 	  { id24 (2, 0x80 + (sub_op << 5), 0); FE ($2, 11, 5); F ($4, 16, 4); F ($6, 20, 4); }
1097440a403fSchristos 	| op_shift_rot
1098440a403fSchristos 	;
1099440a403fSchristos 
1100440a403fSchristos float3_op
1101440a403fSchristos 	: '#' EXPR ',' REG
1102440a403fSchristos 	  { rx_check_float_support (); id24 (2, 0x72, sub_op << 4); F ($4, 20, 4); O4 ($2); }
1103440a403fSchristos 	| REG ',' REG
1104440a403fSchristos 	  { rx_check_float_support (); id24 (1, 0x83 + (sub_op << 2), 0); F ($1, 16, 4); F ($3, 20, 4); }
1105440a403fSchristos 	| disp '[' REG ']' opt_l ',' REG
1106440a403fSchristos 	  { rx_check_float_support (); id24 (1, 0x80 + (sub_op << 2), 0); F ($3, 16, 4); F ($7, 20, 4); DSP ($1, 14, LSIZE); }
1107440a403fSchristos 	| REG ',' REG ',' REG
1108440a403fSchristos 	  { rx_check_v2 (); id24 (4, 0x80 + (sub_op << 4), 0 ); F ($1, 16, 4); F ($3, 20, 4); F ($5, 12, 4); }
1109440a403fSchristos 	;
1110440a403fSchristos 
1111440a403fSchristos float2_op
1112440a403fSchristos 	: { rx_check_float_support (); }
1113440a403fSchristos 	  '#' EXPR ',' REG
1114440a403fSchristos 	  { id24 (2, 0x72, sub_op << 4); F ($5, 20, 4); O4 ($3); }
1115440a403fSchristos 	| float2_op_ni
1116440a403fSchristos 	;
1117440a403fSchristos 
1118440a403fSchristos float2_op_ni
1119440a403fSchristos 	: { rx_check_float_support (); }
1120440a403fSchristos 	  REG ',' REG
1121440a403fSchristos 	  { id24 (1, 0x83 + (sub_op << 2), 0); F ($2, 16, 4); F ($4, 20, 4); }
1122440a403fSchristos 	| { rx_check_float_support (); }
1123440a403fSchristos 	  disp '[' REG ']' opt_l ',' REG
1124440a403fSchristos 	  { id24 (1, 0x80 + (sub_op << 2), 0); F ($4, 16, 4); F ($8, 20, 4); DSP ($2, 14, LSIZE); }
1125440a403fSchristos 	;
1126440a403fSchristos 
1127440a403fSchristos mvfa_op
1128440a403fSchristos 	: { rx_check_v2 (); }
1129440a403fSchristos 	  '#' EXPR ',' ACC ',' REG
1130440a403fSchristos 	  { id24 (2, 0x1e, sub_op << 4); F ($7, 20, 4); F ($5, 16, 1);
1131440a403fSchristos 	    if (rx_uintop ($3, 4))
1132440a403fSchristos 	      {
1133440a403fSchristos 		switch (exp_val ($3))
1134440a403fSchristos 		  {
1135440a403fSchristos 		  case 0:
1136440a403fSchristos 		    F (1, 15, 1);
1137440a403fSchristos 		    break;
1138440a403fSchristos 		  case 1:
1139440a403fSchristos 		    F (1, 15, 1);
1140440a403fSchristos 		    F (1, 17, 1);
1141440a403fSchristos 		    break;
1142440a403fSchristos 		  case 2:
1143440a403fSchristos 		    break;
1144440a403fSchristos 		  default:
1145440a403fSchristos 		    as_bad (_("IMM expects #0 to #2"));}
1146440a403fSchristos 	      } else
1147440a403fSchristos 	        as_bad (_("IMM expects #0 to #2"));}
1148440a403fSchristos 	;
1149440a403fSchristos 
1150*b88e3e88Schristos op_xor
1151*b88e3e88Schristos 	: op_dp20_rim
1152*b88e3e88Schristos 	| REG ',' REG ',' REG
1153*b88e3e88Schristos 	  { rx_check_v3(); B3(0xff,0x60,0x00), F ($5, 12, 4), F ($1, 16, 4), F ($3, 20, 4); }
1154*b88e3e88Schristos 	;
1155*b88e3e88Schristos 
1156*b88e3e88Schristos op_bfield
1157*b88e3e88Schristos 	: { rx_check_v3(); }
1158*b88e3e88Schristos 	  '#' EXPR ',' '#' EXPR ',' '#' EXPR ',' REG ',' REG
1159*b88e3e88Schristos 	  { rx_range($3, 0, 31); rx_range($6, 0, 31); rx_range($9, 1, 31);
1160*b88e3e88Schristos 	    B3(0xfc, 0x5a + (sub_op << 2), 0); F($11, 16, 4); F($13, 20, 4);
1161*b88e3e88Schristos 	  rx_bfield($3, $6, $9);}
1162*b88e3e88Schristos 	;
1163*b88e3e88Schristos 
1164*b88e3e88Schristos op_save_rstr
1165*b88e3e88Schristos 	: '#' EXPR
1166*b88e3e88Schristos 	  { B3(0xfd,0x76,0xe0 + (sub_op << 4)); UO1($2); }
1167*b88e3e88Schristos 	| REG
1168*b88e3e88Schristos 	  { B4(0xfd,0x76,0xc0 + (sub_op << 4), 0x00); F($1, 20, 4); }
1169*b88e3e88Schristos 	;
1170*b88e3e88Schristos 
1171*b88e3e88Schristos double2_op
1172*b88e3e88Schristos 	: DREG ',' DREG
1173*b88e3e88Schristos 	{ B4(0x76, 0x90, sub_op, sub_op2); F($1, 16, 4); F($3, 24, 4);}
1174*b88e3e88Schristos 
1175*b88e3e88Schristos double3_op
1176*b88e3e88Schristos 	: DREG ',' DREG ',' DREG
1177*b88e3e88Schristos 	{ B4(0x76, 0x90, sub_op, 0x00); F($1, 28, 4); F($3, 16,4); F($5, 24, 4);}
1178*b88e3e88Schristos 
1179440a403fSchristos /* ====================================================================== */
1180440a403fSchristos 
1181440a403fSchristos disp	:      { $$ = zero_expr (); }
1182440a403fSchristos 	| EXPR { $$ = $1; }
1183440a403fSchristos 	;
1184440a403fSchristos 
1185440a403fSchristos flag	: { need_flag = 1; } FLAG { need_flag = 0; $$ = $2; }
1186440a403fSchristos 	;
1187440a403fSchristos 
1188440a403fSchristos /* DOT_UB is not listed here, it's handled with a separate pattern.  */
1189440a403fSchristos /* Use sizemap[$n] to get LSIZE etc.  */
1190440a403fSchristos memex	: DOT_B  { $$ = 0; }
1191440a403fSchristos 	| DOT_W  { $$ = 1; }
1192440a403fSchristos 	|        { $$ = 2; }
1193440a403fSchristos 	| DOT_L  { $$ = 2; }
1194440a403fSchristos 	| DOT_UW { $$ = 3; }
1195440a403fSchristos 	;
1196440a403fSchristos 
1197440a403fSchristos bwl	:       { $$ = LSIZE; }
1198440a403fSchristos 	| DOT_B { $$ = BSIZE; }
1199440a403fSchristos 	| DOT_W { $$ = WSIZE; }
1200440a403fSchristos 	| DOT_L { $$ = LSIZE; }
1201440a403fSchristos 	;
1202440a403fSchristos 
1203440a403fSchristos bw	:       { $$ = 1; }
1204440a403fSchristos 	| DOT_B { $$ = 0; }
1205440a403fSchristos 	| DOT_W { $$ = 1; }
1206440a403fSchristos 	;
1207440a403fSchristos 
1208440a403fSchristos opt_l	: 	{}
1209440a403fSchristos 	| DOT_L {}
1210440a403fSchristos 	;
1211440a403fSchristos 
1212440a403fSchristos opt_b	: 	{}
1213440a403fSchristos 	| DOT_B {}
1214440a403fSchristos 	;
1215440a403fSchristos 
1216440a403fSchristos %%
1217440a403fSchristos /* ====================================================================== */
1218440a403fSchristos 
1219440a403fSchristos static struct
1220440a403fSchristos {
1221440a403fSchristos   const char * string;
1222440a403fSchristos   int          token;
1223440a403fSchristos   int          val;
1224440a403fSchristos }
1225440a403fSchristos token_table[] =
1226440a403fSchristos {
1227440a403fSchristos   { "r0", REG, 0 },
1228440a403fSchristos   { "r1", REG, 1 },
1229440a403fSchristos   { "r2", REG, 2 },
1230440a403fSchristos   { "r3", REG, 3 },
1231440a403fSchristos   { "r4", REG, 4 },
1232440a403fSchristos   { "r5", REG, 5 },
1233440a403fSchristos   { "r6", REG, 6 },
1234440a403fSchristos   { "r7", REG, 7 },
1235440a403fSchristos   { "r8", REG, 8 },
1236440a403fSchristos   { "r9", REG, 9 },
1237440a403fSchristos   { "r10", REG, 10 },
1238440a403fSchristos   { "r11", REG, 11 },
1239440a403fSchristos   { "r12", REG, 12 },
1240440a403fSchristos   { "r13", REG, 13 },
1241440a403fSchristos   { "r14", REG, 14 },
1242440a403fSchristos   { "r15", REG, 15 },
1243440a403fSchristos 
1244440a403fSchristos   { "psw", CREG, 0 },
1245440a403fSchristos   { "pc", CREG, 1 },
1246440a403fSchristos   { "usp", CREG, 2 },
1247440a403fSchristos   { "fpsw", CREG, 3 },
1248440a403fSchristos   /* reserved */
1249440a403fSchristos   /* reserved */
1250440a403fSchristos   /* reserved */
1251440a403fSchristos   { "wr", CREG, 7 },
1252440a403fSchristos 
1253440a403fSchristos   { "bpsw", CREG, 8 },
1254440a403fSchristos   { "bpc", CREG, 9 },
1255440a403fSchristos   { "isp", CREG, 10 },
1256440a403fSchristos   { "fintv", CREG, 11 },
1257440a403fSchristos   { "intb", CREG, 12 },
1258440a403fSchristos   { "extb", CREG, 13 },
1259440a403fSchristos 
1260440a403fSchristos   { "pbp", CREG, 16 },
1261440a403fSchristos   { "pben", CREG, 17 },
1262440a403fSchristos 
1263440a403fSchristos   { "bbpsw", CREG, 24 },
1264440a403fSchristos   { "bbpc", CREG, 25 },
1265440a403fSchristos 
1266*b88e3e88Schristos   { "dr0", DREG, 0 },
1267*b88e3e88Schristos   { "dr1", DREG, 1 },
1268*b88e3e88Schristos   { "dr2", DREG, 2 },
1269*b88e3e88Schristos   { "dr3", DREG, 3 },
1270*b88e3e88Schristos   { "dr4", DREG, 4 },
1271*b88e3e88Schristos   { "dr5", DREG, 5 },
1272*b88e3e88Schristos   { "dr6", DREG, 6 },
1273*b88e3e88Schristos   { "dr7", DREG, 7 },
1274*b88e3e88Schristos   { "dr8", DREG, 8 },
1275*b88e3e88Schristos   { "dr9", DREG, 9 },
1276*b88e3e88Schristos   { "dr10", DREG, 10 },
1277*b88e3e88Schristos   { "dr11", DREG, 11 },
1278*b88e3e88Schristos   { "dr12", DREG, 12 },
1279*b88e3e88Schristos   { "dr13", DREG, 13 },
1280*b88e3e88Schristos   { "dr14", DREG, 14 },
1281*b88e3e88Schristos   { "dr15", DREG, 15 },
1282*b88e3e88Schristos 
1283*b88e3e88Schristos   { "drh0", DREGH, 0 },
1284*b88e3e88Schristos   { "drh1", DREGH, 1 },
1285*b88e3e88Schristos   { "drh2", DREGH, 2 },
1286*b88e3e88Schristos   { "drh3", DREGH, 3 },
1287*b88e3e88Schristos   { "drh4", DREGH, 4 },
1288*b88e3e88Schristos   { "drh5", DREGH, 5 },
1289*b88e3e88Schristos   { "drh6", DREGH, 6 },
1290*b88e3e88Schristos   { "drh7", DREGH, 7 },
1291*b88e3e88Schristos   { "drh8", DREGH, 8 },
1292*b88e3e88Schristos   { "drh9", DREGH, 9 },
1293*b88e3e88Schristos   { "drh10", DREGH, 10 },
1294*b88e3e88Schristos   { "drh11", DREGH, 11 },
1295*b88e3e88Schristos   { "drh12", DREGH, 12 },
1296*b88e3e88Schristos   { "drh13", DREGH, 13 },
1297*b88e3e88Schristos   { "drh14", DREGH, 14 },
1298*b88e3e88Schristos   { "drh15", DREGH, 15 },
1299*b88e3e88Schristos 
1300*b88e3e88Schristos   { "drl0", DREGL, 0 },
1301*b88e3e88Schristos   { "drl1", DREGL, 1 },
1302*b88e3e88Schristos   { "drl2", DREGL, 2 },
1303*b88e3e88Schristos   { "drl3", DREGL, 3 },
1304*b88e3e88Schristos   { "drl4", DREGL, 4 },
1305*b88e3e88Schristos   { "drl5", DREGL, 5 },
1306*b88e3e88Schristos   { "drl6", DREGL, 6 },
1307*b88e3e88Schristos   { "drl7", DREGL, 7 },
1308*b88e3e88Schristos   { "drl8", DREGL, 8 },
1309*b88e3e88Schristos   { "drl9", DREGL, 9 },
1310*b88e3e88Schristos   { "drl10", DREGL, 10 },
1311*b88e3e88Schristos   { "drl11", DREGL, 11 },
1312*b88e3e88Schristos   { "drl12", DREGL, 12 },
1313*b88e3e88Schristos   { "drl13", DREGL, 13 },
1314*b88e3e88Schristos   { "drl14", DREGL, 14 },
1315*b88e3e88Schristos   { "drl15", DREGL, 15 },
1316*b88e3e88Schristos 
1317*b88e3e88Schristos   { "DPSW", DCREG, 0 },
1318*b88e3e88Schristos   { "DCMR", DCREG, 1 },
1319*b88e3e88Schristos   { "DCENT", DCREG, 2 },
1320*b88e3e88Schristos   { "DEPC", DCREG, 3 },
1321*b88e3e88Schristos   { "DCR0", DCREG, 0 },
1322*b88e3e88Schristos   { "DCR1", DCREG, 1 },
1323*b88e3e88Schristos   { "DCR2", DCREG, 2 },
1324*b88e3e88Schristos   { "DCR3", DCREG, 3 },
1325*b88e3e88Schristos 
1326440a403fSchristos   { ".s", DOT_S, 0 },
1327440a403fSchristos   { ".b", DOT_B, 0 },
1328440a403fSchristos   { ".w", DOT_W, 0 },
1329440a403fSchristos   { ".l", DOT_L, 0 },
1330440a403fSchristos   { ".a", DOT_A , 0},
1331440a403fSchristos   { ".ub", DOT_UB, 0 },
1332440a403fSchristos   { ".uw", DOT_UW , 0},
1333*b88e3e88Schristos   { ".d", DOT_D , 0},
1334440a403fSchristos 
1335440a403fSchristos   { "c", FLAG, 0 },
1336440a403fSchristos   { "z", FLAG, 1 },
1337440a403fSchristos   { "s", FLAG, 2 },
1338440a403fSchristos   { "o", FLAG, 3 },
1339440a403fSchristos   { "i", FLAG, 8 },
1340440a403fSchristos   { "u", FLAG, 9 },
1341440a403fSchristos 
1342440a403fSchristos   { "a0", ACC, 0 },
1343440a403fSchristos   { "a1", ACC, 1 },
1344440a403fSchristos 
1345440a403fSchristos #define OPC(x) { #x, x, IS_OPCODE }
1346440a403fSchristos   OPC(ABS),
1347440a403fSchristos   OPC(ADC),
1348440a403fSchristos   OPC(ADD),
1349440a403fSchristos   { "and", AND_, IS_OPCODE },
1350440a403fSchristos   OPC(BCLR),
1351440a403fSchristos   OPC(BCND),
1352*b88e3e88Schristos   OPC(BFMOV),
1353*b88e3e88Schristos   OPC(BFMOVZ),
1354440a403fSchristos   OPC(BMCND),
1355440a403fSchristos   OPC(BNOT),
1356440a403fSchristos   OPC(BRA),
1357440a403fSchristos   OPC(BRK),
1358440a403fSchristos   OPC(BSET),
1359440a403fSchristos   OPC(BSR),
1360440a403fSchristos   OPC(BTST),
1361440a403fSchristos   OPC(CLRPSW),
1362440a403fSchristos   OPC(CMP),
1363*b88e3e88Schristos   OPC(DABS),
1364*b88e3e88Schristos   OPC(DADD),
1365440a403fSchristos   OPC(DBT),
1366*b88e3e88Schristos   OPC(DDIV),
1367440a403fSchristos   OPC(DIV),
1368440a403fSchristos   OPC(DIVU),
1369*b88e3e88Schristos   OPC(DMOV),
1370*b88e3e88Schristos   OPC(DMUL),
1371*b88e3e88Schristos   OPC(DNEG),
1372*b88e3e88Schristos   OPC(DPOPM),
1373*b88e3e88Schristos   OPC(DPUSHM),
1374*b88e3e88Schristos   OPC(DROUND),
1375*b88e3e88Schristos   OPC(DSQRT),
1376*b88e3e88Schristos   OPC(DSUB),
1377*b88e3e88Schristos   OPC(DTOF),
1378*b88e3e88Schristos   OPC(DTOI),
1379*b88e3e88Schristos   OPC(DTOU),
1380440a403fSchristos   OPC(EDIV),
1381440a403fSchristos   OPC(EDIVU),
1382440a403fSchristos   OPC(EMACA),
1383440a403fSchristos   OPC(EMSBA),
1384440a403fSchristos   OPC(EMUL),
1385440a403fSchristos   OPC(EMULA),
1386440a403fSchristos   OPC(EMULU),
1387440a403fSchristos   OPC(FADD),
1388440a403fSchristos   OPC(FCMP),
1389440a403fSchristos   OPC(FDIV),
1390440a403fSchristos   OPC(FMUL),
1391440a403fSchristos   OPC(FREIT),
1392440a403fSchristos   OPC(FSQRT),
1393*b88e3e88Schristos   OPC(FTOD),
1394440a403fSchristos   OPC(FTOU),
1395440a403fSchristos   OPC(FSUB),
1396440a403fSchristos   OPC(FTOI),
1397440a403fSchristos   OPC(INT),
1398*b88e3e88Schristos   OPC(ITOD),
1399440a403fSchristos   OPC(ITOF),
1400440a403fSchristos   OPC(JMP),
1401440a403fSchristos   OPC(JSR),
1402440a403fSchristos   OPC(MVFACGU),
1403440a403fSchristos   OPC(MVFACHI),
1404440a403fSchristos   OPC(MVFACMI),
1405440a403fSchristos   OPC(MVFACLO),
1406440a403fSchristos   OPC(MVFC),
1407*b88e3e88Schristos   OPC(MVFDC),
1408*b88e3e88Schristos   OPC(MVFDR),
1409*b88e3e88Schristos   OPC(MVTDC),
1410440a403fSchristos   OPC(MVTACGU),
1411440a403fSchristos   OPC(MVTACHI),
1412440a403fSchristos   OPC(MVTACLO),
1413440a403fSchristos   OPC(MVTC),
1414440a403fSchristos   OPC(MVTIPL),
1415440a403fSchristos   OPC(MACHI),
1416440a403fSchristos   OPC(MACLO),
1417440a403fSchristos   OPC(MACLH),
1418440a403fSchristos   OPC(MAX),
1419440a403fSchristos   OPC(MIN),
1420440a403fSchristos   OPC(MOV),
1421440a403fSchristos   OPC(MOVCO),
1422440a403fSchristos   OPC(MOVLI),
1423440a403fSchristos   OPC(MOVU),
1424440a403fSchristos   OPC(MSBHI),
1425440a403fSchristos   OPC(MSBLH),
1426440a403fSchristos   OPC(MSBLO),
1427440a403fSchristos   OPC(MUL),
1428440a403fSchristos   OPC(MULHI),
1429440a403fSchristos   OPC(MULLH),
1430440a403fSchristos   OPC(MULLO),
1431440a403fSchristos   OPC(MULU),
1432440a403fSchristos   OPC(NEG),
1433440a403fSchristos   OPC(NOP),
1434440a403fSchristos   OPC(NOT),
1435440a403fSchristos   OPC(OR),
1436440a403fSchristos   OPC(POP),
1437440a403fSchristos   OPC(POPC),
1438440a403fSchristos   OPC(POPM),
1439440a403fSchristos   OPC(PUSH),
1440440a403fSchristos   OPC(PUSHA),
1441440a403fSchristos   OPC(PUSHC),
1442440a403fSchristos   OPC(PUSHM),
1443440a403fSchristos   OPC(RACL),
1444440a403fSchristos   OPC(RACW),
1445440a403fSchristos   OPC(RDACL),
1446440a403fSchristos   OPC(RDACW),
1447440a403fSchristos   OPC(REIT),
1448440a403fSchristos   OPC(REVL),
1449440a403fSchristos   OPC(REVW),
1450440a403fSchristos   OPC(RMPA),
1451440a403fSchristos   OPC(ROLC),
1452440a403fSchristos   OPC(RORC),
1453440a403fSchristos   OPC(ROTL),
1454440a403fSchristos   OPC(ROTR),
1455440a403fSchristos   OPC(ROUND),
1456*b88e3e88Schristos   OPC(RSTR),
1457440a403fSchristos   OPC(RTE),
1458440a403fSchristos   OPC(RTFI),
1459440a403fSchristos   OPC(RTS),
1460440a403fSchristos   OPC(RTSD),
1461440a403fSchristos   OPC(SAT),
1462440a403fSchristos   OPC(SATR),
1463*b88e3e88Schristos   OPC(SAVE),
1464440a403fSchristos   OPC(SBB),
1465440a403fSchristos   OPC(SCCND),
1466440a403fSchristos   OPC(SCMPU),
1467440a403fSchristos   OPC(SETPSW),
1468440a403fSchristos   OPC(SHAR),
1469440a403fSchristos   OPC(SHLL),
1470440a403fSchristos   OPC(SHLR),
1471440a403fSchristos   OPC(SMOVB),
1472440a403fSchristos   OPC(SMOVF),
1473440a403fSchristos   OPC(SMOVU),
1474440a403fSchristos   OPC(SSTR),
1475440a403fSchristos   OPC(STNZ),
1476440a403fSchristos   OPC(STOP),
1477440a403fSchristos   OPC(STZ),
1478440a403fSchristos   OPC(SUB),
1479440a403fSchristos   OPC(SUNTIL),
1480440a403fSchristos   OPC(SWHILE),
1481440a403fSchristos   OPC(TST),
1482*b88e3e88Schristos   OPC(UTOD),
1483440a403fSchristos   OPC(UTOF),
1484440a403fSchristos   OPC(WAIT),
1485440a403fSchristos   OPC(XCHG),
1486440a403fSchristos   OPC(XOR),
1487440a403fSchristos };
1488440a403fSchristos 
1489440a403fSchristos #define NUM_TOKENS (sizeof (token_table) / sizeof (token_table[0]))
1490440a403fSchristos 
1491440a403fSchristos static struct
1492440a403fSchristos {
1493440a403fSchristos   const char * string;
1494440a403fSchristos   int    token;
1495440a403fSchristos }
1496440a403fSchristos condition_opcode_table[] =
1497440a403fSchristos {
1498440a403fSchristos   { "b", BCND },
1499440a403fSchristos   { "bm", BMCND },
1500440a403fSchristos   { "sc", SCCND },
1501440a403fSchristos };
1502440a403fSchristos 
1503440a403fSchristos #define NUM_CONDITION_OPCODES (sizeof (condition_opcode_table) / sizeof (condition_opcode_table[0]))
1504440a403fSchristos 
1505*b88e3e88Schristos struct condition_symbol
1506440a403fSchristos {
1507440a403fSchristos   const char * string;
1508440a403fSchristos   int    val;
1509*b88e3e88Schristos };
1510*b88e3e88Schristos 
1511*b88e3e88Schristos static struct condition_symbol condition_table[] =
1512440a403fSchristos {
1513440a403fSchristos   { "z", 0 },
1514440a403fSchristos   { "eq", 0 },
1515440a403fSchristos   { "geu",  2 },
1516440a403fSchristos   { "c",  2 },
1517440a403fSchristos   { "gtu", 4 },
1518440a403fSchristos   { "pz", 6 },
1519440a403fSchristos   { "ge", 8 },
1520440a403fSchristos   { "gt", 10 },
1521440a403fSchristos   { "o",  12},
1522440a403fSchristos   /* always = 14 */
1523440a403fSchristos   { "nz", 1 },
1524440a403fSchristos   { "ne", 1 },
1525440a403fSchristos   { "ltu", 3 },
1526440a403fSchristos   { "nc", 3 },
1527440a403fSchristos   { "leu", 5 },
1528440a403fSchristos   { "n", 7 },
1529440a403fSchristos   { "lt", 9 },
1530440a403fSchristos   { "le", 11 },
1531*b88e3e88Schristos   { "no", 13 },
1532440a403fSchristos   /* never = 15 */
1533440a403fSchristos };
1534440a403fSchristos 
1535*b88e3e88Schristos static struct condition_symbol double_condition_table[] =
1536*b88e3e88Schristos {
1537*b88e3e88Schristos   { "un", 1 },
1538*b88e3e88Schristos   { "eq", 2 },
1539*b88e3e88Schristos   { "lt", 4 },
1540*b88e3e88Schristos   { "le", 6 },
1541*b88e3e88Schristos };
1542*b88e3e88Schristos 
1543440a403fSchristos #define NUM_CONDITIONS (sizeof (condition_table) / sizeof (condition_table[0]))
1544*b88e3e88Schristos #define NUM_DOUBLE_CONDITIONS (sizeof (double_condition_table) / sizeof (double_condition_table[0]))
1545440a403fSchristos 
1546440a403fSchristos void
rx_lex_init(char * beginning,char * ending)1547440a403fSchristos rx_lex_init (char * beginning, char * ending)
1548440a403fSchristos {
1549440a403fSchristos   rx_init_start = beginning;
1550440a403fSchristos   rx_lex_start = beginning;
1551440a403fSchristos   rx_lex_end = ending;
1552440a403fSchristos   rx_in_brackets = 0;
1553440a403fSchristos   rx_last_token = 0;
1554440a403fSchristos 
1555440a403fSchristos   setbuf (stdout, 0);
1556440a403fSchristos }
1557440a403fSchristos 
1558440a403fSchristos static int
check_condition(const char * base,struct condition_symbol * t,unsigned int num)1559*b88e3e88Schristos check_condition (const char * base, struct condition_symbol *t, unsigned int num)
1560440a403fSchristos {
1561440a403fSchristos   char * cp;
1562440a403fSchristos   unsigned int i;
1563440a403fSchristos 
1564440a403fSchristos   if ((unsigned) (rx_lex_end - rx_lex_start) < strlen (base) + 1)
1565440a403fSchristos     return 0;
1566440a403fSchristos   if (memcmp (rx_lex_start, base, strlen (base)))
1567440a403fSchristos     return 0;
1568440a403fSchristos   cp = rx_lex_start + strlen (base);
1569*b88e3e88Schristos   for (i = 0; i < num; i ++)
1570440a403fSchristos     {
1571*b88e3e88Schristos       if (strcasecmp (cp, t[i].string) == 0)
1572440a403fSchristos 	{
1573*b88e3e88Schristos 	  rx_lval.regno = t[i].val;
1574440a403fSchristos 	  return 1;
1575440a403fSchristos 	}
1576440a403fSchristos     }
1577440a403fSchristos   return 0;
1578440a403fSchristos }
1579440a403fSchristos 
1580440a403fSchristos static int
rx_lex(void)1581440a403fSchristos rx_lex (void)
1582440a403fSchristos {
1583440a403fSchristos   unsigned int ci;
1584440a403fSchristos   char * save_input_pointer;
1585440a403fSchristos 
1586440a403fSchristos   while (ISSPACE (*rx_lex_start)
1587440a403fSchristos 	 && rx_lex_start != rx_lex_end)
1588440a403fSchristos     rx_lex_start ++;
1589440a403fSchristos 
1590440a403fSchristos   rx_last_exp_start = rx_lex_start;
1591440a403fSchristos 
1592440a403fSchristos   if (rx_lex_start == rx_lex_end)
1593440a403fSchristos     return 0;
1594440a403fSchristos 
1595440a403fSchristos   if (ISALPHA (*rx_lex_start)
1596440a403fSchristos       || (rx_pid_register != -1 && memcmp (rx_lex_start, "%pidreg", 7) == 0)
1597440a403fSchristos       || (rx_gp_register != -1 && memcmp (rx_lex_start, "%gpreg", 6) == 0)
1598440a403fSchristos       || (*rx_lex_start == '.' && ISALPHA (rx_lex_start[1])))
1599440a403fSchristos     {
1600440a403fSchristos       unsigned int i;
1601440a403fSchristos       char * e;
1602440a403fSchristos       char save;
1603440a403fSchristos 
1604440a403fSchristos       for (e = rx_lex_start + 1;
1605440a403fSchristos 	   e < rx_lex_end && ISALNUM (*e);
1606440a403fSchristos 	   e ++)
1607440a403fSchristos 	;
1608440a403fSchristos       save = *e;
1609440a403fSchristos       *e = 0;
1610440a403fSchristos 
1611440a403fSchristos       if (strcmp (rx_lex_start, "%pidreg") == 0)
1612440a403fSchristos 	{
1613440a403fSchristos 	  {
1614440a403fSchristos 	    rx_lval.regno = rx_pid_register;
1615440a403fSchristos 	    *e = save;
1616440a403fSchristos 	    rx_lex_start = e;
1617440a403fSchristos 	    rx_last_token = REG;
1618440a403fSchristos 	    return REG;
1619440a403fSchristos 	  }
1620440a403fSchristos 	}
1621440a403fSchristos 
1622440a403fSchristos       if (strcmp (rx_lex_start, "%gpreg") == 0)
1623440a403fSchristos 	{
1624440a403fSchristos 	  {
1625440a403fSchristos 	    rx_lval.regno = rx_gp_register;
1626440a403fSchristos 	    *e = save;
1627440a403fSchristos 	    rx_lex_start = e;
1628440a403fSchristos 	    rx_last_token = REG;
1629440a403fSchristos 	    return REG;
1630440a403fSchristos 	  }
1631440a403fSchristos 	}
1632440a403fSchristos 
1633440a403fSchristos       if (rx_last_token == 0)
1634*b88e3e88Schristos 	{
1635440a403fSchristos 	  for (ci = 0; ci < NUM_CONDITION_OPCODES; ci ++)
1636*b88e3e88Schristos 	    if (check_condition (condition_opcode_table[ci].string,
1637*b88e3e88Schristos 				 condition_table, NUM_CONDITIONS))
1638440a403fSchristos 	      {
1639440a403fSchristos 		*e = save;
1640440a403fSchristos 		rx_lex_start = e;
1641440a403fSchristos 		rx_last_token = condition_opcode_table[ci].token;
1642440a403fSchristos 		return condition_opcode_table[ci].token;
1643440a403fSchristos 	      }
1644*b88e3e88Schristos 	  if  (check_condition ("dcmp", double_condition_table,
1645*b88e3e88Schristos 				NUM_DOUBLE_CONDITIONS))
1646*b88e3e88Schristos 	    {
1647*b88e3e88Schristos 	      *e = save;
1648*b88e3e88Schristos 	      rx_lex_start = e;
1649*b88e3e88Schristos 	      rx_last_token = DCMP;
1650*b88e3e88Schristos 	      return DCMP;
1651*b88e3e88Schristos 	    }
1652*b88e3e88Schristos 	}
1653440a403fSchristos 
1654440a403fSchristos       for (i = 0; i < NUM_TOKENS; i++)
1655440a403fSchristos 	if (strcasecmp (rx_lex_start, token_table[i].string) == 0
1656440a403fSchristos 	    && !(token_table[i].val == IS_OPCODE && rx_last_token != 0)
1657440a403fSchristos 	    && !(token_table[i].token == FLAG && !need_flag))
1658440a403fSchristos 	  {
1659440a403fSchristos 	    rx_lval.regno = token_table[i].val;
1660440a403fSchristos 	    *e = save;
1661440a403fSchristos 	    rx_lex_start = e;
1662440a403fSchristos 	    rx_last_token = token_table[i].token;
1663440a403fSchristos 	    return token_table[i].token;
1664440a403fSchristos 	  }
1665440a403fSchristos       *e = save;
1666440a403fSchristos     }
1667440a403fSchristos 
1668440a403fSchristos   if (rx_last_token == 0)
1669440a403fSchristos     {
1670440a403fSchristos       rx_last_token = UNKNOWN_OPCODE;
1671440a403fSchristos       return UNKNOWN_OPCODE;
1672440a403fSchristos     }
1673440a403fSchristos 
1674440a403fSchristos   if (rx_last_token == UNKNOWN_OPCODE)
1675440a403fSchristos     return 0;
1676440a403fSchristos 
1677440a403fSchristos   if (*rx_lex_start == '[')
1678440a403fSchristos     rx_in_brackets = 1;
1679440a403fSchristos   if (*rx_lex_start == ']')
1680440a403fSchristos     rx_in_brackets = 0;
1681440a403fSchristos 
1682440a403fSchristos   if (rx_in_brackets
1683*b88e3e88Schristos       || rx_last_token == REG || rx_last_token == DREG || rx_last_token == DCREG
1684440a403fSchristos       || strchr ("[],#", *rx_lex_start))
1685440a403fSchristos     {
1686440a403fSchristos       rx_last_token = *rx_lex_start;
1687440a403fSchristos       return *rx_lex_start ++;
1688440a403fSchristos     }
1689440a403fSchristos 
1690440a403fSchristos   save_input_pointer = input_line_pointer;
1691440a403fSchristos   input_line_pointer = rx_lex_start;
1692440a403fSchristos   rx_lval.exp.X_md = 0;
1693440a403fSchristos   expression (&rx_lval.exp);
1694440a403fSchristos 
1695440a403fSchristos   /* We parse but ignore any :<size> modifier on expressions.  */
1696440a403fSchristos   if (*input_line_pointer == ':')
1697440a403fSchristos     {
1698440a403fSchristos       char *cp;
1699440a403fSchristos 
1700440a403fSchristos       for (cp  = input_line_pointer + 1; *cp && cp < rx_lex_end; cp++)
1701440a403fSchristos 	if (!ISDIGIT (*cp))
1702440a403fSchristos 	  break;
1703440a403fSchristos       if (cp > input_line_pointer+1)
1704440a403fSchristos 	input_line_pointer = cp;
1705440a403fSchristos     }
1706440a403fSchristos 
1707440a403fSchristos   rx_lex_start = input_line_pointer;
1708440a403fSchristos   input_line_pointer = save_input_pointer;
1709440a403fSchristos   rx_last_token = EXPR;
1710440a403fSchristos   return EXPR;
1711440a403fSchristos }
1712440a403fSchristos 
1713440a403fSchristos int
rx_error(const char * str)1714440a403fSchristos rx_error (const char * str)
1715440a403fSchristos {
1716440a403fSchristos   int len;
1717440a403fSchristos 
1718440a403fSchristos   len = rx_last_exp_start - rx_init_start;
1719440a403fSchristos 
1720440a403fSchristos   as_bad ("%s", rx_init_start);
1721440a403fSchristos   as_bad ("%*s^ %s", len, "", str);
1722440a403fSchristos   return 0;
1723440a403fSchristos }
1724440a403fSchristos 
1725440a403fSchristos static int
rx_intop(expressionS exp,int nbits,int opbits)1726440a403fSchristos rx_intop (expressionS exp, int nbits, int opbits)
1727440a403fSchristos {
1728440a403fSchristos   long v;
1729440a403fSchristos   long mask, msb;
1730440a403fSchristos 
1731440a403fSchristos   if (exp.X_op == O_big)
1732440a403fSchristos     {
1733440a403fSchristos       if (nbits == 32)
1734440a403fSchristos 	return 1;
1735440a403fSchristos       if (exp.X_add_number == -1)
1736440a403fSchristos 	return 0;
1737440a403fSchristos     }
1738440a403fSchristos   else if (exp.X_op != O_constant)
1739440a403fSchristos     return 0;
1740440a403fSchristos   v = exp.X_add_number;
1741440a403fSchristos 
1742440a403fSchristos   msb = 1UL << (opbits - 1);
1743440a403fSchristos   mask = (1UL << opbits) - 1;
1744440a403fSchristos 
1745440a403fSchristos   if ((v & msb) && ! (v & ~mask))
1746440a403fSchristos     v -= 1UL << opbits;
1747440a403fSchristos 
1748440a403fSchristos   switch (nbits)
1749440a403fSchristos     {
1750440a403fSchristos     case 4:
1751440a403fSchristos       return -0x8 <= v && v <= 0x7;
1752440a403fSchristos     case 5:
1753440a403fSchristos       return -0x10 <= v && v <= 0x17;
1754440a403fSchristos     case 8:
1755440a403fSchristos       return -0x80 <= v && v <= 0x7f;
1756440a403fSchristos     case 16:
1757440a403fSchristos       return -0x8000 <= v && v <= 0x7fff;
1758440a403fSchristos     case 24:
1759440a403fSchristos       return -0x800000 <= v && v <= 0x7fffff;
1760440a403fSchristos     case 32:
1761440a403fSchristos       return 1;
1762440a403fSchristos     default:
1763440a403fSchristos       printf ("rx_intop passed %d\n", nbits);
1764440a403fSchristos       abort ();
1765440a403fSchristos     }
1766440a403fSchristos   return 1;
1767440a403fSchristos }
1768440a403fSchristos 
1769440a403fSchristos static int
rx_uintop(expressionS exp,int nbits)1770440a403fSchristos rx_uintop (expressionS exp, int nbits)
1771440a403fSchristos {
1772440a403fSchristos   unsigned long v;
1773440a403fSchristos 
1774440a403fSchristos   if (exp.X_op != O_constant)
1775440a403fSchristos     return 0;
1776440a403fSchristos   v = exp.X_add_number;
1777440a403fSchristos 
1778440a403fSchristos   switch (nbits)
1779440a403fSchristos     {
1780440a403fSchristos     case 4:
1781440a403fSchristos       return v <= 0xf;
1782440a403fSchristos     case 8:
1783440a403fSchristos       return v <= 0xff;
1784440a403fSchristos     case 16:
1785440a403fSchristos       return v <= 0xffff;
1786440a403fSchristos     case 24:
1787440a403fSchristos       return v <= 0xffffff;
1788440a403fSchristos     default:
1789440a403fSchristos       printf ("rx_uintop passed %d\n", nbits);
1790440a403fSchristos       abort ();
1791440a403fSchristos     }
1792440a403fSchristos   return 1;
1793440a403fSchristos }
1794440a403fSchristos 
1795440a403fSchristos static int
rx_disp3op(expressionS exp)1796440a403fSchristos rx_disp3op (expressionS exp)
1797440a403fSchristos {
1798440a403fSchristos   unsigned long v;
1799440a403fSchristos 
1800440a403fSchristos   if (exp.X_op != O_constant)
1801440a403fSchristos     return 0;
1802440a403fSchristos   v = exp.X_add_number;
1803440a403fSchristos   if (v < 3 || v > 10)
1804440a403fSchristos     return 0;
1805440a403fSchristos   return 1;
1806440a403fSchristos }
1807440a403fSchristos 
1808440a403fSchristos static int
rx_disp5op(expressionS * exp,int msize)1809440a403fSchristos rx_disp5op (expressionS * exp, int msize)
1810440a403fSchristos {
1811440a403fSchristos   long v;
1812440a403fSchristos 
1813440a403fSchristos   if (exp->X_op != O_constant)
1814440a403fSchristos     return 0;
1815440a403fSchristos   v = exp->X_add_number;
1816440a403fSchristos 
1817440a403fSchristos   switch (msize)
1818440a403fSchristos     {
1819440a403fSchristos     case BSIZE:
1820440a403fSchristos       if (0 <= v && v <= 31)
1821440a403fSchristos 	return 1;
1822440a403fSchristos       break;
1823440a403fSchristos     case WSIZE:
1824440a403fSchristos       if (v & 1)
1825440a403fSchristos 	return 0;
1826440a403fSchristos       if (0 <= v && v <= 63)
1827440a403fSchristos 	{
1828440a403fSchristos 	  exp->X_add_number >>= 1;
1829440a403fSchristos 	  return 1;
1830440a403fSchristos 	}
1831440a403fSchristos       break;
1832440a403fSchristos     case LSIZE:
1833440a403fSchristos       if (v & 3)
1834440a403fSchristos 	return 0;
1835440a403fSchristos       if (0 <= v && v <= 127)
1836440a403fSchristos 	{
1837440a403fSchristos 	  exp->X_add_number >>= 2;
1838440a403fSchristos 	  return 1;
1839440a403fSchristos 	}
1840440a403fSchristos       break;
1841440a403fSchristos     }
1842440a403fSchristos   return 0;
1843440a403fSchristos }
1844440a403fSchristos 
1845440a403fSchristos /* Just like the above, but allows a zero displacement.  */
1846440a403fSchristos 
1847440a403fSchristos static int
rx_disp5op0(expressionS * exp,int msize)1848440a403fSchristos rx_disp5op0 (expressionS * exp, int msize)
1849440a403fSchristos {
1850440a403fSchristos   if (exp->X_op != O_constant)
1851440a403fSchristos     return 0;
1852440a403fSchristos   if (exp->X_add_number == 0)
1853440a403fSchristos     return 1;
1854440a403fSchristos   return rx_disp5op (exp, msize);
1855440a403fSchristos }
1856440a403fSchristos 
1857440a403fSchristos static int
exp_val(expressionS exp)1858440a403fSchristos exp_val (expressionS exp)
1859440a403fSchristos {
1860440a403fSchristos   if (exp.X_op != O_constant)
1861440a403fSchristos   {
1862440a403fSchristos     rx_error (_("constant expected"));
1863440a403fSchristos     return 0;
1864440a403fSchristos   }
1865440a403fSchristos   return exp.X_add_number;
1866440a403fSchristos }
1867440a403fSchristos 
1868440a403fSchristos static expressionS
zero_expr(void)1869440a403fSchristos zero_expr (void)
1870440a403fSchristos {
1871440a403fSchristos   /* Static, so program load sets it to all zeros, which is what we want.  */
1872440a403fSchristos   static expressionS zero;
1873440a403fSchristos   zero.X_op = O_constant;
1874440a403fSchristos   return zero;
1875440a403fSchristos }
1876440a403fSchristos 
1877440a403fSchristos static int
immediate(expressionS exp,int type,int pos,int bits)1878440a403fSchristos immediate (expressionS exp, int type, int pos, int bits)
1879440a403fSchristos {
188006324dcfSchristos   /* We will emit constants ourselves here, so negate them.  */
1881440a403fSchristos   if (type == RXREL_NEGATIVE && exp.X_op == O_constant)
1882440a403fSchristos     exp.X_add_number = - exp.X_add_number;
1883440a403fSchristos   if (type == RXREL_NEGATIVE_BORROW)
1884440a403fSchristos     {
1885440a403fSchristos       if (exp.X_op == O_constant)
1886440a403fSchristos 	exp.X_add_number = - exp.X_add_number - 1;
1887440a403fSchristos       else
1888440a403fSchristos 	rx_error (_("sbb cannot use symbolic immediates"));
1889440a403fSchristos     }
1890440a403fSchristos 
1891*b88e3e88Schristos   if (pos >= 0 && rx_intop (exp, 8, bits))
1892440a403fSchristos     {
1893440a403fSchristos       rx_op (exp, 1, type);
1894440a403fSchristos       return 1;
1895440a403fSchristos     }
1896*b88e3e88Schristos   else if (pos >= 0 && rx_intop (exp, 16, bits))
1897440a403fSchristos     {
1898440a403fSchristos       rx_op (exp, 2, type);
1899440a403fSchristos       return 2;
1900440a403fSchristos     }
1901*b88e3e88Schristos   else if (pos >= 0 && rx_uintop (exp, 16) && bits == 16)
1902440a403fSchristos     {
1903440a403fSchristos       rx_op (exp, 2, type);
1904440a403fSchristos       return 2;
1905440a403fSchristos     }
1906*b88e3e88Schristos   else if (pos >= 0 && rx_intop (exp, 24, bits))
1907440a403fSchristos     {
1908440a403fSchristos       rx_op (exp, 3, type);
1909440a403fSchristos       return 3;
1910440a403fSchristos     }
1911*b88e3e88Schristos   else if (pos < 0 || rx_intop (exp, 32, bits))
1912440a403fSchristos     {
1913440a403fSchristos       rx_op (exp, 4, type);
1914440a403fSchristos       return 0;
1915440a403fSchristos     }
1916*b88e3e88Schristos   else if (type == RXREL_SIGNED && pos >= 0)
1917440a403fSchristos     {
1918440a403fSchristos       /* This is a symbolic immediate, we will relax it later.  */
1919440a403fSchristos       rx_relax (RX_RELAX_IMM, pos);
1920440a403fSchristos       rx_op (exp, linkrelax ? 4 : 1, type);
1921440a403fSchristos       return 1;
1922440a403fSchristos     }
1923440a403fSchristos   else
1924440a403fSchristos     {
1925440a403fSchristos       /* Let the linker deal with it.  */
1926440a403fSchristos       rx_op (exp, 4, type);
1927440a403fSchristos       return 0;
1928440a403fSchristos     }
1929440a403fSchristos }
1930440a403fSchristos 
1931440a403fSchristos static int
displacement(expressionS exp,int msize)1932440a403fSchristos displacement (expressionS exp, int msize)
1933440a403fSchristos {
1934440a403fSchristos   int val;
1935440a403fSchristos   int vshift = 0;
1936440a403fSchristos 
1937440a403fSchristos   if (exp.X_op == O_symbol
1938440a403fSchristos       && exp.X_md)
1939440a403fSchristos     {
1940440a403fSchristos       switch (exp.X_md)
1941440a403fSchristos 	{
1942440a403fSchristos 	case BFD_RELOC_GPREL16:
1943440a403fSchristos 	  switch (msize)
1944440a403fSchristos 	    {
1945440a403fSchristos 	    case BSIZE:
1946440a403fSchristos 	      exp.X_md = BFD_RELOC_RX_GPRELB;
1947440a403fSchristos 	      break;
1948440a403fSchristos 	    case WSIZE:
1949440a403fSchristos 	      exp.X_md = BFD_RELOC_RX_GPRELW;
1950440a403fSchristos 	      break;
1951440a403fSchristos 	    case LSIZE:
1952440a403fSchristos 	      exp.X_md = BFD_RELOC_RX_GPRELL;
1953440a403fSchristos 	      break;
1954440a403fSchristos 	    }
1955440a403fSchristos 	  O2 (exp);
1956440a403fSchristos 	  return 2;
1957440a403fSchristos 	}
1958440a403fSchristos     }
1959440a403fSchristos 
1960440a403fSchristos   if (exp.X_op == O_subtract)
1961440a403fSchristos     {
1962440a403fSchristos       exp.X_md = BFD_RELOC_RX_DIFF;
1963440a403fSchristos       O2 (exp);
1964440a403fSchristos       return 2;
1965440a403fSchristos     }
1966440a403fSchristos 
1967440a403fSchristos   if (exp.X_op != O_constant)
1968440a403fSchristos     {
1969440a403fSchristos       rx_error (_("displacements must be constants"));
1970440a403fSchristos       return -1;
1971440a403fSchristos     }
1972440a403fSchristos   val = exp.X_add_number;
1973440a403fSchristos 
1974440a403fSchristos   if (val == 0)
1975440a403fSchristos     return 0;
1976440a403fSchristos 
1977440a403fSchristos   switch (msize)
1978440a403fSchristos     {
1979440a403fSchristos     case BSIZE:
1980440a403fSchristos       break;
1981440a403fSchristos     case WSIZE:
1982440a403fSchristos       if (val & 1)
1983440a403fSchristos 	rx_error (_("word displacement not word-aligned"));
1984440a403fSchristos       vshift = 1;
1985440a403fSchristos       break;
1986440a403fSchristos     case LSIZE:
1987440a403fSchristos       if (val & 3)
1988440a403fSchristos 	rx_error (_("long displacement not long-aligned"));
1989440a403fSchristos       vshift = 2;
1990440a403fSchristos       break;
1991*b88e3e88Schristos     case DSIZE:
1992*b88e3e88Schristos       if (val & 7)
1993*b88e3e88Schristos 	rx_error (_("double displacement not double-aligned"));
1994*b88e3e88Schristos       vshift = 3;
1995*b88e3e88Schristos       break;
1996440a403fSchristos     default:
1997440a403fSchristos       as_bad (_("displacement with unknown size (internal bug?)\n"));
1998440a403fSchristos       break;
1999440a403fSchristos     }
2000440a403fSchristos 
2001440a403fSchristos   val >>= vshift;
2002440a403fSchristos   exp.X_add_number = val;
2003440a403fSchristos 
2004440a403fSchristos   if (0 <= val && val <= 255 )
2005440a403fSchristos     {
2006440a403fSchristos       O1 (exp);
2007440a403fSchristos       return 1;
2008440a403fSchristos     }
2009440a403fSchristos 
2010440a403fSchristos   if (0 <= val && val <= 65535)
2011440a403fSchristos     {
2012440a403fSchristos       O2 (exp);
2013440a403fSchristos       return 2;
2014440a403fSchristos     }
2015440a403fSchristos   if (val < 0)
2016440a403fSchristos     rx_error (_("negative displacements not allowed"));
2017440a403fSchristos   else
2018440a403fSchristos     rx_error (_("displacement too large"));
2019440a403fSchristos   return -1;
2020440a403fSchristos }
2021440a403fSchristos 
2022440a403fSchristos static void
rtsd_immediate(expressionS exp)2023440a403fSchristos rtsd_immediate (expressionS exp)
2024440a403fSchristos {
2025440a403fSchristos   int val;
2026440a403fSchristos 
2027440a403fSchristos   if (exp.X_op != O_constant)
2028440a403fSchristos     {
2029440a403fSchristos       rx_error (_("rtsd size must be constant"));
2030440a403fSchristos       return;
2031440a403fSchristos     }
2032440a403fSchristos   val = exp.X_add_number;
2033440a403fSchristos   if (val & 3)
2034440a403fSchristos     rx_error (_("rtsd size must be multiple of 4"));
2035440a403fSchristos 
2036440a403fSchristos   if (val < 0 || val > 1020)
2037440a403fSchristos     rx_error (_("rtsd size must be 0..1020"));
2038440a403fSchristos 
2039440a403fSchristos   val >>= 2;
2040440a403fSchristos   exp.X_add_number = val;
2041440a403fSchristos   O1 (exp);
2042440a403fSchristos }
2043440a403fSchristos 
2044440a403fSchristos static void
rx_range(expressionS exp,int minv,int maxv)2045440a403fSchristos rx_range (expressionS exp, int minv, int maxv)
2046440a403fSchristos {
2047440a403fSchristos   int val;
2048440a403fSchristos 
2049440a403fSchristos   if (exp.X_op != O_constant)
2050440a403fSchristos     return;
2051440a403fSchristos 
2052440a403fSchristos   val = exp.X_add_number;
2053440a403fSchristos   if (val < minv || val > maxv)
2054440a403fSchristos     as_warn (_("Value %d out of range %d..%d"), val, minv, maxv);
2055440a403fSchristos }
2056440a403fSchristos 
2057440a403fSchristos static void
rx_check_float_support(void)2058440a403fSchristos rx_check_float_support (void)
2059440a403fSchristos {
2060440a403fSchristos   if (rx_cpu == RX100 || rx_cpu == RX200)
2061440a403fSchristos     rx_error (_("target CPU type does not support floating point instructions"));
2062440a403fSchristos }
2063440a403fSchristos 
2064440a403fSchristos static void
rx_check_v2(void)2065440a403fSchristos rx_check_v2 (void)
2066440a403fSchristos {
2067440a403fSchristos   if (rx_cpu < RXV2)
2068440a403fSchristos     rx_error (_("target CPU type does not support v2 instructions"));
2069440a403fSchristos }
2070*b88e3e88Schristos 
2071*b88e3e88Schristos static void
rx_check_v3(void)2072*b88e3e88Schristos rx_check_v3 (void)
2073*b88e3e88Schristos {
2074*b88e3e88Schristos   if (rx_cpu < RXV3)
2075*b88e3e88Schristos     rx_error (_("target CPU type does not support v3 instructions"));
2076*b88e3e88Schristos }
2077*b88e3e88Schristos 
2078*b88e3e88Schristos static void
rx_check_dfpu(void)2079*b88e3e88Schristos rx_check_dfpu (void)
2080*b88e3e88Schristos {
2081*b88e3e88Schristos   if (rx_cpu != RXV3FPU)
2082*b88e3e88Schristos     rx_error (_("target CPU type does not support double float instructions"));
2083*b88e3e88Schristos }
2084