xref: /openbmc/qemu/target/hexagon/idef-parser/idef-parser.y (revision 804467e148a254a503834a2c712cad827f6f4b25)
1 %{
2 /*
3  *  Copyright(c) 2019-2023 rev.ng Labs Srl. All Rights Reserved.
4  *
5  *  This program is distributed in the hope that it will be useful,
6  *  but WITHOUT ANY WARRANTY; without even the implied warranty of
7  *  MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE.  See the
8  *  GNU General Public License for more details.
9  *
10  *  You should have received a copy of the GNU General Public License
11  *  along with this program; if not, see <http://www.gnu.org/licenses/>.
12  */
13 
14 #include "idef-parser.h"
15 #include "parser-helpers.h"
16 #include "idef-parser.tab.h"
17 #include "idef-parser.yy.h"
18 
19 /* Uncomment this to disable yyasserts */
20 /* #define NDEBUG */
21 
22 #define ERR_LINE_CONTEXT 40
23 
24 %}
25 
26 %lex-param {void *scanner}
27 %parse-param {void *scanner}
28 %parse-param {Context *c}
29 
30 %define parse.error verbose
31 %define parse.lac full
32 %define api.pure full
33 
34 %locations
35 
36 %union {
37     GString *string;
38     HexValue rvalue;
39     HexSat sat;
40     HexCast cast;
41     HexExtract extract;
42     HexMpy mpy;
43     HexSignedness signedness;
44     int index;
45 }
46 
47 /* Tokens */
48 %start input
49 
50 %expect 1
51 
52 %token IN INAME VAR
53 %token ABS CROUND ROUND CIRCADD COUNTONES INC DEC ANDA ORA XORA PLUSPLUS ASL
54 %token ASR LSR EQ NEQ LTE GTE MIN MAX ANDL FOR ICIRC IF MUN FSCR FCHK SXT
55 %token ZXT CONSTEXT LOCNT BREV SIGN LOAD STORE PC LPCFG
56 %token LOAD_CANCEL STORE_CANCEL CANCEL IDENTITY ROTL INSBITS SETBITS EXTRANGE
57 %token CAST4_8U FAIL CARRY_FROM_ADD ADDSAT64 LSBNEW
58 %token TYPE_SIZE_T TYPE_INT TYPE_SIGNED TYPE_UNSIGNED TYPE_LONG
59 
60 %token <rvalue> REG IMM PRED
61 %token <index> ELSE
62 %token <mpy> MPY
63 %token <sat> SAT
64 %token <cast> CAST DEPOSIT SETHALF
65 %token <extract> EXTRACT
66 %type <string> INAME
67 %type <rvalue> rvalue lvalue VAR assign_statement var var_decl var_type
68 %type <rvalue> FAIL
69 %type <rvalue> TYPE_SIGNED TYPE_UNSIGNED TYPE_INT TYPE_LONG TYPE_SIZE_T
70 %type <index> if_stmt IF
71 %type <signedness> SIGN
72 
73 /* Operator Precedences */
74 %left MIN MAX
75 %left '('
76 %left ','
77 %left '='
78 %right CIRCADD
79 %right INC DEC ANDA ORA XORA
80 %left '?' ':'
81 %left ANDL
82 %left '|'
83 %left '^' ANDOR
84 %left '&'
85 %left EQ NEQ
86 %left '<' '>' LTE GTE
87 %left ASL ASR LSR
88 %right ABS
89 %left '-' '+'
90 %left '*' '/' '%' MPY
91 %right '~' '!'
92 %left '['
93 %right CAST
94 %right LOCNT BREV
95 
96 /* Bison Grammar */
97 %%
98 
99 /* Input file containing the description of each hexagon instruction */
100 input : instructions
101       {
102           /* Suppress warning about unused yynerrs */
103           (void) yynerrs;
104           YYACCEPT;
105       }
106       ;
107 
108 instructions : instruction instructions
109              | %empty
110              ;
111 
112 instruction : INAME
113               {
114                   gen_inst(c, $1);
115               }
116               arguments
117               {
118                   EMIT_SIG(c, ")");
119                   EMIT_HEAD(c, "{\n");
120               }
121               code
122               {
123                   gen_inst_code(c, &@1);
124               }
125             | error /* Recover gracefully after instruction compilation error */
126               {
127                   free_instruction(c);
128               }
129             ;
130 
131 arguments : '(' ')'
132           | '(' argument_list ')';
133 
134 argument_list : argument_decl ',' argument_list
135               | argument_decl
136               ;
137 
138 var : VAR
139       {
140           track_string(c, $1.var.name);
141           $$ = $1;
142       }
143     ;
144 
145 /*
146  * Here the integer types are defined from valid combinations of
147  * `signed`, `unsigned`, `int`, and `long` tokens. The `signed`
148  * and `unsigned` tokens are here assumed to always be placed
149  * first in the type declaration, which is not the case in
150  * normal C. Similarly, `int` is assumed to always be placed
151  * last in the type.
152  */
153 type_int : TYPE_INT
154          | TYPE_SIGNED
155          | TYPE_SIGNED TYPE_INT;
156 type_uint : TYPE_UNSIGNED
157           | TYPE_UNSIGNED TYPE_INT;
158 type_ulonglong : TYPE_UNSIGNED TYPE_LONG TYPE_LONG
159                | TYPE_UNSIGNED TYPE_LONG TYPE_LONG TYPE_INT;
160 
161 /*
162  * Here the various valid int types defined above specify
163  * their `signedness` and `bit_width`. The LP64 convention
164  * is assumed where longs are 64-bit, long longs are then
165  * assumed to also be 64-bit.
166  */
167 var_type : TYPE_SIZE_T
168            {
169               yyassert(c, &@1, $1.bit_width <= 64,
170                        "Variables with size > 64-bit are not supported!");
171               $$ = $1;
172            }
173          | type_int
174            {
175               $$.signedness = SIGNED;
176               $$.bit_width  = 32;
177            }
178          | type_uint
179            {
180               $$.signedness = UNSIGNED;
181               $$.bit_width  = 32;
182            }
183          | type_ulonglong
184            {
185               $$.signedness = UNSIGNED;
186               $$.bit_width  = 64;
187            }
188          ;
189 
190 /* Rule to capture declarations of VARs */
191 var_decl : var_type IMM
192            {
193               /*
194                * Rule to capture "int i;" declarations since "i" is special
195                * and assumed to be always be IMM. Moreover, "i" is only
196                * assumed to be used in for-loops.
197                *
198                * Therefore we want to NOP these declarations.
199                */
200               yyassert(c, &@2, $2.imm.type == I,
201                        "Variable declaration with immedaties only allowed"
202                        " for the loop induction variable \"i\"");
203               $$ = $2;
204            }
205          | var_type var
206            {
207               /*
208                * Allocate new variable, this checks that it hasn't already
209                * been declared.
210                */
211               gen_varid_allocate(c, &@1, &$2, $1.bit_width, $1.signedness);
212               /* Copy var for variable name */
213               $$ = $2;
214               /* Copy type info from var_type */
215               $$.signedness = $1.signedness;
216               $$.bit_width  = $1.bit_width;
217            }
218          ;
219 
220 /* Return the modified registers list */
221 code : '{' statements '}'
222        {
223            c->inst.code_begin = c->input_buffer + @2.first_column - 1;
224            c->inst.code_end = c->input_buffer + @2.last_column - 1;
225        }
226      | '{'
227        {
228            /* Nop */
229        }
230        '}'
231      ;
232 
233 argument_decl : REG
234                 {
235                     emit_arg(c, &@1, &$1);
236                 }
237               | PRED
238                 {
239                     emit_arg(c, &@1, &$1);
240                     /* Enqueue predicate into initialization list */
241                     g_array_append_val(c->inst.init_list, $1);
242                 }
243               | IN REG
244                 {
245                     emit_arg(c, &@2, &$2);
246                 }
247               | IN PRED
248                 {
249                     emit_arg(c, &@2, &$2);
250                 }
251               | IMM
252                 {
253                     EMIT_SIG(c, ", int %ciV", $1.imm.id);
254                 }
255               ;
256 
257 code_block : '{' statements '}'
258            | '{' '}'
259            ;
260 
261 /* A list of one or more statements */
262 statements : statements statement
263            | statement
264            ;
265 
266 /* Statements can be assignment (rvalue ';'), control or memory statements */
267 statement : control_statement
268           | var_decl ';'
269           | rvalue ';'
270           | code_block
271           | ';'
272           ;
273 
274 assign_statement : lvalue '=' rvalue
275                    {
276                        @1.last_column = @3.last_column;
277                        gen_assign(c, &@1, &$1, &$3);
278                        $$ = $1;
279                    }
280                  | var_decl '=' rvalue
281                    {
282                        @1.last_column = @3.last_column;
283                        gen_assign(c, &@1, &$1, &$3);
284                        $$ = $1;
285                    }
286                  | lvalue INC rvalue
287                    {
288                        @1.last_column = @3.last_column;
289                        HexValue tmp = gen_bin_op(c, &@1, ADD_OP, &$1, &$3);
290                        gen_assign(c, &@1, &$1, &tmp);
291                        $$ = $1;
292                    }
293                  | lvalue DEC rvalue
294                    {
295                        @1.last_column = @3.last_column;
296                        HexValue tmp = gen_bin_op(c, &@1, SUB_OP, &$1, &$3);
297                        gen_assign(c, &@1, &$1, &tmp);
298                        $$ = $1;
299                    }
300                  | lvalue ANDA rvalue
301                    {
302                        @1.last_column = @3.last_column;
303                        HexValue tmp = gen_bin_op(c, &@1, ANDB_OP, &$1, &$3);
304                        gen_assign(c, &@1, &$1, &tmp);
305                        $$ = $1;
306                    }
307                  | lvalue ORA rvalue
308                    {
309                        @1.last_column = @3.last_column;
310                        HexValue tmp = gen_bin_op(c, &@1, ORB_OP, &$1, &$3);
311                        gen_assign(c, &@1, &$1, &tmp);
312                        $$ = $1;
313                    }
314                  | lvalue XORA rvalue
315                    {
316                        @1.last_column = @3.last_column;
317                        HexValue tmp = gen_bin_op(c, &@1, XORB_OP, &$1, &$3);
318                        gen_assign(c, &@1, &$1, &tmp);
319                        $$ = $1;
320                    }
321                  | PRED '=' rvalue
322                    {
323                        @1.last_column = @3.last_column;
324                        gen_pred_assign(c, &@1, &$1, &$3);
325                    }
326                  | IMM '=' rvalue
327                    {
328                        @1.last_column = @3.last_column;
329                        yyassert(c, &@1, $3.type == IMMEDIATE,
330                                 "Cannot assign non-immediate to immediate!");
331                        yyassert(c, &@1, $1.imm.type == VARIABLE,
332                                 "Cannot assign to non-variable!");
333                        /* Assign to the function argument */
334                        OUT(c, &@1, &$1, " = ", &$3, ";\n");
335                        $$ = $1;
336                    }
337                  | LOAD '(' IMM ',' IMM ',' SIGN ',' var ',' lvalue ')'
338                    {
339                        @1.last_column = @12.last_column;
340                        yyassert(c, &@1, !is_inside_ternary(c),
341                                 "Assignment side-effect not modeled!");
342                        yyassert(c, &@1, $3.imm.value == 1,
343                                 "LOAD of arrays not supported!");
344                        gen_load(c, &@1, &$5, $7, &$9, &$11);
345                    }
346                  | STORE '(' IMM ',' IMM ',' var ',' rvalue ')'
347                    /* Store primitive */
348                    {
349                        @1.last_column = @10.last_column;
350                        yyassert(c, &@1, !is_inside_ternary(c),
351                                 "Assignment side-effect not modeled!");
352                        yyassert(c, &@1, $3.imm.value == 1,
353                                 "STORE of arrays not supported!");
354                        gen_store(c, &@1, &$5, &$7, &$9);
355                    }
356                  | LPCFG '=' rvalue
357                    {
358                        @1.last_column = @3.last_column;
359                        yyassert(c, &@1, !is_inside_ternary(c),
360                                 "Assignment side-effect not modeled!");
361                        $3 = gen_rvalue_truncate(c, &@1, &$3);
362                        $3 = rvalue_materialize(c, &@1, &$3);
363                        OUT(c, &@1, "gen_set_usr_field(ctx, USR_LPCFG, ", &$3, ");\n");
364                    }
365                  | DEPOSIT '(' rvalue ',' rvalue ',' rvalue ')'
366                    {
367                        @1.last_column = @8.last_column;
368                        yyassert(c, &@1, !is_inside_ternary(c),
369                                 "Assignment side-effect not modeled!");
370                        gen_deposit_op(c, &@1, &$5, &$7, &$3, &$1);
371                    }
372                  | SETHALF '(' rvalue ',' lvalue ',' rvalue ')'
373                    {
374                        @1.last_column = @8.last_column;
375                        yyassert(c, &@1, !is_inside_ternary(c),
376                                 "Assignment side-effect not modeled!");
377                        gen_sethalf(c, &@1, &$1, &$3, &$5, &$7);
378                    }
379                  | SETBITS '(' rvalue ',' rvalue ',' rvalue ',' rvalue ')'
380                    {
381                        @1.last_column = @10.last_column;
382                        yyassert(c, &@1, !is_inside_ternary(c),
383                                 "Assignment side-effect not modeled!");
384                        gen_setbits(c, &@1, &$3, &$5, &$7, &$9);
385                    }
386                  | INSBITS '(' lvalue ',' rvalue ',' rvalue ',' rvalue ')'
387                    {
388                        @1.last_column = @10.last_column;
389                        yyassert(c, &@1, !is_inside_ternary(c),
390                                 "Assignment side-effect not modeled!");
391                        gen_rdeposit_op(c, &@1, &$3, &$9, &$7, &$5);
392                    }
393                  | IDENTITY '(' rvalue ')'
394                    {
395                        @1.last_column = @4.last_column;
396                        $$ = $3;
397                    }
398                  ;
399 
400 control_statement : frame_check
401                   | cancel_statement
402                   | if_statement
403                   | for_statement
404                   ;
405 
406 frame_check : FCHK '(' rvalue ',' rvalue ')' ';'
407             ;
408 
409 cancel_statement : LOAD_CANCEL
410                    {
411                        gen_load_cancel(c, &@1);
412                    }
413                  | STORE_CANCEL
414                    {
415                        gen_cancel(c, &@1);
416                    }
417                  | CANCEL
418                  ;
419 
420 if_statement : if_stmt
421                {
422                    /* Fix else label */
423                    OUT(c, &@1, "gen_set_label(if_label_", &$1, ");\n");
424                }
425              | if_stmt ELSE
426                {
427                    @1.last_column = @2.last_column;
428                    $2 = gen_if_else(c, &@1, $1);
429                }
430                statement
431                {
432                    OUT(c, &@1, "gen_set_label(if_label_", &$2, ");\n");
433                }
434              ;
435 
436 for_statement : FOR '(' IMM '=' IMM ';' IMM '<' IMM ';' IMM PLUSPLUS ')'
437                 {
438                     yyassert(c, &@3,
439                              $3.imm.type == I &&
440                              $7.imm.type == I &&
441                              $11.imm.type == I,
442                              "Loop induction variable must be \"i\"");
443                     @1.last_column = @13.last_column;
444                     OUT(c, &@1, "for (int ", &$3, " = ", &$5, "; ",
445                         &$7, " < ", &$9);
446                     OUT(c, &@1, "; ", &$11, "++) {\n");
447                 }
448                 code_block
449                 {
450                     OUT(c, &@1, "}\n");
451                 }
452               ;
453 
454 if_stmt : IF '(' rvalue ')'
455           {
456               @1.last_column = @3.last_column;
457               $1 = gen_if_cond(c, &@1, &$3);
458           }
459           statement
460           {
461               $$ = $1;
462           }
463         ;
464 
465 rvalue : FAIL
466          {
467              yyassert(c, &@1, false, "Encountered a FAIL token as rvalue.\n");
468          }
469        | assign_statement
470        | REG
471          {
472              $$ = $1;
473          }
474        | IMM
475          {
476              $$ = $1;
477          }
478        | PRED
479          {
480              $$ = gen_rvalue_pred(c, &@1, &$1);
481          }
482        | PC
483          {
484              /* Read PC from the CR */
485              HexValue rvalue;
486              memset(&rvalue, 0, sizeof(HexValue));
487              rvalue.type = IMMEDIATE;
488              rvalue.imm.type = IMM_PC;
489              rvalue.bit_width = 32;
490              rvalue.signedness = UNSIGNED;
491              $$ = rvalue;
492          }
493        | CONSTEXT
494          {
495              HexValue rvalue;
496              memset(&rvalue, 0, sizeof(HexValue));
497              rvalue.type = IMMEDIATE;
498              rvalue.imm.type = IMM_CONSTEXT;
499              rvalue.signedness = UNSIGNED;
500              rvalue.is_dotnew = false;
501              $$ = rvalue;
502          }
503        | var
504          {
505              $$ = gen_rvalue_var(c, &@1, &$1);
506          }
507        | MPY '(' rvalue ',' rvalue ')'
508          {
509              @1.last_column = @6.last_column;
510              $$ = gen_rvalue_mpy(c, &@1, &$1, &$3, &$5);
511          }
512        | rvalue '+' rvalue
513          {
514              @1.last_column = @3.last_column;
515              $$ = gen_bin_op(c, &@1, ADD_OP, &$1, &$3);
516          }
517        | rvalue '-' rvalue
518          {
519              @1.last_column = @3.last_column;
520              $$ = gen_bin_op(c, &@1, SUB_OP, &$1, &$3);
521          }
522        | rvalue '*' rvalue
523          {
524              @1.last_column = @3.last_column;
525              $$ = gen_bin_op(c, &@1, MUL_OP, &$1, &$3);
526          }
527        | rvalue ASL rvalue
528          {
529              @1.last_column = @3.last_column;
530              $$ = gen_bin_op(c, &@1, ASL_OP, &$1, &$3);
531          }
532        | rvalue ASR rvalue
533          {
534              @1.last_column = @3.last_column;
535              assert_signedness(c, &@1, $1.signedness);
536              if ($1.signedness == UNSIGNED) {
537                  $$ = gen_bin_op(c, &@1, LSR_OP, &$1, &$3);
538              } else if ($1.signedness == SIGNED) {
539                  $$ = gen_bin_op(c, &@1, ASR_OP, &$1, &$3);
540              }
541          }
542        | rvalue LSR rvalue
543          {
544              @1.last_column = @3.last_column;
545              $$ = gen_bin_op(c, &@1, LSR_OP, &$1, &$3);
546          }
547        | rvalue '&' rvalue
548          {
549              @1.last_column = @3.last_column;
550              $$ = gen_bin_op(c, &@1, ANDB_OP, &$1, &$3);
551          }
552        | rvalue '|' rvalue
553          {
554              @1.last_column = @3.last_column;
555              $$ = gen_bin_op(c, &@1, ORB_OP, &$1, &$3);
556          }
557        | rvalue '^' rvalue
558          {
559              @1.last_column = @3.last_column;
560              $$ = gen_bin_op(c, &@1, XORB_OP, &$1, &$3);
561          }
562        | rvalue ANDL rvalue
563          {
564              @1.last_column = @3.last_column;
565              $$ = gen_bin_op(c, &@1, ANDL_OP, &$1, &$3);
566          }
567        | MIN '(' rvalue ',' rvalue ')'
568          {
569              @1.last_column = @3.last_column;
570              $$ = gen_bin_op(c, &@1, MINI_OP, &$3, &$5);
571          }
572        | MAX '(' rvalue ',' rvalue ')'
573          {
574              @1.last_column = @3.last_column;
575              $$ = gen_bin_op(c, &@1, MAXI_OP, &$3, &$5);
576          }
577        | '~' rvalue
578          {
579              @1.last_column = @2.last_column;
580              $$ = gen_rvalue_not(c, &@1, &$2);
581          }
582        | '!' rvalue
583          {
584              @1.last_column = @2.last_column;
585              $$ = gen_rvalue_notl(c, &@1, &$2);
586          }
587        | SAT '(' IMM ',' rvalue ')'
588          {
589              @1.last_column = @6.last_column;
590              $$ = gen_rvalue_sat(c, &@1, &$1, &$3, &$5);
591          }
592        | CAST rvalue
593          {
594              @1.last_column = @2.last_column;
595              $$ = gen_cast_op(c, &@1, &$2, $1.bit_width, $1.signedness);
596          }
597        | rvalue EQ rvalue
598          {
599              @1.last_column = @3.last_column;
600              $$ = gen_bin_cmp(c, &@1, TCG_COND_EQ, &$1, &$3);
601          }
602        | rvalue NEQ rvalue
603          {
604              @1.last_column = @3.last_column;
605              $$ = gen_bin_cmp(c, &@1, TCG_COND_NE, &$1, &$3);
606          }
607        | rvalue '<' rvalue
608          {
609              @1.last_column = @3.last_column;
610 
611              assert_signedness(c, &@1, $1.signedness);
612              assert_signedness(c, &@1, $3.signedness);
613              if ($1.signedness == UNSIGNED || $3.signedness == UNSIGNED) {
614                  $$ = gen_bin_cmp(c, &@1, TCG_COND_LTU, &$1, &$3);
615              } else {
616                  $$ = gen_bin_cmp(c, &@1, TCG_COND_LT, &$1, &$3);
617              }
618          }
619        | rvalue '>' rvalue
620          {
621              @1.last_column = @3.last_column;
622 
623              assert_signedness(c, &@1, $1.signedness);
624              assert_signedness(c, &@1, $3.signedness);
625              if ($1.signedness == UNSIGNED || $3.signedness == UNSIGNED) {
626                  $$ = gen_bin_cmp(c, &@1, TCG_COND_GTU, &$1, &$3);
627              } else {
628                  $$ = gen_bin_cmp(c, &@1, TCG_COND_GT, &$1, &$3);
629              }
630          }
631        | rvalue LTE rvalue
632          {
633              @1.last_column = @3.last_column;
634 
635              assert_signedness(c, &@1, $1.signedness);
636              assert_signedness(c, &@1, $3.signedness);
637              if ($1.signedness == UNSIGNED || $3.signedness == UNSIGNED) {
638                  $$ = gen_bin_cmp(c, &@1, TCG_COND_LEU, &$1, &$3);
639              } else {
640                  $$ = gen_bin_cmp(c, &@1, TCG_COND_LE, &$1, &$3);
641              }
642          }
643        | rvalue GTE rvalue
644          {
645              @1.last_column = @3.last_column;
646 
647              assert_signedness(c, &@1, $1.signedness);
648              assert_signedness(c, &@1, $3.signedness);
649              if ($1.signedness == UNSIGNED || $3.signedness == UNSIGNED) {
650                  $$ = gen_bin_cmp(c, &@1, TCG_COND_GEU, &$1, &$3);
651              } else {
652                  $$ = gen_bin_cmp(c, &@1, TCG_COND_GE, &$1, &$3);
653              }
654          }
655        | rvalue '?'
656          {
657              Ternary t = { 0 };
658              t.state = IN_LEFT;
659              t.cond = $1;
660              g_array_append_val(c->ternary, t);
661          }
662          rvalue ':'
663          {
664              Ternary *t = &g_array_index(c->ternary, Ternary,
665                                          c->ternary->len - 1);
666              t->state = IN_RIGHT;
667          }
668          rvalue
669          {
670              @1.last_column = @5.last_column;
671              $$ = gen_rvalue_ternary(c, &@1, &$1, &$4, &$7);
672          }
673        | FSCR '(' rvalue ')'
674          {
675              @1.last_column = @4.last_column;
676              $$ = gen_rvalue_fscr(c, &@1, &$3);
677          }
678        | SXT '(' rvalue ',' IMM ',' rvalue ')'
679          {
680              @1.last_column = @8.last_column;
681              yyassert(c, &@1, $5.type == IMMEDIATE &&
682                       $5.imm.type == VALUE,
683                       "SXT expects immediate values\n");
684              $$ = gen_extend_op(c, &@1, &$3, 64, &$7, SIGNED);
685          }
686        | ZXT '(' rvalue ',' IMM ',' rvalue ')'
687          {
688              @1.last_column = @8.last_column;
689              yyassert(c, &@1, $5.type == IMMEDIATE &&
690                       $5.imm.type == VALUE,
691                       "ZXT expects immediate values\n");
692              $$ = gen_extend_op(c, &@1, &$3, 64, &$7, UNSIGNED);
693          }
694        | '(' rvalue ')'
695          {
696              $$ = $2;
697          }
698        | ABS rvalue
699          {
700              @1.last_column = @2.last_column;
701              $$ = gen_rvalue_abs(c, &@1, &$2);
702          }
703        | CROUND '(' rvalue ',' rvalue ')'
704          {
705              @1.last_column = @6.last_column;
706              $$ = gen_convround_n(c, &@1, &$3, &$5);
707          }
708        | CROUND '(' rvalue ')'
709          {
710              @1.last_column = @4.last_column;
711              $$ = gen_convround(c, &@1, &$3);
712          }
713        | ROUND '(' rvalue ',' rvalue ')'
714          {
715              @1.last_column = @6.last_column;
716              $$ = gen_round(c, &@1, &$3, &$5);
717          }
718        | '-' rvalue
719          {
720              @1.last_column = @2.last_column;
721              $$ = gen_rvalue_neg(c, &@1, &$2);
722          }
723        | ICIRC '(' rvalue ')' ASL IMM
724          {
725              @1.last_column = @6.last_column;
726              $$ = gen_tmp(c, &@1, 32, UNSIGNED);
727              OUT(c, &@1, "gen_read_ireg(", &$$, ", ", &$3, ", ", &$6, ");\n");
728          }
729        | CIRCADD '(' rvalue ',' rvalue ',' rvalue ')'
730          {
731              @1.last_column = @8.last_column;
732              gen_circ_op(c, &@1, &$3, &$5, &$7);
733          }
734        | LOCNT '(' rvalue ')'
735          {
736              @1.last_column = @4.last_column;
737              /* Leading ones count */
738              $$ = gen_locnt_op(c, &@1, &$3);
739          }
740        | COUNTONES '(' rvalue ')'
741          {
742              @1.last_column = @4.last_column;
743              /* Ones count */
744              $$ = gen_ctpop_op(c, &@1, &$3);
745          }
746        | EXTRACT '(' rvalue ',' rvalue ')'
747          {
748              @1.last_column = @6.last_column;
749              $$ = gen_extract_op(c, &@1, &$5, &$3, &$1);
750          }
751        | EXTRANGE '(' rvalue ',' rvalue ',' rvalue ')'
752          {
753              @1.last_column = @8.last_column;
754              yyassert(c, &@1, $5.type == IMMEDIATE &&
755                       $5.imm.type == VALUE &&
756                       $7.type == IMMEDIATE &&
757                       $7.imm.type == VALUE,
758                       "Range extract needs immediate values!\n");
759              $$ = gen_rextract_op(c,
760                                   &@1,
761                                   &$3,
762                                   $7.imm.value,
763                                   $5.imm.value - $7.imm.value + 1);
764          }
765        | CAST4_8U '(' rvalue ')'
766          {
767              @1.last_column = @4.last_column;
768              $$ = gen_rvalue_truncate(c, &@1, &$3);
769              $$.signedness = UNSIGNED;
770              $$ = rvalue_materialize(c, &@1, &$$);
771              $$ = gen_rvalue_extend(c, &@1, &$$);
772          }
773        | BREV '(' rvalue ')'
774          {
775              @1.last_column = @4.last_column;
776              $$ = gen_rvalue_brev(c, &@1, &$3);
777          }
778        | ROTL '(' rvalue ',' rvalue ')'
779          {
780              @1.last_column = @6.last_column;
781              $$ = gen_rotl(c, &@1, &$3, &$5);
782          }
783        | ADDSAT64 '(' rvalue ',' rvalue ',' rvalue ')'
784          {
785              @1.last_column = @8.last_column;
786              gen_addsat64(c, &@1, &$3, &$5, &$7);
787          }
788        | CARRY_FROM_ADD '(' rvalue ',' rvalue ',' rvalue ')'
789          {
790              @1.last_column = @8.last_column;
791              $$ = gen_carry_from_add(c, &@1, &$3, &$5, &$7);
792          }
793        | LSBNEW '(' rvalue ')'
794          {
795              @1.last_column = @4.last_column;
796              HexValue one = gen_imm_value(c, &@1, 1, 32, UNSIGNED);
797              $$ = gen_bin_op(c, &@1, ANDB_OP, &$3, &one);
798          }
799        ;
800 
801 lvalue : FAIL
802          {
803              yyassert(c, &@1, false, "Encountered a FAIL token as lvalue.\n");
804          }
805        | REG
806          {
807              $$ = $1;
808          }
809        | var
810          {
811              $$ = $1;
812          }
813        ;
814 
815 %%
816 
817 int main(int argc, char **argv)
818 {
819     if (argc != 5) {
820         fprintf(stderr,
821                 "Semantics: Hexagon ISA to tinycode generator compiler\n\n");
822         fprintf(stderr,
823                 "Usage: ./semantics IDEFS EMITTER_C EMITTER_H "
824                 "ENABLED_INSTRUCTIONS_LIST\n");
825         return 1;
826     }
827 
828     enum {
829         ARG_INDEX_ARGV0 = 0,
830         ARG_INDEX_IDEFS,
831         ARG_INDEX_EMITTER_C,
832         ARG_INDEX_EMITTER_H,
833         ARG_INDEX_ENABLED_INSTRUCTIONS_LIST
834     };
835 
836     FILE *enabled_file = fopen(argv[ARG_INDEX_ENABLED_INSTRUCTIONS_LIST], "w");
837 
838     FILE *output_file = fopen(argv[ARG_INDEX_EMITTER_C], "w");
839     fputs("#include \"qemu/osdep.h\"\n", output_file);
840     fputs("#include \"qemu/log.h\"\n", output_file);
841     fputs("#include \"cpu.h\"\n", output_file);
842     fputs("#include \"internal.h\"\n", output_file);
843     fputs("#include \"tcg/tcg.h\"\n", output_file);
844     fputs("#include \"tcg/tcg-op.h\"\n", output_file);
845     fputs("#include \"exec/helper-gen.h\"\n", output_file);
846     fputs("#include \"insn.h\"\n", output_file);
847     fputs("#include \"opcodes.h\"\n", output_file);
848     fputs("#include \"translate.h\"\n", output_file);
849     fputs("#define QEMU_GENERATE\n", output_file);
850     fputs("#include \"genptr.h\"\n", output_file);
851     fputs("#include \"macros.h\"\n", output_file);
852     fprintf(output_file, "#include \"%s\"\n", argv[ARG_INDEX_EMITTER_H]);
853 
854     FILE *defines_file = fopen(argv[ARG_INDEX_EMITTER_H], "w");
855     assert(defines_file != NULL);
856     fputs("#ifndef HEX_EMITTER_H\n", defines_file);
857     fputs("#define HEX_EMITTER_H\n", defines_file);
858     fputs("\n", defines_file);
859     fputs("#include \"insn.h\"\n\n", defines_file);
860 
861     /* Parser input file */
862     Context context = { 0 };
863     context.defines_file = defines_file;
864     context.output_file = output_file;
865     context.enabled_file = enabled_file;
866     /* Initialize buffers */
867     context.out_str = g_string_new(NULL);
868     context.signature_str = g_string_new(NULL);
869     context.header_str = g_string_new(NULL);
870     context.ternary = g_array_new(FALSE, TRUE, sizeof(Ternary));
871     /* Read input file */
872     FILE *input_file = fopen(argv[ARG_INDEX_IDEFS], "r");
873     fseek(input_file, 0L, SEEK_END);
874     long input_size = ftell(input_file);
875     context.input_buffer = (char *) calloc(input_size + 1, sizeof(char));
876     fseek(input_file, 0L, SEEK_SET);
877     size_t read_chars = fread(context.input_buffer,
878                               sizeof(char),
879                               input_size,
880                               input_file);
881     if (read_chars != (size_t) input_size) {
882         fprintf(stderr, "Error: an error occurred while reading input file!\n");
883         return -1;
884     }
885     yylex_init(&context.scanner);
886     YY_BUFFER_STATE buffer;
887     buffer = yy_scan_string(context.input_buffer, context.scanner);
888     /* Start the parsing procedure */
889     yyparse(context.scanner, &context);
890     if (context.implemented_insn != context.total_insn) {
891         fprintf(stderr,
892                 "Warning: %d/%d meta instructions have been implemented!\n",
893                 context.implemented_insn,
894                 context.total_insn);
895     }
896     fputs("#endif " START_COMMENT " HEX_EMITTER_h " END_COMMENT "\n",
897           defines_file);
898     /* Cleanup */
899     yy_delete_buffer(buffer, context.scanner);
900     yylex_destroy(context.scanner);
901     free(context.input_buffer);
902     g_string_free(context.out_str, TRUE);
903     g_string_free(context.signature_str, TRUE);
904     g_string_free(context.header_str, TRUE);
905     g_array_free(context.ternary, TRUE);
906     fclose(output_file);
907     fclose(input_file);
908     fclose(defines_file);
909     fclose(enabled_file);
910 
911     return 0;
912 }
913