1 %{
2 /*
3  *  Copyright(c) 2019-2022 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 NPC LPCFG
56 %token LOAD_CANCEL CANCEL IDENTITY PART1 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                     /* Enqueue register into initialization list */
237                     g_array_append_val(c->inst.init_list, $1);
238                 }
239               | PRED
240                 {
241                     emit_arg(c, &@1, &$1);
242                     /* Enqueue predicate into initialization list */
243                     g_array_append_val(c->inst.init_list, $1);
244                 }
245               | IN REG
246                 {
247                     emit_arg(c, &@2, &$2);
248                 }
249               | IN PRED
250                 {
251                     emit_arg(c, &@2, &$2);
252                 }
253               | IMM
254                 {
255                     EMIT_SIG(c, ", int %ciV", $1.imm.id);
256                 }
257               ;
258 
259 code_block : '{' statements '}'
260            | '{' '}'
261            ;
262 
263 /* A list of one or more statements */
264 statements : statements statement
265            | statement
266            ;
267 
268 /* Statements can be assignment (rvalue ';'), control or memory statements */
269 statement : control_statement
270           | var_decl ';'
271           | rvalue ';'
272             {
273                 gen_rvalue_free(c, &@1, &$1);
274             }
275           | code_block
276           | ';'
277           ;
278 
279 assign_statement : lvalue '=' rvalue
280                    {
281                        @1.last_column = @3.last_column;
282                        gen_assign(c, &@1, &$1, &$3);
283                        $$ = $1;
284                    }
285                  | var_decl '=' rvalue
286                    {
287                        @1.last_column = @3.last_column;
288                        gen_assign(c, &@1, &$1, &$3);
289                        $$ = $1;
290                    }
291                  | lvalue INC rvalue
292                    {
293                        @1.last_column = @3.last_column;
294                        HexValue tmp = gen_bin_op(c, &@1, ADD_OP, &$1, &$3);
295                        gen_assign(c, &@1, &$1, &tmp);
296                        $$ = $1;
297                    }
298                  | lvalue DEC rvalue
299                    {
300                        @1.last_column = @3.last_column;
301                        HexValue tmp = gen_bin_op(c, &@1, SUB_OP, &$1, &$3);
302                        gen_assign(c, &@1, &$1, &tmp);
303                        $$ = $1;
304                    }
305                  | lvalue ANDA rvalue
306                    {
307                        @1.last_column = @3.last_column;
308                        HexValue tmp = gen_bin_op(c, &@1, ANDB_OP, &$1, &$3);
309                        gen_assign(c, &@1, &$1, &tmp);
310                        $$ = $1;
311                    }
312                  | lvalue ORA rvalue
313                    {
314                        @1.last_column = @3.last_column;
315                        HexValue tmp = gen_bin_op(c, &@1, ORB_OP, &$1, &$3);
316                        gen_assign(c, &@1, &$1, &tmp);
317                        $$ = $1;
318                    }
319                  | lvalue XORA rvalue
320                    {
321                        @1.last_column = @3.last_column;
322                        HexValue tmp = gen_bin_op(c, &@1, XORB_OP, &$1, &$3);
323                        gen_assign(c, &@1, &$1, &tmp);
324                        $$ = $1;
325                    }
326                  | PRED '=' rvalue
327                    {
328                        @1.last_column = @3.last_column;
329                        gen_pred_assign(c, &@1, &$1, &$3);
330                    }
331                  | IMM '=' rvalue
332                    {
333                        @1.last_column = @3.last_column;
334                        yyassert(c, &@1, $3.type == IMMEDIATE,
335                                 "Cannot assign non-immediate to immediate!");
336                        yyassert(c, &@1, $1.imm.type == VARIABLE,
337                                 "Cannot assign to non-variable!");
338                        /* Assign to the function argument */
339                        OUT(c, &@1, &$1, " = ", &$3, ";\n");
340                        $$ = $1;
341                    }
342                  | PC '=' rvalue
343                    {
344                        @1.last_column = @3.last_column;
345                        yyassert(c, &@1, !is_inside_ternary(c),
346                                 "Assignment side-effect not modeled!");
347                        $3 = gen_rvalue_truncate(c, &@1, &$3);
348                        $3 = rvalue_materialize(c, &@1, &$3);
349                        OUT(c, &@1, "gen_write_new_pc(", &$3, ");\n");
350                        gen_rvalue_free(c, &@1, &$3); /* Free temporary value */
351                    }
352                  | LOAD '(' IMM ',' IMM ',' SIGN ',' var ',' lvalue ')'
353                    {
354                        @1.last_column = @12.last_column;
355                        yyassert(c, &@1, !is_inside_ternary(c),
356                                 "Assignment side-effect not modeled!");
357                        yyassert(c, &@1, $3.imm.value == 1,
358                                 "LOAD of arrays not supported!");
359                        gen_load(c, &@1, &$5, $7, &$9, &$11);
360                    }
361                  | STORE '(' IMM ',' IMM ',' var ',' rvalue ')'
362                    /* Store primitive */
363                    {
364                        @1.last_column = @10.last_column;
365                        yyassert(c, &@1, !is_inside_ternary(c),
366                                 "Assignment side-effect not modeled!");
367                        yyassert(c, &@1, $3.imm.value == 1,
368                                 "STORE of arrays not supported!");
369                        gen_store(c, &@1, &$5, &$7, &$9);
370                    }
371                  | LPCFG '=' rvalue
372                    {
373                        @1.last_column = @3.last_column;
374                        yyassert(c, &@1, !is_inside_ternary(c),
375                                 "Assignment side-effect not modeled!");
376                        $3 = gen_rvalue_truncate(c, &@1, &$3);
377                        $3 = rvalue_materialize(c, &@1, &$3);
378                        OUT(c, &@1, "SET_USR_FIELD(USR_LPCFG, ", &$3, ");\n");
379                        gen_rvalue_free(c, &@1, &$3);
380                    }
381                  | DEPOSIT '(' rvalue ',' rvalue ',' rvalue ')'
382                    {
383                        @1.last_column = @8.last_column;
384                        yyassert(c, &@1, !is_inside_ternary(c),
385                                 "Assignment side-effect not modeled!");
386                        gen_deposit_op(c, &@1, &$5, &$7, &$3, &$1);
387                    }
388                  | SETHALF '(' rvalue ',' lvalue ',' rvalue ')'
389                    {
390                        @1.last_column = @8.last_column;
391                        yyassert(c, &@1, !is_inside_ternary(c),
392                                 "Assignment side-effect not modeled!");
393                        gen_sethalf(c, &@1, &$1, &$3, &$5, &$7);
394                    }
395                  | SETBITS '(' rvalue ',' rvalue ',' rvalue ',' rvalue ')'
396                    {
397                        @1.last_column = @10.last_column;
398                        yyassert(c, &@1, !is_inside_ternary(c),
399                                 "Assignment side-effect not modeled!");
400                        gen_setbits(c, &@1, &$3, &$5, &$7, &$9);
401                    }
402                  | INSBITS '(' lvalue ',' rvalue ',' rvalue ',' rvalue ')'
403                    {
404                        @1.last_column = @10.last_column;
405                        yyassert(c, &@1, !is_inside_ternary(c),
406                                 "Assignment side-effect not modeled!");
407                        gen_rdeposit_op(c, &@1, &$3, &$9, &$7, &$5);
408                    }
409                  | IDENTITY '(' rvalue ')'
410                    {
411                        @1.last_column = @4.last_column;
412                        $$ = $3;
413                    }
414                  ;
415 
416 control_statement : frame_check
417                   | cancel_statement
418                   | if_statement
419                   | for_statement
420                   | fpart1_statement
421                   ;
422 
423 frame_check : FCHK '(' rvalue ',' rvalue ')' ';'
424               {
425                   gen_rvalue_free(c, &@1, &$3);
426                   gen_rvalue_free(c, &@1, &$5);
427               }
428             ;
429 
430 cancel_statement : LOAD_CANCEL
431                    {
432                        gen_load_cancel(c, &@1);
433                    }
434                  | CANCEL
435                    {
436                        gen_cancel(c, &@1);
437                    }
438                  ;
439 
440 if_statement : if_stmt
441                {
442                    /* Fix else label */
443                    OUT(c, &@1, "gen_set_label(if_label_", &$1, ");\n");
444                }
445              | if_stmt ELSE
446                {
447                    @1.last_column = @2.last_column;
448                    $2 = gen_if_else(c, &@1, $1);
449                }
450                statement
451                {
452                    OUT(c, &@1, "gen_set_label(if_label_", &$2, ");\n");
453                }
454              ;
455 
456 for_statement : FOR '(' IMM '=' IMM ';' IMM '<' IMM ';' IMM PLUSPLUS ')'
457                 {
458                     yyassert(c, &@3,
459                              $3.imm.type == I &&
460                              $7.imm.type == I &&
461                              $11.imm.type == I,
462                              "Loop induction variable must be \"i\"");
463                     @1.last_column = @13.last_column;
464                     OUT(c, &@1, "for (int ", &$3, " = ", &$5, "; ",
465                         &$7, " < ", &$9);
466                     OUT(c, &@1, "; ", &$11, "++) {\n");
467                 }
468                 code_block
469                 {
470                     OUT(c, &@1, "}\n");
471                 }
472               ;
473 
474 fpart1_statement : PART1
475                    {
476                        OUT(c, &@1, "if (insn->part1) {\n");
477                    }
478                    '(' statements ')'
479                    {
480                        @1.last_column = @3.last_column;
481                        OUT(c, &@1, "return; }\n");
482                    }
483                  ;
484 
485 if_stmt : IF '(' rvalue ')'
486           {
487               @1.last_column = @3.last_column;
488               $1 = gen_if_cond(c, &@1, &$3);
489           }
490           statement
491           {
492               $$ = $1;
493           }
494         ;
495 
496 rvalue : FAIL
497          {
498              yyassert(c, &@1, false, "Encountered a FAIL token as rvalue.\n");
499          }
500        | assign_statement
501        | REG
502          {
503              $$ = $1;
504          }
505        | IMM
506          {
507              $$ = $1;
508          }
509        | PRED
510          {
511              $$ = gen_rvalue_pred(c, &@1, &$1);
512          }
513        | PC
514          {
515              /* Read PC from the CR */
516              HexValue rvalue;
517              memset(&rvalue, 0, sizeof(HexValue));
518              rvalue.type = IMMEDIATE;
519              rvalue.imm.type = IMM_PC;
520              rvalue.bit_width = 32;
521              rvalue.signedness = UNSIGNED;
522              $$ = rvalue;
523          }
524        | NPC
525          {
526              /*
527               * NPC is only read from CALLs, so we can hardcode it
528               * at translation time
529               */
530              HexValue rvalue;
531              memset(&rvalue, 0, sizeof(HexValue));
532              rvalue.type = IMMEDIATE;
533              rvalue.imm.type = IMM_NPC;
534              rvalue.bit_width = 32;
535              rvalue.signedness = UNSIGNED;
536              $$ = rvalue;
537          }
538        | CONSTEXT
539          {
540              HexValue rvalue;
541              memset(&rvalue, 0, sizeof(HexValue));
542              rvalue.type = IMMEDIATE;
543              rvalue.imm.type = IMM_CONSTEXT;
544              rvalue.signedness = UNSIGNED;
545              rvalue.is_dotnew = false;
546              rvalue.is_manual = false;
547              $$ = rvalue;
548          }
549        | var
550          {
551              $$ = gen_rvalue_var(c, &@1, &$1);
552          }
553        | MPY '(' rvalue ',' rvalue ')'
554          {
555              @1.last_column = @6.last_column;
556              $$ = gen_rvalue_mpy(c, &@1, &$1, &$3, &$5);
557          }
558        | rvalue '+' rvalue
559          {
560              @1.last_column = @3.last_column;
561              $$ = gen_bin_op(c, &@1, ADD_OP, &$1, &$3);
562          }
563        | rvalue '-' rvalue
564          {
565              @1.last_column = @3.last_column;
566              $$ = gen_bin_op(c, &@1, SUB_OP, &$1, &$3);
567          }
568        | rvalue '*' rvalue
569          {
570              @1.last_column = @3.last_column;
571              $$ = gen_bin_op(c, &@1, MUL_OP, &$1, &$3);
572          }
573        | rvalue ASL rvalue
574          {
575              @1.last_column = @3.last_column;
576              $$ = gen_bin_op(c, &@1, ASL_OP, &$1, &$3);
577          }
578        | rvalue ASR rvalue
579          {
580              @1.last_column = @3.last_column;
581              assert_signedness(c, &@1, $1.signedness);
582              if ($1.signedness == UNSIGNED) {
583                  $$ = gen_bin_op(c, &@1, LSR_OP, &$1, &$3);
584              } else if ($1.signedness == SIGNED) {
585                  $$ = gen_bin_op(c, &@1, ASR_OP, &$1, &$3);
586              }
587          }
588        | rvalue LSR rvalue
589          {
590              @1.last_column = @3.last_column;
591              $$ = gen_bin_op(c, &@1, LSR_OP, &$1, &$3);
592          }
593        | rvalue '&' rvalue
594          {
595              @1.last_column = @3.last_column;
596              $$ = gen_bin_op(c, &@1, ANDB_OP, &$1, &$3);
597          }
598        | rvalue '|' rvalue
599          {
600              @1.last_column = @3.last_column;
601              $$ = gen_bin_op(c, &@1, ORB_OP, &$1, &$3);
602          }
603        | rvalue '^' rvalue
604          {
605              @1.last_column = @3.last_column;
606              $$ = gen_bin_op(c, &@1, XORB_OP, &$1, &$3);
607          }
608        | rvalue ANDL rvalue
609          {
610              @1.last_column = @3.last_column;
611              $$ = gen_bin_op(c, &@1, ANDL_OP, &$1, &$3);
612          }
613        | MIN '(' rvalue ',' rvalue ')'
614          {
615              @1.last_column = @3.last_column;
616              $$ = gen_bin_op(c, &@1, MINI_OP, &$3, &$5);
617          }
618        | MAX '(' rvalue ',' rvalue ')'
619          {
620              @1.last_column = @3.last_column;
621              $$ = gen_bin_op(c, &@1, MAXI_OP, &$3, &$5);
622          }
623        | '~' rvalue
624          {
625              @1.last_column = @2.last_column;
626              $$ = gen_rvalue_not(c, &@1, &$2);
627          }
628        | '!' rvalue
629          {
630              @1.last_column = @2.last_column;
631              $$ = gen_rvalue_notl(c, &@1, &$2);
632          }
633        | SAT '(' IMM ',' rvalue ')'
634          {
635              @1.last_column = @6.last_column;
636              $$ = gen_rvalue_sat(c, &@1, &$1, &$3, &$5);
637          }
638        | CAST rvalue
639          {
640              @1.last_column = @2.last_column;
641              /* Assign target signedness */
642              $2.signedness = $1.signedness;
643              $$ = gen_cast_op(c, &@1, &$2, $1.bit_width, $1.signedness);
644          }
645        | rvalue EQ rvalue
646          {
647              @1.last_column = @3.last_column;
648              $$ = gen_bin_cmp(c, &@1, TCG_COND_EQ, &$1, &$3);
649          }
650        | rvalue NEQ rvalue
651          {
652              @1.last_column = @3.last_column;
653              $$ = gen_bin_cmp(c, &@1, TCG_COND_NE, &$1, &$3);
654          }
655        | rvalue '<' rvalue
656          {
657              @1.last_column = @3.last_column;
658 
659              assert_signedness(c, &@1, $1.signedness);
660              assert_signedness(c, &@1, $3.signedness);
661              if ($1.signedness == UNSIGNED || $3.signedness == UNSIGNED) {
662                  $$ = gen_bin_cmp(c, &@1, TCG_COND_LTU, &$1, &$3);
663              } else {
664                  $$ = gen_bin_cmp(c, &@1, TCG_COND_LT, &$1, &$3);
665              }
666          }
667        | rvalue '>' rvalue
668          {
669              @1.last_column = @3.last_column;
670 
671              assert_signedness(c, &@1, $1.signedness);
672              assert_signedness(c, &@1, $3.signedness);
673              if ($1.signedness == UNSIGNED || $3.signedness == UNSIGNED) {
674                  $$ = gen_bin_cmp(c, &@1, TCG_COND_GTU, &$1, &$3);
675              } else {
676                  $$ = gen_bin_cmp(c, &@1, TCG_COND_GT, &$1, &$3);
677              }
678          }
679        | rvalue LTE rvalue
680          {
681              @1.last_column = @3.last_column;
682 
683              assert_signedness(c, &@1, $1.signedness);
684              assert_signedness(c, &@1, $3.signedness);
685              if ($1.signedness == UNSIGNED || $3.signedness == UNSIGNED) {
686                  $$ = gen_bin_cmp(c, &@1, TCG_COND_LEU, &$1, &$3);
687              } else {
688                  $$ = gen_bin_cmp(c, &@1, TCG_COND_LE, &$1, &$3);
689              }
690          }
691        | rvalue GTE rvalue
692          {
693              @1.last_column = @3.last_column;
694 
695              assert_signedness(c, &@1, $1.signedness);
696              assert_signedness(c, &@1, $3.signedness);
697              if ($1.signedness == UNSIGNED || $3.signedness == UNSIGNED) {
698                  $$ = gen_bin_cmp(c, &@1, TCG_COND_GEU, &$1, &$3);
699              } else {
700                  $$ = gen_bin_cmp(c, &@1, TCG_COND_GE, &$1, &$3);
701              }
702          }
703        | rvalue '?'
704          {
705              $1.is_manual = true;
706              Ternary t = { 0 };
707              t.state = IN_LEFT;
708              t.cond = $1;
709              g_array_append_val(c->ternary, t);
710          }
711          rvalue ':'
712          {
713              Ternary *t = &g_array_index(c->ternary, Ternary,
714                                          c->ternary->len - 1);
715              t->state = IN_RIGHT;
716          }
717          rvalue
718          {
719              @1.last_column = @5.last_column;
720              $$ = gen_rvalue_ternary(c, &@1, &$1, &$4, &$7);
721          }
722        | FSCR '(' rvalue ')'
723          {
724              @1.last_column = @4.last_column;
725              $$ = gen_rvalue_fscr(c, &@1, &$3);
726          }
727        | SXT '(' rvalue ',' IMM ',' rvalue ')'
728          {
729              @1.last_column = @8.last_column;
730              yyassert(c, &@1, $5.type == IMMEDIATE &&
731                       $5.imm.type == VALUE,
732                       "SXT expects immediate values\n");
733              $$ = gen_extend_op(c, &@1, &$3, $5.imm.value, &$7, SIGNED);
734          }
735        | ZXT '(' rvalue ',' IMM ',' rvalue ')'
736          {
737              @1.last_column = @8.last_column;
738              yyassert(c, &@1, $5.type == IMMEDIATE &&
739                       $5.imm.type == VALUE,
740                       "ZXT expects immediate values\n");
741              $$ = gen_extend_op(c, &@1, &$3, $5.imm.value, &$7, UNSIGNED);
742          }
743        | '(' rvalue ')'
744          {
745              $$ = $2;
746          }
747        | ABS rvalue
748          {
749              @1.last_column = @2.last_column;
750              $$ = gen_rvalue_abs(c, &@1, &$2);
751          }
752        | CROUND '(' rvalue ',' rvalue ')'
753          {
754              @1.last_column = @6.last_column;
755              $$ = gen_convround_n(c, &@1, &$3, &$5);
756          }
757        | CROUND '(' rvalue ')'
758          {
759              @1.last_column = @4.last_column;
760              $$ = gen_convround(c, &@1, &$3);
761          }
762        | ROUND '(' rvalue ',' rvalue ')'
763          {
764              @1.last_column = @6.last_column;
765              $$ = gen_round(c, &@1, &$3, &$5);
766          }
767        | '-' rvalue
768          {
769              @1.last_column = @2.last_column;
770              $$ = gen_rvalue_neg(c, &@1, &$2);
771          }
772        | ICIRC '(' rvalue ')' ASL IMM
773          {
774              @1.last_column = @6.last_column;
775              $$ = gen_tmp(c, &@1, 32, UNSIGNED);
776              OUT(c, &@1, "gen_read_ireg(", &$$, ", ", &$3, ", ", &$6, ");\n");
777              gen_rvalue_free(c, &@1, &$3);
778          }
779        | CIRCADD '(' rvalue ',' rvalue ',' rvalue ')'
780          {
781              @1.last_column = @8.last_column;
782              gen_circ_op(c, &@1, &$3, &$5, &$7);
783          }
784        | LOCNT '(' rvalue ')'
785          {
786              @1.last_column = @4.last_column;
787              /* Leading ones count */
788              $$ = gen_locnt_op(c, &@1, &$3);
789          }
790        | COUNTONES '(' rvalue ')'
791          {
792              @1.last_column = @4.last_column;
793              /* Ones count */
794              $$ = gen_ctpop_op(c, &@1, &$3);
795          }
796        | LPCFG
797          {
798              $$ = gen_tmp_value(c, &@1, "0", 32, UNSIGNED);
799              OUT(c, &@1, "GET_USR_FIELD(USR_LPCFG, ", &$$, ");\n");
800          }
801        | EXTRACT '(' rvalue ',' rvalue ')'
802          {
803              @1.last_column = @6.last_column;
804              $$ = gen_extract_op(c, &@1, &$5, &$3, &$1);
805          }
806        | EXTRANGE '(' rvalue ',' rvalue ',' rvalue ')'
807          {
808              @1.last_column = @8.last_column;
809              yyassert(c, &@1, $5.type == IMMEDIATE &&
810                       $5.imm.type == VALUE &&
811                       $7.type == IMMEDIATE &&
812                       $7.imm.type == VALUE,
813                       "Range extract needs immediate values!\n");
814              $$ = gen_rextract_op(c,
815                                   &@1,
816                                   &$3,
817                                   $7.imm.value,
818                                   $5.imm.value - $7.imm.value + 1);
819          }
820        | CAST4_8U '(' rvalue ')'
821          {
822              @1.last_column = @4.last_column;
823              $$ = gen_rvalue_truncate(c, &@1, &$3);
824              $$.signedness = UNSIGNED;
825              $$ = rvalue_materialize(c, &@1, &$$);
826              $$ = gen_rvalue_extend(c, &@1, &$$);
827          }
828        | BREV '(' rvalue ')'
829          {
830              @1.last_column = @4.last_column;
831              $$ = gen_rvalue_brev(c, &@1, &$3);
832          }
833        | ROTL '(' rvalue ',' rvalue ')'
834          {
835              @1.last_column = @6.last_column;
836              $$ = gen_rotl(c, &@1, &$3, &$5);
837          }
838        | ADDSAT64 '(' rvalue ',' rvalue ',' rvalue ')'
839          {
840              @1.last_column = @8.last_column;
841              gen_addsat64(c, &@1, &$3, &$5, &$7);
842          }
843        | CARRY_FROM_ADD '(' rvalue ',' rvalue ',' rvalue ')'
844          {
845              @1.last_column = @8.last_column;
846              $$ = gen_carry_from_add(c, &@1, &$3, &$5, &$7);
847          }
848        | LSBNEW '(' rvalue ')'
849          {
850              @1.last_column = @4.last_column;
851              HexValue one = gen_imm_value(c, &@1, 1, 32, UNSIGNED);
852              $$ = gen_bin_op(c, &@1, ANDB_OP, &$3, &one);
853          }
854        ;
855 
856 lvalue : FAIL
857          {
858              @1.last_column = @1.last_column;
859              yyassert(c, &@1, false, "Encountered a FAIL token as lvalue.\n");
860          }
861        | REG
862          {
863              $$ = $1;
864          }
865        | var
866          {
867              $$ = $1;
868          }
869        ;
870 
871 %%
872 
873 int main(int argc, char **argv)
874 {
875     if (argc != 5) {
876         fprintf(stderr,
877                 "Semantics: Hexagon ISA to tinycode generator compiler\n\n");
878         fprintf(stderr,
879                 "Usage: ./semantics IDEFS EMITTER_C EMITTER_H "
880                 "ENABLED_INSTRUCTIONS_LIST\n");
881         return 1;
882     }
883 
884     enum {
885         ARG_INDEX_ARGV0 = 0,
886         ARG_INDEX_IDEFS,
887         ARG_INDEX_EMITTER_C,
888         ARG_INDEX_EMITTER_H,
889         ARG_INDEX_ENABLED_INSTRUCTIONS_LIST
890     };
891 
892     FILE *enabled_file = fopen(argv[ARG_INDEX_ENABLED_INSTRUCTIONS_LIST], "w");
893 
894     FILE *output_file = fopen(argv[ARG_INDEX_EMITTER_C], "w");
895     fputs("#include \"qemu/osdep.h\"\n", output_file);
896     fputs("#include \"qemu/log.h\"\n", output_file);
897     fputs("#include \"cpu.h\"\n", output_file);
898     fputs("#include \"internal.h\"\n", output_file);
899     fputs("#include \"tcg/tcg-op.h\"\n", output_file);
900     fputs("#include \"insn.h\"\n", output_file);
901     fputs("#include \"opcodes.h\"\n", output_file);
902     fputs("#include \"translate.h\"\n", output_file);
903     fputs("#define QEMU_GENERATE\n", output_file);
904     fputs("#include \"genptr.h\"\n", output_file);
905     fputs("#include \"tcg/tcg.h\"\n", output_file);
906     fputs("#include \"macros.h\"\n", output_file);
907     fprintf(output_file, "#include \"%s\"\n", argv[ARG_INDEX_EMITTER_H]);
908 
909     FILE *defines_file = fopen(argv[ARG_INDEX_EMITTER_H], "w");
910     assert(defines_file != NULL);
911     fputs("#ifndef HEX_EMITTER_H\n", defines_file);
912     fputs("#define HEX_EMITTER_H\n", defines_file);
913     fputs("\n", defines_file);
914     fputs("#include \"insn.h\"\n\n", defines_file);
915 
916     /* Parser input file */
917     Context context = { 0 };
918     context.defines_file = defines_file;
919     context.output_file = output_file;
920     context.enabled_file = enabled_file;
921     /* Initialize buffers */
922     context.out_str = g_string_new(NULL);
923     context.signature_str = g_string_new(NULL);
924     context.header_str = g_string_new(NULL);
925     context.ternary = g_array_new(FALSE, TRUE, sizeof(Ternary));
926     /* Read input file */
927     FILE *input_file = fopen(argv[ARG_INDEX_IDEFS], "r");
928     fseek(input_file, 0L, SEEK_END);
929     long input_size = ftell(input_file);
930     context.input_buffer = (char *) calloc(input_size + 1, sizeof(char));
931     fseek(input_file, 0L, SEEK_SET);
932     size_t read_chars = fread(context.input_buffer,
933                               sizeof(char),
934                               input_size,
935                               input_file);
936     if (read_chars != (size_t) input_size) {
937         fprintf(stderr, "Error: an error occurred while reading input file!\n");
938         return -1;
939     }
940     yylex_init(&context.scanner);
941     YY_BUFFER_STATE buffer;
942     buffer = yy_scan_string(context.input_buffer, context.scanner);
943     /* Start the parsing procedure */
944     yyparse(context.scanner, &context);
945     if (context.implemented_insn != context.total_insn) {
946         fprintf(stderr,
947                 "Warning: %d/%d meta instructions have been implemented!\n",
948                 context.implemented_insn,
949                 context.total_insn);
950     }
951     fputs("#endif " START_COMMENT " HEX_EMITTER_h " END_COMMENT "\n",
952           defines_file);
953     /* Cleanup */
954     yy_delete_buffer(buffer, context.scanner);
955     yylex_destroy(context.scanner);
956     free(context.input_buffer);
957     g_string_free(context.out_str, TRUE);
958     g_string_free(context.signature_str, TRUE);
959     g_string_free(context.header_str, TRUE);
960     g_array_free(context.ternary, TRUE);
961     fclose(output_file);
962     fclose(input_file);
963     fclose(defines_file);
964     fclose(enabled_file);
965 
966     return 0;
967 }
968