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