More updated translations
[binutils-gdb.git] / gdb / d-exp.y
blobdf89cb63a35def07716ab71d23361bda65a258e6
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
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 bound_minimal_symbol msymbol
467 = lookup_minimal_symbol (current_program_space, copy.c_str ());
468 if (msymbol.minsym != NULL)
469 pstate->push_new<var_msym_value_operation> (msymbol);
470 else if (!have_full_symbols (current_program_space)
471 && !have_partial_symbols (current_program_space))
472 error (_("No symbol table is loaded. Use the \"file\" command"));
473 else
474 error (_("No symbol \"%s\" in current context."),
475 copy.c_str ());
478 | TypeExp '.' IdentifierExp
479 { struct type *type = check_typedef ($1);
481 /* Check if the qualified name is in the global
482 context. However if the symbol has not already
483 been resolved, it's not likely to be found. */
484 if (type->code () == TYPE_CODE_MODULE)
486 struct block_symbol sym;
487 const char *type_name = TYPE_SAFE_NAME (type);
488 int type_name_len = strlen (type_name);
489 std::string name
490 = string_printf ("%.*s.%.*s",
491 type_name_len, type_name,
492 $3.length, $3.ptr);
494 sym =
495 lookup_symbol (name.c_str (),
496 (const struct block *) NULL,
497 SEARCH_VFT, NULL);
498 pstate->push_symbol (name.c_str (), sym);
500 else
502 /* Check if the qualified name resolves as a member
503 of an aggregate or an enum type. */
504 if (!type_aggregate_p (type))
505 error (_("`%s' is not defined as an aggregate type."),
506 TYPE_SAFE_NAME (type));
508 pstate->push_new<scope_operation>
509 (type, copy_name ($3));
512 | DOLLAR_VARIABLE
513 { pstate->push_dollar ($1); }
514 | NAME_OR_INT
515 { YYSTYPE val;
516 parse_number (pstate, $1.ptr, $1.length, 0, &val);
517 pstate->push_new<long_const_operation>
518 (val.typed_val_int.type, val.typed_val_int.val); }
519 | NULL_KEYWORD
520 { struct type *type = parse_d_type (pstate)->builtin_void;
521 type = lookup_pointer_type (type);
522 pstate->push_new<long_const_operation> (type, 0); }
523 | TRUE_KEYWORD
524 { pstate->push_new<bool_operation> (true); }
525 | FALSE_KEYWORD
526 { pstate->push_new<bool_operation> (false); }
527 | INTEGER_LITERAL
528 { pstate->push_new<long_const_operation> ($1.type, $1.val); }
529 | FLOAT_LITERAL
531 float_data data;
532 std::copy (std::begin ($1.val), std::end ($1.val),
533 std::begin (data));
534 pstate->push_new<float_const_operation> ($1.type, data);
536 | CHARACTER_LITERAL
537 { struct stoken_vector vec;
538 vec.len = 1;
539 vec.tokens = &$1;
540 pstate->push_c_string (0, &vec); }
541 | StringExp
542 { int i;
543 pstate->push_c_string (0, &$1);
544 for (i = 0; i < $1.len; ++i)
545 free ($1.tokens[i].ptr);
546 free ($1.tokens); }
547 | ArrayLiteral
549 std::vector<operation_up> args
550 = pstate->pop_vector ($1);
551 pstate->push_new<array_operation>
552 (0, $1 - 1, std::move (args));
554 | TYPEOF_KEYWORD '(' Expression ')'
555 { pstate->wrap<typeof_operation> (); }
558 ArrayLiteral:
559 '[' ArgumentList_opt ']'
560 { $$ = pstate->arglist_len; }
563 IdentifierExp:
564 IDENTIFIER
567 StringExp:
568 STRING_LITERAL
569 { /* We copy the string here, and not in the
570 lexer, to guarantee that we do not leak a
571 string. Note that we follow the
572 NUL-termination convention of the
573 lexer. */
574 struct typed_stoken *vec = XNEW (struct typed_stoken);
575 $$.len = 1;
576 $$.tokens = vec;
578 vec->type = $1.type;
579 vec->length = $1.length;
580 vec->ptr = (char *) malloc ($1.length + 1);
581 memcpy (vec->ptr, $1.ptr, $1.length + 1);
583 | StringExp STRING_LITERAL
584 { /* Note that we NUL-terminate here, but just
585 for convenience. */
586 char *p;
587 ++$$.len;
588 $$.tokens
589 = XRESIZEVEC (struct typed_stoken, $$.tokens, $$.len);
591 p = (char *) malloc ($2.length + 1);
592 memcpy (p, $2.ptr, $2.length + 1);
594 $$.tokens[$$.len - 1].type = $2.type;
595 $$.tokens[$$.len - 1].length = $2.length;
596 $$.tokens[$$.len - 1].ptr = p;
600 TypeExp:
601 '(' TypeExp ')'
602 { /* Do nothing. */ }
603 | BasicType
604 { pstate->push_new<type_operation> ($1); }
605 | BasicType BasicType2
606 { $$ = type_stack->follow_types ($1);
607 pstate->push_new<type_operation> ($$);
611 BasicType2:
613 { type_stack->push (tp_pointer); }
614 | '*' BasicType2
615 { type_stack->push (tp_pointer); }
616 | '[' INTEGER_LITERAL ']'
617 { type_stack->push ($2.val);
618 type_stack->push (tp_array); }
619 | '[' INTEGER_LITERAL ']' BasicType2
620 { type_stack->push ($2.val);
621 type_stack->push (tp_array); }
624 BasicType:
625 TYPENAME
626 { $$ = $1.type; }
631 /* Return true if the type is aggregate-like. */
633 static int
634 type_aggregate_p (struct type *type)
636 return (type->code () == TYPE_CODE_STRUCT
637 || type->code () == TYPE_CODE_UNION
638 || type->code () == TYPE_CODE_MODULE
639 || (type->code () == TYPE_CODE_ENUM
640 && type->is_declared_class ()));
643 /* Take care of parsing a number (anything that starts with a digit).
644 Set yylval and return the token type; update lexptr.
645 LEN is the number of characters in it. */
647 /*** Needs some error checking for the float case ***/
649 static int
650 parse_number (struct parser_state *ps, const char *p,
651 int len, int parsed_float, YYSTYPE *putithere)
653 ULONGEST n = 0;
654 ULONGEST prevn = 0;
655 ULONGEST un;
657 int i = 0;
658 int c;
659 int base = input_radix;
660 int unsigned_p = 0;
661 int long_p = 0;
663 /* We have found a "L" or "U" suffix. */
664 int found_suffix = 0;
666 ULONGEST high_bit;
667 struct type *signed_type;
668 struct type *unsigned_type;
670 if (parsed_float)
672 char *s, *sp;
674 /* Strip out all embedded '_' before passing to parse_float. */
675 s = (char *) alloca (len + 1);
676 sp = s;
677 while (len-- > 0)
679 if (*p != '_')
680 *sp++ = *p;
681 p++;
683 *sp = '\0';
684 len = strlen (s);
686 /* Check suffix for `i' , `fi' or `li' (idouble, ifloat or ireal). */
687 if (len >= 1 && tolower (s[len - 1]) == 'i')
689 if (len >= 2 && tolower (s[len - 2]) == 'f')
691 putithere->typed_val_float.type
692 = parse_d_type (ps)->builtin_ifloat;
693 len -= 2;
695 else if (len >= 2 && tolower (s[len - 2]) == 'l')
697 putithere->typed_val_float.type
698 = parse_d_type (ps)->builtin_ireal;
699 len -= 2;
701 else
703 putithere->typed_val_float.type
704 = parse_d_type (ps)->builtin_idouble;
705 len -= 1;
708 /* Check suffix for `f' or `l'' (float or real). */
709 else if (len >= 1 && tolower (s[len - 1]) == 'f')
711 putithere->typed_val_float.type
712 = parse_d_type (ps)->builtin_float;
713 len -= 1;
715 else if (len >= 1 && tolower (s[len - 1]) == 'l')
717 putithere->typed_val_float.type
718 = parse_d_type (ps)->builtin_real;
719 len -= 1;
721 /* Default type if no suffix. */
722 else
724 putithere->typed_val_float.type
725 = parse_d_type (ps)->builtin_double;
728 if (!parse_float (s, len,
729 putithere->typed_val_float.type,
730 putithere->typed_val_float.val))
731 return ERROR;
733 return FLOAT_LITERAL;
736 /* Handle base-switching prefixes 0x, 0b, 0 */
737 if (p[0] == '0')
738 switch (p[1])
740 case 'x':
741 case 'X':
742 if (len >= 3)
744 p += 2;
745 base = 16;
746 len -= 2;
748 break;
750 case 'b':
751 case 'B':
752 if (len >= 3)
754 p += 2;
755 base = 2;
756 len -= 2;
758 break;
760 default:
761 base = 8;
762 break;
765 while (len-- > 0)
767 c = *p++;
768 if (c == '_')
769 continue; /* Ignore embedded '_'. */
770 if (c >= 'A' && c <= 'Z')
771 c += 'a' - 'A';
772 if (c != 'l' && c != 'u')
773 n *= base;
774 if (c >= '0' && c <= '9')
776 if (found_suffix)
777 return ERROR;
778 n += i = c - '0';
780 else
782 if (base > 10 && c >= 'a' && c <= 'f')
784 if (found_suffix)
785 return ERROR;
786 n += i = c - 'a' + 10;
788 else if (c == 'l' && long_p == 0)
790 long_p = 1;
791 found_suffix = 1;
793 else if (c == 'u' && unsigned_p == 0)
795 unsigned_p = 1;
796 found_suffix = 1;
798 else
799 return ERROR; /* Char not a digit */
801 if (i >= base)
802 return ERROR; /* Invalid digit in this base. */
803 /* Portably test for integer overflow. */
804 if (c != 'l' && c != 'u')
806 ULONGEST n2 = prevn * base;
807 if ((n2 / base != prevn) || (n2 + i < prevn))
808 error (_("Numeric constant too large."));
810 prevn = n;
813 /* An integer constant is an int or a long. An L suffix forces it to
814 be long, and a U suffix forces it to be unsigned. To figure out
815 whether it fits, we shift it right and see whether anything remains.
816 Note that we can't shift sizeof (LONGEST) * HOST_CHAR_BIT bits or
817 more in one operation, because many compilers will warn about such a
818 shift (which always produces a zero result). To deal with the case
819 where it is we just always shift the value more than once, with fewer
820 bits each time. */
821 un = (ULONGEST) n >> 2;
822 if (long_p == 0 && (un >> 30) == 0)
824 high_bit = ((ULONGEST) 1) << 31;
825 signed_type = parse_d_type (ps)->builtin_int;
826 /* For decimal notation, keep the sign of the worked out type. */
827 if (base == 10 && !unsigned_p)
828 unsigned_type = parse_d_type (ps)->builtin_long;
829 else
830 unsigned_type = parse_d_type (ps)->builtin_uint;
832 else
834 int shift;
835 if (sizeof (ULONGEST) * HOST_CHAR_BIT < 64)
836 /* A long long does not fit in a LONGEST. */
837 shift = (sizeof (ULONGEST) * HOST_CHAR_BIT - 1);
838 else
839 shift = 63;
840 high_bit = (ULONGEST) 1 << shift;
841 signed_type = parse_d_type (ps)->builtin_long;
842 unsigned_type = parse_d_type (ps)->builtin_ulong;
845 putithere->typed_val_int.val = n;
847 /* If the high bit of the worked out type is set then this number
848 has to be unsigned_type. */
849 if (unsigned_p || (n & high_bit))
850 putithere->typed_val_int.type = unsigned_type;
851 else
852 putithere->typed_val_int.type = signed_type;
854 return INTEGER_LITERAL;
857 /* Temporary obstack used for holding strings. */
858 static struct obstack tempbuf;
859 static int tempbuf_init;
861 /* Parse a string or character literal from TOKPTR. The string or
862 character may be wide or unicode. *OUTPTR is set to just after the
863 end of the literal in the input string. The resulting token is
864 stored in VALUE. This returns a token value, either STRING or
865 CHAR, depending on what was parsed. *HOST_CHARS is set to the
866 number of host characters in the literal. */
868 static int
869 parse_string_or_char (const char *tokptr, const char **outptr,
870 struct typed_stoken *value, int *host_chars)
872 int quote;
874 /* Build the gdb internal form of the input string in tempbuf. Note
875 that the buffer is null byte terminated *only* for the
876 convenience of debugging gdb itself and printing the buffer
877 contents when the buffer contains no embedded nulls. Gdb does
878 not depend upon the buffer being null byte terminated, it uses
879 the length string instead. This allows gdb to handle C strings
880 (as well as strings in other languages) with embedded null
881 bytes */
883 if (!tempbuf_init)
884 tempbuf_init = 1;
885 else
886 obstack_free (&tempbuf, NULL);
887 obstack_init (&tempbuf);
889 /* Skip the quote. */
890 quote = *tokptr;
891 ++tokptr;
893 *host_chars = 0;
895 while (*tokptr)
897 char c = *tokptr;
898 if (c == '\\')
900 ++tokptr;
901 *host_chars += c_parse_escape (&tokptr, &tempbuf);
903 else if (c == quote)
904 break;
905 else
907 obstack_1grow (&tempbuf, c);
908 ++tokptr;
909 /* FIXME: this does the wrong thing with multi-byte host
910 characters. We could use mbrlen here, but that would
911 make "set host-charset" a bit less useful. */
912 ++*host_chars;
916 if (*tokptr != quote)
918 if (quote == '"' || quote == '`')
919 error (_("Unterminated string in expression."));
920 else
921 error (_("Unmatched single quote."));
923 ++tokptr;
925 /* FIXME: should instead use own language string_type enum
926 and handle D-specific string suffixes here. */
927 if (quote == '\'')
928 value->type = C_CHAR;
929 else
930 value->type = C_STRING;
932 value->ptr = (char *) obstack_base (&tempbuf);
933 value->length = obstack_object_size (&tempbuf);
935 *outptr = tokptr;
937 return quote == '\'' ? CHARACTER_LITERAL : STRING_LITERAL;
940 struct d_token
942 const char *oper;
943 int token;
944 enum exp_opcode opcode;
947 static const struct d_token tokentab3[] =
949 {"^^=", ASSIGN_MODIFY, BINOP_EXP},
950 {"<<=", ASSIGN_MODIFY, BINOP_LSH},
951 {">>=", ASSIGN_MODIFY, BINOP_RSH},
954 static const struct d_token tokentab2[] =
956 {"+=", ASSIGN_MODIFY, BINOP_ADD},
957 {"-=", ASSIGN_MODIFY, BINOP_SUB},
958 {"*=", ASSIGN_MODIFY, BINOP_MUL},
959 {"/=", ASSIGN_MODIFY, BINOP_DIV},
960 {"%=", ASSIGN_MODIFY, BINOP_REM},
961 {"|=", ASSIGN_MODIFY, BINOP_BITWISE_IOR},
962 {"&=", ASSIGN_MODIFY, BINOP_BITWISE_AND},
963 {"^=", ASSIGN_MODIFY, BINOP_BITWISE_XOR},
964 {"++", INCREMENT, OP_NULL},
965 {"--", DECREMENT, OP_NULL},
966 {"&&", ANDAND, OP_NULL},
967 {"||", OROR, OP_NULL},
968 {"^^", HATHAT, OP_NULL},
969 {"<<", LSH, OP_NULL},
970 {">>", RSH, OP_NULL},
971 {"==", EQUAL, OP_NULL},
972 {"!=", NOTEQUAL, OP_NULL},
973 {"<=", LEQ, OP_NULL},
974 {">=", GEQ, OP_NULL},
975 {"..", DOTDOT, OP_NULL},
978 /* Identifier-like tokens. */
979 static const struct d_token ident_tokens[] =
981 {"is", IDENTITY, OP_NULL},
982 {"!is", NOTIDENTITY, OP_NULL},
984 {"cast", CAST_KEYWORD, OP_NULL},
985 {"const", CONST_KEYWORD, OP_NULL},
986 {"immutable", IMMUTABLE_KEYWORD, OP_NULL},
987 {"shared", SHARED_KEYWORD, OP_NULL},
988 {"super", SUPER_KEYWORD, OP_NULL},
990 {"null", NULL_KEYWORD, OP_NULL},
991 {"true", TRUE_KEYWORD, OP_NULL},
992 {"false", FALSE_KEYWORD, OP_NULL},
994 {"init", INIT_KEYWORD, OP_NULL},
995 {"sizeof", SIZEOF_KEYWORD, OP_NULL},
996 {"typeof", TYPEOF_KEYWORD, OP_NULL},
997 {"typeid", TYPEID_KEYWORD, OP_NULL},
999 {"delegate", DELEGATE_KEYWORD, OP_NULL},
1000 {"function", FUNCTION_KEYWORD, OP_NULL},
1001 {"struct", STRUCT_KEYWORD, OP_NULL},
1002 {"union", UNION_KEYWORD, OP_NULL},
1003 {"class", CLASS_KEYWORD, OP_NULL},
1004 {"interface", INTERFACE_KEYWORD, OP_NULL},
1005 {"enum", ENUM_KEYWORD, OP_NULL},
1006 {"template", TEMPLATE_KEYWORD, OP_NULL},
1009 /* This is set if a NAME token appeared at the very end of the input
1010 string, with no whitespace separating the name from the EOF. This
1011 is used only when parsing to do field name completion. */
1012 static int saw_name_at_eof;
1014 /* This is set if the previously-returned token was a structure operator.
1015 This is used only when parsing to do field name completion. */
1016 static int last_was_structop;
1018 /* Depth of parentheses. */
1019 static int paren_depth;
1021 /* Read one token, getting characters through lexptr. */
1023 static int
1024 lex_one_token (struct parser_state *par_state)
1026 int c;
1027 int namelen;
1028 const char *tokstart;
1029 int saw_structop = last_was_structop;
1031 last_was_structop = 0;
1033 retry:
1035 pstate->prev_lexptr = pstate->lexptr;
1037 tokstart = pstate->lexptr;
1038 /* See if it is a special token of length 3. */
1039 for (const auto &token : tokentab3)
1040 if (strncmp (tokstart, token.oper, 3) == 0)
1042 pstate->lexptr += 3;
1043 yylval.opcode = token.opcode;
1044 return token.token;
1047 /* See if it is a special token of length 2. */
1048 for (const auto &token : tokentab2)
1049 if (strncmp (tokstart, token.oper, 2) == 0)
1051 pstate->lexptr += 2;
1052 yylval.opcode = token.opcode;
1053 return token.token;
1056 switch (c = *tokstart)
1058 case 0:
1059 /* If we're parsing for field name completion, and the previous
1060 token allows such completion, return a COMPLETE token.
1061 Otherwise, we were already scanning the original text, and
1062 we're really done. */
1063 if (saw_name_at_eof)
1065 saw_name_at_eof = 0;
1066 return COMPLETE;
1068 else if (saw_structop)
1069 return COMPLETE;
1070 else
1071 return 0;
1073 case ' ':
1074 case '\t':
1075 case '\n':
1076 pstate->lexptr++;
1077 goto retry;
1079 case '[':
1080 case '(':
1081 paren_depth++;
1082 pstate->lexptr++;
1083 return c;
1085 case ']':
1086 case ')':
1087 if (paren_depth == 0)
1088 return 0;
1089 paren_depth--;
1090 pstate->lexptr++;
1091 return c;
1093 case ',':
1094 if (pstate->comma_terminates && paren_depth == 0)
1095 return 0;
1096 pstate->lexptr++;
1097 return c;
1099 case '.':
1100 /* Might be a floating point number. */
1101 if (pstate->lexptr[1] < '0' || pstate->lexptr[1] > '9')
1103 if (pstate->parse_completion)
1104 last_was_structop = 1;
1105 goto symbol; /* Nope, must be a symbol. */
1107 [[fallthrough]];
1109 case '0':
1110 case '1':
1111 case '2':
1112 case '3':
1113 case '4':
1114 case '5':
1115 case '6':
1116 case '7':
1117 case '8':
1118 case '9':
1120 /* It's a number. */
1121 int got_dot = 0, got_e = 0, toktype;
1122 const char *p = tokstart;
1123 int hex = input_radix > 10;
1125 if (c == '0' && (p[1] == 'x' || p[1] == 'X'))
1127 p += 2;
1128 hex = 1;
1131 for (;; ++p)
1133 /* Hex exponents start with 'p', because 'e' is a valid hex
1134 digit and thus does not indicate a floating point number
1135 when the radix is hex. */
1136 if ((!hex && !got_e && tolower (p[0]) == 'e')
1137 || (hex && !got_e && tolower (p[0] == 'p')))
1138 got_dot = got_e = 1;
1139 /* A '.' always indicates a decimal floating point number
1140 regardless of the radix. If we have a '..' then its the
1141 end of the number and the beginning of a slice. */
1142 else if (!got_dot && (p[0] == '.' && p[1] != '.'))
1143 got_dot = 1;
1144 /* This is the sign of the exponent, not the end of the number. */
1145 else if (got_e && (tolower (p[-1]) == 'e' || tolower (p[-1]) == 'p')
1146 && (*p == '-' || *p == '+'))
1147 continue;
1148 /* We will take any letters or digits, ignoring any embedded '_'.
1149 parse_number will complain if past the radix, or if L or U are
1150 not final. */
1151 else if ((*p < '0' || *p > '9') && (*p != '_')
1152 && ((*p < 'a' || *p > 'z') && (*p < 'A' || *p > 'Z')))
1153 break;
1156 toktype = parse_number (par_state, tokstart, p - tokstart,
1157 got_dot|got_e, &yylval);
1158 if (toktype == ERROR)
1159 error (_("Invalid number \"%.*s\"."), (int) (p - tokstart),
1160 tokstart);
1161 pstate->lexptr = p;
1162 return toktype;
1165 case '@':
1167 const char *p = &tokstart[1];
1168 size_t len = strlen ("entry");
1170 while (isspace (*p))
1171 p++;
1172 if (strncmp (p, "entry", len) == 0 && !isalnum (p[len])
1173 && p[len] != '_')
1175 pstate->lexptr = &p[len];
1176 return ENTRY;
1179 [[fallthrough]];
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 case '}':
1197 symbol:
1198 pstate->lexptr++;
1199 return c;
1201 case '\'':
1202 case '"':
1203 case '`':
1205 int host_len;
1206 int result = parse_string_or_char (tokstart, &pstate->lexptr,
1207 &yylval.tsval, &host_len);
1208 if (result == CHARACTER_LITERAL)
1210 if (host_len == 0)
1211 error (_("Empty character constant."));
1212 else if (host_len > 2 && c == '\'')
1214 ++tokstart;
1215 namelen = pstate->lexptr - tokstart - 1;
1216 goto tryname;
1218 else if (host_len > 1)
1219 error (_("Invalid character constant."));
1221 return result;
1225 if (!(c == '_' || c == '$'
1226 || (c >= 'a' && c <= 'z') || (c >= 'A' && c <= 'Z')))
1227 /* We must have come across a bad character (e.g. ';'). */
1228 error (_("Invalid character '%c' in expression"), c);
1230 /* It's a name. See how long it is. */
1231 namelen = 0;
1232 for (c = tokstart[namelen];
1233 (c == '_' || c == '$' || (c >= '0' && c <= '9')
1234 || (c >= 'a' && c <= 'z') || (c >= 'A' && c <= 'Z'));)
1235 c = tokstart[++namelen];
1237 /* The token "if" terminates the expression and is NOT
1238 removed from the input stream. */
1239 if (namelen == 2 && tokstart[0] == 'i' && tokstart[1] == 'f')
1240 return 0;
1242 /* For the same reason (breakpoint conditions), "thread N"
1243 terminates the expression. "thread" could be an identifier, but
1244 an identifier is never followed by a number without intervening
1245 punctuation. "task" is similar. Handle abbreviations of these,
1246 similarly to breakpoint.c:find_condition_and_thread. */
1247 if (namelen >= 1
1248 && (strncmp (tokstart, "thread", namelen) == 0
1249 || strncmp (tokstart, "task", namelen) == 0)
1250 && (tokstart[namelen] == ' ' || tokstart[namelen] == '\t'))
1252 const char *p = tokstart + namelen + 1;
1254 while (*p == ' ' || *p == '\t')
1255 p++;
1256 if (*p >= '0' && *p <= '9')
1257 return 0;
1260 pstate->lexptr += namelen;
1262 tryname:
1264 yylval.sval.ptr = tokstart;
1265 yylval.sval.length = namelen;
1267 /* Catch specific keywords. */
1268 std::string copy = copy_name (yylval.sval);
1269 for (const auto &token : ident_tokens)
1270 if (copy == token.oper)
1272 /* It is ok to always set this, even though we don't always
1273 strictly need to. */
1274 yylval.opcode = token.opcode;
1275 return token.token;
1278 if (*tokstart == '$')
1279 return DOLLAR_VARIABLE;
1281 yylval.tsym.type
1282 = language_lookup_primitive_type (par_state->language (),
1283 par_state->gdbarch (), copy.c_str ());
1284 if (yylval.tsym.type != NULL)
1285 return TYPENAME;
1287 /* Input names that aren't symbols but ARE valid hex numbers,
1288 when the input radix permits them, can be names or numbers
1289 depending on the parse. Note we support radixes > 16 here. */
1290 if ((tokstart[0] >= 'a' && tokstart[0] < 'a' + input_radix - 10)
1291 || (tokstart[0] >= 'A' && tokstart[0] < 'A' + input_radix - 10))
1293 YYSTYPE newlval; /* Its value is ignored. */
1294 int hextype = parse_number (par_state, tokstart, namelen, 0, &newlval);
1295 if (hextype == INTEGER_LITERAL)
1296 return NAME_OR_INT;
1299 if (pstate->parse_completion && *pstate->lexptr == '\0')
1300 saw_name_at_eof = 1;
1302 return IDENTIFIER;
1305 /* An object of this type is pushed on a FIFO by the "outer" lexer. */
1306 struct d_token_and_value
1308 int token;
1309 YYSTYPE value;
1313 /* A FIFO of tokens that have been read but not yet returned to the
1314 parser. */
1315 static std::vector<d_token_and_value> token_fifo;
1317 /* Non-zero if the lexer should return tokens from the FIFO. */
1318 static int popping;
1320 /* Temporary storage for yylex; this holds symbol names as they are
1321 built up. */
1322 static auto_obstack name_obstack;
1324 /* Classify an IDENTIFIER token. The contents of the token are in `yylval'.
1325 Updates yylval and returns the new token type. BLOCK is the block
1326 in which lookups start; this can be NULL to mean the global scope. */
1328 static int
1329 classify_name (struct parser_state *par_state, const struct block *block)
1331 struct block_symbol sym;
1332 struct field_of_this_result is_a_field_of_this;
1334 std::string copy = copy_name (yylval.sval);
1336 sym = lookup_symbol (copy.c_str (), block, SEARCH_VFT, &is_a_field_of_this);
1337 if (sym.symbol && sym.symbol->aclass () == LOC_TYPEDEF)
1339 yylval.tsym.type = sym.symbol->type ();
1340 return TYPENAME;
1342 else if (sym.symbol == NULL)
1344 /* Look-up first for a module name, then a type. */
1345 sym = lookup_symbol (copy.c_str (), block, SEARCH_MODULE_DOMAIN,
1346 nullptr);
1347 if (sym.symbol == NULL)
1348 sym = lookup_symbol (copy.c_str (), block, SEARCH_STRUCT_DOMAIN,
1349 nullptr);
1351 if (sym.symbol != NULL)
1353 yylval.tsym.type = sym.symbol->type ();
1354 return TYPENAME;
1357 return UNKNOWN_NAME;
1360 return IDENTIFIER;
1363 /* Like classify_name, but used by the inner loop of the lexer, when a
1364 name might have already been seen. CONTEXT is the context type, or
1365 NULL if this is the first component of a name. */
1367 static int
1368 classify_inner_name (struct parser_state *par_state,
1369 const struct block *block, struct type *context)
1371 struct type *type;
1373 if (context == NULL)
1374 return classify_name (par_state, block);
1376 type = check_typedef (context);
1377 if (!type_aggregate_p (type))
1378 return ERROR;
1380 std::string copy = copy_name (yylval.ssym.stoken);
1381 yylval.ssym.sym = d_lookup_nested_symbol (type, copy.c_str (), block);
1383 if (yylval.ssym.sym.symbol == NULL)
1384 return ERROR;
1386 if (yylval.ssym.sym.symbol->aclass () == LOC_TYPEDEF)
1388 yylval.tsym.type = yylval.ssym.sym.symbol->type ();
1389 return TYPENAME;
1392 return IDENTIFIER;
1395 /* The outer level of a two-level lexer. This calls the inner lexer
1396 to return tokens. It then either returns these tokens, or
1397 aggregates them into a larger token. This lets us work around a
1398 problem in our parsing approach, where the parser could not
1399 distinguish between qualified names and qualified types at the
1400 right point. */
1402 static int
1403 yylex (void)
1405 d_token_and_value current;
1406 int last_was_dot;
1407 struct type *context_type = NULL;
1408 int last_to_examine, next_to_examine, checkpoint;
1409 const struct block *search_block;
1411 if (popping && !token_fifo.empty ())
1412 goto do_pop;
1413 popping = 0;
1415 /* Read the first token and decide what to do. */
1416 current.token = lex_one_token (pstate);
1417 if (current.token != IDENTIFIER && current.token != '.')
1418 return current.token;
1420 /* Read any sequence of alternating "." and identifier tokens into
1421 the token FIFO. */
1422 current.value = yylval;
1423 token_fifo.push_back (current);
1424 last_was_dot = current.token == '.';
1426 while (1)
1428 current.token = lex_one_token (pstate);
1429 current.value = yylval;
1430 token_fifo.push_back (current);
1432 if ((last_was_dot && current.token != IDENTIFIER)
1433 || (!last_was_dot && current.token != '.'))
1434 break;
1436 last_was_dot = !last_was_dot;
1438 popping = 1;
1440 /* We always read one extra token, so compute the number of tokens
1441 to examine accordingly. */
1442 last_to_examine = token_fifo.size () - 2;
1443 next_to_examine = 0;
1445 current = token_fifo[next_to_examine];
1446 ++next_to_examine;
1448 /* If we are not dealing with a typename, now is the time to find out. */
1449 if (current.token == IDENTIFIER)
1451 yylval = current.value;
1452 current.token = classify_name (pstate, pstate->expression_context_block);
1453 current.value = yylval;
1456 /* If the IDENTIFIER is not known, it could be a package symbol,
1457 first try building up a name until we find the qualified module. */
1458 if (current.token == UNKNOWN_NAME)
1460 name_obstack.clear ();
1461 obstack_grow (&name_obstack, current.value.sval.ptr,
1462 current.value.sval.length);
1464 last_was_dot = 0;
1466 while (next_to_examine <= last_to_examine)
1468 d_token_and_value next;
1470 next = token_fifo[next_to_examine];
1471 ++next_to_examine;
1473 if (next.token == IDENTIFIER && last_was_dot)
1475 /* Update the partial name we are constructing. */
1476 obstack_grow_str (&name_obstack, ".");
1477 obstack_grow (&name_obstack, next.value.sval.ptr,
1478 next.value.sval.length);
1480 yylval.sval.ptr = (char *) obstack_base (&name_obstack);
1481 yylval.sval.length = obstack_object_size (&name_obstack);
1483 current.token = classify_name (pstate,
1484 pstate->expression_context_block);
1485 current.value = yylval;
1487 /* We keep going until we find a TYPENAME. */
1488 if (current.token == TYPENAME)
1490 /* Install it as the first token in the FIFO. */
1491 token_fifo[0] = current;
1492 token_fifo.erase (token_fifo.begin () + 1,
1493 token_fifo.begin () + next_to_examine);
1494 break;
1497 else if (next.token == '.' && !last_was_dot)
1498 last_was_dot = 1;
1499 else
1501 /* We've reached the end of the name. */
1502 break;
1506 /* Reset our current token back to the start, if we found nothing
1507 this means that we will just jump to do pop. */
1508 current = token_fifo[0];
1509 next_to_examine = 1;
1511 if (current.token != TYPENAME && current.token != '.')
1512 goto do_pop;
1514 name_obstack.clear ();
1515 checkpoint = 0;
1516 if (current.token == '.')
1517 search_block = NULL;
1518 else
1520 gdb_assert (current.token == TYPENAME);
1521 search_block = pstate->expression_context_block;
1522 obstack_grow (&name_obstack, current.value.sval.ptr,
1523 current.value.sval.length);
1524 context_type = current.value.tsym.type;
1525 checkpoint = 1;
1528 last_was_dot = current.token == '.';
1530 while (next_to_examine <= last_to_examine)
1532 d_token_and_value next;
1534 next = token_fifo[next_to_examine];
1535 ++next_to_examine;
1537 if (next.token == IDENTIFIER && last_was_dot)
1539 int classification;
1541 yylval = next.value;
1542 classification = classify_inner_name (pstate, search_block,
1543 context_type);
1544 /* We keep going until we either run out of names, or until
1545 we have a qualified name which is not a type. */
1546 if (classification != TYPENAME && classification != IDENTIFIER)
1547 break;
1549 /* Accept up to this token. */
1550 checkpoint = next_to_examine;
1552 /* Update the partial name we are constructing. */
1553 if (context_type != NULL)
1555 /* We don't want to put a leading "." into the name. */
1556 obstack_grow_str (&name_obstack, ".");
1558 obstack_grow (&name_obstack, next.value.sval.ptr,
1559 next.value.sval.length);
1561 yylval.sval.ptr = (char *) obstack_base (&name_obstack);
1562 yylval.sval.length = obstack_object_size (&name_obstack);
1563 current.value = yylval;
1564 current.token = classification;
1566 last_was_dot = 0;
1568 if (classification == IDENTIFIER)
1569 break;
1571 context_type = yylval.tsym.type;
1573 else if (next.token == '.' && !last_was_dot)
1574 last_was_dot = 1;
1575 else
1577 /* We've reached the end of the name. */
1578 break;
1582 /* If we have a replacement token, install it as the first token in
1583 the FIFO, and delete the other constituent tokens. */
1584 if (checkpoint > 0)
1586 token_fifo[0] = current;
1587 if (checkpoint > 1)
1588 token_fifo.erase (token_fifo.begin () + 1,
1589 token_fifo.begin () + checkpoint);
1592 do_pop:
1593 current = token_fifo[0];
1594 token_fifo.erase (token_fifo.begin ());
1595 yylval = current.value;
1596 return current.token;
1600 d_parse (struct parser_state *par_state)
1602 /* Setting up the parser state. */
1603 scoped_restore pstate_restore = make_scoped_restore (&pstate);
1604 gdb_assert (par_state != NULL);
1605 pstate = par_state;
1607 scoped_restore restore_yydebug = make_scoped_restore (&yydebug,
1608 par_state->debug);
1610 struct type_stack stack;
1611 scoped_restore restore_type_stack = make_scoped_restore (&type_stack,
1612 &stack);
1614 /* Initialize some state used by the lexer. */
1615 last_was_structop = 0;
1616 saw_name_at_eof = 0;
1617 paren_depth = 0;
1619 token_fifo.clear ();
1620 popping = 0;
1621 name_obstack.clear ();
1623 int result = yyparse ();
1624 if (!result)
1625 pstate->set_operation (pstate->pop ());
1626 return result;
1629 static void
1630 yyerror (const char *msg)
1632 pstate->parse_error (msg);