Updated translations for the bfd, binutils, gas, ld and opcodes directories
[binutils-gdb.git] / gdb / d-exp.y
blob6feacd8e3648f181cf2fb0a32b23b2d32f114649
1 /* YACC parser for D expressions, for GDB.
3 Copyright (C) 2014-2024 Free Software Foundation, Inc.
5 This file is part of GDB.
7 This program is free software; you can redistribute it and/or modify
8 it under the terms of the GNU General Public License as published by
9 the Free Software Foundation; either version 3 of the License, or
10 (at your option) any later version.
12 This program is distributed in the hope that it will be useful,
13 but WITHOUT ANY WARRANTY; without even the implied warranty of
14 MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the
15 GNU General Public License for more details.
17 You should have received a copy of the GNU General Public License
18 along with this program. If not, see <http://www.gnu.org/licenses/>. */
20 /* This file is derived from c-exp.y, jv-exp.y. */
22 /* Parse a D expression from text in a string,
23 and return the result as a struct expression pointer.
24 That structure contains arithmetic operations in reverse polish,
25 with constants represented by operations that are followed by special data.
26 See expression.h for the details of the format.
27 What is important here is that it can be built up sequentially
28 during the process of parsing; the lower levels of the tree always
29 come first in the result.
31 Note that malloc's and realloc's in this file are transformed to
32 xmalloc and xrealloc respectively by the same sed command in the
33 makefile that remaps any other malloc/realloc inserted by the parser
34 generator. Doing this with #defines and trying to control the interaction
35 with include files (<malloc.h> and <stdlib.h> for example) just became
36 too messy, particularly when such includes can be inserted at random
37 times by the parser generator. */
41 #include <ctype.h>
42 #include "expression.h"
43 #include "value.h"
44 #include "parser-defs.h"
45 #include "language.h"
46 #include "c-lang.h"
47 #include "d-lang.h"
48 #include "charset.h"
49 #include "block.h"
50 #include "type-stack.h"
51 #include "expop.h"
53 #define parse_type(ps) builtin_type (ps->gdbarch ())
54 #define parse_d_type(ps) builtin_d_type (ps->gdbarch ())
56 /* Remap normal yacc parser interface names (yyparse, yylex, yyerror,
57 etc). */
58 #define GDB_YY_REMAP_PREFIX d_
59 #include "yy-remap.h"
61 /* The state of the parser, used internally when we are parsing the
62 expression. */
64 static struct parser_state *pstate = NULL;
66 /* The current type stack. */
67 static struct type_stack *type_stack;
69 int yyparse (void);
71 static int yylex (void);
73 static void yyerror (const char *);
75 static int type_aggregate_p (struct type *);
77 using namespace expr;
81 /* Although the yacc "value" of an expression is not used,
82 since the result is stored in the structure being created,
83 other node types do have values. */
85 %union
87 struct {
88 LONGEST val;
89 struct type *type;
90 } typed_val_int;
91 struct {
92 gdb_byte val[16];
93 struct type *type;
94 } typed_val_float;
95 struct symbol *sym;
96 struct type *tval;
97 struct typed_stoken tsval;
98 struct stoken sval;
99 struct ttype tsym;
100 struct symtoken ssym;
101 int ival;
102 int voidval;
103 enum exp_opcode opcode;
104 struct stoken_vector svec;
108 /* YYSTYPE gets defined by %union */
109 static int parse_number (struct parser_state *, const char *,
110 int, int, YYSTYPE *);
113 %token <sval> IDENTIFIER UNKNOWN_NAME
114 %token <tsym> TYPENAME
115 %token <voidval> COMPLETE
117 /* A NAME_OR_INT is a symbol which is not known in the symbol table,
118 but which would parse as a valid number in the current input radix.
119 E.g. "c" when input_radix==16. Depending on the parse, it will be
120 turned into a name or into a number. */
122 %token <sval> NAME_OR_INT
124 %token <typed_val_int> INTEGER_LITERAL
125 %token <typed_val_float> FLOAT_LITERAL
126 %token <tsval> CHARACTER_LITERAL
127 %token <tsval> STRING_LITERAL
129 %type <svec> StringExp
130 %type <tval> BasicType TypeExp
131 %type <sval> IdentifierExp
132 %type <ival> ArrayLiteral
134 %token ENTRY
135 %token ERROR
137 /* Keywords that have a constant value. */
138 %token TRUE_KEYWORD FALSE_KEYWORD NULL_KEYWORD
139 /* Class 'super' accessor. */
140 %token SUPER_KEYWORD
141 /* Properties. */
142 %token CAST_KEYWORD SIZEOF_KEYWORD
143 %token TYPEOF_KEYWORD TYPEID_KEYWORD
144 %token INIT_KEYWORD
145 /* Comparison keywords. */
146 /* Type storage classes. */
147 %token IMMUTABLE_KEYWORD CONST_KEYWORD SHARED_KEYWORD
148 /* Non-scalar type keywords. */
149 %token STRUCT_KEYWORD UNION_KEYWORD
150 %token CLASS_KEYWORD INTERFACE_KEYWORD
151 %token ENUM_KEYWORD TEMPLATE_KEYWORD
152 %token DELEGATE_KEYWORD FUNCTION_KEYWORD
154 %token <sval> DOLLAR_VARIABLE
156 %token <opcode> ASSIGN_MODIFY
158 %left ','
159 %right '=' ASSIGN_MODIFY
160 %right '?'
161 %left OROR
162 %left ANDAND
163 %left '|'
164 %left '^'
165 %left '&'
166 %left EQUAL NOTEQUAL '<' '>' LEQ GEQ
167 %right LSH RSH
168 %left '+' '-'
169 %left '*' '/' '%'
170 %right HATHAT
171 %left IDENTITY NOTIDENTITY
172 %right INCREMENT DECREMENT
173 %right '.' '[' '('
174 %token DOTDOT
179 start :
180 Expression
181 | TypeExp
184 /* Expressions, including the comma operator. */
186 Expression:
187 CommaExpression
190 CommaExpression:
191 AssignExpression
192 | AssignExpression ',' CommaExpression
193 { pstate->wrap2<comma_operation> (); }
196 AssignExpression:
197 ConditionalExpression
198 | ConditionalExpression '=' AssignExpression
199 { pstate->wrap2<assign_operation> (); }
200 | ConditionalExpression ASSIGN_MODIFY AssignExpression
202 operation_up rhs = pstate->pop ();
203 operation_up lhs = pstate->pop ();
204 pstate->push_new<assign_modify_operation>
205 ($2, std::move (lhs), std::move (rhs));
209 ConditionalExpression:
210 OrOrExpression
211 | OrOrExpression '?' Expression ':' ConditionalExpression
213 operation_up last = pstate->pop ();
214 operation_up mid = pstate->pop ();
215 operation_up first = pstate->pop ();
216 pstate->push_new<ternop_cond_operation>
217 (std::move (first), std::move (mid),
218 std::move (last));
222 OrOrExpression:
223 AndAndExpression
224 | OrOrExpression OROR AndAndExpression
225 { pstate->wrap2<logical_or_operation> (); }
228 AndAndExpression:
229 OrExpression
230 | AndAndExpression ANDAND OrExpression
231 { pstate->wrap2<logical_and_operation> (); }
234 OrExpression:
235 XorExpression
236 | OrExpression '|' XorExpression
237 { pstate->wrap2<bitwise_ior_operation> (); }
240 XorExpression:
241 AndExpression
242 | XorExpression '^' AndExpression
243 { pstate->wrap2<bitwise_xor_operation> (); }
246 AndExpression:
247 CmpExpression
248 | AndExpression '&' CmpExpression
249 { pstate->wrap2<bitwise_and_operation> (); }
252 CmpExpression:
253 ShiftExpression
254 | EqualExpression
255 | IdentityExpression
256 | RelExpression
259 EqualExpression:
260 ShiftExpression EQUAL ShiftExpression
261 { pstate->wrap2<equal_operation> (); }
262 | ShiftExpression NOTEQUAL ShiftExpression
263 { pstate->wrap2<notequal_operation> (); }
266 IdentityExpression:
267 ShiftExpression IDENTITY ShiftExpression
268 { pstate->wrap2<equal_operation> (); }
269 | ShiftExpression NOTIDENTITY ShiftExpression
270 { pstate->wrap2<notequal_operation> (); }
273 RelExpression:
274 ShiftExpression '<' ShiftExpression
275 { pstate->wrap2<less_operation> (); }
276 | ShiftExpression LEQ ShiftExpression
277 { pstate->wrap2<leq_operation> (); }
278 | ShiftExpression '>' ShiftExpression
279 { pstate->wrap2<gtr_operation> (); }
280 | ShiftExpression GEQ ShiftExpression
281 { pstate->wrap2<geq_operation> (); }
284 ShiftExpression:
285 AddExpression
286 | ShiftExpression LSH AddExpression
287 { pstate->wrap2<lsh_operation> (); }
288 | ShiftExpression RSH AddExpression
289 { pstate->wrap2<rsh_operation> (); }
292 AddExpression:
293 MulExpression
294 | AddExpression '+' MulExpression
295 { pstate->wrap2<add_operation> (); }
296 | AddExpression '-' MulExpression
297 { pstate->wrap2<sub_operation> (); }
298 | AddExpression '~' MulExpression
299 { pstate->wrap2<concat_operation> (); }
302 MulExpression:
303 UnaryExpression
304 | MulExpression '*' UnaryExpression
305 { pstate->wrap2<mul_operation> (); }
306 | MulExpression '/' UnaryExpression
307 { pstate->wrap2<div_operation> (); }
308 | MulExpression '%' UnaryExpression
309 { pstate->wrap2<rem_operation> (); }
311 UnaryExpression:
312 '&' UnaryExpression
313 { pstate->wrap<unop_addr_operation> (); }
314 | INCREMENT UnaryExpression
315 { pstate->wrap<preinc_operation> (); }
316 | DECREMENT UnaryExpression
317 { pstate->wrap<predec_operation> (); }
318 | '*' UnaryExpression
319 { pstate->wrap<unop_ind_operation> (); }
320 | '-' UnaryExpression
321 { pstate->wrap<unary_neg_operation> (); }
322 | '+' UnaryExpression
323 { pstate->wrap<unary_plus_operation> (); }
324 | '!' UnaryExpression
325 { pstate->wrap<unary_logical_not_operation> (); }
326 | '~' UnaryExpression
327 { pstate->wrap<unary_complement_operation> (); }
328 | TypeExp '.' SIZEOF_KEYWORD
329 { pstate->wrap<unop_sizeof_operation> (); }
330 | CastExpression
331 | PowExpression
334 CastExpression:
335 CAST_KEYWORD '(' TypeExp ')' UnaryExpression
336 { pstate->wrap2<unop_cast_type_operation> (); }
337 /* C style cast is illegal D, but is still recognised in
338 the grammar, so we keep this around for convenience. */
339 | '(' TypeExp ')' UnaryExpression
340 { pstate->wrap2<unop_cast_type_operation> (); }
343 PowExpression:
344 PostfixExpression
345 | PostfixExpression HATHAT UnaryExpression
346 { pstate->wrap2<exp_operation> (); }
349 PostfixExpression:
350 PrimaryExpression
351 | PostfixExpression '.' COMPLETE
353 structop_base_operation *op
354 = new structop_ptr_operation (pstate->pop (), "");
355 pstate->mark_struct_expression (op);
356 pstate->push (operation_up (op));
358 | PostfixExpression '.' IDENTIFIER
360 pstate->push_new<structop_operation>
361 (pstate->pop (), copy_name ($3));
363 | PostfixExpression '.' IDENTIFIER COMPLETE
365 structop_base_operation *op
366 = new structop_operation (pstate->pop (), copy_name ($3));
367 pstate->mark_struct_expression (op);
368 pstate->push (operation_up (op));
370 | PostfixExpression '.' SIZEOF_KEYWORD
371 { pstate->wrap<unop_sizeof_operation> (); }
372 | PostfixExpression INCREMENT
373 { pstate->wrap<postinc_operation> (); }
374 | PostfixExpression DECREMENT
375 { pstate->wrap<postdec_operation> (); }
376 | CallExpression
377 | IndexExpression
378 | SliceExpression
381 ArgumentList:
382 AssignExpression
383 { pstate->arglist_len = 1; }
384 | ArgumentList ',' AssignExpression
385 { pstate->arglist_len++; }
388 ArgumentList_opt:
389 /* EMPTY */
390 { pstate->arglist_len = 0; }
391 | ArgumentList
394 CallExpression:
395 PostfixExpression '('
396 { pstate->start_arglist (); }
397 ArgumentList_opt ')'
399 std::vector<operation_up> args
400 = pstate->pop_vector (pstate->end_arglist ());
401 pstate->push_new<funcall_operation>
402 (pstate->pop (), std::move (args));
406 IndexExpression:
407 PostfixExpression '[' ArgumentList ']'
408 { if (pstate->arglist_len > 0)
410 std::vector<operation_up> args
411 = pstate->pop_vector (pstate->arglist_len);
412 pstate->push_new<multi_subscript_operation>
413 (pstate->pop (), std::move (args));
415 else
416 pstate->wrap2<subscript_operation> ();
420 SliceExpression:
421 PostfixExpression '[' ']'
422 { /* Do nothing. */ }
423 | PostfixExpression '[' AssignExpression DOTDOT AssignExpression ']'
425 operation_up last = pstate->pop ();
426 operation_up mid = pstate->pop ();
427 operation_up first = pstate->pop ();
428 pstate->push_new<ternop_slice_operation>
429 (std::move (first), std::move (mid),
430 std::move (last));
434 PrimaryExpression:
435 '(' Expression ')'
436 { /* Do nothing. */ }
437 | IdentifierExp
438 { struct bound_minimal_symbol msymbol;
439 std::string copy = copy_name ($1);
440 struct field_of_this_result is_a_field_of_this;
441 struct block_symbol sym;
443 /* Handle VAR, which could be local or global. */
444 sym = lookup_symbol (copy.c_str (),
445 pstate->expression_context_block,
446 SEARCH_VFT, &is_a_field_of_this);
447 if (sym.symbol && sym.symbol->aclass () != LOC_TYPEDEF)
449 if (symbol_read_needs_frame (sym.symbol))
450 pstate->block_tracker->update (sym);
451 pstate->push_new<var_value_operation> (sym);
453 else if (is_a_field_of_this.type != NULL)
455 /* It hangs off of `this'. Must not inadvertently convert from a
456 method call to data ref. */
457 pstate->block_tracker->update (sym);
458 operation_up thisop
459 = make_operation<op_this_operation> ();
460 pstate->push_new<structop_ptr_operation>
461 (std::move (thisop), std::move (copy));
463 else
465 /* Lookup foreign name in global static symbols. */
466 msymbol = lookup_bound_minimal_symbol (copy.c_str ());
467 if (msymbol.minsym != NULL)
468 pstate->push_new<var_msym_value_operation> (msymbol);
469 else if (!have_full_symbols (current_program_space)
470 && !have_partial_symbols (current_program_space))
471 error (_("No symbol table is loaded. Use the \"file\" command"));
472 else
473 error (_("No symbol \"%s\" in current context."),
474 copy.c_str ());
477 | TypeExp '.' IdentifierExp
478 { struct type *type = check_typedef ($1);
480 /* Check if the qualified name is in the global
481 context. However if the symbol has not already
482 been resolved, it's not likely to be found. */
483 if (type->code () == TYPE_CODE_MODULE)
485 struct block_symbol sym;
486 const char *type_name = TYPE_SAFE_NAME (type);
487 int type_name_len = strlen (type_name);
488 std::string name
489 = string_printf ("%.*s.%.*s",
490 type_name_len, type_name,
491 $3.length, $3.ptr);
493 sym =
494 lookup_symbol (name.c_str (),
495 (const struct block *) NULL,
496 SEARCH_VFT, NULL);
497 pstate->push_symbol (name.c_str (), sym);
499 else
501 /* Check if the qualified name resolves as a member
502 of an aggregate or an enum type. */
503 if (!type_aggregate_p (type))
504 error (_("`%s' is not defined as an aggregate type."),
505 TYPE_SAFE_NAME (type));
507 pstate->push_new<scope_operation>
508 (type, copy_name ($3));
511 | DOLLAR_VARIABLE
512 { pstate->push_dollar ($1); }
513 | NAME_OR_INT
514 { YYSTYPE val;
515 parse_number (pstate, $1.ptr, $1.length, 0, &val);
516 pstate->push_new<long_const_operation>
517 (val.typed_val_int.type, val.typed_val_int.val); }
518 | NULL_KEYWORD
519 { struct type *type = parse_d_type (pstate)->builtin_void;
520 type = lookup_pointer_type (type);
521 pstate->push_new<long_const_operation> (type, 0); }
522 | TRUE_KEYWORD
523 { pstate->push_new<bool_operation> (true); }
524 | FALSE_KEYWORD
525 { pstate->push_new<bool_operation> (false); }
526 | INTEGER_LITERAL
527 { pstate->push_new<long_const_operation> ($1.type, $1.val); }
528 | FLOAT_LITERAL
530 float_data data;
531 std::copy (std::begin ($1.val), std::end ($1.val),
532 std::begin (data));
533 pstate->push_new<float_const_operation> ($1.type, data);
535 | CHARACTER_LITERAL
536 { struct stoken_vector vec;
537 vec.len = 1;
538 vec.tokens = &$1;
539 pstate->push_c_string (0, &vec); }
540 | StringExp
541 { int i;
542 pstate->push_c_string (0, &$1);
543 for (i = 0; i < $1.len; ++i)
544 free ($1.tokens[i].ptr);
545 free ($1.tokens); }
546 | ArrayLiteral
548 std::vector<operation_up> args
549 = pstate->pop_vector ($1);
550 pstate->push_new<array_operation>
551 (0, $1 - 1, std::move (args));
553 | TYPEOF_KEYWORD '(' Expression ')'
554 { pstate->wrap<typeof_operation> (); }
557 ArrayLiteral:
558 '[' ArgumentList_opt ']'
559 { $$ = pstate->arglist_len; }
562 IdentifierExp:
563 IDENTIFIER
566 StringExp:
567 STRING_LITERAL
568 { /* We copy the string here, and not in the
569 lexer, to guarantee that we do not leak a
570 string. Note that we follow the
571 NUL-termination convention of the
572 lexer. */
573 struct typed_stoken *vec = XNEW (struct typed_stoken);
574 $$.len = 1;
575 $$.tokens = vec;
577 vec->type = $1.type;
578 vec->length = $1.length;
579 vec->ptr = (char *) malloc ($1.length + 1);
580 memcpy (vec->ptr, $1.ptr, $1.length + 1);
582 | StringExp STRING_LITERAL
583 { /* Note that we NUL-terminate here, but just
584 for convenience. */
585 char *p;
586 ++$$.len;
587 $$.tokens
588 = XRESIZEVEC (struct typed_stoken, $$.tokens, $$.len);
590 p = (char *) malloc ($2.length + 1);
591 memcpy (p, $2.ptr, $2.length + 1);
593 $$.tokens[$$.len - 1].type = $2.type;
594 $$.tokens[$$.len - 1].length = $2.length;
595 $$.tokens[$$.len - 1].ptr = p;
599 TypeExp:
600 '(' TypeExp ')'
601 { /* Do nothing. */ }
602 | BasicType
603 { pstate->push_new<type_operation> ($1); }
604 | BasicType BasicType2
605 { $$ = type_stack->follow_types ($1);
606 pstate->push_new<type_operation> ($$);
610 BasicType2:
612 { type_stack->push (tp_pointer); }
613 | '*' BasicType2
614 { type_stack->push (tp_pointer); }
615 | '[' INTEGER_LITERAL ']'
616 { type_stack->push ($2.val);
617 type_stack->push (tp_array); }
618 | '[' INTEGER_LITERAL ']' BasicType2
619 { type_stack->push ($2.val);
620 type_stack->push (tp_array); }
623 BasicType:
624 TYPENAME
625 { $$ = $1.type; }
630 /* Return true if the type is aggregate-like. */
632 static int
633 type_aggregate_p (struct type *type)
635 return (type->code () == TYPE_CODE_STRUCT
636 || type->code () == TYPE_CODE_UNION
637 || type->code () == TYPE_CODE_MODULE
638 || (type->code () == TYPE_CODE_ENUM
639 && type->is_declared_class ()));
642 /* Take care of parsing a number (anything that starts with a digit).
643 Set yylval and return the token type; update lexptr.
644 LEN is the number of characters in it. */
646 /*** Needs some error checking for the float case ***/
648 static int
649 parse_number (struct parser_state *ps, const char *p,
650 int len, int parsed_float, YYSTYPE *putithere)
652 ULONGEST n = 0;
653 ULONGEST prevn = 0;
654 ULONGEST un;
656 int i = 0;
657 int c;
658 int base = input_radix;
659 int unsigned_p = 0;
660 int long_p = 0;
662 /* We have found a "L" or "U" suffix. */
663 int found_suffix = 0;
665 ULONGEST high_bit;
666 struct type *signed_type;
667 struct type *unsigned_type;
669 if (parsed_float)
671 char *s, *sp;
673 /* Strip out all embedded '_' before passing to parse_float. */
674 s = (char *) alloca (len + 1);
675 sp = s;
676 while (len-- > 0)
678 if (*p != '_')
679 *sp++ = *p;
680 p++;
682 *sp = '\0';
683 len = strlen (s);
685 /* Check suffix for `i' , `fi' or `li' (idouble, ifloat or ireal). */
686 if (len >= 1 && tolower (s[len - 1]) == 'i')
688 if (len >= 2 && tolower (s[len - 2]) == 'f')
690 putithere->typed_val_float.type
691 = parse_d_type (ps)->builtin_ifloat;
692 len -= 2;
694 else if (len >= 2 && tolower (s[len - 2]) == 'l')
696 putithere->typed_val_float.type
697 = parse_d_type (ps)->builtin_ireal;
698 len -= 2;
700 else
702 putithere->typed_val_float.type
703 = parse_d_type (ps)->builtin_idouble;
704 len -= 1;
707 /* Check suffix for `f' or `l'' (float or real). */
708 else if (len >= 1 && tolower (s[len - 1]) == 'f')
710 putithere->typed_val_float.type
711 = parse_d_type (ps)->builtin_float;
712 len -= 1;
714 else if (len >= 1 && tolower (s[len - 1]) == 'l')
716 putithere->typed_val_float.type
717 = parse_d_type (ps)->builtin_real;
718 len -= 1;
720 /* Default type if no suffix. */
721 else
723 putithere->typed_val_float.type
724 = parse_d_type (ps)->builtin_double;
727 if (!parse_float (s, len,
728 putithere->typed_val_float.type,
729 putithere->typed_val_float.val))
730 return ERROR;
732 return FLOAT_LITERAL;
735 /* Handle base-switching prefixes 0x, 0b, 0 */
736 if (p[0] == '0')
737 switch (p[1])
739 case 'x':
740 case 'X':
741 if (len >= 3)
743 p += 2;
744 base = 16;
745 len -= 2;
747 break;
749 case 'b':
750 case 'B':
751 if (len >= 3)
753 p += 2;
754 base = 2;
755 len -= 2;
757 break;
759 default:
760 base = 8;
761 break;
764 while (len-- > 0)
766 c = *p++;
767 if (c == '_')
768 continue; /* Ignore embedded '_'. */
769 if (c >= 'A' && c <= 'Z')
770 c += 'a' - 'A';
771 if (c != 'l' && c != 'u')
772 n *= base;
773 if (c >= '0' && c <= '9')
775 if (found_suffix)
776 return ERROR;
777 n += i = c - '0';
779 else
781 if (base > 10 && c >= 'a' && c <= 'f')
783 if (found_suffix)
784 return ERROR;
785 n += i = c - 'a' + 10;
787 else if (c == 'l' && long_p == 0)
789 long_p = 1;
790 found_suffix = 1;
792 else if (c == 'u' && unsigned_p == 0)
794 unsigned_p = 1;
795 found_suffix = 1;
797 else
798 return ERROR; /* Char not a digit */
800 if (i >= base)
801 return ERROR; /* Invalid digit in this base. */
802 /* Portably test for integer overflow. */
803 if (c != 'l' && c != 'u')
805 ULONGEST n2 = prevn * base;
806 if ((n2 / base != prevn) || (n2 + i < prevn))
807 error (_("Numeric constant too large."));
809 prevn = n;
812 /* An integer constant is an int or a long. An L suffix forces it to
813 be long, and a U suffix forces it to be unsigned. To figure out
814 whether it fits, we shift it right and see whether anything remains.
815 Note that we can't shift sizeof (LONGEST) * HOST_CHAR_BIT bits or
816 more in one operation, because many compilers will warn about such a
817 shift (which always produces a zero result). To deal with the case
818 where it is we just always shift the value more than once, with fewer
819 bits each time. */
820 un = (ULONGEST) n >> 2;
821 if (long_p == 0 && (un >> 30) == 0)
823 high_bit = ((ULONGEST) 1) << 31;
824 signed_type = parse_d_type (ps)->builtin_int;
825 /* For decimal notation, keep the sign of the worked out type. */
826 if (base == 10 && !unsigned_p)
827 unsigned_type = parse_d_type (ps)->builtin_long;
828 else
829 unsigned_type = parse_d_type (ps)->builtin_uint;
831 else
833 int shift;
834 if (sizeof (ULONGEST) * HOST_CHAR_BIT < 64)
835 /* A long long does not fit in a LONGEST. */
836 shift = (sizeof (ULONGEST) * HOST_CHAR_BIT - 1);
837 else
838 shift = 63;
839 high_bit = (ULONGEST) 1 << shift;
840 signed_type = parse_d_type (ps)->builtin_long;
841 unsigned_type = parse_d_type (ps)->builtin_ulong;
844 putithere->typed_val_int.val = n;
846 /* If the high bit of the worked out type is set then this number
847 has to be unsigned_type. */
848 if (unsigned_p || (n & high_bit))
849 putithere->typed_val_int.type = unsigned_type;
850 else
851 putithere->typed_val_int.type = signed_type;
853 return INTEGER_LITERAL;
856 /* Temporary obstack used for holding strings. */
857 static struct obstack tempbuf;
858 static int tempbuf_init;
860 /* Parse a string or character literal from TOKPTR. The string or
861 character may be wide or unicode. *OUTPTR is set to just after the
862 end of the literal in the input string. The resulting token is
863 stored in VALUE. This returns a token value, either STRING or
864 CHAR, depending on what was parsed. *HOST_CHARS is set to the
865 number of host characters in the literal. */
867 static int
868 parse_string_or_char (const char *tokptr, const char **outptr,
869 struct typed_stoken *value, int *host_chars)
871 int quote;
873 /* Build the gdb internal form of the input string in tempbuf. Note
874 that the buffer is null byte terminated *only* for the
875 convenience of debugging gdb itself and printing the buffer
876 contents when the buffer contains no embedded nulls. Gdb does
877 not depend upon the buffer being null byte terminated, it uses
878 the length string instead. This allows gdb to handle C strings
879 (as well as strings in other languages) with embedded null
880 bytes */
882 if (!tempbuf_init)
883 tempbuf_init = 1;
884 else
885 obstack_free (&tempbuf, NULL);
886 obstack_init (&tempbuf);
888 /* Skip the quote. */
889 quote = *tokptr;
890 ++tokptr;
892 *host_chars = 0;
894 while (*tokptr)
896 char c = *tokptr;
897 if (c == '\\')
899 ++tokptr;
900 *host_chars += c_parse_escape (&tokptr, &tempbuf);
902 else if (c == quote)
903 break;
904 else
906 obstack_1grow (&tempbuf, c);
907 ++tokptr;
908 /* FIXME: this does the wrong thing with multi-byte host
909 characters. We could use mbrlen here, but that would
910 make "set host-charset" a bit less useful. */
911 ++*host_chars;
915 if (*tokptr != quote)
917 if (quote == '"' || quote == '`')
918 error (_("Unterminated string in expression."));
919 else
920 error (_("Unmatched single quote."));
922 ++tokptr;
924 /* FIXME: should instead use own language string_type enum
925 and handle D-specific string suffixes here. */
926 if (quote == '\'')
927 value->type = C_CHAR;
928 else
929 value->type = C_STRING;
931 value->ptr = (char *) obstack_base (&tempbuf);
932 value->length = obstack_object_size (&tempbuf);
934 *outptr = tokptr;
936 return quote == '\'' ? CHARACTER_LITERAL : STRING_LITERAL;
939 struct d_token
941 const char *oper;
942 int token;
943 enum exp_opcode opcode;
946 static const struct d_token tokentab3[] =
948 {"^^=", ASSIGN_MODIFY, BINOP_EXP},
949 {"<<=", ASSIGN_MODIFY, BINOP_LSH},
950 {">>=", ASSIGN_MODIFY, BINOP_RSH},
953 static const struct d_token tokentab2[] =
955 {"+=", ASSIGN_MODIFY, BINOP_ADD},
956 {"-=", ASSIGN_MODIFY, BINOP_SUB},
957 {"*=", ASSIGN_MODIFY, BINOP_MUL},
958 {"/=", ASSIGN_MODIFY, BINOP_DIV},
959 {"%=", ASSIGN_MODIFY, BINOP_REM},
960 {"|=", ASSIGN_MODIFY, BINOP_BITWISE_IOR},
961 {"&=", ASSIGN_MODIFY, BINOP_BITWISE_AND},
962 {"^=", ASSIGN_MODIFY, BINOP_BITWISE_XOR},
963 {"++", INCREMENT, OP_NULL},
964 {"--", DECREMENT, OP_NULL},
965 {"&&", ANDAND, OP_NULL},
966 {"||", OROR, OP_NULL},
967 {"^^", HATHAT, OP_NULL},
968 {"<<", LSH, OP_NULL},
969 {">>", RSH, OP_NULL},
970 {"==", EQUAL, OP_NULL},
971 {"!=", NOTEQUAL, OP_NULL},
972 {"<=", LEQ, OP_NULL},
973 {">=", GEQ, OP_NULL},
974 {"..", DOTDOT, OP_NULL},
977 /* Identifier-like tokens. */
978 static const struct d_token ident_tokens[] =
980 {"is", IDENTITY, OP_NULL},
981 {"!is", NOTIDENTITY, OP_NULL},
983 {"cast", CAST_KEYWORD, OP_NULL},
984 {"const", CONST_KEYWORD, OP_NULL},
985 {"immutable", IMMUTABLE_KEYWORD, OP_NULL},
986 {"shared", SHARED_KEYWORD, OP_NULL},
987 {"super", SUPER_KEYWORD, OP_NULL},
989 {"null", NULL_KEYWORD, OP_NULL},
990 {"true", TRUE_KEYWORD, OP_NULL},
991 {"false", FALSE_KEYWORD, OP_NULL},
993 {"init", INIT_KEYWORD, OP_NULL},
994 {"sizeof", SIZEOF_KEYWORD, OP_NULL},
995 {"typeof", TYPEOF_KEYWORD, OP_NULL},
996 {"typeid", TYPEID_KEYWORD, OP_NULL},
998 {"delegate", DELEGATE_KEYWORD, OP_NULL},
999 {"function", FUNCTION_KEYWORD, OP_NULL},
1000 {"struct", STRUCT_KEYWORD, OP_NULL},
1001 {"union", UNION_KEYWORD, OP_NULL},
1002 {"class", CLASS_KEYWORD, OP_NULL},
1003 {"interface", INTERFACE_KEYWORD, OP_NULL},
1004 {"enum", ENUM_KEYWORD, OP_NULL},
1005 {"template", TEMPLATE_KEYWORD, OP_NULL},
1008 /* This is set if a NAME token appeared at the very end of the input
1009 string, with no whitespace separating the name from the EOF. This
1010 is used only when parsing to do field name completion. */
1011 static int saw_name_at_eof;
1013 /* This is set if the previously-returned token was a structure operator.
1014 This is used only when parsing to do field name completion. */
1015 static int last_was_structop;
1017 /* Depth of parentheses. */
1018 static int paren_depth;
1020 /* Read one token, getting characters through lexptr. */
1022 static int
1023 lex_one_token (struct parser_state *par_state)
1025 int c;
1026 int namelen;
1027 const char *tokstart;
1028 int saw_structop = last_was_structop;
1030 last_was_structop = 0;
1032 retry:
1034 pstate->prev_lexptr = pstate->lexptr;
1036 tokstart = pstate->lexptr;
1037 /* See if it is a special token of length 3. */
1038 for (const auto &token : tokentab3)
1039 if (strncmp (tokstart, token.oper, 3) == 0)
1041 pstate->lexptr += 3;
1042 yylval.opcode = token.opcode;
1043 return token.token;
1046 /* See if it is a special token of length 2. */
1047 for (const auto &token : tokentab2)
1048 if (strncmp (tokstart, token.oper, 2) == 0)
1050 pstate->lexptr += 2;
1051 yylval.opcode = token.opcode;
1052 return token.token;
1055 switch (c = *tokstart)
1057 case 0:
1058 /* If we're parsing for field name completion, and the previous
1059 token allows such completion, return a COMPLETE token.
1060 Otherwise, we were already scanning the original text, and
1061 we're really done. */
1062 if (saw_name_at_eof)
1064 saw_name_at_eof = 0;
1065 return COMPLETE;
1067 else if (saw_structop)
1068 return COMPLETE;
1069 else
1070 return 0;
1072 case ' ':
1073 case '\t':
1074 case '\n':
1075 pstate->lexptr++;
1076 goto retry;
1078 case '[':
1079 case '(':
1080 paren_depth++;
1081 pstate->lexptr++;
1082 return c;
1084 case ']':
1085 case ')':
1086 if (paren_depth == 0)
1087 return 0;
1088 paren_depth--;
1089 pstate->lexptr++;
1090 return c;
1092 case ',':
1093 if (pstate->comma_terminates && paren_depth == 0)
1094 return 0;
1095 pstate->lexptr++;
1096 return c;
1098 case '.':
1099 /* Might be a floating point number. */
1100 if (pstate->lexptr[1] < '0' || pstate->lexptr[1] > '9')
1102 if (pstate->parse_completion)
1103 last_was_structop = 1;
1104 goto symbol; /* Nope, must be a symbol. */
1106 [[fallthrough]];
1108 case '0':
1109 case '1':
1110 case '2':
1111 case '3':
1112 case '4':
1113 case '5':
1114 case '6':
1115 case '7':
1116 case '8':
1117 case '9':
1119 /* It's a number. */
1120 int got_dot = 0, got_e = 0, toktype;
1121 const char *p = tokstart;
1122 int hex = input_radix > 10;
1124 if (c == '0' && (p[1] == 'x' || p[1] == 'X'))
1126 p += 2;
1127 hex = 1;
1130 for (;; ++p)
1132 /* Hex exponents start with 'p', because 'e' is a valid hex
1133 digit and thus does not indicate a floating point number
1134 when the radix is hex. */
1135 if ((!hex && !got_e && tolower (p[0]) == 'e')
1136 || (hex && !got_e && tolower (p[0] == 'p')))
1137 got_dot = got_e = 1;
1138 /* A '.' always indicates a decimal floating point number
1139 regardless of the radix. If we have a '..' then its the
1140 end of the number and the beginning of a slice. */
1141 else if (!got_dot && (p[0] == '.' && p[1] != '.'))
1142 got_dot = 1;
1143 /* This is the sign of the exponent, not the end of the number. */
1144 else if (got_e && (tolower (p[-1]) == 'e' || tolower (p[-1]) == 'p')
1145 && (*p == '-' || *p == '+'))
1146 continue;
1147 /* We will take any letters or digits, ignoring any embedded '_'.
1148 parse_number will complain if past the radix, or if L or U are
1149 not final. */
1150 else if ((*p < '0' || *p > '9') && (*p != '_')
1151 && ((*p < 'a' || *p > 'z') && (*p < 'A' || *p > 'Z')))
1152 break;
1155 toktype = parse_number (par_state, tokstart, p - tokstart,
1156 got_dot|got_e, &yylval);
1157 if (toktype == ERROR)
1158 error (_("Invalid number \"%.*s\"."), (int) (p - tokstart),
1159 tokstart);
1160 pstate->lexptr = p;
1161 return toktype;
1164 case '@':
1166 const char *p = &tokstart[1];
1167 size_t len = strlen ("entry");
1169 while (isspace (*p))
1170 p++;
1171 if (strncmp (p, "entry", len) == 0 && !isalnum (p[len])
1172 && p[len] != '_')
1174 pstate->lexptr = &p[len];
1175 return ENTRY;
1178 [[fallthrough]];
1179 case '+':
1180 case '-':
1181 case '*':
1182 case '/':
1183 case '%':
1184 case '|':
1185 case '&':
1186 case '^':
1187 case '~':
1188 case '!':
1189 case '<':
1190 case '>':
1191 case '?':
1192 case ':':
1193 case '=':
1194 case '{':
1195 case '}':
1196 symbol:
1197 pstate->lexptr++;
1198 return c;
1200 case '\'':
1201 case '"':
1202 case '`':
1204 int host_len;
1205 int result = parse_string_or_char (tokstart, &pstate->lexptr,
1206 &yylval.tsval, &host_len);
1207 if (result == CHARACTER_LITERAL)
1209 if (host_len == 0)
1210 error (_("Empty character constant."));
1211 else if (host_len > 2 && c == '\'')
1213 ++tokstart;
1214 namelen = pstate->lexptr - tokstart - 1;
1215 goto tryname;
1217 else if (host_len > 1)
1218 error (_("Invalid character constant."));
1220 return result;
1224 if (!(c == '_' || c == '$'
1225 || (c >= 'a' && c <= 'z') || (c >= 'A' && c <= 'Z')))
1226 /* We must have come across a bad character (e.g. ';'). */
1227 error (_("Invalid character '%c' in expression"), c);
1229 /* It's a name. See how long it is. */
1230 namelen = 0;
1231 for (c = tokstart[namelen];
1232 (c == '_' || c == '$' || (c >= '0' && c <= '9')
1233 || (c >= 'a' && c <= 'z') || (c >= 'A' && c <= 'Z'));)
1234 c = tokstart[++namelen];
1236 /* The token "if" terminates the expression and is NOT
1237 removed from the input stream. */
1238 if (namelen == 2 && tokstart[0] == 'i' && tokstart[1] == 'f')
1239 return 0;
1241 /* For the same reason (breakpoint conditions), "thread N"
1242 terminates the expression. "thread" could be an identifier, but
1243 an identifier is never followed by a number without intervening
1244 punctuation. "task" is similar. Handle abbreviations of these,
1245 similarly to breakpoint.c:find_condition_and_thread. */
1246 if (namelen >= 1
1247 && (strncmp (tokstart, "thread", namelen) == 0
1248 || strncmp (tokstart, "task", namelen) == 0)
1249 && (tokstart[namelen] == ' ' || tokstart[namelen] == '\t'))
1251 const char *p = tokstart + namelen + 1;
1253 while (*p == ' ' || *p == '\t')
1254 p++;
1255 if (*p >= '0' && *p <= '9')
1256 return 0;
1259 pstate->lexptr += namelen;
1261 tryname:
1263 yylval.sval.ptr = tokstart;
1264 yylval.sval.length = namelen;
1266 /* Catch specific keywords. */
1267 std::string copy = copy_name (yylval.sval);
1268 for (const auto &token : ident_tokens)
1269 if (copy == token.oper)
1271 /* It is ok to always set this, even though we don't always
1272 strictly need to. */
1273 yylval.opcode = token.opcode;
1274 return token.token;
1277 if (*tokstart == '$')
1278 return DOLLAR_VARIABLE;
1280 yylval.tsym.type
1281 = language_lookup_primitive_type (par_state->language (),
1282 par_state->gdbarch (), copy.c_str ());
1283 if (yylval.tsym.type != NULL)
1284 return TYPENAME;
1286 /* Input names that aren't symbols but ARE valid hex numbers,
1287 when the input radix permits them, can be names or numbers
1288 depending on the parse. Note we support radixes > 16 here. */
1289 if ((tokstart[0] >= 'a' && tokstart[0] < 'a' + input_radix - 10)
1290 || (tokstart[0] >= 'A' && tokstart[0] < 'A' + input_radix - 10))
1292 YYSTYPE newlval; /* Its value is ignored. */
1293 int hextype = parse_number (par_state, tokstart, namelen, 0, &newlval);
1294 if (hextype == INTEGER_LITERAL)
1295 return NAME_OR_INT;
1298 if (pstate->parse_completion && *pstate->lexptr == '\0')
1299 saw_name_at_eof = 1;
1301 return IDENTIFIER;
1304 /* An object of this type is pushed on a FIFO by the "outer" lexer. */
1305 struct d_token_and_value
1307 int token;
1308 YYSTYPE value;
1312 /* A FIFO of tokens that have been read but not yet returned to the
1313 parser. */
1314 static std::vector<d_token_and_value> token_fifo;
1316 /* Non-zero if the lexer should return tokens from the FIFO. */
1317 static int popping;
1319 /* Temporary storage for yylex; this holds symbol names as they are
1320 built up. */
1321 static auto_obstack name_obstack;
1323 /* Classify an IDENTIFIER token. The contents of the token are in `yylval'.
1324 Updates yylval and returns the new token type. BLOCK is the block
1325 in which lookups start; this can be NULL to mean the global scope. */
1327 static int
1328 classify_name (struct parser_state *par_state, const struct block *block)
1330 struct block_symbol sym;
1331 struct field_of_this_result is_a_field_of_this;
1333 std::string copy = copy_name (yylval.sval);
1335 sym = lookup_symbol (copy.c_str (), block, SEARCH_VFT, &is_a_field_of_this);
1336 if (sym.symbol && sym.symbol->aclass () == LOC_TYPEDEF)
1338 yylval.tsym.type = sym.symbol->type ();
1339 return TYPENAME;
1341 else if (sym.symbol == NULL)
1343 /* Look-up first for a module name, then a type. */
1344 sym = lookup_symbol (copy.c_str (), block, SEARCH_MODULE_DOMAIN,
1345 nullptr);
1346 if (sym.symbol == NULL)
1347 sym = lookup_symbol (copy.c_str (), block, SEARCH_STRUCT_DOMAIN,
1348 nullptr);
1350 if (sym.symbol != NULL)
1352 yylval.tsym.type = sym.symbol->type ();
1353 return TYPENAME;
1356 return UNKNOWN_NAME;
1359 return IDENTIFIER;
1362 /* Like classify_name, but used by the inner loop of the lexer, when a
1363 name might have already been seen. CONTEXT is the context type, or
1364 NULL if this is the first component of a name. */
1366 static int
1367 classify_inner_name (struct parser_state *par_state,
1368 const struct block *block, struct type *context)
1370 struct type *type;
1372 if (context == NULL)
1373 return classify_name (par_state, block);
1375 type = check_typedef (context);
1376 if (!type_aggregate_p (type))
1377 return ERROR;
1379 std::string copy = copy_name (yylval.ssym.stoken);
1380 yylval.ssym.sym = d_lookup_nested_symbol (type, copy.c_str (), block);
1382 if (yylval.ssym.sym.symbol == NULL)
1383 return ERROR;
1385 if (yylval.ssym.sym.symbol->aclass () == LOC_TYPEDEF)
1387 yylval.tsym.type = yylval.ssym.sym.symbol->type ();
1388 return TYPENAME;
1391 return IDENTIFIER;
1394 /* The outer level of a two-level lexer. This calls the inner lexer
1395 to return tokens. It then either returns these tokens, or
1396 aggregates them into a larger token. This lets us work around a
1397 problem in our parsing approach, where the parser could not
1398 distinguish between qualified names and qualified types at the
1399 right point. */
1401 static int
1402 yylex (void)
1404 d_token_and_value current;
1405 int last_was_dot;
1406 struct type *context_type = NULL;
1407 int last_to_examine, next_to_examine, checkpoint;
1408 const struct block *search_block;
1410 if (popping && !token_fifo.empty ())
1411 goto do_pop;
1412 popping = 0;
1414 /* Read the first token and decide what to do. */
1415 current.token = lex_one_token (pstate);
1416 if (current.token != IDENTIFIER && current.token != '.')
1417 return current.token;
1419 /* Read any sequence of alternating "." and identifier tokens into
1420 the token FIFO. */
1421 current.value = yylval;
1422 token_fifo.push_back (current);
1423 last_was_dot = current.token == '.';
1425 while (1)
1427 current.token = lex_one_token (pstate);
1428 current.value = yylval;
1429 token_fifo.push_back (current);
1431 if ((last_was_dot && current.token != IDENTIFIER)
1432 || (!last_was_dot && current.token != '.'))
1433 break;
1435 last_was_dot = !last_was_dot;
1437 popping = 1;
1439 /* We always read one extra token, so compute the number of tokens
1440 to examine accordingly. */
1441 last_to_examine = token_fifo.size () - 2;
1442 next_to_examine = 0;
1444 current = token_fifo[next_to_examine];
1445 ++next_to_examine;
1447 /* If we are not dealing with a typename, now is the time to find out. */
1448 if (current.token == IDENTIFIER)
1450 yylval = current.value;
1451 current.token = classify_name (pstate, pstate->expression_context_block);
1452 current.value = yylval;
1455 /* If the IDENTIFIER is not known, it could be a package symbol,
1456 first try building up a name until we find the qualified module. */
1457 if (current.token == UNKNOWN_NAME)
1459 name_obstack.clear ();
1460 obstack_grow (&name_obstack, current.value.sval.ptr,
1461 current.value.sval.length);
1463 last_was_dot = 0;
1465 while (next_to_examine <= last_to_examine)
1467 d_token_and_value next;
1469 next = token_fifo[next_to_examine];
1470 ++next_to_examine;
1472 if (next.token == IDENTIFIER && last_was_dot)
1474 /* Update the partial name we are constructing. */
1475 obstack_grow_str (&name_obstack, ".");
1476 obstack_grow (&name_obstack, next.value.sval.ptr,
1477 next.value.sval.length);
1479 yylval.sval.ptr = (char *) obstack_base (&name_obstack);
1480 yylval.sval.length = obstack_object_size (&name_obstack);
1482 current.token = classify_name (pstate,
1483 pstate->expression_context_block);
1484 current.value = yylval;
1486 /* We keep going until we find a TYPENAME. */
1487 if (current.token == TYPENAME)
1489 /* Install it as the first token in the FIFO. */
1490 token_fifo[0] = current;
1491 token_fifo.erase (token_fifo.begin () + 1,
1492 token_fifo.begin () + next_to_examine);
1493 break;
1496 else if (next.token == '.' && !last_was_dot)
1497 last_was_dot = 1;
1498 else
1500 /* We've reached the end of the name. */
1501 break;
1505 /* Reset our current token back to the start, if we found nothing
1506 this means that we will just jump to do pop. */
1507 current = token_fifo[0];
1508 next_to_examine = 1;
1510 if (current.token != TYPENAME && current.token != '.')
1511 goto do_pop;
1513 name_obstack.clear ();
1514 checkpoint = 0;
1515 if (current.token == '.')
1516 search_block = NULL;
1517 else
1519 gdb_assert (current.token == TYPENAME);
1520 search_block = pstate->expression_context_block;
1521 obstack_grow (&name_obstack, current.value.sval.ptr,
1522 current.value.sval.length);
1523 context_type = current.value.tsym.type;
1524 checkpoint = 1;
1527 last_was_dot = current.token == '.';
1529 while (next_to_examine <= last_to_examine)
1531 d_token_and_value next;
1533 next = token_fifo[next_to_examine];
1534 ++next_to_examine;
1536 if (next.token == IDENTIFIER && last_was_dot)
1538 int classification;
1540 yylval = next.value;
1541 classification = classify_inner_name (pstate, search_block,
1542 context_type);
1543 /* We keep going until we either run out of names, or until
1544 we have a qualified name which is not a type. */
1545 if (classification != TYPENAME && classification != IDENTIFIER)
1546 break;
1548 /* Accept up to this token. */
1549 checkpoint = next_to_examine;
1551 /* Update the partial name we are constructing. */
1552 if (context_type != NULL)
1554 /* We don't want to put a leading "." into the name. */
1555 obstack_grow_str (&name_obstack, ".");
1557 obstack_grow (&name_obstack, next.value.sval.ptr,
1558 next.value.sval.length);
1560 yylval.sval.ptr = (char *) obstack_base (&name_obstack);
1561 yylval.sval.length = obstack_object_size (&name_obstack);
1562 current.value = yylval;
1563 current.token = classification;
1565 last_was_dot = 0;
1567 if (classification == IDENTIFIER)
1568 break;
1570 context_type = yylval.tsym.type;
1572 else if (next.token == '.' && !last_was_dot)
1573 last_was_dot = 1;
1574 else
1576 /* We've reached the end of the name. */
1577 break;
1581 /* If we have a replacement token, install it as the first token in
1582 the FIFO, and delete the other constituent tokens. */
1583 if (checkpoint > 0)
1585 token_fifo[0] = current;
1586 if (checkpoint > 1)
1587 token_fifo.erase (token_fifo.begin () + 1,
1588 token_fifo.begin () + checkpoint);
1591 do_pop:
1592 current = token_fifo[0];
1593 token_fifo.erase (token_fifo.begin ());
1594 yylval = current.value;
1595 return current.token;
1599 d_parse (struct parser_state *par_state)
1601 /* Setting up the parser state. */
1602 scoped_restore pstate_restore = make_scoped_restore (&pstate);
1603 gdb_assert (par_state != NULL);
1604 pstate = par_state;
1606 scoped_restore restore_yydebug = make_scoped_restore (&yydebug,
1607 par_state->debug);
1609 struct type_stack stack;
1610 scoped_restore restore_type_stack = make_scoped_restore (&type_stack,
1611 &stack);
1613 /* Initialize some state used by the lexer. */
1614 last_was_structop = 0;
1615 saw_name_at_eof = 0;
1616 paren_depth = 0;
1618 token_fifo.clear ();
1619 popping = 0;
1620 name_obstack.clear ();
1622 int result = yyparse ();
1623 if (!result)
1624 pstate->set_operation (pstate->pop ());
1625 return result;
1628 static void
1629 yyerror (const char *msg)
1631 pstate->parse_error (msg);