Automatic date update in version.in
[binutils-gdb.git] / gdb / d-exp.y
blobb2adad24d1a924464f4bbf255397f28ca943dad5
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 () && !have_partial_symbols ())
470 error (_("No symbol table is loaded. Use the \"file\" command"));
471 else
472 error (_("No symbol \"%s\" in current context."),
473 copy.c_str ());
476 | TypeExp '.' IdentifierExp
477 { struct type *type = check_typedef ($1);
479 /* Check if the qualified name is in the global
480 context. However if the symbol has not already
481 been resolved, it's not likely to be found. */
482 if (type->code () == TYPE_CODE_MODULE)
484 struct block_symbol sym;
485 const char *type_name = TYPE_SAFE_NAME (type);
486 int type_name_len = strlen (type_name);
487 std::string name
488 = string_printf ("%.*s.%.*s",
489 type_name_len, type_name,
490 $3.length, $3.ptr);
492 sym =
493 lookup_symbol (name.c_str (),
494 (const struct block *) NULL,
495 SEARCH_VFT, NULL);
496 pstate->push_symbol (name.c_str (), sym);
498 else
500 /* Check if the qualified name resolves as a member
501 of an aggregate or an enum type. */
502 if (!type_aggregate_p (type))
503 error (_("`%s' is not defined as an aggregate type."),
504 TYPE_SAFE_NAME (type));
506 pstate->push_new<scope_operation>
507 (type, copy_name ($3));
510 | DOLLAR_VARIABLE
511 { pstate->push_dollar ($1); }
512 | NAME_OR_INT
513 { YYSTYPE val;
514 parse_number (pstate, $1.ptr, $1.length, 0, &val);
515 pstate->push_new<long_const_operation>
516 (val.typed_val_int.type, val.typed_val_int.val); }
517 | NULL_KEYWORD
518 { struct type *type = parse_d_type (pstate)->builtin_void;
519 type = lookup_pointer_type (type);
520 pstate->push_new<long_const_operation> (type, 0); }
521 | TRUE_KEYWORD
522 { pstate->push_new<bool_operation> (true); }
523 | FALSE_KEYWORD
524 { pstate->push_new<bool_operation> (false); }
525 | INTEGER_LITERAL
526 { pstate->push_new<long_const_operation> ($1.type, $1.val); }
527 | FLOAT_LITERAL
529 float_data data;
530 std::copy (std::begin ($1.val), std::end ($1.val),
531 std::begin (data));
532 pstate->push_new<float_const_operation> ($1.type, data);
534 | CHARACTER_LITERAL
535 { struct stoken_vector vec;
536 vec.len = 1;
537 vec.tokens = &$1;
538 pstate->push_c_string (0, &vec); }
539 | StringExp
540 { int i;
541 pstate->push_c_string (0, &$1);
542 for (i = 0; i < $1.len; ++i)
543 free ($1.tokens[i].ptr);
544 free ($1.tokens); }
545 | ArrayLiteral
547 std::vector<operation_up> args
548 = pstate->pop_vector ($1);
549 pstate->push_new<array_operation>
550 (0, $1 - 1, std::move (args));
552 | TYPEOF_KEYWORD '(' Expression ')'
553 { pstate->wrap<typeof_operation> (); }
556 ArrayLiteral:
557 '[' ArgumentList_opt ']'
558 { $$ = pstate->arglist_len; }
561 IdentifierExp:
562 IDENTIFIER
565 StringExp:
566 STRING_LITERAL
567 { /* We copy the string here, and not in the
568 lexer, to guarantee that we do not leak a
569 string. Note that we follow the
570 NUL-termination convention of the
571 lexer. */
572 struct typed_stoken *vec = XNEW (struct typed_stoken);
573 $$.len = 1;
574 $$.tokens = vec;
576 vec->type = $1.type;
577 vec->length = $1.length;
578 vec->ptr = (char *) malloc ($1.length + 1);
579 memcpy (vec->ptr, $1.ptr, $1.length + 1);
581 | StringExp STRING_LITERAL
582 { /* Note that we NUL-terminate here, but just
583 for convenience. */
584 char *p;
585 ++$$.len;
586 $$.tokens
587 = XRESIZEVEC (struct typed_stoken, $$.tokens, $$.len);
589 p = (char *) malloc ($2.length + 1);
590 memcpy (p, $2.ptr, $2.length + 1);
592 $$.tokens[$$.len - 1].type = $2.type;
593 $$.tokens[$$.len - 1].length = $2.length;
594 $$.tokens[$$.len - 1].ptr = p;
598 TypeExp:
599 '(' TypeExp ')'
600 { /* Do nothing. */ }
601 | BasicType
602 { pstate->push_new<type_operation> ($1); }
603 | BasicType BasicType2
604 { $$ = type_stack->follow_types ($1);
605 pstate->push_new<type_operation> ($$);
609 BasicType2:
611 { type_stack->push (tp_pointer); }
612 | '*' BasicType2
613 { type_stack->push (tp_pointer); }
614 | '[' INTEGER_LITERAL ']'
615 { type_stack->push ($2.val);
616 type_stack->push (tp_array); }
617 | '[' INTEGER_LITERAL ']' BasicType2
618 { type_stack->push ($2.val);
619 type_stack->push (tp_array); }
622 BasicType:
623 TYPENAME
624 { $$ = $1.type; }
629 /* Return true if the type is aggregate-like. */
631 static int
632 type_aggregate_p (struct type *type)
634 return (type->code () == TYPE_CODE_STRUCT
635 || type->code () == TYPE_CODE_UNION
636 || type->code () == TYPE_CODE_MODULE
637 || (type->code () == TYPE_CODE_ENUM
638 && type->is_declared_class ()));
641 /* Take care of parsing a number (anything that starts with a digit).
642 Set yylval and return the token type; update lexptr.
643 LEN is the number of characters in it. */
645 /*** Needs some error checking for the float case ***/
647 static int
648 parse_number (struct parser_state *ps, const char *p,
649 int len, int parsed_float, YYSTYPE *putithere)
651 ULONGEST n = 0;
652 ULONGEST prevn = 0;
653 ULONGEST un;
655 int i = 0;
656 int c;
657 int base = input_radix;
658 int unsigned_p = 0;
659 int long_p = 0;
661 /* We have found a "L" or "U" suffix. */
662 int found_suffix = 0;
664 ULONGEST high_bit;
665 struct type *signed_type;
666 struct type *unsigned_type;
668 if (parsed_float)
670 char *s, *sp;
672 /* Strip out all embedded '_' before passing to parse_float. */
673 s = (char *) alloca (len + 1);
674 sp = s;
675 while (len-- > 0)
677 if (*p != '_')
678 *sp++ = *p;
679 p++;
681 *sp = '\0';
682 len = strlen (s);
684 /* Check suffix for `i' , `fi' or `li' (idouble, ifloat or ireal). */
685 if (len >= 1 && tolower (s[len - 1]) == 'i')
687 if (len >= 2 && tolower (s[len - 2]) == 'f')
689 putithere->typed_val_float.type
690 = parse_d_type (ps)->builtin_ifloat;
691 len -= 2;
693 else if (len >= 2 && tolower (s[len - 2]) == 'l')
695 putithere->typed_val_float.type
696 = parse_d_type (ps)->builtin_ireal;
697 len -= 2;
699 else
701 putithere->typed_val_float.type
702 = parse_d_type (ps)->builtin_idouble;
703 len -= 1;
706 /* Check suffix for `f' or `l'' (float or real). */
707 else if (len >= 1 && tolower (s[len - 1]) == 'f')
709 putithere->typed_val_float.type
710 = parse_d_type (ps)->builtin_float;
711 len -= 1;
713 else if (len >= 1 && tolower (s[len - 1]) == 'l')
715 putithere->typed_val_float.type
716 = parse_d_type (ps)->builtin_real;
717 len -= 1;
719 /* Default type if no suffix. */
720 else
722 putithere->typed_val_float.type
723 = parse_d_type (ps)->builtin_double;
726 if (!parse_float (s, len,
727 putithere->typed_val_float.type,
728 putithere->typed_val_float.val))
729 return ERROR;
731 return FLOAT_LITERAL;
734 /* Handle base-switching prefixes 0x, 0b, 0 */
735 if (p[0] == '0')
736 switch (p[1])
738 case 'x':
739 case 'X':
740 if (len >= 3)
742 p += 2;
743 base = 16;
744 len -= 2;
746 break;
748 case 'b':
749 case 'B':
750 if (len >= 3)
752 p += 2;
753 base = 2;
754 len -= 2;
756 break;
758 default:
759 base = 8;
760 break;
763 while (len-- > 0)
765 c = *p++;
766 if (c == '_')
767 continue; /* Ignore embedded '_'. */
768 if (c >= 'A' && c <= 'Z')
769 c += 'a' - 'A';
770 if (c != 'l' && c != 'u')
771 n *= base;
772 if (c >= '0' && c <= '9')
774 if (found_suffix)
775 return ERROR;
776 n += i = c - '0';
778 else
780 if (base > 10 && c >= 'a' && c <= 'f')
782 if (found_suffix)
783 return ERROR;
784 n += i = c - 'a' + 10;
786 else if (c == 'l' && long_p == 0)
788 long_p = 1;
789 found_suffix = 1;
791 else if (c == 'u' && unsigned_p == 0)
793 unsigned_p = 1;
794 found_suffix = 1;
796 else
797 return ERROR; /* Char not a digit */
799 if (i >= base)
800 return ERROR; /* Invalid digit in this base. */
801 /* Portably test for integer overflow. */
802 if (c != 'l' && c != 'u')
804 ULONGEST n2 = prevn * base;
805 if ((n2 / base != prevn) || (n2 + i < prevn))
806 error (_("Numeric constant too large."));
808 prevn = n;
811 /* An integer constant is an int or a long. An L suffix forces it to
812 be long, and a U suffix forces it to be unsigned. To figure out
813 whether it fits, we shift it right and see whether anything remains.
814 Note that we can't shift sizeof (LONGEST) * HOST_CHAR_BIT bits or
815 more in one operation, because many compilers will warn about such a
816 shift (which always produces a zero result). To deal with the case
817 where it is we just always shift the value more than once, with fewer
818 bits each time. */
819 un = (ULONGEST) n >> 2;
820 if (long_p == 0 && (un >> 30) == 0)
822 high_bit = ((ULONGEST) 1) << 31;
823 signed_type = parse_d_type (ps)->builtin_int;
824 /* For decimal notation, keep the sign of the worked out type. */
825 if (base == 10 && !unsigned_p)
826 unsigned_type = parse_d_type (ps)->builtin_long;
827 else
828 unsigned_type = parse_d_type (ps)->builtin_uint;
830 else
832 int shift;
833 if (sizeof (ULONGEST) * HOST_CHAR_BIT < 64)
834 /* A long long does not fit in a LONGEST. */
835 shift = (sizeof (ULONGEST) * HOST_CHAR_BIT - 1);
836 else
837 shift = 63;
838 high_bit = (ULONGEST) 1 << shift;
839 signed_type = parse_d_type (ps)->builtin_long;
840 unsigned_type = parse_d_type (ps)->builtin_ulong;
843 putithere->typed_val_int.val = n;
845 /* If the high bit of the worked out type is set then this number
846 has to be unsigned_type. */
847 if (unsigned_p || (n & high_bit))
848 putithere->typed_val_int.type = unsigned_type;
849 else
850 putithere->typed_val_int.type = signed_type;
852 return INTEGER_LITERAL;
855 /* Temporary obstack used for holding strings. */
856 static struct obstack tempbuf;
857 static int tempbuf_init;
859 /* Parse a string or character literal from TOKPTR. The string or
860 character may be wide or unicode. *OUTPTR is set to just after the
861 end of the literal in the input string. The resulting token is
862 stored in VALUE. This returns a token value, either STRING or
863 CHAR, depending on what was parsed. *HOST_CHARS is set to the
864 number of host characters in the literal. */
866 static int
867 parse_string_or_char (const char *tokptr, const char **outptr,
868 struct typed_stoken *value, int *host_chars)
870 int quote;
872 /* Build the gdb internal form of the input string in tempbuf. Note
873 that the buffer is null byte terminated *only* for the
874 convenience of debugging gdb itself and printing the buffer
875 contents when the buffer contains no embedded nulls. Gdb does
876 not depend upon the buffer being null byte terminated, it uses
877 the length string instead. This allows gdb to handle C strings
878 (as well as strings in other languages) with embedded null
879 bytes */
881 if (!tempbuf_init)
882 tempbuf_init = 1;
883 else
884 obstack_free (&tempbuf, NULL);
885 obstack_init (&tempbuf);
887 /* Skip the quote. */
888 quote = *tokptr;
889 ++tokptr;
891 *host_chars = 0;
893 while (*tokptr)
895 char c = *tokptr;
896 if (c == '\\')
898 ++tokptr;
899 *host_chars += c_parse_escape (&tokptr, &tempbuf);
901 else if (c == quote)
902 break;
903 else
905 obstack_1grow (&tempbuf, c);
906 ++tokptr;
907 /* FIXME: this does the wrong thing with multi-byte host
908 characters. We could use mbrlen here, but that would
909 make "set host-charset" a bit less useful. */
910 ++*host_chars;
914 if (*tokptr != quote)
916 if (quote == '"' || quote == '`')
917 error (_("Unterminated string in expression."));
918 else
919 error (_("Unmatched single quote."));
921 ++tokptr;
923 /* FIXME: should instead use own language string_type enum
924 and handle D-specific string suffixes here. */
925 if (quote == '\'')
926 value->type = C_CHAR;
927 else
928 value->type = C_STRING;
930 value->ptr = (char *) obstack_base (&tempbuf);
931 value->length = obstack_object_size (&tempbuf);
933 *outptr = tokptr;
935 return quote == '\'' ? CHARACTER_LITERAL : STRING_LITERAL;
938 struct d_token
940 const char *oper;
941 int token;
942 enum exp_opcode opcode;
945 static const struct d_token tokentab3[] =
947 {"^^=", ASSIGN_MODIFY, BINOP_EXP},
948 {"<<=", ASSIGN_MODIFY, BINOP_LSH},
949 {">>=", ASSIGN_MODIFY, BINOP_RSH},
952 static const struct d_token tokentab2[] =
954 {"+=", ASSIGN_MODIFY, BINOP_ADD},
955 {"-=", ASSIGN_MODIFY, BINOP_SUB},
956 {"*=", ASSIGN_MODIFY, BINOP_MUL},
957 {"/=", ASSIGN_MODIFY, BINOP_DIV},
958 {"%=", ASSIGN_MODIFY, BINOP_REM},
959 {"|=", ASSIGN_MODIFY, BINOP_BITWISE_IOR},
960 {"&=", ASSIGN_MODIFY, BINOP_BITWISE_AND},
961 {"^=", ASSIGN_MODIFY, BINOP_BITWISE_XOR},
962 {"++", INCREMENT, OP_NULL},
963 {"--", DECREMENT, OP_NULL},
964 {"&&", ANDAND, OP_NULL},
965 {"||", OROR, OP_NULL},
966 {"^^", HATHAT, OP_NULL},
967 {"<<", LSH, OP_NULL},
968 {">>", RSH, OP_NULL},
969 {"==", EQUAL, OP_NULL},
970 {"!=", NOTEQUAL, OP_NULL},
971 {"<=", LEQ, OP_NULL},
972 {">=", GEQ, OP_NULL},
973 {"..", DOTDOT, OP_NULL},
976 /* Identifier-like tokens. */
977 static const struct d_token ident_tokens[] =
979 {"is", IDENTITY, OP_NULL},
980 {"!is", NOTIDENTITY, OP_NULL},
982 {"cast", CAST_KEYWORD, OP_NULL},
983 {"const", CONST_KEYWORD, OP_NULL},
984 {"immutable", IMMUTABLE_KEYWORD, OP_NULL},
985 {"shared", SHARED_KEYWORD, OP_NULL},
986 {"super", SUPER_KEYWORD, OP_NULL},
988 {"null", NULL_KEYWORD, OP_NULL},
989 {"true", TRUE_KEYWORD, OP_NULL},
990 {"false", FALSE_KEYWORD, OP_NULL},
992 {"init", INIT_KEYWORD, OP_NULL},
993 {"sizeof", SIZEOF_KEYWORD, OP_NULL},
994 {"typeof", TYPEOF_KEYWORD, OP_NULL},
995 {"typeid", TYPEID_KEYWORD, OP_NULL},
997 {"delegate", DELEGATE_KEYWORD, OP_NULL},
998 {"function", FUNCTION_KEYWORD, OP_NULL},
999 {"struct", STRUCT_KEYWORD, OP_NULL},
1000 {"union", UNION_KEYWORD, OP_NULL},
1001 {"class", CLASS_KEYWORD, OP_NULL},
1002 {"interface", INTERFACE_KEYWORD, OP_NULL},
1003 {"enum", ENUM_KEYWORD, OP_NULL},
1004 {"template", TEMPLATE_KEYWORD, OP_NULL},
1007 /* This is set if a NAME token appeared at the very end of the input
1008 string, with no whitespace separating the name from the EOF. This
1009 is used only when parsing to do field name completion. */
1010 static int saw_name_at_eof;
1012 /* This is set if the previously-returned token was a structure operator.
1013 This is used only when parsing to do field name completion. */
1014 static int last_was_structop;
1016 /* Depth of parentheses. */
1017 static int paren_depth;
1019 /* Read one token, getting characters through lexptr. */
1021 static int
1022 lex_one_token (struct parser_state *par_state)
1024 int c;
1025 int namelen;
1026 const char *tokstart;
1027 int saw_structop = last_was_structop;
1029 last_was_structop = 0;
1031 retry:
1033 pstate->prev_lexptr = pstate->lexptr;
1035 tokstart = pstate->lexptr;
1036 /* See if it is a special token of length 3. */
1037 for (const auto &token : tokentab3)
1038 if (strncmp (tokstart, token.oper, 3) == 0)
1040 pstate->lexptr += 3;
1041 yylval.opcode = token.opcode;
1042 return token.token;
1045 /* See if it is a special token of length 2. */
1046 for (const auto &token : tokentab2)
1047 if (strncmp (tokstart, token.oper, 2) == 0)
1049 pstate->lexptr += 2;
1050 yylval.opcode = token.opcode;
1051 return token.token;
1054 switch (c = *tokstart)
1056 case 0:
1057 /* If we're parsing for field name completion, and the previous
1058 token allows such completion, return a COMPLETE token.
1059 Otherwise, we were already scanning the original text, and
1060 we're really done. */
1061 if (saw_name_at_eof)
1063 saw_name_at_eof = 0;
1064 return COMPLETE;
1066 else if (saw_structop)
1067 return COMPLETE;
1068 else
1069 return 0;
1071 case ' ':
1072 case '\t':
1073 case '\n':
1074 pstate->lexptr++;
1075 goto retry;
1077 case '[':
1078 case '(':
1079 paren_depth++;
1080 pstate->lexptr++;
1081 return c;
1083 case ']':
1084 case ')':
1085 if (paren_depth == 0)
1086 return 0;
1087 paren_depth--;
1088 pstate->lexptr++;
1089 return c;
1091 case ',':
1092 if (pstate->comma_terminates && paren_depth == 0)
1093 return 0;
1094 pstate->lexptr++;
1095 return c;
1097 case '.':
1098 /* Might be a floating point number. */
1099 if (pstate->lexptr[1] < '0' || pstate->lexptr[1] > '9')
1101 if (pstate->parse_completion)
1102 last_was_structop = 1;
1103 goto symbol; /* Nope, must be a symbol. */
1105 [[fallthrough]];
1107 case '0':
1108 case '1':
1109 case '2':
1110 case '3':
1111 case '4':
1112 case '5':
1113 case '6':
1114 case '7':
1115 case '8':
1116 case '9':
1118 /* It's a number. */
1119 int got_dot = 0, got_e = 0, toktype;
1120 const char *p = tokstart;
1121 int hex = input_radix > 10;
1123 if (c == '0' && (p[1] == 'x' || p[1] == 'X'))
1125 p += 2;
1126 hex = 1;
1129 for (;; ++p)
1131 /* Hex exponents start with 'p', because 'e' is a valid hex
1132 digit and thus does not indicate a floating point number
1133 when the radix is hex. */
1134 if ((!hex && !got_e && tolower (p[0]) == 'e')
1135 || (hex && !got_e && tolower (p[0] == 'p')))
1136 got_dot = got_e = 1;
1137 /* A '.' always indicates a decimal floating point number
1138 regardless of the radix. If we have a '..' then its the
1139 end of the number and the beginning of a slice. */
1140 else if (!got_dot && (p[0] == '.' && p[1] != '.'))
1141 got_dot = 1;
1142 /* This is the sign of the exponent, not the end of the number. */
1143 else if (got_e && (tolower (p[-1]) == 'e' || tolower (p[-1]) == 'p')
1144 && (*p == '-' || *p == '+'))
1145 continue;
1146 /* We will take any letters or digits, ignoring any embedded '_'.
1147 parse_number will complain if past the radix, or if L or U are
1148 not final. */
1149 else if ((*p < '0' || *p > '9') && (*p != '_')
1150 && ((*p < 'a' || *p > 'z') && (*p < 'A' || *p > 'Z')))
1151 break;
1154 toktype = parse_number (par_state, tokstart, p - tokstart,
1155 got_dot|got_e, &yylval);
1156 if (toktype == ERROR)
1158 char *err_copy = (char *) alloca (p - tokstart + 1);
1160 memcpy (err_copy, tokstart, p - tokstart);
1161 err_copy[p - tokstart] = 0;
1162 error (_("Invalid number \"%s\"."), err_copy);
1164 pstate->lexptr = p;
1165 return toktype;
1168 case '@':
1170 const char *p = &tokstart[1];
1171 size_t len = strlen ("entry");
1173 while (isspace (*p))
1174 p++;
1175 if (strncmp (p, "entry", len) == 0 && !isalnum (p[len])
1176 && p[len] != '_')
1178 pstate->lexptr = &p[len];
1179 return ENTRY;
1182 [[fallthrough]];
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 case ':':
1197 case '=':
1198 case '{':
1199 case '}':
1200 symbol:
1201 pstate->lexptr++;
1202 return c;
1204 case '\'':
1205 case '"':
1206 case '`':
1208 int host_len;
1209 int result = parse_string_or_char (tokstart, &pstate->lexptr,
1210 &yylval.tsval, &host_len);
1211 if (result == CHARACTER_LITERAL)
1213 if (host_len == 0)
1214 error (_("Empty character constant."));
1215 else if (host_len > 2 && c == '\'')
1217 ++tokstart;
1218 namelen = pstate->lexptr - tokstart - 1;
1219 goto tryname;
1221 else if (host_len > 1)
1222 error (_("Invalid character constant."));
1224 return result;
1228 if (!(c == '_' || c == '$'
1229 || (c >= 'a' && c <= 'z') || (c >= 'A' && c <= 'Z')))
1230 /* We must have come across a bad character (e.g. ';'). */
1231 error (_("Invalid character '%c' in expression"), c);
1233 /* It's a name. See how long it is. */
1234 namelen = 0;
1235 for (c = tokstart[namelen];
1236 (c == '_' || c == '$' || (c >= '0' && c <= '9')
1237 || (c >= 'a' && c <= 'z') || (c >= 'A' && c <= 'Z'));)
1238 c = tokstart[++namelen];
1240 /* The token "if" terminates the expression and is NOT
1241 removed from the input stream. */
1242 if (namelen == 2 && tokstart[0] == 'i' && tokstart[1] == 'f')
1243 return 0;
1245 /* For the same reason (breakpoint conditions), "thread N"
1246 terminates the expression. "thread" could be an identifier, but
1247 an identifier is never followed by a number without intervening
1248 punctuation. "task" is similar. Handle abbreviations of these,
1249 similarly to breakpoint.c:find_condition_and_thread. */
1250 if (namelen >= 1
1251 && (strncmp (tokstart, "thread", namelen) == 0
1252 || strncmp (tokstart, "task", namelen) == 0)
1253 && (tokstart[namelen] == ' ' || tokstart[namelen] == '\t'))
1255 const char *p = tokstart + namelen + 1;
1257 while (*p == ' ' || *p == '\t')
1258 p++;
1259 if (*p >= '0' && *p <= '9')
1260 return 0;
1263 pstate->lexptr += namelen;
1265 tryname:
1267 yylval.sval.ptr = tokstart;
1268 yylval.sval.length = namelen;
1270 /* Catch specific keywords. */
1271 std::string copy = copy_name (yylval.sval);
1272 for (const auto &token : ident_tokens)
1273 if (copy == token.oper)
1275 /* It is ok to always set this, even though we don't always
1276 strictly need to. */
1277 yylval.opcode = token.opcode;
1278 return token.token;
1281 if (*tokstart == '$')
1282 return DOLLAR_VARIABLE;
1284 yylval.tsym.type
1285 = language_lookup_primitive_type (par_state->language (),
1286 par_state->gdbarch (), copy.c_str ());
1287 if (yylval.tsym.type != NULL)
1288 return TYPENAME;
1290 /* Input names that aren't symbols but ARE valid hex numbers,
1291 when the input radix permits them, can be names or numbers
1292 depending on the parse. Note we support radixes > 16 here. */
1293 if ((tokstart[0] >= 'a' && tokstart[0] < 'a' + input_radix - 10)
1294 || (tokstart[0] >= 'A' && tokstart[0] < 'A' + input_radix - 10))
1296 YYSTYPE newlval; /* Its value is ignored. */
1297 int hextype = parse_number (par_state, tokstart, namelen, 0, &newlval);
1298 if (hextype == INTEGER_LITERAL)
1299 return NAME_OR_INT;
1302 if (pstate->parse_completion && *pstate->lexptr == '\0')
1303 saw_name_at_eof = 1;
1305 return IDENTIFIER;
1308 /* An object of this type is pushed on a FIFO by the "outer" lexer. */
1309 struct d_token_and_value
1311 int token;
1312 YYSTYPE value;
1316 /* A FIFO of tokens that have been read but not yet returned to the
1317 parser. */
1318 static std::vector<d_token_and_value> token_fifo;
1320 /* Non-zero if the lexer should return tokens from the FIFO. */
1321 static int popping;
1323 /* Temporary storage for yylex; this holds symbol names as they are
1324 built up. */
1325 static auto_obstack name_obstack;
1327 /* Classify an IDENTIFIER token. The contents of the token are in `yylval'.
1328 Updates yylval and returns the new token type. BLOCK is the block
1329 in which lookups start; this can be NULL to mean the global scope. */
1331 static int
1332 classify_name (struct parser_state *par_state, const struct block *block)
1334 struct block_symbol sym;
1335 struct field_of_this_result is_a_field_of_this;
1337 std::string copy = copy_name (yylval.sval);
1339 sym = lookup_symbol (copy.c_str (), block, SEARCH_VFT, &is_a_field_of_this);
1340 if (sym.symbol && sym.symbol->aclass () == LOC_TYPEDEF)
1342 yylval.tsym.type = sym.symbol->type ();
1343 return TYPENAME;
1345 else if (sym.symbol == NULL)
1347 /* Look-up first for a module name, then a type. */
1348 sym = lookup_symbol (copy.c_str (), block, SEARCH_MODULE_DOMAIN,
1349 nullptr);
1350 if (sym.symbol == NULL)
1351 sym = lookup_symbol (copy.c_str (), block, SEARCH_STRUCT_DOMAIN,
1352 nullptr);
1354 if (sym.symbol != NULL)
1356 yylval.tsym.type = sym.symbol->type ();
1357 return TYPENAME;
1360 return UNKNOWN_NAME;
1363 return IDENTIFIER;
1366 /* Like classify_name, but used by the inner loop of the lexer, when a
1367 name might have already been seen. CONTEXT is the context type, or
1368 NULL if this is the first component of a name. */
1370 static int
1371 classify_inner_name (struct parser_state *par_state,
1372 const struct block *block, struct type *context)
1374 struct type *type;
1376 if (context == NULL)
1377 return classify_name (par_state, block);
1379 type = check_typedef (context);
1380 if (!type_aggregate_p (type))
1381 return ERROR;
1383 std::string copy = copy_name (yylval.ssym.stoken);
1384 yylval.ssym.sym = d_lookup_nested_symbol (type, copy.c_str (), block);
1386 if (yylval.ssym.sym.symbol == NULL)
1387 return ERROR;
1389 if (yylval.ssym.sym.symbol->aclass () == LOC_TYPEDEF)
1391 yylval.tsym.type = yylval.ssym.sym.symbol->type ();
1392 return TYPENAME;
1395 return IDENTIFIER;
1398 /* The outer level of a two-level lexer. This calls the inner lexer
1399 to return tokens. It then either returns these tokens, or
1400 aggregates them into a larger token. This lets us work around a
1401 problem in our parsing approach, where the parser could not
1402 distinguish between qualified names and qualified types at the
1403 right point. */
1405 static int
1406 yylex (void)
1408 d_token_and_value current;
1409 int last_was_dot;
1410 struct type *context_type = NULL;
1411 int last_to_examine, next_to_examine, checkpoint;
1412 const struct block *search_block;
1414 if (popping && !token_fifo.empty ())
1415 goto do_pop;
1416 popping = 0;
1418 /* Read the first token and decide what to do. */
1419 current.token = lex_one_token (pstate);
1420 if (current.token != IDENTIFIER && current.token != '.')
1421 return current.token;
1423 /* Read any sequence of alternating "." and identifier tokens into
1424 the token FIFO. */
1425 current.value = yylval;
1426 token_fifo.push_back (current);
1427 last_was_dot = current.token == '.';
1429 while (1)
1431 current.token = lex_one_token (pstate);
1432 current.value = yylval;
1433 token_fifo.push_back (current);
1435 if ((last_was_dot && current.token != IDENTIFIER)
1436 || (!last_was_dot && current.token != '.'))
1437 break;
1439 last_was_dot = !last_was_dot;
1441 popping = 1;
1443 /* We always read one extra token, so compute the number of tokens
1444 to examine accordingly. */
1445 last_to_examine = token_fifo.size () - 2;
1446 next_to_examine = 0;
1448 current = token_fifo[next_to_examine];
1449 ++next_to_examine;
1451 /* If we are not dealing with a typename, now is the time to find out. */
1452 if (current.token == IDENTIFIER)
1454 yylval = current.value;
1455 current.token = classify_name (pstate, pstate->expression_context_block);
1456 current.value = yylval;
1459 /* If the IDENTIFIER is not known, it could be a package symbol,
1460 first try building up a name until we find the qualified module. */
1461 if (current.token == UNKNOWN_NAME)
1463 name_obstack.clear ();
1464 obstack_grow (&name_obstack, current.value.sval.ptr,
1465 current.value.sval.length);
1467 last_was_dot = 0;
1469 while (next_to_examine <= last_to_examine)
1471 d_token_and_value next;
1473 next = token_fifo[next_to_examine];
1474 ++next_to_examine;
1476 if (next.token == IDENTIFIER && last_was_dot)
1478 /* Update the partial name we are constructing. */
1479 obstack_grow_str (&name_obstack, ".");
1480 obstack_grow (&name_obstack, next.value.sval.ptr,
1481 next.value.sval.length);
1483 yylval.sval.ptr = (char *) obstack_base (&name_obstack);
1484 yylval.sval.length = obstack_object_size (&name_obstack);
1486 current.token = classify_name (pstate,
1487 pstate->expression_context_block);
1488 current.value = yylval;
1490 /* We keep going until we find a TYPENAME. */
1491 if (current.token == TYPENAME)
1493 /* Install it as the first token in the FIFO. */
1494 token_fifo[0] = current;
1495 token_fifo.erase (token_fifo.begin () + 1,
1496 token_fifo.begin () + next_to_examine);
1497 break;
1500 else if (next.token == '.' && !last_was_dot)
1501 last_was_dot = 1;
1502 else
1504 /* We've reached the end of the name. */
1505 break;
1509 /* Reset our current token back to the start, if we found nothing
1510 this means that we will just jump to do pop. */
1511 current = token_fifo[0];
1512 next_to_examine = 1;
1514 if (current.token != TYPENAME && current.token != '.')
1515 goto do_pop;
1517 name_obstack.clear ();
1518 checkpoint = 0;
1519 if (current.token == '.')
1520 search_block = NULL;
1521 else
1523 gdb_assert (current.token == TYPENAME);
1524 search_block = pstate->expression_context_block;
1525 obstack_grow (&name_obstack, current.value.sval.ptr,
1526 current.value.sval.length);
1527 context_type = current.value.tsym.type;
1528 checkpoint = 1;
1531 last_was_dot = current.token == '.';
1533 while (next_to_examine <= last_to_examine)
1535 d_token_and_value next;
1537 next = token_fifo[next_to_examine];
1538 ++next_to_examine;
1540 if (next.token == IDENTIFIER && last_was_dot)
1542 int classification;
1544 yylval = next.value;
1545 classification = classify_inner_name (pstate, search_block,
1546 context_type);
1547 /* We keep going until we either run out of names, or until
1548 we have a qualified name which is not a type. */
1549 if (classification != TYPENAME && classification != IDENTIFIER)
1550 break;
1552 /* Accept up to this token. */
1553 checkpoint = next_to_examine;
1555 /* Update the partial name we are constructing. */
1556 if (context_type != NULL)
1558 /* We don't want to put a leading "." into the name. */
1559 obstack_grow_str (&name_obstack, ".");
1561 obstack_grow (&name_obstack, next.value.sval.ptr,
1562 next.value.sval.length);
1564 yylval.sval.ptr = (char *) obstack_base (&name_obstack);
1565 yylval.sval.length = obstack_object_size (&name_obstack);
1566 current.value = yylval;
1567 current.token = classification;
1569 last_was_dot = 0;
1571 if (classification == IDENTIFIER)
1572 break;
1574 context_type = yylval.tsym.type;
1576 else if (next.token == '.' && !last_was_dot)
1577 last_was_dot = 1;
1578 else
1580 /* We've reached the end of the name. */
1581 break;
1585 /* If we have a replacement token, install it as the first token in
1586 the FIFO, and delete the other constituent tokens. */
1587 if (checkpoint > 0)
1589 token_fifo[0] = current;
1590 if (checkpoint > 1)
1591 token_fifo.erase (token_fifo.begin () + 1,
1592 token_fifo.begin () + checkpoint);
1595 do_pop:
1596 current = token_fifo[0];
1597 token_fifo.erase (token_fifo.begin ());
1598 yylval = current.value;
1599 return current.token;
1603 d_parse (struct parser_state *par_state)
1605 /* Setting up the parser state. */
1606 scoped_restore pstate_restore = make_scoped_restore (&pstate);
1607 gdb_assert (par_state != NULL);
1608 pstate = par_state;
1610 scoped_restore restore_yydebug = make_scoped_restore (&yydebug,
1611 par_state->debug);
1613 struct type_stack stack;
1614 scoped_restore restore_type_stack = make_scoped_restore (&type_stack,
1615 &stack);
1617 /* Initialize some state used by the lexer. */
1618 last_was_structop = 0;
1619 saw_name_at_eof = 0;
1620 paren_depth = 0;
1622 token_fifo.clear ();
1623 popping = 0;
1624 name_obstack.clear ();
1626 int result = yyparse ();
1627 if (!result)
1628 pstate->set_operation (pstate->pop ());
1629 return result;
1632 static void
1633 yyerror (const char *msg)
1635 pstate->parse_error (msg);