20d6da99dbc26bf95caccc4c35f06421b0802db9
[fw/sdcc] / as / xa51 / xa_rasm.y
1 %{
2 /* This file is part of Paul's XA51 Assembler, Copyright 1997,2002 Paul Stoffregen
3  *
4  * Paul's XA51 Assembler is free software; you can redistribute it and/or modify
5  * it under the terms of the GNU General Public License as published by
6  * the Free Software Foundation; version 2.
7  *
8  * Paul's XA51 Assembler is distributed in the hope that it will be useful,
9  * but WITHOUT ANY WARRANTY; without even the implied warranty of
10  * MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE.  See the
11  * GNU General Public License for more details.
12  *
13  * You should have received a copy of the GNU General Public License
14  * along with Foobar; if not, write to the Free Software
15  * Foundation, Inc., 59 Temple Place, Suite 330, Boston, MA  02111-1307  USA
16  */
17
18 /* Author contact: paul@pjrc.com */
19
20 /* parser for the 51-XA assembler, Paul Stoffregen, July 1997 */
21 #include <stdio.h>
22 #include <stdlib.h>
23 #include <string.h>
24
25 #include "xa_main.h"
26   
27 int op[MAX_DB];
28 int size;
29 int inst_size;
30 int arith_opcode, short_opcode, num_op, opcode0, opcode1;
31 int shift_imm_opcode, shift_reg_opcode, rotate_opcode;
32 int stack_addr_opcode, stack_reg_opcode, branch_opcode;
33 int rlist_reg_bank, rlist_bitmask, rlist_size;
34 int db_count, dw_count, i;
35 char symbol_name[MAX_SYMBOL], base_symbol_name[MAX_SYMBOL]={'\0'};
36 char expr_var[2][MAX_SYMBOL]={{'\0'},{'\0'}};
37
38 extern char lex_sym_name[];
39 extern int yylex();
40
41 extern void yyrestart(FILE *new_file);
42 extern char * disasm(int byte, int memory_location);
43 void error(char *s);
44
45
46 void RELOC_FF(unsigned where, unsigned pc, short rl) {
47   // pc = PC of the next instruction
48   struct symbol *sym;
49   if ((sym=findSymbol(yytext))) {
50     if (sym->mode=='X') {
51       sprintf (rel_line[rl], "R %04x REL_FF %s %04x", 
52                where, sym->name, pc);
53     }
54   }
55 }
56  
57 void RELOC_FFFF(unsigned where, unsigned pc, short rl) {
58   struct symbol *sym;
59   if ((sym=findSymbol(yytext))) {
60     if (sym->mode=='X') {
61       sprintf (rel_line[rl], "R %04x REL_FFFF %s %04x", 
62                where, sym->name, pc);
63     }
64   }
65 }
66  
67 void RELOC_ABS_0F(unsigned where, int expr) {
68   struct symbol *sym;
69   if ((sym=findSymbol(expr_var[expr]))) {
70     if (sym->mode=='X') {
71       sprintf (rel_line[expr], "R %04x ABS_0F %s 0", where, sym->name);
72     }
73   }
74 }
75
76 void RELOC_ABS_FF(unsigned where, int expr) {
77   struct symbol *sym;
78   if ((sym=findSymbol(expr_var[expr]))) {
79     if (sym->mode=='X') {
80       sprintf (rel_line[expr], "R %04x ABS_FF %s 0", where, sym->name);
81     }
82   }
83 }
84
85 void RELOC_ABS_03FF(unsigned where, int expr) {
86   struct symbol *sym;
87   if (expr_var[0]) {
88     if ((sym=findSymbol(expr_var[expr]))) {
89       if (sym->mode=='X') {
90         sprintf (rel_line[expr], "R %04x ABS_03FF %s 0", where, sym->name);
91       }
92     }
93   }
94 }
95
96 void RELOC_ABS_07ff(unsigned where, int expr) {
97   struct symbol *sym;
98   if (expr_var[0]) {
99     if ((sym=findSymbol(expr_var[expr]))) {
100       if (sym->mode=='X') {
101         sprintf (rel_line[expr], "R %04x ABS_07ff %s 0", where, sym->name);
102       }
103     }
104   }
105 }
106
107 void RELOC_ABS_F0FF(unsigned where, int expr) {
108   struct symbol *sym;
109   if (expr_var[0]) {
110     if ((sym=findSymbol(expr_var[expr]))) {
111       if (sym->mode=='X') {
112         sprintf (rel_line[expr], "R %04x ABS_F0FF %s", where, sym->name);
113       }
114     }
115   }
116 }
117  
118 void RELOC_ABS_FFFF(unsigned where, int expr) {
119   struct symbol *sym;
120   if (expr_var[0]) {
121     if ((sym=findSymbol(expr_var[expr]))) {
122       if (sym->mode=='X') {
123         sprintf (rel_line[expr], "R %04x ABS_FFFF %s 0", where, sym->name);
124       }
125     }
126   }
127 }
128  
129 void RELOC_ABS_0F00FF(unsigned where, int expr) {
130   struct symbol *sym;
131   if (expr_var[0]) {
132     if ((sym=findSymbol(expr_var[expr]))) {
133       if (sym->mode=='X') {
134         sprintf (rel_line[expr], "R %04x ABS_0F00FF %s", where, sym->name);
135       }
136     }
137   }
138 }
139  
140 %}
141
142 %token ADD ADDC ADDS AND ANL ASL ASR BCC BCS BEQ BG BGE BGT
143 %token BKPT BL BLE BLT BMI BNE BNV BOV BPL BR CALL CJNE CLR
144 %token CMP CPL DA DIV DIVU DJNZ FCALL FJMP JB JBC JMP JNB JNZ
145 %token JZ LEA LSR MOV MOVC MOVS MOVX MUL MULU NEG NOP NORM
146 %token OR ORL POP POPU PUSH PUSHU RESET RET RETI RL RLC RR RRC
147 %token SETB SEXT SUB SUBB TRAP XCH XOR
148 %token REG DPTR PC A C USP
149 %token WORD BIT NUMBER CHAR STRING EOL LOCAL_LABEL
150 %token ORG EQU SFR DB DW BITDEF REGDEF LOW HIGH
151 %token RSHIFT LSHIFT
152 %token AREA AREA_NAME AREA_DESC DS
153 %token MODULE GLOBL 
154
155 %left '&' '|' '^'
156 %left RSHIFT LSHIFT
157 %left '+' '-'
158 %left '*' '/'
159 %nonassoc UNARY
160
161 %%
162
163 all:           line
164              | line all;
165
166 line:          linesymbol ':' linenosym {
167                         if (p1) {
168                                 build_sym_list(symbol_name);
169                                 if (current_area == AREA_BSEG) {
170                                         mk_bit(symbol_name, current_area);
171                                 }
172                         }
173                         if (p1 || p2) assign_value(symbol_name, MEM_POS, 'R');
174                         MEM_POS += $3;
175                 }
176              | linenosym {
177                         MEM_POS += $1;
178                 }
179
180 linenosym:     directive EOL {
181                         if (p3) out(op, $1);
182                         $$ = $1;
183                 }
184              | instruction EOL {
185                         if (p3) out(op, $1);
186                         $$ = $1;
187                 }
188              | EOL {
189                         if (p3) out(NULL, 0);
190                         $$ = 0;
191                 }
192              | error EOL        /* try to recover from any parse error */
193
194
195 directive:     '.' ORG expr {
196                         MEM_POS = $3;
197                         $$ = 0;
198                 }
199              | ORG expr {
200                         MEM_POS = $2;
201                         $$ = 0;
202                 }
203              | '.' EQU symbol ',' expr { 
204                         if (p1) build_sym_list(symbol_name);
205                         if (p1 || p2) assign_value(symbol_name, $5, '?');
206                         $$ = 0;
207                 }
208              | symbol '=' expr {
209                         if (p1) build_sym_list(symbol_name);
210                         if (p1 || p2) assign_value(symbol_name, $3, '=');
211                 }
212              | symbol SFR expr {
213                         if (p1) build_sym_list(symbol_name);
214                         if (p1 || p2) assign_value(symbol_name, $3, 'A');
215                         if (p1 || p2) mk_sfr(symbol_name);
216                         $$ = 0;
217                 }
218              | '.' BITDEF bitsymbol ',' bit {
219                         if (p1) {
220                                 build_sym_list(symbol_name);
221                                 mk_bit(symbol_name, 0);
222                         }
223                         if (p1 || p2) assign_value(symbol_name, $5, '?');
224                         $$ = 0;
225                 }
226              | bitsymbol BITDEF bit {
227                         if (p1) {
228                                 build_sym_list(symbol_name);
229                                 mk_bit(symbol_name, 0);
230                         }
231                         if (p1 || p2) assign_value(symbol_name, $3, '?');
232                         $$ = 0;
233                 }
234              | bitsymbol BITDEF expr {
235                         if (p1) {
236                                 build_sym_list(symbol_name);
237                                 mk_bit(symbol_name, 0);
238                         }
239                         if (p1 || p2) assign_value(symbol_name, $3, 'A');
240                         $$ = 0;
241                 }
242              | '.' REGDEF regsymbol ',' REG {
243                         if (p1) {
244                                 build_sym_list(symbol_name);
245                                 mk_reg(symbol_name);
246                         }
247                         if (p1 || p2) assign_value(symbol_name, $5, '?');
248                         $$ = 0;
249                 }
250              | regsymbol REGDEF REG {
251                         if (p1) {
252                                 build_sym_list(symbol_name);
253                                 mk_reg(symbol_name);
254                         }
255                         if (p1 || p2) assign_value(symbol_name, $3, '?');
256                         $$ = 0;
257                 }
258
259              | '.' db_directive bytes {
260                         $$ = db_count;
261                 }
262              | '.' dw_directive words {
263                         $$ = dw_count;
264                 }
265              | '.' AREA AREA_NAME AREA_DESC {
266                         if ($3 < 0 || $3 > NUM_AREAS) {
267                                 error("Illegal Area Directive");
268                         }
269                         symbol_name[0] = '\0';
270                         current_area = $3;
271                         $$ = 0;
272                 }
273              | '.' MODULE WORD {
274                         /* ignore module definition */
275                         $$ = 0;
276                 }
277              | '.' GLOBL WORD {
278                         mk_global(lex_sym_name);
279                         /* ignore global symbol declaration */
280                         $$ = 0;
281                 }
282              | '.' GLOBL bit {
283                         /* ignore bit symbol declaration */
284                         $$ = 0;
285                 }
286              | '.' DS expr {
287                         /* todo: if CSEG, emit some filler bytes */
288                         $$ = $3;
289                 }
290
291 db_directive:   DB {db_count = 0;}
292
293
294 linesymbol:    normal_or_bit_symbol  { 
295                         strcpy(symbol_name, lex_sym_name);
296                         if (!strchr(lex_sym_name, ':')) {
297                                 /* non-local label, remember base name */
298                                 strcpy(base_symbol_name, lex_sym_name);
299                         }
300                         if (is_target(symbol_name)) pad_with_nop();
301                 }
302
303 normal_or_bit_symbol: WORD {$$ = $1;}
304                 | BIT {$$ = $1;}
305
306 bytes:            byte_element
307                 | bytes ',' byte_element
308
309 byte_element:   expr {
310                         op[db_count] = $1 & 255;
311                         if (++db_count >= MAX_DB) {
312                                 error("too many bytes, use two DB");
313                                 db_count--;
314                         }
315                 }
316                 | STRING {
317                         for(i=1; i < strlen(yytext)-1; i++) {
318                                 op[db_count++] = yytext[i];
319                                 if (db_count >= MAX_DB) {
320                                         error("too many bytes, use two DB");
321                                         db_count--;
322                                 }
323                         }
324                 }
325
326 dw_directive:   DW {dw_count = 0;}
327
328 words:            words ',' word_element
329                 | word_element
330
331 word_element:   expr {
332                         op[dw_count] = $1 & 255;
333                         op[dw_count+1] = ($1 >> 8) & 255;
334                         dw_count += 2;
335                         if (dw_count >= MAX_DB) {
336                                 error("too many bytes, use two DW");
337                                 db_count -= 2;
338                         }
339                 }
340
341
342
343 symbol:     WORD  {
344                 strcpy(symbol_name, lex_sym_name);
345                 }
346
347 bitsymbol:    WORD { strcpy(symbol_name, lex_sym_name); }
348             | BIT  { strcpy(symbol_name, lex_sym_name); }
349
350
351 regsymbol:    WORD { strcpy(symbol_name, lex_sym_name); }
352             | REG  { strcpy(symbol_name, lex_sym_name); }
353
354 bit:    expr '.' expr {
355                 if ($3 < 0 || $3 > 7) {
356                         /* only 8 bits in a byte */
357                         error("Only eight bits in a byte");
358                 }
359                 $$ = 100000;    /* should really check $1 is valid */
360                 if ($1 >= 0x20 && $1 <= 0x3F) {
361                         $$ = $1 * 8 + $3;
362                 }
363                 if ($1 >= 0x400 && $1 <= 0x43F) {
364                         $$ = ($1 - 0x400) * 8 + $3 + 0x200;
365                 }
366         }
367         | REG '.' expr {
368                 $$ = 100000;
369                 if (find_size_reg($1) == SIZE8) {
370                         if ($3 < 0 || $3 > 7)
371                                 error("byte reg has only 8 bits");
372                         $$ = reg($1) * 8 + $3;
373                 }
374                 if (find_size_reg($1) == SIZE16) {
375                         if ($3 < 0 || $3 > 15)
376                                 error("word reg has only 16 bits");
377                         $$ = reg($1) * 16 + $3;
378                 }
379         }
380         | BIT {$$ = $1;}
381
382 jmpaddr:        WORD {
383                         $$ = $1;
384                         if (p1) build_target_list(lex_sym_name);
385                 }
386               | NUMBER {
387                         if ($1 & 1) error("Jump target must be aligned");
388                         $$ = $1;
389                 }
390
391
392 expr:   value   {$$ = $1;}
393         | expr '+' expr {$$ = $1 + $3;}
394         | expr '-' expr {$$ = $1 - $3;}
395         | expr '*' expr {$$ = $1 * $3;}
396         | expr '/' expr {$$ = $1 / $3;}
397         | expr '&' expr {$$ = $1 & $3;}
398         | expr '|' expr {$$ = $1 | $3;}
399         | expr '^' expr {$$ = $1 ^ $3;}
400         | expr RSHIFT expr {$$ = $1 >> $3;}
401         | expr LSHIFT expr {$$ = $1 << $3;}
402         | '-' expr %prec UNARY {$$ = $2 * -1;}
403         | '+' expr %prec UNARY {$$ = $2;}
404         | '(' expr ')' {$$ = $2;}
405         | LOW expr %prec UNARY {$$ = $2 & 255;}
406         | HIGH expr %prec UNARY {$$ = ($2 >> 8) & 255;}
407
408
409 value:    NUMBER {$$ = $1;}
410         | CHAR {$$ = $1;}
411         | WORD {
412           $$ = $1; 
413           if (expr_var[0][0]=='\0') {
414             strcpy(expr_var[0], yytext);
415           } else {
416             strcpy(expr_var[1], yytext);
417           }
418         }
419
420
421 rlist:  REG {
422                 rlist_bitmask = 1<<(reg($1) % 8);
423                 rlist_reg_bank = (reg($1) / 8) ? 1 : 0;
424                 rlist_size = find_size_reg($1);
425         }
426         | REG ',' rlist {
427                 rlist_bitmask |= 1<<(reg($1) % 8);
428                 if (rlist_reg_bank != ((reg($1) / 8) ? 1 : 0))
429                         error("register list may not mix 0-7/8-15 regs");
430                 if (rlist_size != find_size_reg($1))
431                         error("register list may not mix 8/16 bit registers");
432         }
433
434
435
436
437
438 instruction:
439
440   arith_inst REG ',' REG {
441         $$ = 2;
442         size = find_size2(inst_size, $2, $4);
443         op[0] = arith_opcode * 16 + size * 8 + 1;
444         op[1] = reg($2) * 16 + reg($4);
445   }
446 | arith_inst REG ',' '[' REG ']' {
447         $$ = 2;
448         size = find_size1(inst_size, $2);
449         op[0] = arith_opcode * 16 + size * 8 + 2;
450         op[1] = reg($2) * 16 + reg_indirect($5);
451   }
452 | arith_inst '[' REG ']' ',' REG {
453         $$ = 2;
454         size = find_size1(inst_size, $6);
455         op[0] = arith_opcode * 16 + size * 8 + 2;
456         op[1] = reg($6) * 16 + 8 + reg_indirect($3);
457   }
458 | arith_inst REG ',' '[' REG '+' expr ']' {
459         size = find_size1(inst_size, $2);
460         if ($7 >= -128 && $7 <= 127) {
461                 $$ = 3;
462                 op[0] = arith_opcode * 16 + size * 8 + 4;
463                 op[1] = reg($2) * 16 + reg_indirect($5);
464                 op[2] = ($7 >= 0) ? $7 : 256 + $7;
465                 RELOC_ABS_FF(MEM_POS+2,0);
466         } else {
467                 $$ = 4;
468                 op[0] = arith_opcode * 16 + size * 8 + 5;
469                 op[1] = reg($2) * 16 + reg_indirect($5);
470                 op[2] = ($7 >= 0) ? msb($7) : msb(65536 + $7);
471                 op[3] = ($7 >= 0) ? lsb($7) : lsb(65536 + $7);
472                 RELOC_ABS_FFFF(MEM_POS+2,0);
473         }
474   }
475 | arith_inst '[' REG '+' expr ']' ',' REG {
476         size = find_size1(inst_size, $8);
477         if ($5 >= -128 && $5 <= 127) {
478                 $$ = 3;
479                 op[0] = arith_opcode * 16 + size * 8 + 4;
480                 op[1] = reg($8) * 16 + 8 + reg_indirect($3);
481                 op[2] = ($5 >= 0) ? $5 : 256 + $5;
482                 RELOC_ABS_FF(MEM_POS+2,0);
483         } else {
484                 $$ = 4;
485                 op[0] = arith_opcode * 16 + size * 8 + 5;
486                 op[1] = reg($8) * 16 + 8 + reg_indirect($3);
487                 op[2] = ($5 >= 0) ? msb($5) : msb(65536 + $5);
488                 op[3] = ($5 >= 0) ? lsb($5) : lsb(65536 + $5);
489                 RELOC_ABS_FFFF(MEM_POS+2,0);
490         }
491   }
492 | arith_inst REG ',' '[' REG '+' ']' {
493         $$ = 2;
494         size = find_size1(inst_size, $2);
495         op[0] = arith_opcode * 16 + size * 8 + 3;
496         op[1] = reg($2) * 16 + reg_indirect($5);
497   }
498 | arith_inst '[' REG '+' ']' ',' REG {
499         $$ = 2;
500         size = find_size1(inst_size, $7);
501         op[0] = arith_opcode * 16 + size * 8 + 3;
502         op[1] = reg($7) * 16 + 8 + reg_indirect($3);
503   }
504 | arith_inst WORD ',' REG {
505         $$ = 3;
506         size = find_size1(inst_size, $4);
507         op[0] = arith_opcode * 16 + size * 8 + 6;
508         op[1] = reg($4) * 16 + 8 + msb(direct_addr($2));
509         op[2] = lsb(direct_addr($2));
510         RELOC_ABS_07ff(MEM_POS+1, 0);
511   }
512 | arith_inst REG ',' WORD {
513         $$ = 3;
514         size = find_size1(inst_size, $2);
515         op[0] = arith_opcode * 16 + size * 8 + 6;
516         op[1] = reg($2) * 16 + msb(direct_addr($4));
517         op[2] = lsb(direct_addr($4));
518         RELOC_ABS_07ff(MEM_POS+1, 0);
519   }
520 | arith_inst REG ',' '#' expr {
521         size = find_size1(inst_size, $2);
522         if (size == SIZE8) {
523                 $$ = 3;
524                 op[0] = 0x91;
525                 op[1] = reg($2) * 16 + arith_opcode;
526                 op[2] = imm_data8($5);
527                 RELOC_ABS_FF(MEM_POS+2, 0);
528         } else {
529                 $$ = 4;
530                 op[0] = 0x99;
531                 op[1] = reg($2) * 16 + arith_opcode;
532                 op[2] = msb(imm_data16($5));
533                 op[3] = lsb(imm_data16($5));
534                 RELOC_ABS_FFFF (MEM_POS+2, 0);
535         }
536   }
537 | arith_inst '[' REG ']' ',' '#' expr {
538         size = find_size0(inst_size);
539         if (size == SIZE8) {
540                 $$ = 3;
541                 op[0] = 0x92;
542                 op[1] = reg_indirect($3) * 16 + arith_opcode;
543                 op[2] = imm_data8($7);
544                 RELOC_ABS_FF(MEM_POS+2, 0);
545         } else {
546                 $$ = 4;
547                 op[0] = 0x9A;
548                 op[1] = reg_indirect($3) * 16 + arith_opcode;
549                 op[2] = msb(imm_data16($7));
550                 op[3] = lsb(imm_data16($7));
551                 RELOC_ABS_FFFF (MEM_POS+2, 0);
552         }
553   }
554 | arith_inst '[' REG '+' ']' ',' '#' expr {
555         size = find_size0(inst_size);
556         if (size == SIZE8) {
557                 $$ = 3;
558                 op[0] = 0x93;
559                 op[1] = reg_indirect($3) * 16 + arith_opcode;
560                 op[2] = imm_data8($8);
561                 RELOC_ABS_FF(MEM_POS+2, 0);
562         } else {
563                 $$ = 4;
564                 op[0] = 0x9B;
565                 op[1] = reg_indirect($3) * 16 + arith_opcode;
566                 op[2] = msb(imm_data16($8));
567                 op[3] = lsb(imm_data16($8));
568                 RELOC_ABS_FFFF (MEM_POS+2, 0);
569         }
570   }
571 | arith_inst '[' REG '+' expr ']' ',' '#' expr {
572         size = find_size0(inst_size);
573         if ($5 >= -128 && $5 <= 127) {
574                 if (size == SIZE8) {
575                         $$ = 4;
576                         op[0] = 0x94;
577                         op[1] = reg_indirect($3) * 16 + arith_opcode;
578                         op[2] = ($5 >= 0) ? $5 : 256 + $5;
579                         op[3] = imm_data8($9);
580                         RELOC_ABS_FF(MEM_POS+2, 0);
581                         RELOC_ABS_FF(MEM_POS+3, 1);
582                 } else {
583                         $$ = 5;
584                         op[0] = 0x9C;
585                         op[1] = reg_indirect($3) * 16 + arith_opcode;
586                         op[2] = ($5 >= 0) ? $5 : 256 + $5;
587                         op[3] = msb(imm_data16($9));
588                         op[4] = lsb(imm_data16($9));
589                         RELOC_ABS_FF(MEM_POS+2, 0);
590                         RELOC_ABS_FFFF(MEM_POS+3, 1);
591                 }
592         } else {
593                 if (size == SIZE8) {
594                         $$ = 5;
595                         op[0] = 0x95;
596                         op[1] = reg_indirect($3) * 16 + arith_opcode;
597                         op[2] = ($5 >= 0) ? msb($5) : msb(65536 + $5);
598                         op[3] = ($5 >= 0) ? lsb($5) : lsb(65536 + $5);
599                         op[4] = imm_data8($9);
600                         RELOC_ABS_FFFF(MEM_POS+2,0);
601                         RELOC_ABS_FF(MEM_POS+4,1);
602                 } else {
603                         $$ = 6;
604                         op[0] = 0x9D;
605                         op[1] = reg_indirect($3) * 16 + arith_opcode;
606                         op[2] = ($5 >= 0) ? msb($5) : msb(65536 + $5);
607                         op[3] = ($5 >= 0) ? lsb($5) : lsb(65536 + $5);
608                         op[4] = msb(imm_data16($9));
609                         op[5] = lsb(imm_data16($9));
610                         RELOC_ABS_FFFF(MEM_POS+2, 0);
611                         RELOC_ABS_FFFF(MEM_POS+4, 1);
612                 }
613         }
614   }
615 | arith_inst WORD ',' '#' expr {
616         size = find_size0(inst_size);
617         if (size == SIZE8) {
618                 $$ = 4;
619                 op[0] = 0x96;
620                 op[1] = msb(direct_addr($2)) * 16 + arith_opcode;
621                 op[2] = lsb(direct_addr($2));
622                 op[3] = imm_data8($5);
623                 RELOC_ABS_F0FF(MEM_POS+1,0);
624                 RELOC_ABS_FF(MEM_POS+3,1);
625         } else {
626                 $$ = 5;
627                 op[0] = 0x9E;
628                 op[1] = msb(direct_addr($2)) * 16 + arith_opcode;
629                 op[2] = lsb(direct_addr($2));
630                 op[3] = msb(imm_data16($5));
631                 op[4] = lsb(imm_data16($5));
632                 RELOC_ABS_F0FF(MEM_POS+1,0);
633                 RELOC_ABS_FFFF (MEM_POS+3,1);
634         }
635   }
636
637 /* the next 8 instructions are MOV, but because MOV was used in the */
638 /* arith_inst group, it will cause a shift/reduce conflict if used */
639 /* directly below... so we're forced to use arith_inst and then */
640 /* add a bit of code to make sure it was MOV and not the other ones */
641
642 | arith_inst '[' REG '+' ']' ',' '[' REG '+' ']' {
643         /* this addr mode is only valid for MOV */
644         if (arith_opcode != 8) error("Addr mode only valid for MOV (1)");
645         size = find_size0(inst_size);
646         $$ = 2;
647         op[0] = 0x90 + size * 8;
648         op[1] = reg_indirect($3) * 16 + reg_indirect($8);
649   }
650 | arith_inst WORD ',' '[' REG ']' {
651         /* this addr mode is only valid for MOV */
652         if (arith_opcode != 8) error("Addr mode only valid for MOV (2)");
653         size = find_size0(inst_size);
654         $$ = 3;
655         op[0] = 0xA0 + size * 8;
656         op[1] = 128 + reg_indirect($5) * 16 + msb(direct_addr($2));
657         op[2] = lsb(direct_addr($2));
658         RELOC_ABS_07ff(MEM_POS+1, 0);
659   }
660 | arith_inst '[' REG ']' ',' WORD {
661         /* this addr mode is only valid for MOV */
662         if (arith_opcode != 8) error("Addr mode only valid for MOV (3)");
663         size = find_size0(inst_size);
664         $$ = 3;
665         op[0] = 0xA0 + size * 8;
666         op[1] = reg_indirect($3) * 16 + msb(direct_addr($6));
667         op[2] = lsb(direct_addr($6));
668         RELOC_ABS_07ff(MEM_POS+1, 0);
669   }
670 | arith_inst WORD ',' WORD {
671         /* this addr mode is only valid for MOV */
672         if (arith_opcode != 8) error("Addr mode only valid for MOV (4)");
673         size = find_size0(inst_size);
674         $$ = 4;
675         op[0] = 0x97 + size * 8;
676         op[1] = msb(direct_addr($2)) * 16 + msb(direct_addr($4));
677         op[2] = lsb(direct_addr($2));
678         op[3] = lsb(direct_addr($4));
679         RELOC_ABS_F0FF(MEM_POS+1, 0);
680         RELOC_ABS_0F00FF(MEM_POS+1, 1);
681   }
682 | arith_inst REG ',' USP {
683         /* this addr mode is only valid for MOV */
684         if (arith_opcode != 8) error("Addr mode only valid for MOV (5)");
685         $$ = 2;
686         op[0] = 0x90;
687         op[1] = reg($2) * 16 + 15;
688   }
689 | arith_inst USP ',' REG {
690         /* this addr mode is only valid for MOV */
691         if (arith_opcode != 8) error("Addr mode only valid for MOV (6)");
692         $$ = 2;
693         op[0] = 0x98;
694         op[1] = reg($4) * 16 + 15;
695   }
696 | arith_inst C ',' bit {
697         /* this addr mode is only valid for MOV */
698         if (arith_opcode != 8) error("Addr mode only valid for MOV (7)");
699         $$ = 3;
700         op[0] = 0x08;
701         op[1] = 0x20 + msb(bit_addr($4));
702         op[2] = lsb(bit_addr($4));
703         RELOC_ABS_03FF(MEM_POS+1, 0);
704   }
705 | arith_inst bit ',' C {
706         /* this addr mode is only valid for MOV */
707         if (arith_opcode != 8) error("Addr mode only valid for MOV (8)");
708         $$ = 3;
709         op[0] = 0x08;
710         op[1] = 0x30 + msb(bit_addr($2));
711         op[2] = lsb(bit_addr($2));
712         RELOC_ABS_03FF(MEM_POS+1, 0);
713   }
714
715 | MOVC REG ',' '[' REG '+' ']' {
716         size = find_size1(inst_size, $2);
717         $$ = 2;
718         op[0] = 0x80 + size * 8;
719         op[1] = reg($2) * 16 + reg_indirect($5);
720   }
721 | MOVC A ',' '[' A '+' DPTR ']' {
722         $$ = 2;
723         op[0] = 0x90;
724         op[1] = 0x4E;
725   }
726 | MOVC A ',' '[' A '+' PC ']' {
727         $$ = 2;
728         op[0] = 0x90;
729         op[1] = 0x4C;
730   }
731 | MOVX REG ',' '[' REG ']' {
732         $$ = 2;
733         size = find_size1(inst_size, $2);
734         op[0] = 0xA7 + size * 8;
735         op[1] = reg($2) * 16 + reg_indirect($5);
736   }
737 | MOVX '[' REG ']' ',' REG {
738         $$ = 2;
739         size = find_size1(inst_size, $6);
740         op[0] = 0xA7 + size * 8;
741         op[1] = reg($6) * 16 + 8 + reg_indirect($3);
742   }
743 | XCH REG ',' REG {
744         $$ = 2;
745         size = find_size2(inst_size, $2, $4);
746         op[0] = 0x60 + size * 8;
747         op[1] = reg($2) * 16 + reg($4);
748   }
749 | XCH REG ',' '[' REG ']' {
750         $$ = 2;
751         size = find_size1(inst_size, $2);
752         op[0] = 0x50 + size * 8;
753         op[1] = reg($2) * 16 + reg_indirect($5);
754   }
755 | XCH REG ',' WORD {
756         $$ = 3;
757         size = find_size1(inst_size, $2);
758         op[0] = 0xA0 + size * 8;
759         op[1] = reg($2) * 16 + msb(direct_addr($4));
760         op[2] = lsb(direct_addr($4));
761         RELOC_ABS_07ff(MEM_POS+1, 0);
762   }
763 | short_data_inst REG ',' '#' expr {
764         $$ = 2;
765         size = find_size1(inst_size, $2);
766         op[0] = short_opcode + size * 8 + 1;
767         op[1] = reg($2) * 16 + imm_data4_signed($5);
768         RELOC_ABS_0F(MEM_POS+1, 0);
769   }
770 | short_data_inst '[' REG ']' ',' '#' expr {
771         $$ = 2;
772         size = find_size0(inst_size);
773         op[0] = short_opcode + size * 8 + 2;
774         op[1] = reg_indirect($3) * 16 + imm_data4_signed($7);
775         RELOC_ABS_0F(MEM_POS+1, 0);
776   }
777 | short_data_inst '[' REG '+' ']' ',' '#' expr {
778         $$ = 2;
779         size = find_size0(inst_size);
780         op[0] = short_opcode + size * 8 + 3;
781         op[1] = reg_indirect($3) * 16 + imm_data4_signed($8);
782         RELOC_ABS_0F(MEM_POS+1, 0);
783   }
784 | short_data_inst '[' REG '+' expr ']' ',' '#' expr {
785         size = find_size0(inst_size);
786         if ($5 >= -128 && $5 <= 127) {
787                 $$ = 3;
788                 op[0] = short_opcode + size * 8 + 4;
789                 op[1] = reg_indirect($3) * 16 + imm_data4_signed($9);
790                 op[2] = op[2] = ($5 >= 0) ? $5 : 256 + $5;
791                 RELOC_ABS_0F(MEM_POS+1, 1);
792                 RELOC_ABS_FF(MEM_POS+2, 0);
793         } else {
794                 $$ = 4;
795                 op[0] = short_opcode + size * 8 + 5;
796                 op[1] = reg_indirect($3) * 16 + imm_data4_signed($9);
797                 op[2] = ($5 >= 0) ? msb($5) : msb(65536 + $5);
798                 op[3] = ($5 >= 0) ? lsb($5) : lsb(65536 + $5);
799                 RELOC_ABS_0F(MEM_POS+1, 1);
800                 RELOC_ABS_FFFF(MEM_POS+2, 0);
801         }
802   }
803 | short_data_inst expr ',' '#' expr {
804         $$ = 3;
805         size = find_size0(inst_size);
806         op[0] = short_opcode + size * 8 + 6;
807         op[1] = msb(direct_addr($2)) * 16 + imm_data4_signed($5);
808         op[2] = lsb(direct_addr($2));
809         RELOC_ABS_0F(MEM_POS+1, 0);
810   }
811 | ANL C ',' bit {
812         $$ = 3;
813         op[0] = 0x08;
814         op[1] = 0x40 + msb(bit_addr($4));
815         op[2] = lsb(bit_addr($4));
816         RELOC_ABS_03FF(MEM_POS+1, 0);
817   }
818 | ANL C ',' '/' bit {
819         $$ = 3;
820         op[0] = 0x08;
821         op[1] = 0x50 + msb(bit_addr($5));
822         op[2] = lsb(bit_addr($5));
823         RELOC_ABS_03FF(MEM_POS+1, 0);
824   }
825
826 | ORL C ',' bit {
827         $$ = 3;
828         op[0] = 0x08;
829         op[1] = 0x60 + msb(bit_addr($4));
830         op[2] = lsb(bit_addr($4));
831         RELOC_ABS_03FF(MEM_POS+1, 0);
832   }
833 | ORL C ',' '/' bit {
834         $$ = 3;
835         op[0] = 0x08;
836         op[1] = 0x70 + msb(bit_addr($5));
837         op[2] = lsb(bit_addr($5));
838         RELOC_ABS_03FF(MEM_POS+1, 0);
839   }
840 | CLR bit {
841         $$ = 3;
842         op[0] = 0x08;
843         op[1] = msb(bit_addr($2));
844         op[2] = lsb(bit_addr($2));
845         RELOC_ABS_03FF(MEM_POS+1, 0);
846   }
847 | SETB bit {
848         $$ = 3;
849         op[0] = 0x08;
850         op[1] = 0x10 + msb(bit_addr($2));
851         op[2] = lsb(bit_addr($2));
852         RELOC_ABS_03FF(MEM_POS+1, 0);
853   }
854 | logical_shift_inst REG ',' REG {
855         size = find_size1(inst_size, $2);
856         if (find_size_reg($4) != SIZE8)
857                 error("Second register in logical shift must be byte size");
858         $$ = 2;
859         op[0] = shift_reg_opcode;
860         switch (size) {
861                 case SIZE8:  op[0] += 0; break;
862                 case SIZE16: op[0] += 8; break;
863                 case SIZE32: op[0] += 12; break;
864         }
865         op[1] = reg($2) * 16 + reg($4);
866   }
867 | logical_shift_inst REG ',' '#' NUMBER {
868         size = find_size1(inst_size, $2);
869         $$ = 2;
870         if (shift_imm_opcode == -1)
871                 error("NORM may not use a constant");
872         op[0] = shift_imm_opcode;
873         switch (size) {
874                 case SIZE8:  op[0] += 0; break;
875                 case SIZE16: op[0] += 8; break;
876                 case SIZE32: op[0] += 12; break;
877         }
878         switch (size) {
879                 case SIZE8:
880                 case SIZE16:
881                         op[1] = reg($2) * 16 + imm_data4_unsigned($5);
882                         break;
883                 case SIZE32:
884                         op[1] = (reg($2) / 2) * 32 + imm_data5_unsigned($5);
885                         break;
886         }
887   }
888 | no_opperand_inst {
889         $$ = num_op;
890         op[0] = opcode0;
891         op[1] = opcode1;
892   }
893
894 | TRAP '#' NUMBER {
895         $$ = 2;
896         op[0] = 0xD6;
897         op[1] = 0x30 + imm_data4_unsigned($3);
898   }
899 | CPL REG {
900         $$ = 2;
901         size = find_size1(inst_size, $2);
902         op[0] = 0x90 + size * 8;
903         op[1] = reg($2) * 16 + 10;
904   }
905 | DA REG {
906         $$ = 2;
907         op[0] = 0x90;
908         op[1] = reg($2) * 16 + 8;
909   }
910 | NEG REG {
911         $$ = 2;
912         size = find_size1(inst_size, $2);
913         op[0] = 0x90 + size * 8;
914         op[1] = reg($2) * 16 + 11;
915   }
916 | SEXT REG {
917         $$ = 2;
918         size = find_size1(inst_size, $2);
919         op[0] = 0x90 + size * 8;
920         op[1] = reg($2) * 16 + 9;
921   }
922
923 | rotate_inst REG ',' '#' NUMBER {
924         $$ = 2;
925         size = find_size1(inst_size, $2);
926         op[0] = rotate_opcode + size * 8;
927         op[1] = reg($2) * 16 + imm_data4_unsigned($5);
928   }
929
930
931 | LEA REG ',' REG '+' expr {
932         if ($6 >= -128 && $6 <= 127) {
933                 $$ = 3;
934                 op[0] = 0x40;
935                 op[1] = reg($2) * 16 + reg_indirect($4);
936                 op[2] = ($6 >= 0) ? $6 : 256 + $6;
937                 RELOC_ABS_FF(MEM_POS+2, 0);
938         } else {
939                 op[0] = 0x48;
940                 op[1] = reg($2) * 16 + reg_indirect($4);
941                 op[2] = ($6 >= 0) ? msb($6) : msb(65536 + $6);
942                 op[3] = ($6 >= 0) ? lsb($6) : lsb(65536 + $6);
943                 RELOC_ABS_FFFF(MEM_POS+2, 0);
944         }
945   }
946 | stack_inst WORD {
947         $$ = 3;
948         size = find_size0(inst_size);
949         op[0] = msb(stack_addr_opcode) + size * 8;
950         op[1] = lsb(stack_addr_opcode) + msb(direct_addr($2));
951         op[2] = lsb(direct_addr($2));
952         RELOC_ABS_07ff(MEM_POS+1, 0);
953   }
954 | stack_inst rlist {
955         $$ = 2;
956         if (inst_size != UNKNOWN && find_size0(inst_size) != rlist_size)
957                 error("inst specifies different size than registers used");
958         op[0] = stack_reg_opcode + rlist_reg_bank * 64 + rlist_size * 8;
959         op[1] = rlist_bitmask;
960   }
961
962
963 | MUL REG ',' REG {
964         $$ = 2;
965         size = find_size2(inst_size, $2, $4);
966         op[0] = 0xE6;
967         op[1] = reg($2) * 16 + reg($4);
968   }
969 | MULU REG ',' REG {
970         $$ = 2;
971         size = find_size2(inst_size, $2, $4);
972         if (size == SIZE8) {
973                 op[0] = 0xE0;
974                 op[1] = reg($2) * 16 + reg($4);
975         } else {
976                 op[0] = 0xE4;
977                 op[1] = reg($2) * 16 + reg($4);
978         }
979   }
980 | MUL REG ',' '#' expr {
981         $$ = 2;
982         size = find_size1(inst_size, $2);
983         op[0] = 0xE9;
984         op[1] = reg($2) + 8;
985         op[2] = msb(imm_data16($5));
986         op[3] = lsb(imm_data16($5));
987         RELOC_ABS_FFFF(MEM_POS+2, 0);
988   }
989 | MULU REG ',' '#' expr {
990         size = find_size2(inst_size, $2, $4);
991         if (size == SIZE8) {
992                 $$ = 3;
993                 op[0] = 0xE8;
994                 op[1] = reg($2) * 16;
995                 op[2] = imm_data8($5);
996                 RELOC_ABS_FF(MEM_POS+2, 0);
997         } else {
998                 $$ = 4;
999                 op[0] = 0xE9;
1000                 op[1] = reg($2) * 16;
1001                 op[2] = msb(imm_data16($5));
1002                 op[3] = lsb(imm_data16($5));
1003                 RELOC_ABS_FFFF(MEM_POS+2, 0);
1004         }
1005   }
1006 | DIV REG ',' REG {
1007         $$ = 2;
1008         size = find_size2(inst_size, $2, $4);
1009         switch (size) {
1010         case SIZE8:
1011                 error("Singed DIV can't be 8 bit size"); break;
1012         case SIZE16:
1013                 op[0] = 0xE7;
1014                 op[1] = reg($2) * 16 + reg($4);
1015                 break;
1016         case SIZE32:
1017                 op[0] = 0xEF;
1018                 op[1] = (reg($2) / 2) * 32 + reg($4);
1019                 break;
1020         }
1021   }
1022 | DIVU REG ',' REG {
1023         $$ = 2;
1024         size = find_size2(inst_size, $2, $4);
1025         switch (size) {
1026         case SIZE8:
1027                 op[0] = 0xE1;
1028                 op[1] = reg($2) * 16 + reg($4);
1029                 break;
1030         case SIZE16:
1031                 op[0] = 0xE5;
1032                 op[1] = reg($2) * 16 + reg($4);
1033                 break;
1034         case SIZE32:
1035                 op[0] = 0xED;
1036                 op[1] = (reg($2) / 2) * 32 + reg($4);
1037                 break;
1038         }
1039   }
1040 | DIV REG ',' '#' expr { 
1041         size = find_size1(inst_size, $2);
1042         switch (size) {
1043         case SIZE8:
1044                 error("Singed DIV can't be 8 bit size"); break;
1045         case SIZE16:
1046                 $$ = 3;
1047                 op[0] = 0xE8;
1048                 op[1] = reg($2) * 16 + 11;
1049                 op[2] = imm_data8($5);
1050                 RELOC_ABS_FF(MEM_POS+2, 0);
1051                 break;
1052         case SIZE32:
1053                 $$ = 4;
1054                 op[0] = 0xE9;
1055                 op[1] = (reg($2) / 2) * 32 + 9;
1056                 op[2] = msb(imm_data16($5));
1057                 op[3] = lsb(imm_data16($5));
1058                 RELOC_ABS_FFFF(MEM_POS+2, 0);
1059                 break;
1060         }
1061   }
1062 | DIVU REG ',' '#' expr { 
1063         size = find_size1(inst_size, $2);
1064         switch (size) {
1065         case SIZE8:
1066                 $$ = 3;
1067                 op[0] = 0xE8;
1068                 op[1] = reg($2) * 16 + 1;
1069                 op[2] = imm_data8($5);
1070                 RELOC_ABS_FF(MEM_POS+2, 0);
1071                 break;
1072         case SIZE16:
1073                 $$ = 3;
1074                 op[0] = 0xE8;
1075                 op[1] = reg($2) * 16 + 3;
1076                 op[2] = imm_data8($5);
1077                 RELOC_ABS_FF(MEM_POS+2, 0);
1078                 break;
1079         case SIZE32:
1080                 $$ = 4;
1081                 op[0] = 0xE9;
1082                 op[1] = (reg($2) / 2) * 32 + 1;
1083                 op[2] = msb(imm_data16($5));
1084                 op[3] = lsb(imm_data16($5));
1085                 RELOC_ABS_FFFF(MEM_POS+2, 0);
1086                 break;
1087         }
1088   }
1089 | CALL '[' REG ']' {
1090         $$ = 2;
1091         op[0] = 0xC6;
1092         op[1] = reg($3);
1093   }
1094 | FCALL jmpaddr {
1095         $$ = 4;
1096         op[0] = 0xC4;
1097         op[1] = ($2 >> 8) & 255;
1098         op[2] = $2 & 255;
1099         op[3] = ($2 >> 16) & 255;
1100   }
1101 | FJMP jmpaddr {
1102         $$ = 4;
1103         op[0] = 0xD4;
1104         op[1] = ($2 >> 8) & 255;
1105         op[2] = $2 & 255;
1106         op[3] = ($2 >> 16) & 255;
1107   }
1108 | JMP '[' REG ']' {
1109         $$ = 2;
1110         op[0] = 0xD6;
1111         op[1] = 0x70 + reg_indirect($3);
1112   }
1113 | JMP '[' A '+' DPTR ']' {
1114         $$ = 2;
1115         op[0] = 0xD6;
1116         op[1] = 0x46;
1117   }
1118 | JMP '[' '[' REG '+' ']' ']' {
1119         $$ = 2;
1120         op[0] = 0xD6;
1121         op[1] = 0x60 + reg_indirect($4);
1122   }
1123
1124 | JMP jmpaddr {
1125         $$ = 3;
1126         op[0] = 0xD5;
1127         op[1] = msb(rel16(MEM_POS + $$, $2));
1128         op[2] = lsb(rel16(MEM_POS + $$, $2));
1129         RELOC_FFFF(MEM_POS+1,MEM_POS+$$,0);
1130   }
1131
1132 | CALL jmpaddr {
1133         $$ = 3;
1134         op[0] = 0xC5;
1135         op[1] = msb(rel16(MEM_POS + $$, $2));
1136         op[2] = lsb(rel16(MEM_POS + $$, $2));
1137         RELOC_FFFF(MEM_POS+1, MEM_POS+$$, 0);
1138   }
1139 | branch_inst jmpaddr {
1140         $$ = 2;
1141         op[0] = branch_opcode;
1142         op[1] = rel8(MEM_POS + $$, $2);
1143         RELOC_FF(MEM_POS+1,MEM_POS + $$, 0);
1144   }
1145 | CJNE REG ',' expr ',' jmpaddr {
1146         $$ = 4;
1147         size = find_size1(inst_size, $2);
1148         op[0] = 0xE2 + size * 8;
1149         op[1] = reg($2) * 16 + msb(direct_addr($4));
1150         op[2] = lsb(direct_addr($4));
1151         op[3] = rel8(MEM_POS + $$, $6);
1152         RELOC_ABS_07ff(MEM_POS+1, 0);
1153         RELOC_FF(MEM_POS+3, MEM_POS + $$, 1);
1154   }
1155 | CJNE REG ',' '#' expr ',' jmpaddr {
1156         size  = find_size1(inst_size, $2);
1157         if (size == SIZE8) {
1158                 $$ = 4;
1159                 op[0] = 0xE3;
1160                 op[1] = reg($2) * 16;
1161                 op[2] = rel8(MEM_POS + $$, $7);
1162                 op[3] = imm_data8($5);
1163                 RELOC_ABS_FF(MEM_POS+3, 0);
1164         } else {
1165                 $$ = 5;
1166                 op[0] = 0xEB;
1167                 op[1] = reg($2) * 16;
1168                 op[2] = rel8(MEM_POS + $$, $7);
1169                 op[3] = msb(imm_data16($5));
1170                 op[4] = lsb(imm_data16($5));
1171                 RELOC_ABS_FFFF(MEM_POS+3, 0);
1172         }
1173   }
1174 | CJNE '[' REG ']' ',' '#' expr ',' jmpaddr {
1175         size  = find_size0(inst_size);
1176         if (size == SIZE8) {
1177                 $$ = 4;
1178                 op[0] = 0xE3;
1179                 op[1] = reg_indirect($3) * 16 + 8;
1180                 op[2] = rel8(MEM_POS + $$, $9);
1181                 op[3] = imm_data8($7);
1182                 RELOC_ABS_FF(MEM_POS+3, 0);
1183         } else {
1184                 $$ = 5;
1185                 op[0] = 0xEB;
1186                 op[1] = reg_indirect($3) * 16 + 8;
1187                 op[2] = rel8(MEM_POS + $$, $9);
1188                 op[3] = msb(imm_data16($7));
1189                 op[4] = lsb(imm_data16($7));
1190                 RELOC_ABS_FFFF(MEM_POS+3, 0);
1191         }
1192   }
1193 | DJNZ REG ',' jmpaddr {
1194         $$ = 3;
1195         size  = find_size1(inst_size, $2);
1196         op[0] = 0x87 + size * 8;
1197         op[1] = reg($2) * 16 + 8;
1198         op[2] = rel8(MEM_POS + $$, $4);
1199         RELOC_FF(MEM_POS+2, MEM_POS+$$, 0);
1200   }
1201
1202
1203 | DJNZ WORD ',' jmpaddr {
1204         $$ = 4;
1205         size  = find_size0(inst_size);
1206         op[0] = 0xE2 + size * 8;
1207         op[1] = msb(direct_addr($2)) + 8;
1208         op[2] = lsb(direct_addr($2));
1209         op[3] = rel8(MEM_POS + $$, $4);
1210         RELOC_ABS_07ff(MEM_POS+1, 0);
1211         RELOC_FF(MEM_POS+3, MEM_POS + $$, 1)
1212   }
1213
1214 | JB bit ',' jmpaddr {
1215         $$ = 4;
1216         op[0] = 0x97;
1217         op[1] = 0x80 + msb(bit_addr($2));
1218         op[2] = lsb(bit_addr($2));
1219         op[3] = rel8(MEM_POS + $$, $4);
1220         RELOC_ABS_03FF(MEM_POS+1, 0);
1221         RELOC_FF(MEM_POS+3, MEM_POS + $$, 1);
1222   }
1223
1224 | JBC bit ',' jmpaddr {
1225         $$ = 4;
1226         op[0] = 0x97;
1227         op[1] = 0xC0 + msb(bit_addr($2));
1228         op[2] = lsb(bit_addr($2));
1229         op[3] = rel8(MEM_POS + $$, $4);
1230         RELOC_ABS_03FF(MEM_POS+1, 0);
1231         RELOC_FF(MEM_POS+3, MEM_POS + $$, 1);
1232   }
1233
1234 | JNB bit ',' jmpaddr {
1235         $$ = 4;
1236         op[0] = 0x97;
1237         op[1] = 0xA0 + msb(bit_addr($2));
1238         op[2] = lsb(bit_addr($2));
1239         op[3] = rel8(MEM_POS + $$, $4);
1240         RELOC_ABS_03FF(MEM_POS+1, 0);
1241         RELOC_FF(MEM_POS+3, MEM_POS + $$, 1);
1242   }
1243
1244
1245 arith_inst:
1246           ADD   {arith_opcode = 0;}
1247         | ADDC  {arith_opcode = 1;}
1248         | AND   {arith_opcode = 5;}
1249         | CMP   {arith_opcode = 4;}
1250         | MOV   {arith_opcode = 8;}
1251         | OR    {arith_opcode = 6;}
1252         | SUB   {arith_opcode = 2;}
1253         | SUBB  {arith_opcode = 3;}
1254         | XOR   {arith_opcode = 7;}
1255
1256 short_data_inst:
1257           ADDS {short_opcode = 0xA0;}
1258         | MOVS {short_opcode = 0xB0;}
1259
1260 logical_shift_inst:
1261           ASL  {shift_reg_opcode = 0xC1; shift_imm_opcode = 0xD1;}
1262         | ASR  {shift_reg_opcode = 0xC2; shift_imm_opcode = 0xD2;}
1263         | LSR  {shift_reg_opcode = 0xC0; shift_imm_opcode = 0xD0;}
1264         | NORM {shift_reg_opcode = 0xC3; shift_imm_opcode = -1;}
1265
1266 rotate_inst:
1267           RL    {rotate_opcode = 0xD3;}
1268         | RLC   {rotate_opcode = 0xD7;}
1269         | RR    {rotate_opcode = 0xD0;}
1270         | RRC   {rotate_opcode = 0xD7;}
1271
1272 stack_inst:
1273           POP   {stack_addr_opcode = 0x8710; stack_reg_opcode = 0x27;}
1274         | POPU  {stack_addr_opcode = 0x8700; stack_reg_opcode = 0x37;}
1275         | PUSH  {stack_addr_opcode = 0x8730; stack_reg_opcode = 0x07;}
1276         | PUSHU {stack_addr_opcode = 0x8720; stack_reg_opcode = 0x17;}
1277
1278 no_opperand_inst:
1279           BKPT  {num_op = 1; opcode0 = 255; opcode1 = 0;}
1280         | NOP   {num_op = 1; opcode0 = 0; opcode1 = 0;}
1281         | RESET {num_op = 2; opcode0 = 0xD6; opcode1 = 0x10;}
1282         | RET   {num_op = 2; opcode0 = 0xD6; opcode1 = 0x80;}
1283         | RETI  {num_op = 2; opcode0 = 0xD6; opcode1 = 0x90;}
1284
1285 branch_inst:
1286           BCC   {branch_opcode = 0xF0;}
1287         | BCS   {branch_opcode = 0xF1;}
1288         | BEQ   {branch_opcode = 0xF3;}
1289         | BG    {branch_opcode = 0xF8;}
1290         | BGE   {branch_opcode = 0xFA;}
1291         | BGT   {branch_opcode = 0xFC;}
1292         | BL    {branch_opcode = 0xF9;}
1293         | BLE   {branch_opcode = 0xFD;}
1294         | BLT   {branch_opcode = 0xFB;}
1295         | BMI   {branch_opcode = 0xF7;}
1296         | BNE   {branch_opcode = 0xF2;}
1297         | BNV   {branch_opcode = 0xF4;}
1298         | BOV   {branch_opcode = 0xF5;}
1299         | BPL   {branch_opcode = 0xF6;}
1300         | BR    {branch_opcode = 0xFE;}
1301         | JZ    {branch_opcode = 0xEC;}
1302         | JNZ   {branch_opcode = 0xEE;}
1303
1304
1305
1306 %%
1307
1308
1309 int reg(int reg_spec)
1310 {
1311         return reg_spec & 15;
1312 }
1313
1314 int reg_indirect(int reg_spec)
1315 {
1316         if (reg_spec & BYTE_REG)
1317                 error("Indirect addressing may not use byte registers");
1318         if ((reg_spec & 15) > 7)
1319                 error("Only R0 through R7 may be used for indirect addr");
1320         return reg_spec & 7;
1321 }
1322
1323 int rel16(int pos, int dest)
1324 {
1325         int rel;
1326
1327         if (!p3) return 0;      /* don't bother unless writing code */
1328         if (dest & (BRANCH_SPACING - 1))
1329                 error("Attempt to jump to unaligned location");
1330         pos &= ~(BRANCH_SPACING - 1);
1331         rel = (dest - pos) / BRANCH_SPACING;
1332         if (rel < -32768 || rel > 32767)
1333                 error("Attempt to jump out of 16 bit relative range");
1334         if (rel < 0) rel += 65536;
1335         return rel;
1336 }
1337
1338 int rel8(int pos, int dest)
1339 {
1340         int rel;
1341
1342         if (!p3) return 0;      /* don't bother unless writing code */
1343         if (dest & (BRANCH_SPACING - 1))
1344                 error("Attempt to jump to unaligned location");
1345         pos &= ~(BRANCH_SPACING - 1);
1346         rel = (dest - pos) / BRANCH_SPACING;
1347         if (rel < -128 || rel > 127)
1348                 error("Attempt to jump out of 16 bit relative range");
1349         if (rel < 0) rel += 256;
1350         return rel;
1351 }
1352
1353 int msb(int value)
1354 {
1355         return (value >> 8) & 255;
1356 }
1357
1358 int lsb(int value)
1359 {
1360         return value & 255;
1361 }
1362
1363 int direct_addr(int value)
1364 {
1365         char buf[250];
1366
1367         if (value < 0 || value > 2047) {
1368                 sprintf(buf, "illegal value (%d) for direct address", value);
1369                 error(buf);
1370         }
1371         return value;
1372 }
1373
1374 int imm_data4_signed(int value)
1375 {
1376         if (value < -8 || value > 7)
1377                 error("illegal 4 bit (signed) value");
1378         if (value >= 0) return value;
1379         else return (16 + value);
1380 }
1381
1382 int imm_data4_unsigned(int value)
1383 {
1384         if (value < 0 || value > 15)
1385                 error("illegal 4 bit (unsigned) value");
1386         return value;
1387 }
1388
1389 int imm_data5_unsigned(int value)
1390 {
1391         if (value < 0 || value > 31)
1392                 error("illegal 5 bit (unsigned) value");
1393         return value;
1394 }
1395
1396 int imm_data8(int value)
1397 {
1398         if (value < -128 || value > 255)
1399                 error("illegal 8 bit value");
1400         if (value >= 0) return value;
1401         else return (256 + value);
1402 }
1403
1404 int imm_data16(int value)
1405 {
1406         if (value < -32728 || value > 65535)
1407                 error("illegal 16 bit value");
1408         if (value >= 0) return value;
1409         else return (65536 + value);
1410 }
1411
1412 int bit_addr(int value)
1413 {
1414         if (value < 0 || value > 1023) {
1415                 fprintf(stderr, "bad bit addr of 0x%04X (%d dec)\n",
1416                         value, value);
1417                 error("illegal bit address");
1418         }
1419         return value;
1420 }
1421
1422
1423 int find_size_reg(int op1spec)
1424 {
1425         int op1size=UNKNOWN;
1426
1427         if (op1spec & BYTE_REG) op1size = SIZE8;
1428         if (op1spec & WORD_REG) op1size = SIZE16;
1429         if (op1size == UNKNOWN)
1430                 error("Register without implied size");
1431         return op1size;
1432 }
1433
1434 int find_size0(int isize)
1435 {
1436         if (isize == UNKNOWN)
1437                 error("Can't determine data size from instruction");
1438         return isize;
1439 }
1440
1441 int find_size1(int isize, int op1spec)
1442 {
1443         int op1size=UNKNOWN;
1444
1445         if (op1spec & BYTE_REG) op1size = SIZE8;
1446         if (op1spec & WORD_REG) op1size = SIZE16;
1447         if (op1size == UNKNOWN)
1448                 error("Register without implied size");
1449
1450         if (isize == SIZE32 && op1size == SIZE16) return SIZE32;
1451         if (isize == UNKNOWN) return op1size;
1452         else {
1453                 if (isize != op1size)
1454                         error("data size of register and inst don't agree");
1455                 return isize;
1456         }
1457 }
1458
1459 int find_size2(int isize, int op1spec, int op2spec)
1460 {
1461         int op1size=UNKNOWN, op2size=UNKNOWN;
1462
1463         if (op1spec & BYTE_REG) op1size = SIZE8;
1464         if (op1spec & WORD_REG) op1size = SIZE16;
1465         if (op1size == UNKNOWN)
1466                 error("Register without implied size");
1467         if (op2spec & BYTE_REG) op2size = SIZE8;
1468         if (op2spec & WORD_REG) op2size = SIZE16;
1469         if (op1size == UNKNOWN)
1470                 error("Register without implied size");
1471
1472         if (op1size != op2size)
1473                 error("data sizes of two registers don't agree");
1474         if (isize == UNKNOWN) return op1size;
1475         else {
1476                 if (isize != op1size)
1477                         error("data size of registers and inst don't agree");
1478                 return isize;
1479         }
1480 }
1481
1482 int yyerror(char *s)
1483 {
1484         if (yytext[0] >= 32) {
1485                 fprintf(stderr, "%s near '%s', line %d\n",
1486                         s, yytext, lineno);
1487         } else {
1488                 fprintf(stderr, "%s, line %d\n", s, lineno - 1);
1489         }
1490         return 0;
1491 }
1492
1493 void error(char *s)
1494 {
1495         yyerror(s);
1496         exit(1);
1497 }
1498
1499 int yywrap()
1500 {
1501         return 1;
1502 }