1 /* YACC parser for D expressions, for GDB.
3 Copyright (C) 2014-2021 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. */
43 #include "expression.h"
45 #include "parser-defs.h"
49 #include "bfd.h" /* Required by objfiles.h. */
50 #include "symfile.h" /* Required by objfiles.h. */
51 #include "objfiles.h" /* For have_full_symbols and have_partial_symbols */
54 #include "type-stack.h"
57 #define parse_type(ps) builtin_type (ps->gdbarch ())
58 #define parse_d_type(ps) builtin_d_type (ps->gdbarch ())
60 /* Remap normal yacc parser interface names (yyparse, yylex, yyerror,
62 #define GDB_YY_REMAP_PREFIX d_
65 /* The state of the parser, used internally when we are parsing the
68 static struct parser_state *pstate = NULL;
70 /* The current type stack. */
71 static struct type_stack *type_stack;
75 static int yylex (void);
77 static void yyerror (const char *);
79 static int type_aggregate_p (struct type *);
85 /* Although the yacc "value" of an expression is not used,
86 since the result is stored in the structure being created,
87 other node types do have values. */
101 struct typed_stoken tsval;
104 struct symtoken ssym;
107 enum exp_opcode opcode;
108 struct stoken_vector svec;
112 /* YYSTYPE gets defined by %union */
113 static int parse_number (struct parser_state *, const char *,
114 int, int, YYSTYPE *);
117 %token <sval> IDENTIFIER UNKNOWN_NAME
118 %token <tsym> TYPENAME
119 %token <voidval> COMPLETE
121 /* A NAME_OR_INT is a symbol which is not known in the symbol table,
122 but which would parse as a valid number in the current input radix.
123 E.g. "c" when input_radix==16. Depending on the parse, it will be
124 turned into a name or into a number. */
126 %token <sval> NAME_OR_INT
128 %token <typed_val_int> INTEGER_LITERAL
129 %token <typed_val_float> FLOAT_LITERAL
130 %token <tsval> CHARACTER_LITERAL
131 %token <tsval> STRING_LITERAL
133 %type <svec> StringExp
134 %type <tval> BasicType TypeExp
135 %type <sval> IdentifierExp
136 %type <ival> ArrayLiteral
141 /* Keywords that have a constant value. */
142 %token TRUE_KEYWORD FALSE_KEYWORD NULL_KEYWORD
143 /* Class 'super' accessor. */
146 %token CAST_KEYWORD SIZEOF_KEYWORD
147 %token TYPEOF_KEYWORD TYPEID_KEYWORD
149 /* Comparison keywords. */
150 /* Type storage classes. */
151 %token IMMUTABLE_KEYWORD CONST_KEYWORD SHARED_KEYWORD
152 /* Non-scalar type keywords. */
153 %token STRUCT_KEYWORD UNION_KEYWORD
154 %token CLASS_KEYWORD INTERFACE_KEYWORD
155 %token ENUM_KEYWORD TEMPLATE_KEYWORD
156 %token DELEGATE_KEYWORD FUNCTION_KEYWORD
158 %token <sval> DOLLAR_VARIABLE
160 %token <opcode> ASSIGN_MODIFY
163 %right '=' ASSIGN_MODIFY
170 %left EQUAL NOTEQUAL '<' '>' LEQ GEQ
175 %left IDENTITY NOTIDENTITY
176 %right INCREMENT DECREMENT
188 /* Expressions, including the comma operator. */
196 | AssignExpression ',' CommaExpression
197 { pstate->wrap2<comma_operation> (); }
201 ConditionalExpression
202 | ConditionalExpression '=' AssignExpression
203 { pstate->wrap2<assign_operation> (); }
204 | ConditionalExpression ASSIGN_MODIFY AssignExpression
206 operation_up rhs = pstate->pop ();
207 operation_up lhs = pstate->pop ();
208 pstate->push_new<assign_modify_operation>
209 ($2, std::move (lhs), std::move (rhs));
213 ConditionalExpression:
215 | OrOrExpression '?' Expression ':' ConditionalExpression
217 operation_up last = pstate->pop ();
218 operation_up mid = pstate->pop ();
219 operation_up first = pstate->pop ();
220 pstate->push_new<ternop_cond_operation>
221 (std::move (first), std::move (mid),
228 | OrOrExpression OROR AndAndExpression
229 { pstate->wrap2<logical_or_operation> (); }
234 | AndAndExpression ANDAND OrExpression
235 { pstate->wrap2<logical_and_operation> (); }
240 | OrExpression '|' XorExpression
241 { pstate->wrap2<bitwise_ior_operation> (); }
246 | XorExpression '^' AndExpression
247 { pstate->wrap2<bitwise_xor_operation> (); }
252 | AndExpression '&' CmpExpression
253 { pstate->wrap2<bitwise_and_operation> (); }
264 ShiftExpression EQUAL ShiftExpression
265 { pstate->wrap2<equal_operation> (); }
266 | ShiftExpression NOTEQUAL ShiftExpression
267 { pstate->wrap2<notequal_operation> (); }
271 ShiftExpression IDENTITY ShiftExpression
272 { pstate->wrap2<equal_operation> (); }
273 | ShiftExpression NOTIDENTITY ShiftExpression
274 { pstate->wrap2<notequal_operation> (); }
278 ShiftExpression '<' ShiftExpression
279 { pstate->wrap2<less_operation> (); }
280 | ShiftExpression LEQ ShiftExpression
281 { pstate->wrap2<leq_operation> (); }
282 | ShiftExpression '>' ShiftExpression
283 { pstate->wrap2<gtr_operation> (); }
284 | ShiftExpression GEQ ShiftExpression
285 { pstate->wrap2<geq_operation> (); }
290 | ShiftExpression LSH AddExpression
291 { pstate->wrap2<lsh_operation> (); }
292 | ShiftExpression RSH AddExpression
293 { pstate->wrap2<rsh_operation> (); }
298 | AddExpression '+' MulExpression
299 { pstate->wrap2<add_operation> (); }
300 | AddExpression '-' MulExpression
301 { pstate->wrap2<sub_operation> (); }
302 | AddExpression '~' MulExpression
303 { pstate->wrap2<concat_operation> (); }
308 | MulExpression '*' UnaryExpression
309 { pstate->wrap2<mul_operation> (); }
310 | MulExpression '/' UnaryExpression
311 { pstate->wrap2<div_operation> (); }
312 | MulExpression '%' UnaryExpression
313 { pstate->wrap2<rem_operation> (); }
317 { pstate->wrap<unop_addr_operation> (); }
318 | INCREMENT UnaryExpression
319 { pstate->wrap<preinc_operation> (); }
320 | DECREMENT UnaryExpression
321 { pstate->wrap<predec_operation> (); }
322 | '*' UnaryExpression
323 { pstate->wrap<unop_ind_operation> (); }
324 | '-' UnaryExpression
325 { pstate->wrap<unary_neg_operation> (); }
326 | '+' UnaryExpression
327 { pstate->wrap<unary_plus_operation> (); }
328 | '!' UnaryExpression
329 { pstate->wrap<unary_logical_not_operation> (); }
330 | '~' UnaryExpression
331 { pstate->wrap<unary_complement_operation> (); }
332 | TypeExp '.' SIZEOF_KEYWORD
333 { pstate->wrap<unop_sizeof_operation> (); }
339 CAST_KEYWORD '(' TypeExp ')' UnaryExpression
340 { pstate->wrap2<unop_cast_type_operation> (); }
341 /* C style cast is illegal D, but is still recognised in
342 the grammar, so we keep this around for convenience. */
343 | '(' TypeExp ')' UnaryExpression
344 { pstate->wrap2<unop_cast_type_operation> (); }
349 | PostfixExpression HATHAT UnaryExpression
350 { pstate->wrap2<exp_operation> (); }
355 | PostfixExpression '.' COMPLETE
357 structop_base_operation *op
358 = new structop_ptr_operation (pstate->pop (), "");
359 pstate->mark_struct_expression (op);
360 pstate->push (operation_up (op));
362 | PostfixExpression '.' IDENTIFIER
364 pstate->push_new<structop_operation>
365 (pstate->pop (), copy_name ($3));
367 | PostfixExpression '.' IDENTIFIER COMPLETE
369 structop_base_operation *op
370 = new structop_operation (pstate->pop (), copy_name ($3));
371 pstate->mark_struct_expression (op);
372 pstate->push (operation_up (op));
374 | PostfixExpression '.' SIZEOF_KEYWORD
375 { pstate->wrap<unop_sizeof_operation> (); }
376 | PostfixExpression INCREMENT
377 { pstate->wrap<postinc_operation> (); }
378 | PostfixExpression DECREMENT
379 { pstate->wrap<postdec_operation> (); }
387 { pstate->arglist_len = 1; }
388 | ArgumentList ',' AssignExpression
389 { pstate->arglist_len++; }
394 { pstate->arglist_len = 0; }
399 PostfixExpression '('
400 { pstate->start_arglist (); }
403 std::vector<operation_up> args
404 = pstate->pop_vector (pstate->end_arglist ());
405 pstate->push_new<funcall_operation>
406 (pstate->pop (), std::move (args));
411 PostfixExpression '[' ArgumentList ']'
412 { if (pstate->arglist_len > 0)
414 std::vector<operation_up> args
415 = pstate->pop_vector (pstate->arglist_len);
416 pstate->push_new<multi_subscript_operation>
417 (pstate->pop (), std::move (args));
420 pstate->wrap2<subscript_operation> ();
425 PostfixExpression '[' ']'
426 { /* Do nothing. */ }
427 | PostfixExpression '[' AssignExpression DOTDOT AssignExpression ']'
429 operation_up last = pstate->pop ();
430 operation_up mid = pstate->pop ();
431 operation_up first = pstate->pop ();
432 pstate->push_new<ternop_slice_operation>
433 (std::move (first), std::move (mid),
440 { /* Do nothing. */ }
442 { struct bound_minimal_symbol msymbol;
443 std::string copy = copy_name ($1);
444 struct field_of_this_result is_a_field_of_this;
445 struct block_symbol sym;
447 /* Handle VAR, which could be local or global. */
448 sym = lookup_symbol (copy.c_str (),
449 pstate->expression_context_block,
450 VAR_DOMAIN, &is_a_field_of_this);
451 if (sym.symbol && SYMBOL_CLASS (sym.symbol) != LOC_TYPEDEF)
453 if (symbol_read_needs_frame (sym.symbol))
454 pstate->block_tracker->update (sym);
455 pstate->push_new<var_value_operation> (sym.symbol,
458 else if (is_a_field_of_this.type != NULL)
460 /* It hangs off of `this'. Must not inadvertently convert from a
461 method call to data ref. */
462 pstate->block_tracker->update (sym);
464 = make_operation<op_this_operation> ();
465 pstate->push_new<structop_ptr_operation>
466 (std::move (thisop), std::move (copy));
470 /* Lookup foreign name in global static symbols. */
471 msymbol = lookup_bound_minimal_symbol (copy.c_str ());
472 if (msymbol.minsym != NULL)
473 pstate->push_new<var_msym_value_operation> (msymbol);
474 else if (!have_full_symbols () && !have_partial_symbols ())
475 error (_("No symbol table is loaded. Use the \"file\" command"));
477 error (_("No symbol \"%s\" in current context."),
481 | TypeExp '.' IdentifierExp
482 { struct type *type = check_typedef ($1);
484 /* Check if the qualified name is in the global
485 context. However if the symbol has not already
486 been resolved, it's not likely to be found. */
487 if (type->code () == TYPE_CODE_MODULE)
489 struct block_symbol sym;
490 const char *type_name = TYPE_SAFE_NAME (type);
491 int type_name_len = strlen (type_name);
493 = string_printf ("%.*s.%.*s",
494 type_name_len, type_name,
498 lookup_symbol (name.c_str (),
499 (const struct block *) NULL,
501 pstate->push_symbol (name.c_str (), sym);
505 /* Check if the qualified name resolves as a member
506 of an aggregate or an enum type. */
507 if (!type_aggregate_p (type))
508 error (_("`%s' is not defined as an aggregate type."),
509 TYPE_SAFE_NAME (type));
511 pstate->push_new<scope_operation>
512 (type, copy_name ($3));
516 { pstate->push_dollar ($1); }
519 parse_number (pstate, $1.ptr, $1.length, 0, &val);
520 pstate->push_new<long_const_operation>
521 (val.typed_val_int.type, val.typed_val_int.val); }
523 { struct type *type = parse_d_type (pstate)->builtin_void;
524 type = lookup_pointer_type (type);
525 pstate->push_new<long_const_operation> (type, 0); }
527 { pstate->push_new<bool_operation> (true); }
529 { pstate->push_new<bool_operation> (false); }
531 { pstate->push_new<long_const_operation> ($1.type, $1.val); }
535 std::copy (std::begin ($1.val), std::end ($1.val),
537 pstate->push_new<float_const_operation> ($1.type, data);
540 { struct stoken_vector vec;
543 pstate->push_c_string (0, &vec); }
546 pstate->push_c_string (0, &$1);
547 for (i = 0; i < $1.len; ++i)
548 free ($1.tokens[i].ptr);
552 std::vector<operation_up> args
553 = pstate->pop_vector ($1);
554 pstate->push_new<array_operation>
555 (0, $1 - 1, std::move (args));
557 | TYPEOF_KEYWORD '(' Expression ')'
558 { pstate->wrap<typeof_operation> (); }
562 '[' ArgumentList_opt ']'
563 { $$ = pstate->arglist_len; }
572 { /* We copy the string here, and not in the
573 lexer, to guarantee that we do not leak a
574 string. Note that we follow the
575 NUL-termination convention of the
577 struct typed_stoken *vec = XNEW (struct typed_stoken);
582 vec->length = $1.length;
583 vec->ptr = (char *) malloc ($1.length + 1);
584 memcpy (vec->ptr, $1.ptr, $1.length + 1);
586 | StringExp STRING_LITERAL
587 { /* Note that we NUL-terminate here, but just
592 = XRESIZEVEC (struct typed_stoken, $$.tokens, $$.len);
594 p = (char *) malloc ($2.length + 1);
595 memcpy (p, $2.ptr, $2.length + 1);
597 $$.tokens[$$.len - 1].type = $2.type;
598 $$.tokens[$$.len - 1].length = $2.length;
599 $$.tokens[$$.len - 1].ptr = p;
605 { /* Do nothing. */ }
607 { pstate->push_new<type_operation> ($1); }
608 | BasicType BasicType2
609 { $$ = type_stack->follow_types ($1);
610 pstate->push_new<type_operation> ($$);
616 { type_stack->push (tp_pointer); }
618 { type_stack->push (tp_pointer); }
619 | '[' INTEGER_LITERAL ']'
620 { type_stack->push ($2.val);
621 type_stack->push (tp_array); }
622 | '[' INTEGER_LITERAL ']' BasicType2
623 { type_stack->push ($2.val);
624 type_stack->push (tp_array); }
634 /* Return true if the type is aggregate-like. */
637 type_aggregate_p (struct type *type)
639 return (type->code () == TYPE_CODE_STRUCT
640 || type->code () == TYPE_CODE_UNION
641 || type->code () == TYPE_CODE_MODULE
642 || (type->code () == TYPE_CODE_ENUM
643 && TYPE_DECLARED_CLASS (type)));
646 /* Take care of parsing a number (anything that starts with a digit).
647 Set yylval and return the token type; update lexptr.
648 LEN is the number of characters in it. */
650 /*** Needs some error checking for the float case ***/
653 parse_number (struct parser_state *ps, const char *p,
654 int len, int parsed_float, YYSTYPE *putithere)
662 int base = input_radix;
666 /* We have found a "L" or "U" suffix. */
667 int found_suffix = 0;
670 struct type *signed_type;
671 struct type *unsigned_type;
677 /* Strip out all embedded '_' before passing to parse_float. */
678 s = (char *) alloca (len + 1);
689 /* Check suffix for `i' , `fi' or `li' (idouble, ifloat or ireal). */
690 if (len >= 1 && tolower (s[len - 1]) == 'i')
692 if (len >= 2 && tolower (s[len - 2]) == 'f')
694 putithere->typed_val_float.type
695 = parse_d_type (ps)->builtin_ifloat;
698 else if (len >= 2 && tolower (s[len - 2]) == 'l')
700 putithere->typed_val_float.type
701 = parse_d_type (ps)->builtin_ireal;
706 putithere->typed_val_float.type
707 = parse_d_type (ps)->builtin_idouble;
711 /* Check suffix for `f' or `l'' (float or real). */
712 else if (len >= 1 && tolower (s[len - 1]) == 'f')
714 putithere->typed_val_float.type
715 = parse_d_type (ps)->builtin_float;
718 else if (len >= 1 && tolower (s[len - 1]) == 'l')
720 putithere->typed_val_float.type
721 = parse_d_type (ps)->builtin_real;
724 /* Default type if no suffix. */
727 putithere->typed_val_float.type
728 = parse_d_type (ps)->builtin_double;
731 if (!parse_float (s, len,
732 putithere->typed_val_float.type,
733 putithere->typed_val_float.val))
736 return FLOAT_LITERAL;
739 /* Handle base-switching prefixes 0x, 0b, 0 */
772 continue; /* Ignore embedded '_'. */
773 if (c >= 'A' && c <= 'Z')
775 if (c != 'l' && c != 'u')
777 if (c >= '0' && c <= '9')
785 if (base > 10 && c >= 'a' && c <= 'f')
789 n += i = c - 'a' + 10;
791 else if (c == 'l' && long_p == 0)
796 else if (c == 'u' && unsigned_p == 0)
802 return ERROR; /* Char not a digit */
805 return ERROR; /* Invalid digit in this base. */
806 /* Portably test for integer overflow. */
807 if (c != 'l' && c != 'u')
809 ULONGEST n2 = prevn * base;
810 if ((n2 / base != prevn) || (n2 + i < prevn))
811 error (_("Numeric constant too large."));
816 /* An integer constant is an int or a long. An L suffix forces it to
817 be long, and a U suffix forces it to be unsigned. To figure out
818 whether it fits, we shift it right and see whether anything remains.
819 Note that we can't shift sizeof (LONGEST) * HOST_CHAR_BIT bits or
820 more in one operation, because many compilers will warn about such a
821 shift (which always produces a zero result). To deal with the case
822 where it is we just always shift the value more than once, with fewer
824 un = (ULONGEST) n >> 2;
825 if (long_p == 0 && (un >> 30) == 0)
827 high_bit = ((ULONGEST) 1) << 31;
828 signed_type = parse_d_type (ps)->builtin_int;
829 /* For decimal notation, keep the sign of the worked out type. */
830 if (base == 10 && !unsigned_p)
831 unsigned_type = parse_d_type (ps)->builtin_long;
833 unsigned_type = parse_d_type (ps)->builtin_uint;
838 if (sizeof (ULONGEST) * HOST_CHAR_BIT < 64)
839 /* A long long does not fit in a LONGEST. */
840 shift = (sizeof (ULONGEST) * HOST_CHAR_BIT - 1);
843 high_bit = (ULONGEST) 1 << shift;
844 signed_type = parse_d_type (ps)->builtin_long;
845 unsigned_type = parse_d_type (ps)->builtin_ulong;
848 putithere->typed_val_int.val = n;
850 /* If the high bit of the worked out type is set then this number
851 has to be unsigned_type. */
852 if (unsigned_p || (n & high_bit))
853 putithere->typed_val_int.type = unsigned_type;
855 putithere->typed_val_int.type = signed_type;
857 return INTEGER_LITERAL;
860 /* Temporary obstack used for holding strings. */
861 static struct obstack tempbuf;
862 static int tempbuf_init;
864 /* Parse a string or character literal from TOKPTR. The string or
865 character may be wide or unicode. *OUTPTR is set to just after the
866 end of the literal in the input string. The resulting token is
867 stored in VALUE. This returns a token value, either STRING or
868 CHAR, depending on what was parsed. *HOST_CHARS is set to the
869 number of host characters in the literal. */
872 parse_string_or_char (const char *tokptr, const char **outptr,
873 struct typed_stoken *value, int *host_chars)
877 /* Build the gdb internal form of the input string in tempbuf. Note
878 that the buffer is null byte terminated *only* for the
879 convenience of debugging gdb itself and printing the buffer
880 contents when the buffer contains no embedded nulls. Gdb does
881 not depend upon the buffer being null byte terminated, it uses
882 the length string instead. This allows gdb to handle C strings
883 (as well as strings in other languages) with embedded null
889 obstack_free (&tempbuf, NULL);
890 obstack_init (&tempbuf);
892 /* Skip the quote. */
904 *host_chars += c_parse_escape (&tokptr, &tempbuf);
910 obstack_1grow (&tempbuf, c);
912 /* FIXME: this does the wrong thing with multi-byte host
913 characters. We could use mbrlen here, but that would
914 make "set host-charset" a bit less useful. */
919 if (*tokptr != quote)
921 if (quote == '"' || quote == '`')
922 error (_("Unterminated string in expression."));
924 error (_("Unmatched single quote."));
928 /* FIXME: should instead use own language string_type enum
929 and handle D-specific string suffixes here. */
931 value->type = C_CHAR;
933 value->type = C_STRING;
935 value->ptr = (char *) obstack_base (&tempbuf);
936 value->length = obstack_object_size (&tempbuf);
940 return quote == '\'' ? CHARACTER_LITERAL : STRING_LITERAL;
947 enum exp_opcode opcode;
950 static const struct token tokentab3[] =
952 {"^^=", ASSIGN_MODIFY, BINOP_EXP},
953 {"<<=", ASSIGN_MODIFY, BINOP_LSH},
954 {">>=", ASSIGN_MODIFY, BINOP_RSH},
957 static const struct token tokentab2[] =
959 {"+=", ASSIGN_MODIFY, BINOP_ADD},
960 {"-=", ASSIGN_MODIFY, BINOP_SUB},
961 {"*=", ASSIGN_MODIFY, BINOP_MUL},
962 {"/=", ASSIGN_MODIFY, BINOP_DIV},
963 {"%=", ASSIGN_MODIFY, BINOP_REM},
964 {"|=", ASSIGN_MODIFY, BINOP_BITWISE_IOR},
965 {"&=", ASSIGN_MODIFY, BINOP_BITWISE_AND},
966 {"^=", ASSIGN_MODIFY, BINOP_BITWISE_XOR},
967 {"++", INCREMENT, OP_NULL},
968 {"--", DECREMENT, OP_NULL},
969 {"&&", ANDAND, OP_NULL},
970 {"||", OROR, OP_NULL},
971 {"^^", HATHAT, OP_NULL},
972 {"<<", LSH, OP_NULL},
973 {">>", RSH, OP_NULL},
974 {"==", EQUAL, OP_NULL},
975 {"!=", NOTEQUAL, OP_NULL},
976 {"<=", LEQ, OP_NULL},
977 {">=", GEQ, OP_NULL},
978 {"..", DOTDOT, OP_NULL},
981 /* Identifier-like tokens. */
982 static const struct token ident_tokens[] =
984 {"is", IDENTITY, OP_NULL},
985 {"!is", NOTIDENTITY, OP_NULL},
987 {"cast", CAST_KEYWORD, OP_NULL},
988 {"const", CONST_KEYWORD, OP_NULL},
989 {"immutable", IMMUTABLE_KEYWORD, OP_NULL},
990 {"shared", SHARED_KEYWORD, OP_NULL},
991 {"super", SUPER_KEYWORD, OP_NULL},
993 {"null", NULL_KEYWORD, OP_NULL},
994 {"true", TRUE_KEYWORD, OP_NULL},
995 {"false", FALSE_KEYWORD, OP_NULL},
997 {"init", INIT_KEYWORD, OP_NULL},
998 {"sizeof", SIZEOF_KEYWORD, OP_NULL},
999 {"typeof", TYPEOF_KEYWORD, OP_NULL},
1000 {"typeid", TYPEID_KEYWORD, OP_NULL},
1002 {"delegate", DELEGATE_KEYWORD, OP_NULL},
1003 {"function", FUNCTION_KEYWORD, OP_NULL},
1004 {"struct", STRUCT_KEYWORD, OP_NULL},
1005 {"union", UNION_KEYWORD, OP_NULL},
1006 {"class", CLASS_KEYWORD, OP_NULL},
1007 {"interface", INTERFACE_KEYWORD, OP_NULL},
1008 {"enum", ENUM_KEYWORD, OP_NULL},
1009 {"template", TEMPLATE_KEYWORD, OP_NULL},
1012 /* This is set if a NAME token appeared at the very end of the input
1013 string, with no whitespace separating the name from the EOF. This
1014 is used only when parsing to do field name completion. */
1015 static int saw_name_at_eof;
1017 /* This is set if the previously-returned token was a structure operator.
1018 This is used only when parsing to do field name completion. */
1019 static int last_was_structop;
1021 /* Depth of parentheses. */
1022 static int paren_depth;
1024 /* Read one token, getting characters through lexptr. */
1027 lex_one_token (struct parser_state *par_state)
1032 const char *tokstart;
1033 int saw_structop = last_was_structop;
1035 last_was_structop = 0;
1039 pstate->prev_lexptr = pstate->lexptr;
1041 tokstart = pstate->lexptr;
1042 /* See if it is a special token of length 3. */
1043 for (i = 0; i < sizeof tokentab3 / sizeof tokentab3[0]; i++)
1044 if (strncmp (tokstart, tokentab3[i].oper, 3) == 0)
1046 pstate->lexptr += 3;
1047 yylval.opcode = tokentab3[i].opcode;
1048 return tokentab3[i].token;
1051 /* See if it is a special token of length 2. */
1052 for (i = 0; i < sizeof tokentab2 / sizeof tokentab2[0]; i++)
1053 if (strncmp (tokstart, tokentab2[i].oper, 2) == 0)
1055 pstate->lexptr += 2;
1056 yylval.opcode = tokentab2[i].opcode;
1057 return tokentab2[i].token;
1060 switch (c = *tokstart)
1063 /* If we're parsing for field name completion, and the previous
1064 token allows such completion, return a COMPLETE token.
1065 Otherwise, we were already scanning the original text, and
1066 we're really done. */
1067 if (saw_name_at_eof)
1069 saw_name_at_eof = 0;
1072 else if (saw_structop)
1091 if (paren_depth == 0)
1098 if (pstate->comma_terminates && paren_depth == 0)
1104 /* Might be a floating point number. */
1105 if (pstate->lexptr[1] < '0' || pstate->lexptr[1] > '9')
1107 if (pstate->parse_completion)
1108 last_was_structop = 1;
1109 goto symbol; /* Nope, must be a symbol. */
1124 /* It's a number. */
1125 int got_dot = 0, got_e = 0, toktype;
1126 const char *p = tokstart;
1127 int hex = input_radix > 10;
1129 if (c == '0' && (p[1] == 'x' || p[1] == 'X'))
1137 /* Hex exponents start with 'p', because 'e' is a valid hex
1138 digit and thus does not indicate a floating point number
1139 when the radix is hex. */
1140 if ((!hex && !got_e && tolower (p[0]) == 'e')
1141 || (hex && !got_e && tolower (p[0] == 'p')))
1142 got_dot = got_e = 1;
1143 /* A '.' always indicates a decimal floating point number
1144 regardless of the radix. If we have a '..' then its the
1145 end of the number and the beginning of a slice. */
1146 else if (!got_dot && (p[0] == '.' && p[1] != '.'))
1148 /* This is the sign of the exponent, not the end of the number. */
1149 else if (got_e && (tolower (p[-1]) == 'e' || tolower (p[-1]) == 'p')
1150 && (*p == '-' || *p == '+'))
1152 /* We will take any letters or digits, ignoring any embedded '_'.
1153 parse_number will complain if past the radix, or if L or U are
1155 else if ((*p < '0' || *p > '9') && (*p != '_')
1156 && ((*p < 'a' || *p > 'z') && (*p < 'A' || *p > 'Z')))
1160 toktype = parse_number (par_state, tokstart, p - tokstart,
1161 got_dot|got_e, &yylval);
1162 if (toktype == ERROR)
1164 char *err_copy = (char *) alloca (p - tokstart + 1);
1166 memcpy (err_copy, tokstart, p - tokstart);
1167 err_copy[p - tokstart] = 0;
1168 error (_("Invalid number \"%s\"."), err_copy);
1176 const char *p = &tokstart[1];
1177 size_t len = strlen ("entry");
1179 while (isspace (*p))
1181 if (strncmp (p, "entry", len) == 0 && !isalnum (p[len])
1184 pstate->lexptr = &p[len];
1215 int result = parse_string_or_char (tokstart, &pstate->lexptr,
1216 &yylval.tsval, &host_len);
1217 if (result == CHARACTER_LITERAL)
1220 error (_("Empty character constant."));
1221 else if (host_len > 2 && c == '\'')
1224 namelen = pstate->lexptr - tokstart - 1;
1227 else if (host_len > 1)
1228 error (_("Invalid character constant."));
1234 if (!(c == '_' || c == '$'
1235 || (c >= 'a' && c <= 'z') || (c >= 'A' && c <= 'Z')))
1236 /* We must have come across a bad character (e.g. ';'). */
1237 error (_("Invalid character '%c' in expression"), c);
1239 /* It's a name. See how long it is. */
1241 for (c = tokstart[namelen];
1242 (c == '_' || c == '$' || (c >= '0' && c <= '9')
1243 || (c >= 'a' && c <= 'z') || (c >= 'A' && c <= 'Z'));)
1244 c = tokstart[++namelen];
1246 /* The token "if" terminates the expression and is NOT
1247 removed from the input stream. */
1248 if (namelen == 2 && tokstart[0] == 'i' && tokstart[1] == 'f')
1251 /* For the same reason (breakpoint conditions), "thread N"
1252 terminates the expression. "thread" could be an identifier, but
1253 an identifier is never followed by a number without intervening
1254 punctuation. "task" is similar. Handle abbreviations of these,
1255 similarly to breakpoint.c:find_condition_and_thread. */
1257 && (strncmp (tokstart, "thread", namelen) == 0
1258 || strncmp (tokstart, "task", namelen) == 0)
1259 && (tokstart[namelen] == ' ' || tokstart[namelen] == '\t'))
1261 const char *p = tokstart + namelen + 1;
1263 while (*p == ' ' || *p == '\t')
1265 if (*p >= '0' && *p <= '9')
1269 pstate->lexptr += namelen;
1273 yylval.sval.ptr = tokstart;
1274 yylval.sval.length = namelen;
1276 /* Catch specific keywords. */
1277 std::string copy = copy_name (yylval.sval);
1278 for (i = 0; i < sizeof ident_tokens / sizeof ident_tokens[0]; i++)
1279 if (copy == ident_tokens[i].oper)
1281 /* It is ok to always set this, even though we don't always
1282 strictly need to. */
1283 yylval.opcode = ident_tokens[i].opcode;
1284 return ident_tokens[i].token;
1287 if (*tokstart == '$')
1288 return DOLLAR_VARIABLE;
1291 = language_lookup_primitive_type (par_state->language (),
1292 par_state->gdbarch (), copy.c_str ());
1293 if (yylval.tsym.type != NULL)
1296 /* Input names that aren't symbols but ARE valid hex numbers,
1297 when the input radix permits them, can be names or numbers
1298 depending on the parse. Note we support radixes > 16 here. */
1299 if ((tokstart[0] >= 'a' && tokstart[0] < 'a' + input_radix - 10)
1300 || (tokstart[0] >= 'A' && tokstart[0] < 'A' + input_radix - 10))
1302 YYSTYPE newlval; /* Its value is ignored. */
1303 int hextype = parse_number (par_state, tokstart, namelen, 0, &newlval);
1304 if (hextype == INTEGER_LITERAL)
1308 if (pstate->parse_completion && *pstate->lexptr == '\0')
1309 saw_name_at_eof = 1;
1314 /* An object of this type is pushed on a FIFO by the "outer" lexer. */
1315 struct token_and_value
1322 /* A FIFO of tokens that have been read but not yet returned to the
1324 static std::vector<token_and_value> token_fifo;
1326 /* Non-zero if the lexer should return tokens from the FIFO. */
1329 /* Temporary storage for yylex; this holds symbol names as they are
1331 static auto_obstack name_obstack;
1333 /* Classify an IDENTIFIER token. The contents of the token are in `yylval'.
1334 Updates yylval and returns the new token type. BLOCK is the block
1335 in which lookups start; this can be NULL to mean the global scope. */
1338 classify_name (struct parser_state *par_state, const struct block *block)
1340 struct block_symbol sym;
1341 struct field_of_this_result is_a_field_of_this;
1343 std::string copy = copy_name (yylval.sval);
1345 sym = lookup_symbol (copy.c_str (), block, VAR_DOMAIN, &is_a_field_of_this);
1346 if (sym.symbol && SYMBOL_CLASS (sym.symbol) == LOC_TYPEDEF)
1348 yylval.tsym.type = SYMBOL_TYPE (sym.symbol);
1351 else if (sym.symbol == NULL)
1353 /* Look-up first for a module name, then a type. */
1354 sym = lookup_symbol (copy.c_str (), block, MODULE_DOMAIN, NULL);
1355 if (sym.symbol == NULL)
1356 sym = lookup_symbol (copy.c_str (), block, STRUCT_DOMAIN, NULL);
1358 if (sym.symbol != NULL)
1360 yylval.tsym.type = SYMBOL_TYPE (sym.symbol);
1364 return UNKNOWN_NAME;
1370 /* Like classify_name, but used by the inner loop of the lexer, when a
1371 name might have already been seen. CONTEXT is the context type, or
1372 NULL if this is the first component of a name. */
1375 classify_inner_name (struct parser_state *par_state,
1376 const struct block *block, struct type *context)
1380 if (context == NULL)
1381 return classify_name (par_state, block);
1383 type = check_typedef (context);
1384 if (!type_aggregate_p (type))
1387 std::string copy = copy_name (yylval.ssym.stoken);
1388 yylval.ssym.sym = d_lookup_nested_symbol (type, copy.c_str (), block);
1390 if (yylval.ssym.sym.symbol == NULL)
1393 if (SYMBOL_CLASS (yylval.ssym.sym.symbol) == LOC_TYPEDEF)
1395 yylval.tsym.type = SYMBOL_TYPE (yylval.ssym.sym.symbol);
1402 /* The outer level of a two-level lexer. This calls the inner lexer
1403 to return tokens. It then either returns these tokens, or
1404 aggregates them into a larger token. This lets us work around a
1405 problem in our parsing approach, where the parser could not
1406 distinguish between qualified names and qualified types at the
1412 token_and_value current;
1414 struct type *context_type = NULL;
1415 int last_to_examine, next_to_examine, checkpoint;
1416 const struct block *search_block;
1418 if (popping && !token_fifo.empty ())
1422 /* Read the first token and decide what to do. */
1423 current.token = lex_one_token (pstate);
1424 if (current.token != IDENTIFIER && current.token != '.')
1425 return current.token;
1427 /* Read any sequence of alternating "." and identifier tokens into
1429 current.value = yylval;
1430 token_fifo.push_back (current);
1431 last_was_dot = current.token == '.';
1435 current.token = lex_one_token (pstate);
1436 current.value = yylval;
1437 token_fifo.push_back (current);
1439 if ((last_was_dot && current.token != IDENTIFIER)
1440 || (!last_was_dot && current.token != '.'))
1443 last_was_dot = !last_was_dot;
1447 /* We always read one extra token, so compute the number of tokens
1448 to examine accordingly. */
1449 last_to_examine = token_fifo.size () - 2;
1450 next_to_examine = 0;
1452 current = token_fifo[next_to_examine];
1455 /* If we are not dealing with a typename, now is the time to find out. */
1456 if (current.token == IDENTIFIER)
1458 yylval = current.value;
1459 current.token = classify_name (pstate, pstate->expression_context_block);
1460 current.value = yylval;
1463 /* If the IDENTIFIER is not known, it could be a package symbol,
1464 first try building up a name until we find the qualified module. */
1465 if (current.token == UNKNOWN_NAME)
1467 name_obstack.clear ();
1468 obstack_grow (&name_obstack, current.value.sval.ptr,
1469 current.value.sval.length);
1473 while (next_to_examine <= last_to_examine)
1475 token_and_value next;
1477 next = token_fifo[next_to_examine];
1480 if (next.token == IDENTIFIER && last_was_dot)
1482 /* Update the partial name we are constructing. */
1483 obstack_grow_str (&name_obstack, ".");
1484 obstack_grow (&name_obstack, next.value.sval.ptr,
1485 next.value.sval.length);
1487 yylval.sval.ptr = (char *) obstack_base (&name_obstack);
1488 yylval.sval.length = obstack_object_size (&name_obstack);
1490 current.token = classify_name (pstate,
1491 pstate->expression_context_block);
1492 current.value = yylval;
1494 /* We keep going until we find a TYPENAME. */
1495 if (current.token == TYPENAME)
1497 /* Install it as the first token in the FIFO. */
1498 token_fifo[0] = current;
1499 token_fifo.erase (token_fifo.begin () + 1,
1500 token_fifo.begin () + next_to_examine);
1504 else if (next.token == '.' && !last_was_dot)
1508 /* We've reached the end of the name. */
1513 /* Reset our current token back to the start, if we found nothing
1514 this means that we will just jump to do pop. */
1515 current = token_fifo[0];
1516 next_to_examine = 1;
1518 if (current.token != TYPENAME && current.token != '.')
1521 name_obstack.clear ();
1523 if (current.token == '.')
1524 search_block = NULL;
1527 gdb_assert (current.token == TYPENAME);
1528 search_block = pstate->expression_context_block;
1529 obstack_grow (&name_obstack, current.value.sval.ptr,
1530 current.value.sval.length);
1531 context_type = current.value.tsym.type;
1535 last_was_dot = current.token == '.';
1537 while (next_to_examine <= last_to_examine)
1539 token_and_value next;
1541 next = token_fifo[next_to_examine];
1544 if (next.token == IDENTIFIER && last_was_dot)
1548 yylval = next.value;
1549 classification = classify_inner_name (pstate, search_block,
1551 /* We keep going until we either run out of names, or until
1552 we have a qualified name which is not a type. */
1553 if (classification != TYPENAME && classification != IDENTIFIER)
1556 /* Accept up to this token. */
1557 checkpoint = next_to_examine;
1559 /* Update the partial name we are constructing. */
1560 if (context_type != NULL)
1562 /* We don't want to put a leading "." into the name. */
1563 obstack_grow_str (&name_obstack, ".");
1565 obstack_grow (&name_obstack, next.value.sval.ptr,
1566 next.value.sval.length);
1568 yylval.sval.ptr = (char *) obstack_base (&name_obstack);
1569 yylval.sval.length = obstack_object_size (&name_obstack);
1570 current.value = yylval;
1571 current.token = classification;
1575 if (classification == IDENTIFIER)
1578 context_type = yylval.tsym.type;
1580 else if (next.token == '.' && !last_was_dot)
1584 /* We've reached the end of the name. */
1589 /* If we have a replacement token, install it as the first token in
1590 the FIFO, and delete the other constituent tokens. */
1593 token_fifo[0] = current;
1595 token_fifo.erase (token_fifo.begin () + 1,
1596 token_fifo.begin () + checkpoint);
1600 current = token_fifo[0];
1601 token_fifo.erase (token_fifo.begin ());
1602 yylval = current.value;
1603 return current.token;
1607 d_parse (struct parser_state *par_state)
1609 /* Setting up the parser state. */
1610 scoped_restore pstate_restore = make_scoped_restore (&pstate);
1611 gdb_assert (par_state != NULL);
1614 scoped_restore restore_yydebug = make_scoped_restore (&yydebug,
1617 struct type_stack stack;
1618 scoped_restore restore_type_stack = make_scoped_restore (&type_stack,
1621 /* Initialize some state used by the lexer. */
1622 last_was_structop = 0;
1623 saw_name_at_eof = 0;
1626 token_fifo.clear ();
1628 name_obstack.clear ();
1630 int result = yyparse ();
1632 pstate->set_operation (pstate->pop ());
1637 yyerror (const char *msg)
1639 if (pstate->prev_lexptr)
1640 pstate->lexptr = pstate->prev_lexptr;
1642 error (_("A %s in expression, near `%s'."), msg, pstate->lexptr);