1440a403fSchristos /* rl78-parse.y  Renesas RL78 parser
2*b88e3e88Schristos    Copyright (C) 2011-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 "rl78-defs.h"
25440a403fSchristos 
26440a403fSchristos static int rl78_lex (void);
27440a403fSchristos 
28440a403fSchristos /* Ok, here are the rules for using these macros...
29440a403fSchristos 
30440a403fSchristos    B*() is used to specify the base opcode bytes.  Fields to be filled
31440a403fSchristos         in later, leave zero.  Call this first.
32440a403fSchristos 
33440a403fSchristos    F() and FE() are used to fill in fields within the base opcode bytes.  You MUST
34440a403fSchristos         call B*() before any F() or FE().
35440a403fSchristos 
36440a403fSchristos    [UN]*O*(), PC*() appends operands to the end of the opcode.  You
37440a403fSchristos         must call P() and B*() before any of these, so that the fixups
38440a403fSchristos         have the right byte location.
39440a403fSchristos         O = signed, UO = unsigned, NO = negated, PC = pcrel
40440a403fSchristos 
41440a403fSchristos    IMM() adds an immediate and fills in the field for it.
42440a403fSchristos    NIMM() same, but negates the immediate.
43440a403fSchristos    NBIMM() same, but negates the immediate, for sbb.
44440a403fSchristos    DSP() adds a displacement, and fills in the field for it.
45440a403fSchristos 
46440a403fSchristos    Note that order is significant for the O, IMM, and DSP macros, as
47440a403fSchristos    they append their data to the operand buffer in the order that you
48440a403fSchristos    call them.
49440a403fSchristos 
50440a403fSchristos    Use "disp" for displacements whenever possible; this handles the
51440a403fSchristos    "0" case properly.  */
52440a403fSchristos 
53440a403fSchristos #define B1(b1)             rl78_base1 (b1)
54440a403fSchristos #define B2(b1, b2)         rl78_base2 (b1, b2)
55440a403fSchristos #define B3(b1, b2, b3)     rl78_base3 (b1, b2, b3)
56440a403fSchristos #define B4(b1, b2, b3, b4) rl78_base4 (b1, b2, b3, b4)
57440a403fSchristos 
58440a403fSchristos /* POS is bits from the MSB of the first byte to the LSB of the last byte.  */
59440a403fSchristos #define F(val,pos,sz)      rl78_field (val, pos, sz)
60440a403fSchristos #define FE(exp,pos,sz)	   rl78_field (exp_val (exp), pos, sz);
61440a403fSchristos 
62440a403fSchristos #define O1(v)              rl78_op (v, 1, RL78REL_DATA)
63440a403fSchristos #define O2(v)              rl78_op (v, 2, RL78REL_DATA)
64440a403fSchristos #define O3(v)              rl78_op (v, 3, RL78REL_DATA)
65440a403fSchristos #define O4(v)              rl78_op (v, 4, RL78REL_DATA)
66440a403fSchristos 
67440a403fSchristos #define PC1(v)             rl78_op (v, 1, RL78REL_PCREL)
68440a403fSchristos #define PC2(v)             rl78_op (v, 2, RL78REL_PCREL)
69440a403fSchristos #define PC3(v)             rl78_op (v, 3, RL78REL_PCREL)
70440a403fSchristos 
71440a403fSchristos #define IMM(v,pos)	   F (immediate (v, RL78REL_SIGNED, pos), pos, 2); \
72440a403fSchristos 			   if (v.X_op != O_constant && v.X_op != O_big) rl78_linkrelax_imm (pos)
73440a403fSchristos #define NIMM(v,pos)	   F (immediate (v, RL78REL_NEGATIVE, pos), pos, 2)
74440a403fSchristos #define NBIMM(v,pos)	   F (immediate (v, RL78REL_NEGATIVE_BORROW, pos), pos, 2)
75440a403fSchristos #define DSP(v,pos,msz)	   if (!v.X_md) rl78_relax (RL78_RELAX_DISP, pos); \
76440a403fSchristos 			   else rl78_linkrelax_dsp (pos); \
77440a403fSchristos 			   F (displacement (v, msz), pos, 2)
78440a403fSchristos 
79440a403fSchristos #define id24(a,b2,b3)	   B3 (0xfb+a, b2, b3)
80440a403fSchristos 
81440a403fSchristos static int         expr_is_sfr (expressionS);
82440a403fSchristos static int         expr_is_saddr (expressionS);
83440a403fSchristos static int         expr_is_word_aligned (expressionS);
84440a403fSchristos static int         exp_val (expressionS exp);
85440a403fSchristos 
86440a403fSchristos static int    need_flag = 0;
87440a403fSchristos static int    rl78_in_brackets = 0;
88440a403fSchristos static int    rl78_last_token = 0;
89440a403fSchristos static char * rl78_init_start;
90440a403fSchristos static char * rl78_last_exp_start = 0;
91440a403fSchristos static int    rl78_bit_insn = 0;
92440a403fSchristos 
93440a403fSchristos #define YYDEBUG 1
94440a403fSchristos #define YYERROR_VERBOSE 1
95440a403fSchristos 
96440a403fSchristos #define NOT_SADDR  rl78_error ("Expression not 0xFFE20 to 0xFFF1F")
97440a403fSchristos #define SA(e) if (!expr_is_saddr (e)) NOT_SADDR;
98440a403fSchristos 
99440a403fSchristos #define SET_SA(e) e.X_md = BFD_RELOC_RL78_SADDR
100440a403fSchristos 
101440a403fSchristos #define NOT_SFR  rl78_error ("Expression not 0xFFF00 to 0xFFFFF")
102440a403fSchristos #define SFR(e) if (!expr_is_sfr (e)) NOT_SFR;
103440a403fSchristos 
104440a403fSchristos #define NOT_SFR_OR_SADDR  rl78_error ("Expression not 0xFFE20 to 0xFFFFF")
105440a403fSchristos 
106440a403fSchristos #define NOT_ES if (rl78_has_prefix()) rl78_error ("ES: prefix not allowed here");
107440a403fSchristos 
108440a403fSchristos #define WA(x) if (!expr_is_word_aligned (x)) rl78_error ("Expression not word-aligned");
109440a403fSchristos 
110440a403fSchristos #define ISA_G10(s) if (!rl78_isa_g10()) rl78_error (s " is only supported on the G10")
111440a403fSchristos #define ISA_G13(s) if (!rl78_isa_g13()) rl78_error (s " is only supported on the G13")
112440a403fSchristos #define ISA_G14(s) if (!rl78_isa_g14()) rl78_error (s " is only supported on the G14")
113440a403fSchristos 
114440a403fSchristos static void check_expr_is_bit_index (expressionS);
115440a403fSchristos #define Bit(e) check_expr_is_bit_index (e);
116440a403fSchristos 
117440a403fSchristos /* Returns TRUE (non-zero) if the expression is a constant in the
118440a403fSchristos    given range.  */
119440a403fSchristos static int check_expr_is_const (expressionS, int vmin, int vmax);
120440a403fSchristos 
121440a403fSchristos /* Convert a "regb" value to a "reg_xbc" value.  Error if other
122440a403fSchristos    registers are passed.  Needed to avoid reduce-reduce conflicts.  */
123440a403fSchristos static int
reg_xbc(int reg)124440a403fSchristos reg_xbc (int reg)
125440a403fSchristos {
126440a403fSchristos   switch (reg)
127440a403fSchristos     {
128440a403fSchristos       case 0: /* X */
129440a403fSchristos         return 0x10;
130440a403fSchristos       case 3: /* B */
131440a403fSchristos         return 0x20;
132440a403fSchristos       case 2: /* C */
133440a403fSchristos         return 0x30;
134440a403fSchristos       default:
135440a403fSchristos         rl78_error ("Only X, B, or C allowed here");
136440a403fSchristos 	return 0;
137440a403fSchristos     }
138440a403fSchristos }
139440a403fSchristos 
140440a403fSchristos %}
141440a403fSchristos 
142440a403fSchristos %name-prefix="rl78_"
143440a403fSchristos 
144440a403fSchristos %union {
145440a403fSchristos   int regno;
146440a403fSchristos   expressionS exp;
147440a403fSchristos }
148440a403fSchristos 
149440a403fSchristos %type <regno> regb regb_na regw regw_na FLAG sfr
150440a403fSchristos %type <regno> A X B C D E H L AX BC DE HL
151440a403fSchristos %type <exp> EXPR
152440a403fSchristos 
153440a403fSchristos %type <regno> addsub addsubw andor1 bt_bf setclr1 oneclrb oneclrw
154440a403fSchristos %type <regno> incdec incdecw
155440a403fSchristos 
156440a403fSchristos %token A X B C D E H L AX BC DE HL
157440a403fSchristos %token SPL SPH PSW CS ES PMC MEM
158440a403fSchristos %token FLAG SP CY
159440a403fSchristos %token RB0 RB1 RB2 RB3
160440a403fSchristos 
161440a403fSchristos %token EXPR UNKNOWN_OPCODE IS_OPCODE
162440a403fSchristos 
163440a403fSchristos %token DOT_S DOT_B DOT_W DOT_L DOT_A DOT_UB DOT_UW
164440a403fSchristos 
165440a403fSchristos %token ADD ADDC ADDW AND_ AND1
166440a403fSchristos /* BC is also a register pair */
167440a403fSchristos %token BF BH BNC BNH BNZ BR BRK BRK1 BT BTCLR BZ
168440a403fSchristos %token CALL CALLT CLR1 CLRB CLRW CMP CMP0 CMPS CMPW
169440a403fSchristos %token DEC DECW DI DIVHU DIVWU
170440a403fSchristos %token EI
171440a403fSchristos %token HALT
172440a403fSchristos %token INC INCW
173440a403fSchristos %token MACH MACHU MOV MOV1 MOVS MOVW MULH MULHU MULU
174440a403fSchristos %token NOP NOT1
175440a403fSchristos %token ONEB ONEW OR OR1
176440a403fSchristos %token POP PUSH
177440a403fSchristos %token RET RETI RETB ROL ROLC ROLWC ROR RORC
178440a403fSchristos %token SAR SARW SEL SET1 SHL SHLW SHR SHRW
179440a403fSchristos %token   SKC SKH SKNC SKNH SKNZ SKZ STOP SUB SUBC SUBW
180440a403fSchristos %token XCH XCHW XOR XOR1
181440a403fSchristos 
182440a403fSchristos %%
183440a403fSchristos /* ====================================================================== */
184440a403fSchristos 
185440a403fSchristos statement :
186440a403fSchristos 
187440a403fSchristos 	  UNKNOWN_OPCODE
188440a403fSchristos 	  { as_bad (_("Unknown opcode: %s"), rl78_init_start); }
189440a403fSchristos 
190440a403fSchristos /* The opcodes are listed in approximately alphabetical order.  */
191440a403fSchristos 
192440a403fSchristos /* For reference:
193440a403fSchristos 
194440a403fSchristos   sfr  = special function register - symbol, 0xFFF00 to 0xFFFFF
195440a403fSchristos   sfrp = special function register - symbol, 0xFFF00 to 0xFFFFE, even only
196440a403fSchristos   saddr  = 0xFFE20 to 0xFFF1F
197440a403fSchristos   saddrp = 0xFFE20 to 0xFFF1E, even only
198440a403fSchristos 
199440a403fSchristos   addr20 = 0x00000 to 0xFFFFF
200440a403fSchristos   addr16 = 0x00000 to 0x0FFFF, even only for 16-bit ops
201440a403fSchristos   addr5  = 0x00000 to 0x000BE, even only
202440a403fSchristos */
203440a403fSchristos 
204440a403fSchristos /* ---------------------------------------------------------------------- */
205440a403fSchristos 
206440a403fSchristos /* addsub is ADD, ADDC, SUB, SUBC, AND, OR, XOR, and parts of CMP.  */
207440a403fSchristos 
208440a403fSchristos 	| addsub A ',' '#' EXPR
209440a403fSchristos 	  { B1 (0x0c|$1); O1 ($5); }
210440a403fSchristos 
211440a403fSchristos 	| addsub EXPR {SA($2)} ',' '#' EXPR
212440a403fSchristos 	  { B1 (0x0a|$1); SET_SA ($2); O1 ($2); O1 ($6); }
213440a403fSchristos 
214440a403fSchristos 	| addsub A ',' A
215440a403fSchristos 	  { B2 (0x61, 0x01|$1); }
216440a403fSchristos 
217440a403fSchristos 	| addsub A ',' regb_na
218440a403fSchristos 	  { B2 (0x61, 0x08|$1); F ($4, 13, 3); }
219440a403fSchristos 
220440a403fSchristos 	| addsub regb_na ',' A
221440a403fSchristos 	  { B2 (0x61, 0x00|$1); F ($2, 13, 3); }
222440a403fSchristos 
223440a403fSchristos 	| addsub A ',' EXPR {SA($4)}
224440a403fSchristos 	  { B1 (0x0b|$1); SET_SA ($4); O1 ($4); }
225440a403fSchristos 
226440a403fSchristos 	| addsub A ',' opt_es '!' EXPR
227440a403fSchristos 	  { B1 (0x0f|$1); O2 ($6); rl78_linkrelax_addr16 (); }
228440a403fSchristos 
229440a403fSchristos 	| addsub A ',' opt_es '[' HL ']'
230440a403fSchristos 	  { B1 (0x0d|$1); }
231440a403fSchristos 
232440a403fSchristos 	| addsub A ',' opt_es '[' HL '+' EXPR ']'
233440a403fSchristos 	  { B1 (0x0e|$1); O1 ($8); }
234440a403fSchristos 
235440a403fSchristos 	| addsub A ',' opt_es '[' HL '+' B ']'
236440a403fSchristos 	  { B2 (0x61, 0x80|$1); }
237440a403fSchristos 
238440a403fSchristos 	| addsub A ',' opt_es '[' HL '+' C ']'
239440a403fSchristos 	  { B2 (0x61, 0x82|$1); }
240440a403fSchristos 
241440a403fSchristos 	| addsub opt_es '!' EXPR ',' '#' EXPR
242440a403fSchristos 	  { if ($1 != 0x40)
243440a403fSchristos 	      { rl78_error ("Only CMP takes these operands"); }
244440a403fSchristos 	    else
245440a403fSchristos 	      { B1 (0x00|$1); O2 ($4); O1 ($7); rl78_linkrelax_addr16 (); }
246440a403fSchristos 	  }
247440a403fSchristos 
248440a403fSchristos /* ---------------------------------------------------------------------- */
249440a403fSchristos 
250440a403fSchristos 	| addsubw AX ',' '#' EXPR
251440a403fSchristos 	  { B1 (0x04|$1); O2 ($5); }
252440a403fSchristos 
253440a403fSchristos 	| addsubw AX ',' regw
254440a403fSchristos 	  { B1 (0x01|$1); F ($4, 5, 2); }
255440a403fSchristos 
256440a403fSchristos 	| addsubw AX ',' EXPR {SA($4)}
257440a403fSchristos 	  { B1 (0x06|$1); SET_SA ($4); O1 ($4); }
258440a403fSchristos 
259440a403fSchristos 	| addsubw AX ',' opt_es '!' EXPR
260440a403fSchristos 	  { B1 (0x02|$1); O2 ($6); rl78_linkrelax_addr16 (); }
261440a403fSchristos 
262440a403fSchristos 	| addsubw AX ',' opt_es '[' HL '+' EXPR ']'
263440a403fSchristos 	  { B2 (0x61, 0x09|$1); O1 ($8); }
264440a403fSchristos 
265440a403fSchristos 	| addsubw AX ',' opt_es '[' HL ']'
266440a403fSchristos 	  { B3 (0x61, 0x09|$1, 0); }
267440a403fSchristos 
268440a403fSchristos 	| addsubw SP ',' '#' EXPR
269440a403fSchristos 	  { B1 ($1 ? 0x20 : 0x10); O1 ($5);
270440a403fSchristos 	    if ($1 == 0x40)
271440a403fSchristos 	      rl78_error ("CMPW SP,#imm not allowed");
272440a403fSchristos 	  }
273440a403fSchristos 
274440a403fSchristos /* ---------------------------------------------------------------------- */
275440a403fSchristos 
276440a403fSchristos 	| andor1 CY ',' sfr '.' EXPR {Bit($6)}
277440a403fSchristos 	  { B3 (0x71, 0x08|$1, $4); FE ($6, 9, 3); }
278440a403fSchristos 
279440a403fSchristos 	| andor1 CY ',' EXPR '.' EXPR {Bit($6)}
280440a403fSchristos 	  { if (expr_is_sfr ($4))
281440a403fSchristos 	      { B2 (0x71, 0x08|$1); FE ($6, 9, 3); O1 ($4); }
282440a403fSchristos 	    else if (expr_is_saddr ($4))
283440a403fSchristos 	      { B2 (0x71, 0x00|$1); FE ($6, 9, 3); SET_SA ($4); O1 ($4); }
284440a403fSchristos 	    else
285440a403fSchristos 	      NOT_SFR_OR_SADDR;
286440a403fSchristos 	  }
287440a403fSchristos 
288440a403fSchristos 	| andor1 CY ',' A '.' EXPR {Bit($6)}
289440a403fSchristos 	  { B2 (0x71, 0x88|$1);  FE ($6, 9, 3); }
290440a403fSchristos 
291440a403fSchristos 	| andor1 CY ',' opt_es '[' HL ']' '.' EXPR {Bit($9)}
292440a403fSchristos 	  { B2 (0x71, 0x80|$1);  FE ($9, 9, 3); }
293440a403fSchristos 
294440a403fSchristos /* ---------------------------------------------------------------------- */
295440a403fSchristos 
296440a403fSchristos 	| BC '$' EXPR
297440a403fSchristos 	  { B1 (0xdc); PC1 ($3); rl78_linkrelax_branch (); }
298440a403fSchristos 
299440a403fSchristos 	| BNC '$' EXPR
300440a403fSchristos 	  { B1 (0xde); PC1 ($3); rl78_linkrelax_branch (); }
301440a403fSchristos 
302440a403fSchristos 	| BZ '$' EXPR
303440a403fSchristos 	  { B1 (0xdd); PC1 ($3); rl78_linkrelax_branch (); }
304440a403fSchristos 
305440a403fSchristos 	| BNZ '$' EXPR
306440a403fSchristos 	  { B1 (0xdf); PC1 ($3); rl78_linkrelax_branch (); }
307440a403fSchristos 
308440a403fSchristos 	| BH '$' EXPR
309440a403fSchristos 	  { B2 (0x61, 0xc3); PC1 ($3); rl78_linkrelax_branch (); }
310440a403fSchristos 
311440a403fSchristos 	| BNH '$' EXPR
312440a403fSchristos 	  { B2 (0x61, 0xd3); PC1 ($3); rl78_linkrelax_branch (); }
313440a403fSchristos 
314440a403fSchristos /* ---------------------------------------------------------------------- */
315440a403fSchristos 
316440a403fSchristos 	| bt_bf sfr '.' EXPR ',' '$' EXPR
317440a403fSchristos 	  { B3 (0x31, 0x80|$1, $2); FE ($4, 9, 3); PC1 ($7); }
318440a403fSchristos 
319440a403fSchristos 	| bt_bf EXPR '.' EXPR ',' '$' EXPR
320440a403fSchristos 	  { if (expr_is_sfr ($2))
321440a403fSchristos 	      { B2 (0x31, 0x80|$1); FE ($4, 9, 3); O1 ($2); PC1 ($7); }
322440a403fSchristos 	    else if (expr_is_saddr ($2))
323440a403fSchristos 	      { B2 (0x31, 0x00|$1); FE ($4, 9, 3); SET_SA ($2); O1 ($2); PC1 ($7); }
324440a403fSchristos 	    else
325440a403fSchristos 	      NOT_SFR_OR_SADDR;
326440a403fSchristos 	  }
327440a403fSchristos 
328440a403fSchristos 	| bt_bf A '.' EXPR ',' '$' EXPR
329440a403fSchristos 	  { B2 (0x31, 0x01|$1); FE ($4, 9, 3); PC1 ($7); }
330440a403fSchristos 
331440a403fSchristos 	| bt_bf opt_es '[' HL ']' '.' EXPR ',' '$' EXPR
332440a403fSchristos 	  { B2 (0x31, 0x81|$1); FE ($7, 9, 3); PC1 ($10); }
333440a403fSchristos 
334440a403fSchristos /* ---------------------------------------------------------------------- */
335440a403fSchristos 
336440a403fSchristos 	| BR AX
337440a403fSchristos 	  { B2 (0x61, 0xcb); }
338440a403fSchristos 
339440a403fSchristos 	| BR '$' EXPR
340440a403fSchristos 	  { B1 (0xef); PC1 ($3); rl78_linkrelax_branch (); }
341440a403fSchristos 
342440a403fSchristos 	| BR '$' '!' EXPR
343440a403fSchristos 	  { B1 (0xee); PC2 ($4); rl78_linkrelax_branch (); }
344440a403fSchristos 
345440a403fSchristos 	| BR '!' EXPR
346440a403fSchristos 	  { B1 (0xed); O2 ($3); rl78_linkrelax_branch (); }
347440a403fSchristos 
348440a403fSchristos 	| BR '!' '!' EXPR
349440a403fSchristos 	  { B1 (0xec); O3 ($4); rl78_linkrelax_branch (); }
350440a403fSchristos 
351440a403fSchristos /* ---------------------------------------------------------------------- */
352440a403fSchristos 
353440a403fSchristos 	| BRK
354440a403fSchristos 	  { B2 (0x61, 0xcc); }
355440a403fSchristos 
356440a403fSchristos 	| BRK1
357440a403fSchristos 	  { B1 (0xff); }
358440a403fSchristos 
359440a403fSchristos /* ---------------------------------------------------------------------- */
360440a403fSchristos 
361440a403fSchristos 	| CALL regw
362440a403fSchristos 	  { B2 (0x61, 0xca); F ($2, 10, 2); }
363440a403fSchristos 
364440a403fSchristos 	| CALL '$' '!' EXPR
365440a403fSchristos 	  { B1 (0xfe); PC2 ($4); }
366440a403fSchristos 
367440a403fSchristos 	| CALL '!' EXPR
368440a403fSchristos 	  { B1 (0xfd); O2 ($3); }
369440a403fSchristos 
370440a403fSchristos 	| CALL '!' '!' EXPR
371440a403fSchristos 	  { B1 (0xfc); O3 ($4); rl78_linkrelax_branch (); }
372440a403fSchristos 
373440a403fSchristos 	| CALLT '[' EXPR ']'
374440a403fSchristos 	  { if ($3.X_op != O_constant)
375440a403fSchristos 	      rl78_error ("CALLT requires a numeric address");
376440a403fSchristos 	    else
377440a403fSchristos 	      {
378440a403fSchristos 	        int i = $3.X_add_number;
379440a403fSchristos 		if (i < 0x80 || i > 0xbe)
380440a403fSchristos 		  rl78_error ("CALLT address not 0x80..0xbe");
381440a403fSchristos 		else if (i & 1)
382440a403fSchristos 		  rl78_error ("CALLT address not even");
383440a403fSchristos 		else
384440a403fSchristos 		  {
385440a403fSchristos 		    B2 (0x61, 0x84);
386440a403fSchristos 	    	    F ((i >> 1) & 7, 9, 3);
387440a403fSchristos 	    	    F ((i >> 4) & 7, 14, 2);
388440a403fSchristos 		  }
389440a403fSchristos 	      }
390440a403fSchristos 	  }
391440a403fSchristos 
392440a403fSchristos /* ---------------------------------------------------------------------- */
393440a403fSchristos 
394440a403fSchristos 	| setclr1 CY
395440a403fSchristos 	  { B2 (0x71, $1 ? 0x88 : 0x80); }
396440a403fSchristos 
397440a403fSchristos 	| setclr1 sfr '.' EXPR
398440a403fSchristos 	  { B3 (0x71, 0x0a|$1, $2); FE ($4, 9, 3); }
399440a403fSchristos 
400440a403fSchristos 	| setclr1 EXPR '.' EXPR
401440a403fSchristos 	  { if (expr_is_sfr ($2))
402440a403fSchristos 	      { B2 (0x71, 0x0a|$1); FE ($4, 9, 3); O1 ($2); }
403440a403fSchristos 	    else if (expr_is_saddr ($2))
404440a403fSchristos 	      { B2 (0x71, 0x02|$1); FE ($4, 9, 3); SET_SA ($2); O1 ($2); }
405440a403fSchristos 	    else
406440a403fSchristos 	      NOT_SFR_OR_SADDR;
407440a403fSchristos 	  }
408440a403fSchristos 
409440a403fSchristos 	| setclr1 A '.' EXPR
410440a403fSchristos 	  { B2 (0x71, 0x8a|$1);  FE ($4, 9, 3); }
411440a403fSchristos 
412440a403fSchristos 	| setclr1 opt_es '!' EXPR '.' EXPR
413440a403fSchristos 	  { B2 (0x71, 0x00+$1*0x08); FE ($6, 9, 3); O2 ($4); rl78_linkrelax_addr16 (); }
414440a403fSchristos 
415440a403fSchristos 	| setclr1 opt_es '[' HL ']' '.' EXPR
416440a403fSchristos 	  { B2 (0x71, 0x82|$1); FE ($7, 9, 3); }
417440a403fSchristos 
418440a403fSchristos /* ---------------------------------------------------------------------- */
419440a403fSchristos 
420440a403fSchristos 	| oneclrb A
421440a403fSchristos 	  { B1 (0xe1|$1); }
422440a403fSchristos 	| oneclrb X
423440a403fSchristos 	  { B1 (0xe0|$1); }
424440a403fSchristos 	| oneclrb B
425440a403fSchristos 	  { B1 (0xe3|$1); }
426440a403fSchristos 	| oneclrb C
427440a403fSchristos 	  { B1 (0xe2|$1); }
428440a403fSchristos 
429440a403fSchristos 	| oneclrb EXPR {SA($2)}
430440a403fSchristos 	  { B1 (0xe4|$1); SET_SA ($2); O1 ($2); }
431440a403fSchristos 
432440a403fSchristos 	| oneclrb opt_es '!' EXPR
433440a403fSchristos 	  { B1 (0xe5|$1); O2 ($4); rl78_linkrelax_addr16 (); }
434440a403fSchristos 
435440a403fSchristos /* ---------------------------------------------------------------------- */
436440a403fSchristos 
437440a403fSchristos 	| oneclrw AX
438440a403fSchristos 	  { B1 (0xe6|$1); }
439440a403fSchristos 	| oneclrw BC
440440a403fSchristos 	  { B1 (0xe7|$1); }
441440a403fSchristos 
442440a403fSchristos /* ---------------------------------------------------------------------- */
443440a403fSchristos 
444440a403fSchristos 	| CMP0 A
445440a403fSchristos 	  { B1 (0xd1); }
446440a403fSchristos 
447440a403fSchristos 	| CMP0 X
448440a403fSchristos 	  { B1 (0xd0); }
449440a403fSchristos 
450440a403fSchristos 	| CMP0 B
451440a403fSchristos 	  { B1 (0xd3); }
452440a403fSchristos 
453440a403fSchristos 	| CMP0 C
454440a403fSchristos 	  { B1 (0xd2); }
455440a403fSchristos 
456440a403fSchristos 	| CMP0 EXPR {SA($2)}
457440a403fSchristos 	  { B1 (0xd4); SET_SA ($2); O1 ($2); }
458440a403fSchristos 
459440a403fSchristos 	| CMP0 opt_es '!' EXPR
460440a403fSchristos 	  { B1 (0xd5); O2 ($4); rl78_linkrelax_addr16 (); }
461440a403fSchristos 
462440a403fSchristos /* ---------------------------------------------------------------------- */
463440a403fSchristos 
464440a403fSchristos 	| CMPS X ',' opt_es '[' HL '+' EXPR ']'
465440a403fSchristos 	  { B2 (0x61, 0xde); O1 ($8); }
466440a403fSchristos 
467440a403fSchristos /* ---------------------------------------------------------------------- */
468440a403fSchristos 
469440a403fSchristos 	| incdec regb
470440a403fSchristos 	  { B1 (0x80|$1); F ($2, 5, 3); }
471440a403fSchristos 
472440a403fSchristos 	| incdec EXPR {SA($2)}
473440a403fSchristos 	  { B1 (0xa4|$1); SET_SA ($2); O1 ($2); }
474440a403fSchristos 	| incdec '!' EXPR
475440a403fSchristos 	  { B1 (0xa0|$1); O2 ($3); rl78_linkrelax_addr16 (); }
476440a403fSchristos 	| incdec ES ':' '!' EXPR
477440a403fSchristos 	  { B2 (0x11, 0xa0|$1); O2 ($5); }
478440a403fSchristos 	| incdec '[' HL '+' EXPR ']'
479440a403fSchristos 	  { B2 (0x61, 0x59+$1); O1 ($5); }
480440a403fSchristos 	| incdec ES ':' '[' HL '+' EXPR ']'
481440a403fSchristos 	  { B3 (0x11, 0x61, 0x59+$1); O1 ($7); }
482440a403fSchristos 
483440a403fSchristos /* ---------------------------------------------------------------------- */
484440a403fSchristos 
485440a403fSchristos 	| incdecw regw
486440a403fSchristos 	  { B1 (0xa1|$1); F ($2, 5, 2); }
487440a403fSchristos 
488440a403fSchristos 	| incdecw EXPR {SA($2)}
489440a403fSchristos 	  { B1 (0xa6|$1); SET_SA ($2); O1 ($2); }
490440a403fSchristos 
491440a403fSchristos 	| incdecw opt_es '!' EXPR
492440a403fSchristos 	  { B1 (0xa2|$1); O2 ($4); rl78_linkrelax_addr16 (); }
493440a403fSchristos 
494440a403fSchristos 	| incdecw opt_es '[' HL '+' EXPR ']'
495440a403fSchristos 	  { B2 (0x61, 0x79+$1); O1 ($6); }
496440a403fSchristos 
497440a403fSchristos /* ---------------------------------------------------------------------- */
498440a403fSchristos 
499440a403fSchristos 	| DI
500440a403fSchristos 	  { B3 (0x71, 0x7b, 0xfa); }
501440a403fSchristos 
502440a403fSchristos 	| EI
503440a403fSchristos 	  { B3 (0x71, 0x7a, 0xfa); }
504440a403fSchristos 
505440a403fSchristos /* ---------------------------------------------------------------------- */
506440a403fSchristos 
507440a403fSchristos 	| MULHU { ISA_G14 ("MULHU"); }
508440a403fSchristos 	  { B3 (0xce, 0xfb, 0x01); }
509440a403fSchristos 
510440a403fSchristos 	| MULH { ISA_G14 ("MULH"); }
511440a403fSchristos 	  { B3 (0xce, 0xfb, 0x02); }
512440a403fSchristos 
513440a403fSchristos 	| MULU X
514440a403fSchristos 	  { B1 (0xd6); }
515440a403fSchristos 
516440a403fSchristos 	| DIVHU { ISA_G14 ("DIVHU"); }
517440a403fSchristos 	  { B3 (0xce, 0xfb, 0x03); }
518440a403fSchristos 
519440a403fSchristos /* Note that the DIVWU encoding was changed from [0xce,0xfb,0x04] to
520440a403fSchristos    [0xce,0xfb,0x0b].  Different versions of the Software Manual exist
521440a403fSchristos    with the same version number, but varying encodings.  The version
522440a403fSchristos    here matches the hardware.  */
523440a403fSchristos 
524440a403fSchristos 	| DIVWU { ISA_G14 ("DIVWU"); }
525440a403fSchristos 	  { B3 (0xce, 0xfb, 0x0b); }
526440a403fSchristos 
527440a403fSchristos 	| MACHU { ISA_G14 ("MACHU"); }
528440a403fSchristos 	  { B3 (0xce, 0xfb, 0x05); }
529440a403fSchristos 
530440a403fSchristos 	| MACH { ISA_G14 ("MACH"); }
531440a403fSchristos 	  { B3 (0xce, 0xfb, 0x06); }
532440a403fSchristos 
533440a403fSchristos /* ---------------------------------------------------------------------- */
534440a403fSchristos 
535440a403fSchristos 	| HALT
536440a403fSchristos 	  { B2 (0x61, 0xed); }
537440a403fSchristos 
538440a403fSchristos /* ---------------------------------------------------------------------- */
539440a403fSchristos /* Note that opt_es is included even when it's not an option, to avoid
540440a403fSchristos    shift/reduce conflicts.  The NOT_ES macro produces an error if ES:
541440a403fSchristos    is given by the user.  */
542440a403fSchristos 
543440a403fSchristos 	| MOV A ',' '#' EXPR
544440a403fSchristos 	  { B1 (0x51); O1 ($5); }
545440a403fSchristos 	| MOV regb_na ',' '#' EXPR
546440a403fSchristos 	  { B1 (0x50); F($2, 5, 3); O1 ($5); }
547440a403fSchristos 
548440a403fSchristos 	| MOV sfr ',' '#' EXPR
549440a403fSchristos 	  { if ($2 != 0xfd)
550440a403fSchristos 	      { B2 (0xce, $2); O1 ($5); }
551440a403fSchristos 	    else
552440a403fSchristos 	      { B1 (0x41); O1 ($5); }
553440a403fSchristos 	  }
554440a403fSchristos 
555440a403fSchristos 	| MOV opt_es EXPR ',' '#' EXPR  {NOT_ES}
556440a403fSchristos 	  { if (expr_is_sfr ($3))
557440a403fSchristos 	      { B1 (0xce); O1 ($3); O1 ($6); }
558440a403fSchristos 	    else if (expr_is_saddr ($3))
559440a403fSchristos 	      { B1 (0xcd); SET_SA ($3); O1 ($3); O1 ($6); }
560440a403fSchristos 	    else
561440a403fSchristos 	      NOT_SFR_OR_SADDR;
562440a403fSchristos 	  }
563440a403fSchristos 
564440a403fSchristos 	| MOV '!' EXPR ',' '#' EXPR
565440a403fSchristos 	  { B1 (0xcf); O2 ($3); O1 ($6); rl78_linkrelax_addr16 (); }
566440a403fSchristos 
567440a403fSchristos 	| MOV ES ':' '!' EXPR ',' '#' EXPR
568440a403fSchristos 	  { B2 (0x11, 0xcf); O2 ($5); O1 ($8); }
569440a403fSchristos 
570440a403fSchristos 	| MOV regb_na ',' A
571440a403fSchristos 	  { B1 (0x70); F ($2, 5, 3); }
572440a403fSchristos 
573440a403fSchristos 	| MOV A ',' regb_na
574440a403fSchristos 	  { B1 (0x60); F ($4, 5, 3); }
575440a403fSchristos 
576440a403fSchristos 	| MOV opt_es EXPR ',' A  {NOT_ES}
577440a403fSchristos 	  { if (expr_is_sfr ($3))
578440a403fSchristos 	      { B1 (0x9e); O1 ($3); }
579440a403fSchristos 	    else if (expr_is_saddr ($3))
580440a403fSchristos 	      { B1 (0x9d); SET_SA ($3); O1 ($3); }
581440a403fSchristos 	    else
582440a403fSchristos 	      NOT_SFR_OR_SADDR;
583440a403fSchristos 	  }
584440a403fSchristos 
585440a403fSchristos 	| MOV A ',' opt_es '!' EXPR
586440a403fSchristos 	  { B1 (0x8f); O2 ($6); rl78_linkrelax_addr16 (); }
587440a403fSchristos 
588440a403fSchristos 	| MOV '!' EXPR ',' A
589440a403fSchristos 	  { B1 (0x9f); O2 ($3); rl78_linkrelax_addr16 (); }
590440a403fSchristos 
591440a403fSchristos 	| MOV ES ':' '!' EXPR ',' A
592440a403fSchristos 	  { B2 (0x11, 0x9f); O2 ($5); }
593440a403fSchristos 
594440a403fSchristos 	| MOV regb_na ',' opt_es '!' EXPR
595440a403fSchristos 	  { B1 (0xc9|reg_xbc($2)); O2 ($6); rl78_linkrelax_addr16 (); }
596440a403fSchristos 
597440a403fSchristos 	| MOV A ',' opt_es EXPR  {NOT_ES}
598440a403fSchristos 	  { if (expr_is_saddr ($5))
599440a403fSchristos 	      { B1 (0x8d); SET_SA ($5); O1 ($5); }
600440a403fSchristos 	    else if (expr_is_sfr ($5))
601440a403fSchristos 	      { B1 (0x8e); O1 ($5); }
602440a403fSchristos 	    else
603440a403fSchristos 	      NOT_SFR_OR_SADDR;
604440a403fSchristos 	  }
605440a403fSchristos 
606440a403fSchristos 	| MOV regb_na ',' opt_es EXPR {SA($5)} {NOT_ES}
607440a403fSchristos 	  { B1 (0xc8|reg_xbc($2)); SET_SA ($5); O1 ($5); }
608440a403fSchristos 
609440a403fSchristos 	| MOV A ',' sfr
610440a403fSchristos 	  { B2 (0x8e, $4); }
611440a403fSchristos 
612440a403fSchristos 	| MOV sfr ',' regb
613440a403fSchristos 	  { if ($4 != 1)
614440a403fSchristos 	      rl78_error ("Only A allowed here");
615440a403fSchristos 	    else
616440a403fSchristos 	      { B2 (0x9e, $2); }
617440a403fSchristos 	  }
618440a403fSchristos 
619440a403fSchristos 	| MOV sfr ',' opt_es EXPR {SA($5)} {NOT_ES}
620440a403fSchristos 	  { if ($2 != 0xfd)
621440a403fSchristos 	      rl78_error ("Only ES allowed here");
622440a403fSchristos 	    else
623440a403fSchristos 	      { B2 (0x61, 0xb8); SET_SA ($5); O1 ($5); }
624440a403fSchristos 	  }
625440a403fSchristos 
626440a403fSchristos 	| MOV A ',' opt_es '[' DE ']'
627440a403fSchristos 	  { B1 (0x89); }
628440a403fSchristos 
629440a403fSchristos 	| MOV opt_es '[' DE ']' ',' A
630440a403fSchristos 	  { B1 (0x99); }
631440a403fSchristos 
632440a403fSchristos 	| MOV opt_es '[' DE '+' EXPR ']' ',' '#' EXPR
633440a403fSchristos 	  { B1 (0xca); O1 ($6); O1 ($10); }
634440a403fSchristos 
635440a403fSchristos 	| MOV A ',' opt_es '[' DE '+' EXPR ']'
636440a403fSchristos 	  { B1 (0x8a); O1 ($8); }
637440a403fSchristos 
638440a403fSchristos 	| MOV opt_es '[' DE '+' EXPR ']' ',' A
639440a403fSchristos 	  { B1 (0x9a); O1 ($6); }
640440a403fSchristos 
641440a403fSchristos 	| MOV A ',' opt_es '[' HL ']'
642440a403fSchristos 	  { B1 (0x8b); }
643440a403fSchristos 
644440a403fSchristos 	| MOV opt_es '[' HL ']' ',' A
645440a403fSchristos 	  { B1 (0x9b); }
646440a403fSchristos 
647440a403fSchristos 	| MOV opt_es '[' HL '+' EXPR ']' ',' '#' EXPR
648440a403fSchristos 	  { B1 (0xcc); O1 ($6); O1 ($10); }
649440a403fSchristos 
650440a403fSchristos 	| MOV A ',' opt_es '[' HL '+' EXPR ']'
651440a403fSchristos 	  { B1 (0x8c); O1 ($8); }
652440a403fSchristos 
653440a403fSchristos 	| MOV opt_es '[' HL '+' EXPR ']' ',' A
654440a403fSchristos 	  { B1 (0x9c); O1 ($6); }
655440a403fSchristos 
656440a403fSchristos 	| MOV A ',' opt_es '[' HL '+' B ']'
657440a403fSchristos 	  { B2 (0x61, 0xc9); }
658440a403fSchristos 
659440a403fSchristos 	| MOV opt_es '[' HL '+' B ']' ',' A
660440a403fSchristos 	  { B2 (0x61, 0xd9); }
661440a403fSchristos 
662440a403fSchristos 	| MOV A ',' opt_es '[' HL '+' C ']'
663440a403fSchristos 	  { B2 (0x61, 0xe9); }
664440a403fSchristos 
665440a403fSchristos 	| MOV opt_es '[' HL '+' C ']' ',' A
666440a403fSchristos 	  { B2 (0x61, 0xf9); }
667440a403fSchristos 
668440a403fSchristos 	| MOV opt_es EXPR '[' B ']' ',' '#' EXPR
669440a403fSchristos 	  { B1 (0x19); O2 ($3); O1 ($9); }
670440a403fSchristos 
671440a403fSchristos 	| MOV A ',' opt_es EXPR '[' B ']'
672440a403fSchristos 	  { B1 (0x09); O2 ($5); }
673440a403fSchristos 
674440a403fSchristos 	| MOV opt_es EXPR '[' B ']' ',' A
675440a403fSchristos 	  { B1 (0x18); O2 ($3); }
676440a403fSchristos 
677440a403fSchristos 	| MOV opt_es EXPR '[' C ']' ',' '#' EXPR
678440a403fSchristos 	  { B1 (0x38); O2 ($3); O1 ($9); }
679440a403fSchristos 
680440a403fSchristos 	| MOV A ',' opt_es EXPR '[' C ']'
681440a403fSchristos 	  { B1 (0x29); O2 ($5); }
682440a403fSchristos 
683440a403fSchristos 	| MOV opt_es EXPR '[' C ']' ',' A
684440a403fSchristos 	  { B1 (0x28); O2 ($3); }
685440a403fSchristos 
686440a403fSchristos 	| MOV opt_es EXPR '[' BC ']' ',' '#' EXPR
687440a403fSchristos 	  { B1 (0x39); O2 ($3); O1 ($9); }
688440a403fSchristos 
689440a403fSchristos 	| MOV opt_es '[' BC ']' ',' '#' EXPR
690440a403fSchristos 	  { B3 (0x39, 0, 0); O1 ($8); }
691440a403fSchristos 
692440a403fSchristos 	| MOV A ',' opt_es EXPR '[' BC ']'
693440a403fSchristos 	  { B1 (0x49); O2 ($5); }
694440a403fSchristos 
695440a403fSchristos 	| MOV A ',' opt_es '[' BC ']'
696440a403fSchristos 	  { B3 (0x49, 0, 0); }
697440a403fSchristos 
698440a403fSchristos 	| MOV opt_es EXPR '[' BC ']' ',' A
699440a403fSchristos 	  { B1 (0x48); O2 ($3); }
700440a403fSchristos 
701440a403fSchristos 	| MOV opt_es '[' BC ']' ',' A
702440a403fSchristos 	  { B3 (0x48, 0, 0); }
703440a403fSchristos 
704440a403fSchristos 	| MOV opt_es '[' SP '+' EXPR ']' ',' '#' EXPR  {NOT_ES}
705440a403fSchristos 	  { B1 (0xc8); O1 ($6); O1 ($10); }
706440a403fSchristos 
707440a403fSchristos 	| MOV opt_es '[' SP ']' ',' '#' EXPR  {NOT_ES}
708440a403fSchristos 	  { B2 (0xc8, 0); O1 ($8); }
709440a403fSchristos 
710440a403fSchristos 	| MOV A ',' opt_es '[' SP '+' EXPR ']'  {NOT_ES}
711440a403fSchristos 	  { B1 (0x88); O1 ($8); }
712440a403fSchristos 
713440a403fSchristos 	| MOV A ',' opt_es '[' SP ']'  {NOT_ES}
714440a403fSchristos 	  { B2 (0x88, 0); }
715440a403fSchristos 
716440a403fSchristos 	| MOV opt_es '[' SP '+' EXPR ']' ',' A  {NOT_ES}
717440a403fSchristos 	  { B1 (0x98); O1 ($6); }
718440a403fSchristos 
719440a403fSchristos 	| MOV opt_es '[' SP ']' ',' A  {NOT_ES}
720440a403fSchristos 	  { B2 (0x98, 0); }
721440a403fSchristos 
722440a403fSchristos /* ---------------------------------------------------------------------- */
723440a403fSchristos 
724440a403fSchristos 	| mov1 CY ',' EXPR '.' EXPR
725440a403fSchristos 	  { if (expr_is_saddr ($4))
726440a403fSchristos 	      { B2 (0x71, 0x04); FE ($6, 9, 3); SET_SA ($4); O1 ($4); }
727440a403fSchristos 	    else if (expr_is_sfr ($4))
728440a403fSchristos 	      { B2 (0x71, 0x0c); FE ($6, 9, 3); O1 ($4); }
729440a403fSchristos 	    else
730440a403fSchristos 	      NOT_SFR_OR_SADDR;
731440a403fSchristos 	  }
732440a403fSchristos 
733440a403fSchristos 	| mov1 CY ',' A '.' EXPR
734440a403fSchristos 	  { B2 (0x71, 0x8c); FE ($6, 9, 3); }
735440a403fSchristos 
736440a403fSchristos 	| mov1 CY ',' sfr '.' EXPR
737440a403fSchristos 	  { B3 (0x71, 0x0c, $4); FE ($6, 9, 3); }
738440a403fSchristos 
739440a403fSchristos 	| mov1 CY ',' opt_es '[' HL ']' '.' EXPR
740440a403fSchristos 	  { B2 (0x71, 0x84); FE ($9, 9, 3); }
741440a403fSchristos 
742440a403fSchristos 	| mov1 EXPR '.' EXPR ',' CY
743440a403fSchristos 	  { if (expr_is_saddr ($2))
744440a403fSchristos 	      { B2 (0x71, 0x01); FE ($4, 9, 3); SET_SA ($2); O1 ($2); }
745440a403fSchristos 	    else if (expr_is_sfr ($2))
746440a403fSchristos 	      { B2 (0x71, 0x09); FE ($4, 9, 3); O1 ($2); }
747440a403fSchristos 	    else
748440a403fSchristos 	      NOT_SFR_OR_SADDR;
749440a403fSchristos 	  }
750440a403fSchristos 
751440a403fSchristos 	| mov1 A '.' EXPR ',' CY
752440a403fSchristos 	  { B2 (0x71, 0x89); FE ($4, 9, 3); }
753440a403fSchristos 
754440a403fSchristos 	| mov1 sfr '.' EXPR ',' CY
755440a403fSchristos 	  { B3 (0x71, 0x09, $2); FE ($4, 9, 3); }
756440a403fSchristos 
757440a403fSchristos 	| mov1 opt_es '[' HL ']' '.' EXPR ',' CY
758440a403fSchristos 	  { B2 (0x71, 0x81); FE ($7, 9, 3); }
759440a403fSchristos 
760440a403fSchristos /* ---------------------------------------------------------------------- */
761440a403fSchristos 
762440a403fSchristos 	| MOVS opt_es '[' HL '+' EXPR ']' ',' X
763440a403fSchristos 	  { B2 (0x61, 0xce); O1 ($6); }
764440a403fSchristos 
765440a403fSchristos /* ---------------------------------------------------------------------- */
766440a403fSchristos 
767440a403fSchristos 	| MOVW AX ',' '#' EXPR
768440a403fSchristos 	  { B1 (0x30); O2 ($5); }
769440a403fSchristos 
770440a403fSchristos 	| MOVW regw_na ',' '#' EXPR
771440a403fSchristos 	  { B1 (0x30); F ($2, 5, 2); O2 ($5); }
772440a403fSchristos 
773440a403fSchristos 	| MOVW opt_es EXPR ',' '#' EXPR {NOT_ES}
774440a403fSchristos 	  { if (expr_is_saddr ($3))
775440a403fSchristos 	      { B1 (0xc9); SET_SA ($3); O1 ($3); O2 ($6); }
776440a403fSchristos 	    else if (expr_is_sfr ($3))
777440a403fSchristos 	      { B1 (0xcb); O1 ($3); O2 ($6); }
778440a403fSchristos 	    else
779440a403fSchristos 	      NOT_SFR_OR_SADDR;
780440a403fSchristos 	  }
781440a403fSchristos 
782440a403fSchristos 	| MOVW AX ',' opt_es EXPR {NOT_ES}
783440a403fSchristos 	  { if (expr_is_saddr ($5))
784440a403fSchristos 	      { B1 (0xad); SET_SA ($5); O1 ($5); WA($5); }
785440a403fSchristos 	    else if (expr_is_sfr ($5))
786440a403fSchristos 	      { B1 (0xae); O1 ($5); WA($5); }
787440a403fSchristos 	    else
788440a403fSchristos 	      NOT_SFR_OR_SADDR;
789440a403fSchristos 	  }
790440a403fSchristos 
791440a403fSchristos 	| MOVW opt_es EXPR ',' AX {NOT_ES}
792440a403fSchristos 	  { if (expr_is_saddr ($3))
793440a403fSchristos 	      { B1 (0xbd); SET_SA ($3); O1 ($3); WA($3); }
794440a403fSchristos 	    else if (expr_is_sfr ($3))
795440a403fSchristos 	      { B1 (0xbe); O1 ($3); WA($3); }
796440a403fSchristos 	    else
797440a403fSchristos 	      NOT_SFR_OR_SADDR;
798440a403fSchristos 	  }
799440a403fSchristos 
800440a403fSchristos 	| MOVW AX ',' regw_na
801440a403fSchristos 	  { B1 (0x11); F ($4, 5, 2); }
802440a403fSchristos 
803440a403fSchristos 	| MOVW regw_na ',' AX
804440a403fSchristos 	  { B1 (0x10); F ($2, 5, 2); }
805440a403fSchristos 
806440a403fSchristos 	| MOVW AX ',' opt_es '!' EXPR
807440a403fSchristos 	  { B1 (0xaf); O2 ($6); WA($6); rl78_linkrelax_addr16 (); }
808440a403fSchristos 
809440a403fSchristos 	| MOVW opt_es '!' EXPR ',' AX
810440a403fSchristos 	  { B1 (0xbf); O2 ($4); WA($4); rl78_linkrelax_addr16 (); }
811440a403fSchristos 
812440a403fSchristos 	| MOVW AX ',' opt_es '[' DE ']'
813440a403fSchristos 	  { B1 (0xa9); }
814440a403fSchristos 
815440a403fSchristos 	| MOVW opt_es '[' DE ']' ',' AX
816440a403fSchristos 	  { B1 (0xb9); }
817440a403fSchristos 
818440a403fSchristos 	| MOVW AX ',' opt_es '[' DE '+' EXPR ']'
819440a403fSchristos 	  { B1 (0xaa); O1 ($8); }
820440a403fSchristos 
821440a403fSchristos 	| MOVW opt_es '[' DE '+' EXPR ']' ',' AX
822440a403fSchristos 	  { B1 (0xba); O1 ($6); }
823440a403fSchristos 
824440a403fSchristos 	| MOVW AX ',' opt_es '[' HL ']'
825440a403fSchristos 	  { B1 (0xab); }
826440a403fSchristos 
827440a403fSchristos 	| MOVW opt_es '[' HL ']' ',' AX
828440a403fSchristos 	  { B1 (0xbb); }
829440a403fSchristos 
830440a403fSchristos 	| MOVW AX ',' opt_es '[' HL '+' EXPR ']'
831440a403fSchristos 	  { B1 (0xac); O1 ($8); }
832440a403fSchristos 
833440a403fSchristos 	| MOVW opt_es '[' HL '+' EXPR ']' ',' AX
834440a403fSchristos 	  { B1 (0xbc); O1 ($6); }
835440a403fSchristos 
836440a403fSchristos 	| MOVW AX ',' opt_es EXPR '[' B ']'
837440a403fSchristos 	  { B1 (0x59); O2 ($5); }
838440a403fSchristos 
839440a403fSchristos 	| MOVW opt_es EXPR '[' B ']' ',' AX
840440a403fSchristos 	  { B1 (0x58); O2 ($3); }
841440a403fSchristos 
842440a403fSchristos 	| MOVW AX ',' opt_es EXPR '[' C ']'
843440a403fSchristos 	  { B1 (0x69); O2 ($5); }
844440a403fSchristos 
845440a403fSchristos 	| MOVW opt_es EXPR '[' C ']' ',' AX
846440a403fSchristos 	  { B1 (0x68); O2 ($3); }
847440a403fSchristos 
848440a403fSchristos 	| MOVW AX ',' opt_es EXPR '[' BC ']'
849440a403fSchristos 	  { B1 (0x79); O2 ($5); }
850440a403fSchristos 
851440a403fSchristos 	| MOVW AX ',' opt_es '[' BC ']'
852440a403fSchristos 	  { B3 (0x79, 0, 0); }
853440a403fSchristos 
854440a403fSchristos 	| MOVW opt_es EXPR '[' BC ']' ',' AX
855440a403fSchristos 	  { B1 (0x78); O2 ($3); }
856440a403fSchristos 
857440a403fSchristos 	| MOVW opt_es '[' BC ']' ',' AX
858440a403fSchristos 	  { B3 (0x78, 0, 0); }
859440a403fSchristos 
860440a403fSchristos 	| MOVW AX ',' opt_es '[' SP '+' EXPR ']' {NOT_ES}
861440a403fSchristos 	  { B1 (0xa8); O1 ($8);  WA($8);}
862440a403fSchristos 
863440a403fSchristos 	| MOVW AX ',' opt_es '[' SP ']' {NOT_ES}
864440a403fSchristos 	  { B2 (0xa8, 0); }
865440a403fSchristos 
866440a403fSchristos 	| MOVW opt_es '[' SP '+' EXPR ']' ',' AX {NOT_ES}
867440a403fSchristos 	  { B1 (0xb8); O1 ($6); WA($6); }
868440a403fSchristos 
869440a403fSchristos 	| MOVW opt_es '[' SP ']' ',' AX {NOT_ES}
870440a403fSchristos 	  { B2 (0xb8, 0); }
871440a403fSchristos 
872440a403fSchristos 	| MOVW regw_na ',' EXPR {SA($4)}
873440a403fSchristos 	  { B1 (0xca); F ($2, 2, 2); SET_SA ($4); O1 ($4); WA($4); }
874440a403fSchristos 
875440a403fSchristos 	| MOVW regw_na ',' opt_es '!' EXPR
876440a403fSchristos 	  { B1 (0xcb); F ($2, 2, 2); O2 ($6); WA($6); rl78_linkrelax_addr16 (); }
877440a403fSchristos 
878440a403fSchristos 	| MOVW SP ',' '#' EXPR
879440a403fSchristos 	  { B2 (0xcb, 0xf8); O2 ($5); }
880440a403fSchristos 
881440a403fSchristos 	| MOVW SP ',' AX
882440a403fSchristos 	  { B2 (0xbe, 0xf8); }
883440a403fSchristos 
884440a403fSchristos 	| MOVW AX ',' SP
885440a403fSchristos 	  { B2 (0xae, 0xf8); }
886440a403fSchristos 
887440a403fSchristos 	| MOVW regw_na ',' SP
888440a403fSchristos 	  { B3 (0xcb, 0xf8, 0xff); F ($2, 2, 2); }
889440a403fSchristos 
890440a403fSchristos /* ---------------------------------------------------------------------- */
891440a403fSchristos 
892440a403fSchristos 	| NOP
893440a403fSchristos 	  { B1 (0x00); }
894440a403fSchristos 
895440a403fSchristos /* ---------------------------------------------------------------------- */
896440a403fSchristos 
897440a403fSchristos 	| NOT1 CY
898440a403fSchristos 	  { B2 (0x71, 0xc0); }
899440a403fSchristos 
900440a403fSchristos /* ---------------------------------------------------------------------- */
901440a403fSchristos 
902440a403fSchristos 	| POP regw
903440a403fSchristos 	  { B1 (0xc0); F ($2, 5, 2); }
904440a403fSchristos 
905440a403fSchristos 	| POP PSW
906440a403fSchristos 	  { B2 (0x61, 0xcd); };
907440a403fSchristos 
908440a403fSchristos 	| PUSH regw
909440a403fSchristos 	  { B1 (0xc1); F ($2, 5, 2); }
910440a403fSchristos 
911440a403fSchristos 	| PUSH PSW
912440a403fSchristos 	  { B2 (0x61, 0xdd); };
913440a403fSchristos 
914440a403fSchristos /* ---------------------------------------------------------------------- */
915440a403fSchristos 
916440a403fSchristos 	| RET
917440a403fSchristos 	  { B1 (0xd7); }
918440a403fSchristos 
919440a403fSchristos 	| RETI
920440a403fSchristos 	  { B2 (0x61, 0xfc); }
921440a403fSchristos 
922440a403fSchristos 	| RETB
923440a403fSchristos 	  { B2 (0x61, 0xec); }
924440a403fSchristos 
925440a403fSchristos /* ---------------------------------------------------------------------- */
926440a403fSchristos 
927440a403fSchristos 	| ROL A ',' EXPR
928440a403fSchristos 	  { if (check_expr_is_const ($4, 1, 1))
929440a403fSchristos 	      { B2 (0x61, 0xeb); }
930440a403fSchristos 	  }
931440a403fSchristos 
932440a403fSchristos 	| ROLC A ',' EXPR
933440a403fSchristos 	  { if (check_expr_is_const ($4, 1, 1))
934440a403fSchristos 	      { B2 (0x61, 0xdc); }
935440a403fSchristos 	  }
936440a403fSchristos 
937440a403fSchristos 	| ROLWC AX ',' EXPR
938440a403fSchristos 	  { if (check_expr_is_const ($4, 1, 1))
939440a403fSchristos 	      { B2 (0x61, 0xee); }
940440a403fSchristos 	  }
941440a403fSchristos 
942440a403fSchristos 	| ROLWC BC ',' EXPR
943440a403fSchristos 	  { if (check_expr_is_const ($4, 1, 1))
944440a403fSchristos 	      { B2 (0x61, 0xfe); }
945440a403fSchristos 	  }
946440a403fSchristos 
947440a403fSchristos 	| ROR A ',' EXPR
948440a403fSchristos 	  { if (check_expr_is_const ($4, 1, 1))
949440a403fSchristos 	      { B2 (0x61, 0xdb); }
950440a403fSchristos 	  }
951440a403fSchristos 
952440a403fSchristos 	| RORC A ',' EXPR
953440a403fSchristos 	  { if (check_expr_is_const ($4, 1, 1))
954440a403fSchristos 	      { B2 (0x61, 0xfb);}
955440a403fSchristos 	  }
956440a403fSchristos 
957440a403fSchristos /* ---------------------------------------------------------------------- */
958440a403fSchristos 
959440a403fSchristos 	| SAR A ',' EXPR
960440a403fSchristos 	  { if (check_expr_is_const ($4, 1, 7))
961440a403fSchristos 	      { B2 (0x31, 0x0b); FE ($4, 9, 3); }
962440a403fSchristos 	  }
963440a403fSchristos 
964440a403fSchristos 	| SARW AX ',' EXPR
965440a403fSchristos 	  { if (check_expr_is_const ($4, 1, 15))
966440a403fSchristos 	      { B2 (0x31, 0x0f); FE ($4, 8, 4); }
967440a403fSchristos 	  }
968440a403fSchristos 
969440a403fSchristos /* ---------------------------------------------------------------------- */
970440a403fSchristos 
971440a403fSchristos 	| SEL RB0
972440a403fSchristos 	  { B2 (0x61, 0xcf); }
973440a403fSchristos 
974440a403fSchristos 	| SEL RB1
975440a403fSchristos 	  { B2 (0x61, 0xdf); }
976440a403fSchristos 
977440a403fSchristos 	| SEL RB2
978440a403fSchristos 	  { B2 (0x61, 0xef); }
979440a403fSchristos 
980440a403fSchristos 	| SEL RB3
981440a403fSchristos 	  { B2 (0x61, 0xff); }
982440a403fSchristos 
983440a403fSchristos /* ---------------------------------------------------------------------- */
984440a403fSchristos 
985440a403fSchristos 	| SHL A ',' EXPR
986440a403fSchristos 	  { if (check_expr_is_const ($4, 1, 7))
987440a403fSchristos 	      { B2 (0x31, 0x09); FE ($4, 9, 3); }
988440a403fSchristos 	  }
989440a403fSchristos 
990440a403fSchristos 	| SHL B ',' EXPR
991440a403fSchristos 	  { if (check_expr_is_const ($4, 1, 7))
992440a403fSchristos 	      { B2 (0x31, 0x08); FE ($4, 9, 3); }
993440a403fSchristos 	  }
994440a403fSchristos 
995440a403fSchristos 	| SHL C ',' EXPR
996440a403fSchristos 	  { if (check_expr_is_const ($4, 1, 7))
997440a403fSchristos 	      { B2 (0x31, 0x07); FE ($4, 9, 3); }
998440a403fSchristos 	  }
999440a403fSchristos 
1000440a403fSchristos 	| SHLW AX ',' EXPR
1001440a403fSchristos 	  { if (check_expr_is_const ($4, 1, 15))
1002440a403fSchristos 	      { B2 (0x31, 0x0d); FE ($4, 8, 4); }
1003440a403fSchristos 	  }
1004440a403fSchristos 
1005440a403fSchristos 	| SHLW BC ',' EXPR
1006440a403fSchristos 	  { if (check_expr_is_const ($4, 1, 15))
1007440a403fSchristos 	      { B2 (0x31, 0x0c); FE ($4, 8, 4); }
1008440a403fSchristos 	  }
1009440a403fSchristos 
1010440a403fSchristos /* ---------------------------------------------------------------------- */
1011440a403fSchristos 
1012440a403fSchristos 	| SHR A ',' EXPR
1013440a403fSchristos 	  { if (check_expr_is_const ($4, 1, 7))
1014440a403fSchristos 	      { B2 (0x31, 0x0a); FE ($4, 9, 3); }
1015440a403fSchristos 	  }
1016440a403fSchristos 
1017440a403fSchristos 	| SHRW AX ',' EXPR
1018440a403fSchristos 	  { if (check_expr_is_const ($4, 1, 15))
1019440a403fSchristos 	      { B2 (0x31, 0x0e); FE ($4, 8, 4); }
1020440a403fSchristos 	  }
1021440a403fSchristos 
1022440a403fSchristos /* ---------------------------------------------------------------------- */
1023440a403fSchristos 
1024440a403fSchristos 	| SKC
1025440a403fSchristos 	  { B2 (0x61, 0xc8); rl78_relax (RL78_RELAX_BRANCH, 0); }
1026440a403fSchristos 
1027440a403fSchristos 	| SKH
1028440a403fSchristos 	  { B2 (0x61, 0xe3); rl78_relax (RL78_RELAX_BRANCH, 0); }
1029440a403fSchristos 
1030440a403fSchristos 	| SKNC
1031440a403fSchristos 	  { B2 (0x61, 0xd8); rl78_relax (RL78_RELAX_BRANCH, 0); }
1032440a403fSchristos 
1033440a403fSchristos 	| SKNH
1034440a403fSchristos 	  { B2 (0x61, 0xf3); rl78_relax (RL78_RELAX_BRANCH, 0); }
1035440a403fSchristos 
1036440a403fSchristos 	| SKNZ
1037440a403fSchristos 	  { B2 (0x61, 0xf8); rl78_relax (RL78_RELAX_BRANCH, 0); }
1038440a403fSchristos 
1039440a403fSchristos 	| SKZ
1040440a403fSchristos 	  { B2 (0x61, 0xe8); rl78_relax (RL78_RELAX_BRANCH, 0); }
1041440a403fSchristos 
1042440a403fSchristos /* ---------------------------------------------------------------------- */
1043440a403fSchristos 
1044440a403fSchristos 	| STOP
1045440a403fSchristos 	  { B2 (0x61, 0xfd); }
1046440a403fSchristos 
1047440a403fSchristos /* ---------------------------------------------------------------------- */
1048440a403fSchristos 
1049440a403fSchristos 	| XCH A ',' regb_na
1050440a403fSchristos 	  { if ($4 == 0) /* X */
1051440a403fSchristos 	      { B1 (0x08); }
1052440a403fSchristos 	    else
1053440a403fSchristos 	      { B2 (0x61, 0x88); F ($4, 13, 3); }
1054440a403fSchristos 	  }
1055440a403fSchristos 
1056440a403fSchristos 	| XCH A ',' opt_es '!' EXPR
1057440a403fSchristos 	  { B2 (0x61, 0xaa); O2 ($6); rl78_linkrelax_addr16 (); }
1058440a403fSchristos 
1059440a403fSchristos 	| XCH A ',' opt_es '[' DE ']'
1060440a403fSchristos 	  { B2 (0x61, 0xae); }
1061440a403fSchristos 
1062440a403fSchristos 	| XCH A ',' opt_es '[' DE '+' EXPR ']'
1063440a403fSchristos 	  { B2 (0x61, 0xaf); O1 ($8); }
1064440a403fSchristos 
1065440a403fSchristos 	| XCH A ',' opt_es '[' HL ']'
1066440a403fSchristos 	  { B2 (0x61, 0xac); }
1067440a403fSchristos 
1068440a403fSchristos 	| XCH A ',' opt_es '[' HL '+' EXPR ']'
1069440a403fSchristos 	  { B2 (0x61, 0xad); O1 ($8); }
1070440a403fSchristos 
1071440a403fSchristos 	| XCH A ',' opt_es '[' HL '+' B ']'
1072440a403fSchristos 	  { B2 (0x61, 0xb9); }
1073440a403fSchristos 
1074440a403fSchristos 	| XCH A ',' opt_es '[' HL '+' C ']'
1075440a403fSchristos 	  { B2 (0x61, 0xa9); }
1076440a403fSchristos 
1077440a403fSchristos 	| XCH A ',' EXPR
1078440a403fSchristos 	  { if (expr_is_sfr ($4))
1079440a403fSchristos 	      { B2 (0x61, 0xab); O1 ($4); }
1080440a403fSchristos 	    else if (expr_is_saddr ($4))
1081440a403fSchristos 	      { B2 (0x61, 0xa8); SET_SA ($4); O1 ($4); }
1082440a403fSchristos 	    else
1083440a403fSchristos 	      NOT_SFR_OR_SADDR;
1084440a403fSchristos 	  }
1085440a403fSchristos 
1086440a403fSchristos /* ---------------------------------------------------------------------- */
1087440a403fSchristos 
1088440a403fSchristos 	| XCHW AX ',' regw_na
1089440a403fSchristos 	  { B1 (0x31); F ($4, 5, 2); }
1090440a403fSchristos 
1091440a403fSchristos /* ---------------------------------------------------------------------- */
1092440a403fSchristos 
1093440a403fSchristos 	; /* end of statement */
1094440a403fSchristos 
1095440a403fSchristos /* ---------------------------------------------------------------------- */
1096440a403fSchristos 
1097440a403fSchristos opt_es	: /* nothing */
1098440a403fSchristos 	| ES ':'
1099440a403fSchristos 	  { rl78_prefix (0x11); }
1100440a403fSchristos 	;
1101440a403fSchristos 
1102440a403fSchristos regb	: X { $$ = 0; }
1103440a403fSchristos 	| A { $$ = 1; }
1104440a403fSchristos 	| C { $$ = 2; }
1105440a403fSchristos 	| B { $$ = 3; }
1106440a403fSchristos 	| E { $$ = 4; }
1107440a403fSchristos 	| D { $$ = 5; }
1108440a403fSchristos 	| L { $$ = 6; }
1109440a403fSchristos 	| H { $$ = 7; }
1110440a403fSchristos 	;
1111440a403fSchristos 
1112440a403fSchristos regb_na	: X { $$ = 0; }
1113440a403fSchristos 	| C { $$ = 2; }
1114440a403fSchristos 	| B { $$ = 3; }
1115440a403fSchristos 	| E { $$ = 4; }
1116440a403fSchristos 	| D { $$ = 5; }
1117440a403fSchristos 	| L { $$ = 6; }
1118440a403fSchristos 	| H { $$ = 7; }
1119440a403fSchristos 	;
1120440a403fSchristos 
1121440a403fSchristos regw	: AX { $$ = 0; }
1122440a403fSchristos 	| BC { $$ = 1; }
1123440a403fSchristos 	| DE { $$ = 2; }
1124440a403fSchristos 	| HL { $$ = 3; }
1125440a403fSchristos 	;
1126440a403fSchristos 
1127440a403fSchristos regw_na	: BC { $$ = 1; }
1128440a403fSchristos 	| DE { $$ = 2; }
1129440a403fSchristos 	| HL { $$ = 3; }
1130440a403fSchristos 	;
1131440a403fSchristos 
1132440a403fSchristos sfr	: SPL { $$ = 0xf8; }
1133440a403fSchristos 	| SPH { $$ = 0xf9; }
1134440a403fSchristos 	| PSW { $$ = 0xfa; }
1135440a403fSchristos 	| CS  { $$ = 0xfc; }
1136440a403fSchristos 	| ES  { $$ = 0xfd; }
1137440a403fSchristos 	| PMC { $$ = 0xfe; }
1138440a403fSchristos 	| MEM { $$ = 0xff; }
1139440a403fSchristos 	;
1140440a403fSchristos 
1141440a403fSchristos /* ---------------------------------------------------------------------- */
1142440a403fSchristos /* Shortcuts for groups of opcodes with common encodings.                 */
1143440a403fSchristos 
1144440a403fSchristos addsub	: ADD  { $$ = 0x00; }
1145440a403fSchristos 	| ADDC { $$ = 0x10; }
1146440a403fSchristos 	| SUB  { $$ = 0x20; }
1147440a403fSchristos 	| SUBC { $$ = 0x30; }
1148440a403fSchristos 	| CMP  { $$ = 0x40; }
1149440a403fSchristos 	| AND_ { $$ = 0x50; }
1150440a403fSchristos 	| OR   { $$ = 0x60; }
1151440a403fSchristos 	| XOR  { $$ = 0x70; }
1152440a403fSchristos 	;
1153440a403fSchristos 
1154440a403fSchristos addsubw	: ADDW  { $$ = 0x00; }
1155440a403fSchristos 	| SUBW  { $$ = 0x20; }
1156440a403fSchristos 	| CMPW  { $$ = 0x40; }
1157440a403fSchristos 	;
1158440a403fSchristos 
1159440a403fSchristos andor1	: AND1 { $$ = 0x05; rl78_bit_insn = 1; }
1160440a403fSchristos 	| OR1  { $$ = 0x06; rl78_bit_insn = 1; }
1161440a403fSchristos 	| XOR1 { $$ = 0x07; rl78_bit_insn = 1; }
1162440a403fSchristos 	;
1163440a403fSchristos 
1164440a403fSchristos bt_bf	: BT { $$ = 0x02;    rl78_bit_insn = 1; rl78_linkrelax_branch (); }
1165440a403fSchristos 	| BF { $$ = 0x04;    rl78_bit_insn = 1; rl78_linkrelax_branch (); }
1166440a403fSchristos 	| BTCLR { $$ = 0x00; rl78_bit_insn = 1; }
1167440a403fSchristos 	;
1168440a403fSchristos 
1169440a403fSchristos setclr1	: SET1 { $$ = 0; rl78_bit_insn = 1; }
1170440a403fSchristos 	| CLR1 { $$ = 1; rl78_bit_insn = 1; }
1171440a403fSchristos 	;
1172440a403fSchristos 
1173440a403fSchristos oneclrb	: ONEB { $$ = 0x00; }
1174440a403fSchristos 	| CLRB { $$ = 0x10; }
1175440a403fSchristos 	;
1176440a403fSchristos 
1177440a403fSchristos oneclrw	: ONEW { $$ = 0x00; }
1178440a403fSchristos 	| CLRW { $$ = 0x10; }
1179440a403fSchristos 	;
1180440a403fSchristos 
1181440a403fSchristos incdec	: INC { $$ = 0x00; }
1182440a403fSchristos 	| DEC { $$ = 0x10; }
1183440a403fSchristos 	;
1184440a403fSchristos 
1185440a403fSchristos incdecw	: INCW { $$ = 0x00; }
1186440a403fSchristos 	| DECW { $$ = 0x10; }
1187440a403fSchristos 	;
1188440a403fSchristos 
1189440a403fSchristos mov1	: MOV1 { rl78_bit_insn = 1; }
1190440a403fSchristos 	;
1191440a403fSchristos 
1192440a403fSchristos %%
1193440a403fSchristos /* ====================================================================== */
1194440a403fSchristos 
1195440a403fSchristos static struct
1196440a403fSchristos {
1197440a403fSchristos   const char * string;
1198440a403fSchristos   int          token;
1199440a403fSchristos   int          val;
1200440a403fSchristos }
1201440a403fSchristos token_table[] =
1202440a403fSchristos {
1203440a403fSchristos   { "r0", X, 0 },
1204440a403fSchristos   { "r1", A, 1 },
1205440a403fSchristos   { "r2", C, 2 },
1206440a403fSchristos   { "r3", B, 3 },
1207440a403fSchristos   { "r4", E, 4 },
1208440a403fSchristos   { "r5", D, 5 },
1209440a403fSchristos   { "r6", L, 6 },
1210440a403fSchristos   { "r7", H, 7 },
1211440a403fSchristos   { "x", X, 0 },
1212440a403fSchristos   { "a", A, 1 },
1213440a403fSchristos   { "c", C, 2 },
1214440a403fSchristos   { "b", B, 3 },
1215440a403fSchristos   { "e", E, 4 },
1216440a403fSchristos   { "d", D, 5 },
1217440a403fSchristos   { "l", L, 6 },
1218440a403fSchristos   { "h", H, 7 },
1219440a403fSchristos 
1220440a403fSchristos   { "rp0", AX, 0 },
1221440a403fSchristos   { "rp1", BC, 1 },
1222440a403fSchristos   { "rp2", DE, 2 },
1223440a403fSchristos   { "rp3", HL, 3 },
1224440a403fSchristos   { "ax", AX, 0 },
1225440a403fSchristos   { "bc", BC, 1 },
1226440a403fSchristos   { "de", DE, 2 },
1227440a403fSchristos   { "hl", HL, 3 },
1228440a403fSchristos 
1229440a403fSchristos   { "RB0", RB0, 0 },
1230440a403fSchristos   { "RB1", RB1, 1 },
1231440a403fSchristos   { "RB2", RB2, 2 },
1232440a403fSchristos   { "RB3", RB3, 3 },
1233440a403fSchristos 
1234440a403fSchristos   { "sp", SP, 0 },
1235440a403fSchristos   { "cy", CY, 0 },
1236440a403fSchristos 
1237440a403fSchristos   { "spl", SPL, 0xf8 },
1238440a403fSchristos   { "sph", SPH, 0xf9 },
1239440a403fSchristos   { "psw", PSW, 0xfa },
1240440a403fSchristos   { "cs", CS, 0xfc },
1241440a403fSchristos   { "es", ES, 0xfd },
1242440a403fSchristos   { "pmc", PMC, 0xfe },
1243440a403fSchristos   { "mem", MEM, 0xff },
1244440a403fSchristos 
1245440a403fSchristos   { ".s", DOT_S, 0 },
1246440a403fSchristos   { ".b", DOT_B, 0 },
1247440a403fSchristos   { ".w", DOT_W, 0 },
1248440a403fSchristos   { ".l", DOT_L, 0 },
1249440a403fSchristos   { ".a", DOT_A , 0},
1250440a403fSchristos   { ".ub", DOT_UB, 0 },
1251440a403fSchristos   { ".uw", DOT_UW , 0},
1252440a403fSchristos 
1253440a403fSchristos   { "c", FLAG, 0 },
1254440a403fSchristos   { "z", FLAG, 1 },
1255440a403fSchristos   { "s", FLAG, 2 },
1256440a403fSchristos   { "o", FLAG, 3 },
1257440a403fSchristos   { "i", FLAG, 8 },
1258440a403fSchristos   { "u", FLAG, 9 },
1259440a403fSchristos 
1260440a403fSchristos #define OPC(x) { #x, x, IS_OPCODE }
1261440a403fSchristos 
1262440a403fSchristos   OPC(ADD),
1263440a403fSchristos   OPC(ADDC),
1264440a403fSchristos   OPC(ADDW),
1265440a403fSchristos   { "and", AND_, IS_OPCODE },
1266440a403fSchristos   OPC(AND1),
1267440a403fSchristos   OPC(BC),
1268440a403fSchristos   OPC(BF),
1269440a403fSchristos   OPC(BH),
1270440a403fSchristos   OPC(BNC),
1271440a403fSchristos   OPC(BNH),
1272440a403fSchristos   OPC(BNZ),
1273440a403fSchristos   OPC(BR),
1274440a403fSchristos   OPC(BRK),
1275440a403fSchristos   OPC(BRK1),
1276440a403fSchristos   OPC(BT),
1277440a403fSchristos   OPC(BTCLR),
1278440a403fSchristos   OPC(BZ),
1279440a403fSchristos   OPC(CALL),
1280440a403fSchristos   OPC(CALLT),
1281440a403fSchristos   OPC(CLR1),
1282440a403fSchristos   OPC(CLRB),
1283440a403fSchristos   OPC(CLRW),
1284440a403fSchristos   OPC(CMP),
1285440a403fSchristos   OPC(CMP0),
1286440a403fSchristos   OPC(CMPS),
1287440a403fSchristos   OPC(CMPW),
1288440a403fSchristos   OPC(DEC),
1289440a403fSchristos   OPC(DECW),
1290440a403fSchristos   OPC(DI),
1291440a403fSchristos   OPC(DIVHU),
1292440a403fSchristos   OPC(DIVWU),
1293440a403fSchristos   OPC(EI),
1294440a403fSchristos   OPC(HALT),
1295440a403fSchristos   OPC(INC),
1296440a403fSchristos   OPC(INCW),
1297440a403fSchristos   OPC(MACH),
1298440a403fSchristos   OPC(MACHU),
1299440a403fSchristos   OPC(MOV),
1300440a403fSchristos   OPC(MOV1),
1301440a403fSchristos   OPC(MOVS),
1302440a403fSchristos   OPC(MOVW),
1303440a403fSchristos   OPC(MULH),
1304440a403fSchristos   OPC(MULHU),
1305440a403fSchristos   OPC(MULU),
1306440a403fSchristos   OPC(NOP),
1307440a403fSchristos   OPC(NOT1),
1308440a403fSchristos   OPC(ONEB),
1309440a403fSchristos   OPC(ONEW),
1310440a403fSchristos   OPC(OR),
1311440a403fSchristos   OPC(OR1),
1312440a403fSchristos   OPC(POP),
1313440a403fSchristos   OPC(PUSH),
1314440a403fSchristos   OPC(RET),
1315440a403fSchristos   OPC(RETI),
1316440a403fSchristos   OPC(RETB),
1317440a403fSchristos   OPC(ROL),
1318440a403fSchristos   OPC(ROLC),
1319440a403fSchristos   OPC(ROLWC),
1320440a403fSchristos   OPC(ROR),
1321440a403fSchristos   OPC(RORC),
1322440a403fSchristos   OPC(SAR),
1323440a403fSchristos   OPC(SARW),
1324440a403fSchristos   OPC(SEL),
1325440a403fSchristos   OPC(SET1),
1326440a403fSchristos   OPC(SHL),
1327440a403fSchristos   OPC(SHLW),
1328440a403fSchristos   OPC(SHR),
1329440a403fSchristos   OPC(SHRW),
1330440a403fSchristos   OPC(SKC),
1331440a403fSchristos   OPC(SKH),
1332440a403fSchristos   OPC(SKNC),
1333440a403fSchristos   OPC(SKNH),
1334440a403fSchristos   OPC(SKNZ),
1335440a403fSchristos   OPC(SKZ),
1336440a403fSchristos   OPC(STOP),
1337440a403fSchristos   OPC(SUB),
1338440a403fSchristos   OPC(SUBC),
1339440a403fSchristos   OPC(SUBW),
1340440a403fSchristos   OPC(XCH),
1341440a403fSchristos   OPC(XCHW),
1342440a403fSchristos   OPC(XOR),
1343440a403fSchristos   OPC(XOR1),
1344440a403fSchristos };
1345440a403fSchristos 
1346440a403fSchristos #define NUM_TOKENS (sizeof (token_table) / sizeof (token_table[0]))
1347440a403fSchristos 
1348440a403fSchristos void
rl78_lex_init(char * beginning,char * ending)1349440a403fSchristos rl78_lex_init (char * beginning, char * ending)
1350440a403fSchristos {
1351440a403fSchristos   rl78_init_start = beginning;
1352440a403fSchristos   rl78_lex_start = beginning;
1353440a403fSchristos   rl78_lex_end = ending;
1354440a403fSchristos   rl78_in_brackets = 0;
1355440a403fSchristos   rl78_last_token = 0;
1356440a403fSchristos 
1357440a403fSchristos   rl78_bit_insn = 0;
1358440a403fSchristos 
1359440a403fSchristos   setbuf (stdout, 0);
1360440a403fSchristos }
1361440a403fSchristos 
1362440a403fSchristos /* Return a pointer to the '.' in a bit index expression (like
1363440a403fSchristos    foo.5), or NULL if none is found.  */
1364440a403fSchristos static char *
find_bit_index(char * tok)1365440a403fSchristos find_bit_index (char *tok)
1366440a403fSchristos {
1367440a403fSchristos   char *last_dot = NULL;
1368440a403fSchristos   char *last_digit = NULL;
1369440a403fSchristos   while (*tok && *tok != ',')
1370440a403fSchristos     {
1371440a403fSchristos       if (*tok == '.')
1372440a403fSchristos 	{
1373440a403fSchristos 	  last_dot = tok;
1374440a403fSchristos 	  last_digit = NULL;
1375440a403fSchristos 	}
1376440a403fSchristos       else if (*tok >= '0' && *tok <= '7'
1377440a403fSchristos 	       && last_dot != NULL
1378440a403fSchristos 	       && last_digit == NULL)
1379440a403fSchristos 	{
1380440a403fSchristos 	  last_digit = tok;
1381440a403fSchristos 	}
1382440a403fSchristos       else if (ISSPACE (*tok))
1383440a403fSchristos 	{
1384440a403fSchristos 	  /* skip */
1385440a403fSchristos 	}
1386440a403fSchristos       else
1387440a403fSchristos 	{
1388440a403fSchristos 	  last_dot = NULL;
1389440a403fSchristos 	  last_digit = NULL;
1390440a403fSchristos 	}
1391440a403fSchristos       tok ++;
1392440a403fSchristos     }
1393440a403fSchristos   if (last_dot != NULL
1394440a403fSchristos       && last_digit != NULL)
1395440a403fSchristos     return last_dot;
1396440a403fSchristos   return NULL;
1397440a403fSchristos }
1398440a403fSchristos 
1399440a403fSchristos static int
rl78_lex(void)1400440a403fSchristos rl78_lex (void)
1401440a403fSchristos {
1402440a403fSchristos   /*unsigned int ci;*/
1403440a403fSchristos   char * save_input_pointer;
1404440a403fSchristos   char * bit = NULL;
1405440a403fSchristos 
1406440a403fSchristos   while (ISSPACE (*rl78_lex_start)
1407440a403fSchristos 	 && rl78_lex_start != rl78_lex_end)
1408440a403fSchristos     rl78_lex_start ++;
1409440a403fSchristos 
1410440a403fSchristos   rl78_last_exp_start = rl78_lex_start;
1411440a403fSchristos 
1412440a403fSchristos   if (rl78_lex_start == rl78_lex_end)
1413440a403fSchristos     return 0;
1414440a403fSchristos 
1415440a403fSchristos   if (ISALPHA (*rl78_lex_start)
1416440a403fSchristos       || (*rl78_lex_start == '.' && ISALPHA (rl78_lex_start[1])))
1417440a403fSchristos     {
1418440a403fSchristos       unsigned int i;
1419440a403fSchristos       char * e;
1420440a403fSchristos       char save;
1421440a403fSchristos 
1422440a403fSchristos       for (e = rl78_lex_start + 1;
1423440a403fSchristos 	   e < rl78_lex_end && ISALNUM (*e);
1424440a403fSchristos 	   e ++)
1425440a403fSchristos 	;
1426440a403fSchristos       save = *e;
1427440a403fSchristos       *e = 0;
1428440a403fSchristos 
1429440a403fSchristos       for (i = 0; i < NUM_TOKENS; i++)
1430440a403fSchristos 	if (strcasecmp (rl78_lex_start, token_table[i].string) == 0
1431440a403fSchristos 	    && !(token_table[i].val == IS_OPCODE && rl78_last_token != 0)
1432440a403fSchristos 	    && !(token_table[i].token == FLAG && !need_flag))
1433440a403fSchristos 	  {
1434440a403fSchristos 	    rl78_lval.regno = token_table[i].val;
1435440a403fSchristos 	    *e = save;
1436440a403fSchristos 	    rl78_lex_start = e;
1437440a403fSchristos 	    rl78_last_token = token_table[i].token;
1438440a403fSchristos 	    return token_table[i].token;
1439440a403fSchristos 	  }
1440440a403fSchristos       *e = save;
1441440a403fSchristos     }
1442440a403fSchristos 
1443440a403fSchristos   if (rl78_last_token == 0)
1444440a403fSchristos     {
1445440a403fSchristos       rl78_last_token = UNKNOWN_OPCODE;
1446440a403fSchristos       return UNKNOWN_OPCODE;
1447440a403fSchristos     }
1448440a403fSchristos 
1449440a403fSchristos   if (rl78_last_token == UNKNOWN_OPCODE)
1450440a403fSchristos     return 0;
1451440a403fSchristos 
1452440a403fSchristos   if (*rl78_lex_start == '[')
1453440a403fSchristos     rl78_in_brackets = 1;
1454440a403fSchristos   if (*rl78_lex_start == ']')
1455440a403fSchristos     rl78_in_brackets = 0;
1456440a403fSchristos 
1457440a403fSchristos   /* '.' is funny - the syntax includes it for bitfields, but only for
1458440a403fSchristos       bitfields.  We check for it specially so we can allow labels
1459440a403fSchristos       with '.' in them.  */
1460440a403fSchristos 
1461440a403fSchristos   if (rl78_bit_insn
1462440a403fSchristos       && *rl78_lex_start == '.'
1463440a403fSchristos       && find_bit_index (rl78_lex_start) == rl78_lex_start)
1464440a403fSchristos     {
1465440a403fSchristos       rl78_last_token = *rl78_lex_start;
1466440a403fSchristos       return *rl78_lex_start ++;
1467440a403fSchristos     }
1468440a403fSchristos 
1469440a403fSchristos   if ((rl78_in_brackets && *rl78_lex_start == '+')
1470440a403fSchristos       || strchr ("[],#!$:", *rl78_lex_start))
1471440a403fSchristos     {
1472440a403fSchristos       rl78_last_token = *rl78_lex_start;
1473440a403fSchristos       return *rl78_lex_start ++;
1474440a403fSchristos     }
1475440a403fSchristos 
1476440a403fSchristos   /* Again, '.' is funny.  Look for '.<digit>' at the end of the line
1477440a403fSchristos      or before a comma, which is a bitfield, not an expression.  */
1478440a403fSchristos 
1479440a403fSchristos   if (rl78_bit_insn)
1480440a403fSchristos     {
1481440a403fSchristos       bit = find_bit_index (rl78_lex_start);
1482440a403fSchristos       if (bit)
1483440a403fSchristos 	*bit = 0;
1484440a403fSchristos       else
1485440a403fSchristos 	bit = NULL;
1486440a403fSchristos     }
1487440a403fSchristos 
1488440a403fSchristos   save_input_pointer = input_line_pointer;
1489440a403fSchristos   input_line_pointer = rl78_lex_start;
1490440a403fSchristos   rl78_lval.exp.X_md = 0;
1491440a403fSchristos   expression (&rl78_lval.exp);
1492440a403fSchristos 
1493440a403fSchristos   if (bit)
1494440a403fSchristos     *bit = '.';
1495440a403fSchristos 
1496440a403fSchristos   rl78_lex_start = input_line_pointer;
1497440a403fSchristos   input_line_pointer = save_input_pointer;
1498440a403fSchristos   rl78_last_token = EXPR;
1499440a403fSchristos   return EXPR;
1500440a403fSchristos }
1501440a403fSchristos 
1502440a403fSchristos int
rl78_error(const char * str)1503440a403fSchristos rl78_error (const char * str)
1504440a403fSchristos {
1505440a403fSchristos   int len;
1506440a403fSchristos 
1507440a403fSchristos   len = rl78_last_exp_start - rl78_init_start;
1508440a403fSchristos 
1509440a403fSchristos   as_bad ("%s", rl78_init_start);
1510440a403fSchristos   as_bad ("%*s^ %s", len, "", str);
1511440a403fSchristos   return 0;
1512440a403fSchristos }
1513440a403fSchristos 
1514440a403fSchristos static int
expr_is_sfr(expressionS exp)1515440a403fSchristos expr_is_sfr (expressionS exp)
1516440a403fSchristos {
1517440a403fSchristos   unsigned long v;
1518440a403fSchristos 
1519440a403fSchristos   if (exp.X_op != O_constant)
1520440a403fSchristos     return 0;
1521440a403fSchristos 
1522440a403fSchristos   v = exp.X_add_number;
1523440a403fSchristos   if (0xFFF00 <= v && v <= 0xFFFFF)
1524440a403fSchristos     return 1;
1525440a403fSchristos   return 0;
1526440a403fSchristos }
1527440a403fSchristos 
1528440a403fSchristos static int
expr_is_saddr(expressionS exp)1529440a403fSchristos expr_is_saddr (expressionS exp)
1530440a403fSchristos {
1531440a403fSchristos   unsigned long v;
1532440a403fSchristos 
1533440a403fSchristos   if (exp.X_op != O_constant)
1534440a403fSchristos     return 1;
1535440a403fSchristos 
1536440a403fSchristos   v = exp.X_add_number;
1537440a403fSchristos   if (0xFFE20 <= v && v <= 0xFFF1F)
1538440a403fSchristos     return 1;
1539440a403fSchristos   return 0;
1540440a403fSchristos }
1541440a403fSchristos 
1542440a403fSchristos static int
expr_is_word_aligned(expressionS exp)1543440a403fSchristos expr_is_word_aligned (expressionS exp)
1544440a403fSchristos {
1545440a403fSchristos   unsigned long v;
1546440a403fSchristos 
1547440a403fSchristos   if (exp.X_op != O_constant)
1548440a403fSchristos     return 1;
1549440a403fSchristos 
1550440a403fSchristos   v = exp.X_add_number;
1551440a403fSchristos   if (v & 1)
1552440a403fSchristos     return 0;
1553440a403fSchristos   return 1;
1554440a403fSchristos 
1555440a403fSchristos }
1556440a403fSchristos 
1557440a403fSchristos static void
check_expr_is_bit_index(expressionS exp)1558440a403fSchristos check_expr_is_bit_index (expressionS exp)
1559440a403fSchristos {
1560440a403fSchristos   int val;
1561440a403fSchristos 
1562440a403fSchristos   if (exp.X_op != O_constant)
1563440a403fSchristos     {
1564440a403fSchristos       rl78_error (_("bit index must be a constant"));
1565440a403fSchristos       return;
1566440a403fSchristos     }
1567440a403fSchristos   val = exp.X_add_number;
1568440a403fSchristos 
1569440a403fSchristos   if (val < 0 || val > 7)
1570440a403fSchristos     rl78_error (_("rtsd size must be 0..7"));
1571440a403fSchristos }
1572440a403fSchristos 
1573440a403fSchristos static int
exp_val(expressionS exp)1574440a403fSchristos exp_val (expressionS exp)
1575440a403fSchristos {
1576440a403fSchristos   if (exp.X_op != O_constant)
1577440a403fSchristos   {
1578440a403fSchristos     rl78_error (_("constant expected"));
1579440a403fSchristos     return 0;
1580440a403fSchristos   }
1581440a403fSchristos   return exp.X_add_number;
1582440a403fSchristos }
1583440a403fSchristos 
1584440a403fSchristos static int
check_expr_is_const(expressionS e,int vmin,int vmax)1585440a403fSchristos check_expr_is_const (expressionS e, int vmin, int vmax)
1586440a403fSchristos {
1587440a403fSchristos   static char buf[100];
1588440a403fSchristos   if (e.X_op != O_constant
1589440a403fSchristos       || e.X_add_number < vmin
1590440a403fSchristos       || e.X_add_number > vmax)
1591440a403fSchristos     {
1592440a403fSchristos       if (vmin == vmax)
1593440a403fSchristos 	sprintf (buf, "%d expected here", vmin);
1594440a403fSchristos       else
1595440a403fSchristos 	sprintf (buf, "%d..%d expected here", vmin, vmax);
1596440a403fSchristos       rl78_error(buf);
1597440a403fSchristos       return 0;
1598440a403fSchristos     }
1599440a403fSchristos   return 1;
1600440a403fSchristos }
1601