1 /* YACC parser for D expressions, for GDB.
3 Copyright (C) 2014-2015 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 */
55 #define parse_type(ps) builtin_type (parse_gdbarch (ps))
56 #define parse_d_type(ps) builtin_d_type (parse_gdbarch (ps))
58 /* Remap normal yacc parser interface names (yyparse, yylex, yyerror, etc),
59 as well as gratuitiously global symbol names, so we can have multiple
60 yacc generated parsers in gdb. Note that these are only the variables
61 produced by yacc. If other parser generators (bison, byacc, etc) produce
62 additional global names that conflict at link time, then those parser
63 generators need to be fixed instead of adding those names to this list. */
65 #define yymaxdepth d_maxdepth
66 #define yyparse d_parse_internal
68 #define yyerror d_error
71 #define yydebug d_debug
80 #define yyerrflag d_errflag
81 #define yynerrs d_nerrs
86 #define yystate d_state
92 #define yyreds d_reds /* With YYDEBUG defined */
93 #define yytoks d_toks /* With YYDEBUG defined */
94 #define yyname d_name /* With YYDEBUG defined */
95 #define yyrule d_rule /* With YYDEBUG defined */
98 #define yydefre d_yydefred
99 #define yydgoto d_yydgoto
100 #define yysindex d_yysindex
101 #define yyrindex d_yyrindex
102 #define yygindex d_yygindex
103 #define yytable d_yytable
104 #define yycheck d_yycheck
106 #define yysslim d_yysslim
107 #define yyssp d_yyssp
108 #define yystacksize d_yystacksize
110 #define yyvsp d_yyvsp
113 #define YYDEBUG 1 /* Default to yydebug support */
116 #define YYFPRINTF parser_fprintf
118 /* The state of the parser, used internally when we are parsing the
121 static struct parser_state *pstate = NULL;
125 static int yylex (void);
127 void yyerror (char *);
131 /* Although the yacc "value" of an expression is not used,
132 since the result is stored in the structure being created,
133 other node types do have values. */
147 struct typed_stoken tsval;
150 struct symtoken ssym;
153 enum exp_opcode opcode;
154 struct stoken_vector svec;
158 /* YYSTYPE gets defined by %union */
159 static int parse_number (struct parser_state *, const char *,
160 int, int, YYSTYPE *);
162 static void push_expression_name (struct parser_state *, struct stoken);
165 %token <sval> IDENTIFIER
166 %token <tsym> TYPENAME
167 %token <voidval> COMPLETE
169 /* A NAME_OR_INT is a symbol which is not known in the symbol table,
170 but which would parse as a valid number in the current input radix.
171 E.g. "c" when input_radix==16. Depending on the parse, it will be
172 turned into a name or into a number. */
174 %token <sval> NAME_OR_INT
176 %token <typed_val_int> INTEGER_LITERAL
177 %token <typed_val_float> FLOAT_LITERAL
178 %token <tsval> CHARACTER_LITERAL
179 %token <tsval> STRING_LITERAL
181 %type <svec> StringExp
182 %type <tval> BasicType TypeExp
183 %type <sval> IdentifierExp
184 %type <ival> ArrayLiteral
189 /* Keywords that have a constant value. */
190 %token TRUE_KEYWORD FALSE_KEYWORD NULL_KEYWORD
191 /* Class 'super' accessor. */
194 %token CAST_KEYWORD SIZEOF_KEYWORD
195 %token TYPEOF_KEYWORD TYPEID_KEYWORD
197 /* Comparison keywords. */
198 /* Type storage classes. */
199 %token IMMUTABLE_KEYWORD CONST_KEYWORD SHARED_KEYWORD
200 /* Non-scalar type keywords. */
201 %token STRUCT_KEYWORD UNION_KEYWORD
202 %token CLASS_KEYWORD INTERFACE_KEYWORD
203 %token ENUM_KEYWORD TEMPLATE_KEYWORD
204 %token DELEGATE_KEYWORD FUNCTION_KEYWORD
206 %token <sval> DOLLAR_VARIABLE
208 %token <opcode> ASSIGN_MODIFY
211 %right '=' ASSIGN_MODIFY
218 %left EQUAL NOTEQUAL '<' '>' LEQ GEQ
223 %left IDENTITY NOTIDENTITY
224 %right INCREMENT DECREMENT
236 /* Expressions, including the comma operator. */
244 | AssignExpression ',' CommaExpression
245 { write_exp_elt_opcode (pstate, BINOP_COMMA); }
249 ConditionalExpression
250 | ConditionalExpression '=' AssignExpression
251 { write_exp_elt_opcode (pstate, BINOP_ASSIGN); }
252 | ConditionalExpression ASSIGN_MODIFY AssignExpression
253 { write_exp_elt_opcode (pstate, BINOP_ASSIGN_MODIFY);
254 write_exp_elt_opcode (pstate, $2);
255 write_exp_elt_opcode (pstate, BINOP_ASSIGN_MODIFY); }
258 ConditionalExpression:
260 | OrOrExpression '?' Expression ':' ConditionalExpression
261 { write_exp_elt_opcode (pstate, TERNOP_COND); }
266 | OrOrExpression OROR AndAndExpression
267 { write_exp_elt_opcode (pstate, BINOP_LOGICAL_OR); }
272 | AndAndExpression ANDAND OrExpression
273 { write_exp_elt_opcode (pstate, BINOP_LOGICAL_AND); }
278 | OrExpression '|' XorExpression
279 { write_exp_elt_opcode (pstate, BINOP_BITWISE_IOR); }
284 | XorExpression '^' AndExpression
285 { write_exp_elt_opcode (pstate, BINOP_BITWISE_XOR); }
290 | AndExpression '&' CmpExpression
291 { write_exp_elt_opcode (pstate, BINOP_BITWISE_AND); }
302 ShiftExpression EQUAL ShiftExpression
303 { write_exp_elt_opcode (pstate, BINOP_EQUAL); }
304 | ShiftExpression NOTEQUAL ShiftExpression
305 { write_exp_elt_opcode (pstate, BINOP_NOTEQUAL); }
309 ShiftExpression IDENTITY ShiftExpression
310 { write_exp_elt_opcode (pstate, BINOP_EQUAL); }
311 | ShiftExpression NOTIDENTITY ShiftExpression
312 { write_exp_elt_opcode (pstate, BINOP_NOTEQUAL); }
316 ShiftExpression '<' ShiftExpression
317 { write_exp_elt_opcode (pstate, BINOP_LESS); }
318 | ShiftExpression LEQ ShiftExpression
319 { write_exp_elt_opcode (pstate, BINOP_LEQ); }
320 | ShiftExpression '>' ShiftExpression
321 { write_exp_elt_opcode (pstate, BINOP_GTR); }
322 | ShiftExpression GEQ ShiftExpression
323 { write_exp_elt_opcode (pstate, BINOP_GEQ); }
328 | ShiftExpression LSH AddExpression
329 { write_exp_elt_opcode (pstate, BINOP_LSH); }
330 | ShiftExpression RSH AddExpression
331 { write_exp_elt_opcode (pstate, BINOP_RSH); }
336 | AddExpression '+' MulExpression
337 { write_exp_elt_opcode (pstate, BINOP_ADD); }
338 | AddExpression '-' MulExpression
339 { write_exp_elt_opcode (pstate, BINOP_SUB); }
340 | AddExpression '~' MulExpression
341 { write_exp_elt_opcode (pstate, BINOP_CONCAT); }
346 | MulExpression '*' UnaryExpression
347 { write_exp_elt_opcode (pstate, BINOP_MUL); }
348 | MulExpression '/' UnaryExpression
349 { write_exp_elt_opcode (pstate, BINOP_DIV); }
350 | MulExpression '%' UnaryExpression
351 { write_exp_elt_opcode (pstate, BINOP_REM); }
355 { write_exp_elt_opcode (pstate, UNOP_ADDR); }
356 | INCREMENT UnaryExpression
357 { write_exp_elt_opcode (pstate, UNOP_PREINCREMENT); }
358 | DECREMENT UnaryExpression
359 { write_exp_elt_opcode (pstate, UNOP_PREDECREMENT); }
360 | '*' UnaryExpression
361 { write_exp_elt_opcode (pstate, UNOP_IND); }
362 | '-' UnaryExpression
363 { write_exp_elt_opcode (pstate, UNOP_NEG); }
364 | '+' UnaryExpression
365 { write_exp_elt_opcode (pstate, UNOP_PLUS); }
366 | '!' UnaryExpression
367 { write_exp_elt_opcode (pstate, UNOP_LOGICAL_NOT); }
368 | '~' UnaryExpression
369 { write_exp_elt_opcode (pstate, UNOP_COMPLEMENT); }
375 CAST_KEYWORD '(' TypeExp ')' UnaryExpression
376 { write_exp_elt_opcode (pstate, UNOP_CAST);
377 write_exp_elt_type (pstate, $3);
378 write_exp_elt_opcode (pstate, UNOP_CAST); }
379 /* C style cast is illegal D, but is still recognised in
380 the grammar, so we keep this around for convenience. */
381 | '(' TypeExp ')' UnaryExpression
382 { write_exp_elt_opcode (pstate, UNOP_CAST);
383 write_exp_elt_type (pstate, $2);
384 write_exp_elt_opcode (pstate, UNOP_CAST); }
389 | PostfixExpression HATHAT UnaryExpression
390 { write_exp_elt_opcode (pstate, BINOP_EXP); }
395 | PostfixExpression INCREMENT
396 { write_exp_elt_opcode (pstate, UNOP_POSTINCREMENT); }
397 | PostfixExpression DECREMENT
398 { write_exp_elt_opcode (pstate, UNOP_POSTDECREMENT); }
407 | ArgumentList ',' AssignExpression
418 PostfixExpression '('
419 { start_arglist (); }
421 { write_exp_elt_opcode (pstate, OP_FUNCALL);
422 write_exp_elt_longcst (pstate, (LONGEST) end_arglist ());
423 write_exp_elt_opcode (pstate, OP_FUNCALL); }
427 PostfixExpression '[' ArgumentList ']'
428 { if (arglist_len > 0)
430 write_exp_elt_opcode (pstate, MULTI_SUBSCRIPT);
431 write_exp_elt_longcst (pstate, (LONGEST) arglist_len);
432 write_exp_elt_opcode (pstate, MULTI_SUBSCRIPT);
435 write_exp_elt_opcode (pstate, BINOP_SUBSCRIPT);
440 PostfixExpression '[' ']'
441 { /* Do nothing. */ }
442 | PostfixExpression '[' AssignExpression DOTDOT AssignExpression ']'
443 { write_exp_elt_opcode (pstate, TERNOP_SLICE); }
448 { /* Do nothing. */ }
450 { push_expression_name (pstate, $1); }
451 | IdentifierExp '.' COMPLETE
455 push_expression_name (pstate, $1);
456 mark_struct_expression (pstate);
457 write_exp_elt_opcode (pstate, STRUCTOP_STRUCT);
458 write_exp_string (pstate, s);
459 write_exp_elt_opcode (pstate, STRUCTOP_STRUCT); }
460 | IdentifierExp '.' IDENTIFIER COMPLETE
461 { push_expression_name (pstate, $1);
462 mark_struct_expression (pstate);
463 write_exp_elt_opcode (pstate, STRUCTOP_STRUCT);
464 write_exp_string (pstate, $3);
465 write_exp_elt_opcode (pstate, STRUCTOP_STRUCT); }
467 { write_dollar_variable (pstate, $1); }
470 parse_number (pstate, $1.ptr, $1.length, 0, &val);
471 write_exp_elt_opcode (pstate, OP_LONG);
472 write_exp_elt_type (pstate, val.typed_val_int.type);
473 write_exp_elt_longcst (pstate,
474 (LONGEST) val.typed_val_int.val);
475 write_exp_elt_opcode (pstate, OP_LONG); }
477 { struct type *type = parse_d_type (pstate)->builtin_void;
478 type = lookup_pointer_type (type);
479 write_exp_elt_opcode (pstate, OP_LONG);
480 write_exp_elt_type (pstate, type);
481 write_exp_elt_longcst (pstate, (LONGEST) 0);
482 write_exp_elt_opcode (pstate, OP_LONG); }
484 { write_exp_elt_opcode (pstate, OP_BOOL);
485 write_exp_elt_longcst (pstate, (LONGEST) 1);
486 write_exp_elt_opcode (pstate, OP_BOOL); }
488 { write_exp_elt_opcode (pstate, OP_BOOL);
489 write_exp_elt_longcst (pstate, (LONGEST) 0);
490 write_exp_elt_opcode (pstate, OP_BOOL); }
492 { write_exp_elt_opcode (pstate, OP_LONG);
493 write_exp_elt_type (pstate, $1.type);
494 write_exp_elt_longcst (pstate, (LONGEST)($1.val));
495 write_exp_elt_opcode (pstate, OP_LONG); }
497 { write_exp_elt_opcode (pstate, OP_DOUBLE);
498 write_exp_elt_type (pstate, $1.type);
499 write_exp_elt_dblcst (pstate, $1.dval);
500 write_exp_elt_opcode (pstate, OP_DOUBLE); }
502 { struct stoken_vector vec;
505 write_exp_string_vector (pstate, $1.type, &vec); }
508 write_exp_string_vector (pstate, 0, &$1);
509 for (i = 0; i < $1.len; ++i)
510 free ($1.tokens[i].ptr);
513 { write_exp_elt_opcode (pstate, OP_ARRAY);
514 write_exp_elt_longcst (pstate, (LONGEST) 0);
515 write_exp_elt_longcst (pstate, (LONGEST) $1 - 1);
516 write_exp_elt_opcode (pstate, OP_ARRAY); }
520 '[' ArgumentList_opt ']'
521 { $$ = arglist_len; }
526 | IdentifierExp '.' IDENTIFIER
527 { $$.length = $1.length + $3.length + 1;
528 if ($1.ptr + $1.length + 1 == $3.ptr
529 && $1.ptr[$1.length] == '.')
530 $$.ptr = $1.ptr; /* Optimization. */
533 char *buf = malloc ($$.length + 1);
534 make_cleanup (free, buf);
535 sprintf (buf, "%.*s.%.*s",
536 $1.length, $1.ptr, $3.length, $3.ptr);
544 { /* We copy the string here, and not in the
545 lexer, to guarantee that we do not leak a
546 string. Note that we follow the
547 NUL-termination convention of the
549 struct typed_stoken *vec = XNEW (struct typed_stoken);
554 vec->length = $1.length;
555 vec->ptr = malloc ($1.length + 1);
556 memcpy (vec->ptr, $1.ptr, $1.length + 1);
558 | StringExp STRING_LITERAL
559 { /* Note that we NUL-terminate here, but just
563 $$.tokens = realloc ($$.tokens,
564 $$.len * sizeof (struct typed_stoken));
566 p = malloc ($2.length + 1);
567 memcpy (p, $2.ptr, $2.length + 1);
569 $$.tokens[$$.len - 1].type = $2.type;
570 $$.tokens[$$.len - 1].length = $2.length;
571 $$.tokens[$$.len - 1].ptr = p;
577 { write_exp_elt_opcode (pstate, OP_TYPE);
578 write_exp_elt_type (pstate, $1);
579 write_exp_elt_opcode (pstate, OP_TYPE); }
580 | BasicType BasicType2
581 { $$ = follow_types ($1);
582 write_exp_elt_opcode (pstate, OP_TYPE);
583 write_exp_elt_type (pstate, $$);
584 write_exp_elt_opcode (pstate, OP_TYPE);
590 { push_type (tp_pointer); }
592 { push_type (tp_pointer); }
593 | '[' INTEGER_LITERAL ']'
594 { push_type_int ($2.val);
595 push_type (tp_array); }
596 | '[' INTEGER_LITERAL ']' BasicType2
597 { push_type_int ($2.val);
598 push_type (tp_array); }
604 | CLASS_KEYWORD IdentifierExp
605 { $$ = lookup_struct (copy_name ($2),
606 expression_context_block); }
607 | CLASS_KEYWORD COMPLETE
608 { mark_completion_tag (TYPE_CODE_STRUCT, "", 0);
610 | CLASS_KEYWORD IdentifierExp COMPLETE
611 { mark_completion_tag (TYPE_CODE_STRUCT, $2.ptr, $2.length);
613 | STRUCT_KEYWORD IdentifierExp
614 { $$ = lookup_struct (copy_name ($2),
615 expression_context_block); }
616 | STRUCT_KEYWORD COMPLETE
617 { mark_completion_tag (TYPE_CODE_STRUCT, "", 0);
619 | STRUCT_KEYWORD IdentifierExp COMPLETE
620 { mark_completion_tag (TYPE_CODE_STRUCT, $2.ptr, $2.length);
622 | UNION_KEYWORD IdentifierExp
623 { $$ = lookup_union (copy_name ($2),
624 expression_context_block); }
625 | UNION_KEYWORD COMPLETE
626 { mark_completion_tag (TYPE_CODE_UNION, "", 0);
628 | UNION_KEYWORD IdentifierExp COMPLETE
629 { mark_completion_tag (TYPE_CODE_UNION, $2.ptr, $2.length);
631 | ENUM_KEYWORD IdentifierExp
632 { $$ = lookup_enum (copy_name ($2),
633 expression_context_block); }
634 | ENUM_KEYWORD COMPLETE
635 { mark_completion_tag (TYPE_CODE_ENUM, "", 0);
637 | ENUM_KEYWORD IdentifierExp COMPLETE
638 { mark_completion_tag (TYPE_CODE_ENUM, $2.ptr, $2.length);
644 /* Take care of parsing a number (anything that starts with a digit).
645 Set yylval and return the token type; update lexptr.
646 LEN is the number of characters in it. */
648 /*** Needs some error checking for the float case ***/
651 parse_number (struct parser_state *ps, const char *p,
652 int len, int parsed_float, YYSTYPE *putithere)
660 int base = input_radix;
664 /* We have found a "L" or "U" suffix. */
665 int found_suffix = 0;
668 struct type *signed_type;
669 struct type *unsigned_type;
673 const struct builtin_d_type *builtin_d_types;
678 /* Strip out all embedded '_' before passing to parse_float. */
679 s = (char *) alloca (len + 1);
690 if (! parse_float (s, len, &putithere->typed_val_float.dval, &suffix))
693 suffix_len = s + len - suffix;
697 putithere->typed_val_float.type
698 = parse_d_type (ps)->builtin_double;
700 else if (suffix_len == 1)
702 /* Check suffix for `f', `l', or `i' (float, real, or idouble). */
703 if (tolower (*suffix) == 'f')
705 putithere->typed_val_float.type
706 = parse_d_type (ps)->builtin_float;
708 else if (tolower (*suffix) == 'l')
710 putithere->typed_val_float.type
711 = parse_d_type (ps)->builtin_real;
713 else if (tolower (*suffix) == 'i')
715 putithere->typed_val_float.type
716 = parse_d_type (ps)->builtin_idouble;
721 else if (suffix_len == 2)
723 /* Check suffix for `fi' or `li' (ifloat or ireal). */
724 if (tolower (suffix[0]) == 'f' && tolower (suffix[1] == 'i'))
726 putithere->typed_val_float.type
727 = parse_d_type (ps)->builtin_ifloat;
729 else if (tolower (suffix[0]) == 'l' && tolower (suffix[1] == 'i'))
731 putithere->typed_val_float.type
732 = parse_d_type (ps)->builtin_ireal;
740 return FLOAT_LITERAL;
743 /* Handle base-switching prefixes 0x, 0b, 0 */
776 continue; /* Ignore embedded '_'. */
777 if (c >= 'A' && c <= 'Z')
779 if (c != 'l' && c != 'u')
781 if (c >= '0' && c <= '9')
789 if (base > 10 && c >= 'a' && c <= 'f')
793 n += i = c - 'a' + 10;
795 else if (c == 'l' && long_p == 0)
800 else if (c == 'u' && unsigned_p == 0)
806 return ERROR; /* Char not a digit */
809 return ERROR; /* Invalid digit in this base. */
810 /* Portably test for integer overflow. */
811 if (c != 'l' && c != 'u')
813 ULONGEST n2 = prevn * base;
814 if ((n2 / base != prevn) || (n2 + i < prevn))
815 error (_("Numeric constant too large."));
820 /* An integer constant is an int or a long. An L suffix forces it to
821 be long, and a U suffix forces it to be unsigned. To figure out
822 whether it fits, we shift it right and see whether anything remains.
823 Note that we can't shift sizeof (LONGEST) * HOST_CHAR_BIT bits or
824 more in one operation, because many compilers will warn about such a
825 shift (which always produces a zero result). To deal with the case
826 where it is we just always shift the value more than once, with fewer
828 un = (ULONGEST) n >> 2;
829 if (long_p == 0 && (un >> 30) == 0)
831 high_bit = ((ULONGEST) 1) << 31;
832 signed_type = parse_d_type (ps)->builtin_int;
833 /* For decimal notation, keep the sign of the worked out type. */
834 if (base == 10 && !unsigned_p)
835 unsigned_type = parse_d_type (ps)->builtin_long;
837 unsigned_type = parse_d_type (ps)->builtin_uint;
842 if (sizeof (ULONGEST) * HOST_CHAR_BIT < 64)
843 /* A long long does not fit in a LONGEST. */
844 shift = (sizeof (ULONGEST) * HOST_CHAR_BIT - 1);
847 high_bit = (ULONGEST) 1 << shift;
848 signed_type = parse_d_type (ps)->builtin_long;
849 unsigned_type = parse_d_type (ps)->builtin_ulong;
852 putithere->typed_val_int.val = n;
854 /* If the high bit of the worked out type is set then this number
855 has to be unsigned_type. */
856 if (unsigned_p || (n & high_bit))
857 putithere->typed_val_int.type = unsigned_type;
859 putithere->typed_val_int.type = signed_type;
861 return INTEGER_LITERAL;
864 /* Temporary obstack used for holding strings. */
865 static struct obstack tempbuf;
866 static int tempbuf_init;
868 /* Parse a string or character literal from TOKPTR. The string or
869 character may be wide or unicode. *OUTPTR is set to just after the
870 end of the literal in the input string. The resulting token is
871 stored in VALUE. This returns a token value, either STRING or
872 CHAR, depending on what was parsed. *HOST_CHARS is set to the
873 number of host characters in the literal. */
876 parse_string_or_char (const char *tokptr, const char **outptr,
877 struct typed_stoken *value, int *host_chars)
881 /* Build the gdb internal form of the input string in tempbuf. Note
882 that the buffer is null byte terminated *only* for the
883 convenience of debugging gdb itself and printing the buffer
884 contents when the buffer contains no embedded nulls. Gdb does
885 not depend upon the buffer being null byte terminated, it uses
886 the length string instead. This allows gdb to handle C strings
887 (as well as strings in other languages) with embedded null
893 obstack_free (&tempbuf, NULL);
894 obstack_init (&tempbuf);
896 /* Skip the quote. */
908 *host_chars += c_parse_escape (&tokptr, &tempbuf);
914 obstack_1grow (&tempbuf, c);
916 /* FIXME: this does the wrong thing with multi-byte host
917 characters. We could use mbrlen here, but that would
918 make "set host-charset" a bit less useful. */
923 if (*tokptr != quote)
925 if (quote == '"' || quote == '`')
926 error (_("Unterminated string in expression."));
928 error (_("Unmatched single quote."));
932 /* FIXME: should instead use own language string_type enum
933 and handle D-specific string suffixes here. */
935 value->type = C_CHAR;
937 value->type = C_STRING;
939 value->ptr = obstack_base (&tempbuf);
940 value->length = obstack_object_size (&tempbuf);
944 return quote == '\'' ? CHARACTER_LITERAL : STRING_LITERAL;
951 enum exp_opcode opcode;
954 static const struct token tokentab3[] =
956 {"^^=", ASSIGN_MODIFY, BINOP_EXP},
957 {"<<=", ASSIGN_MODIFY, BINOP_LSH},
958 {">>=", ASSIGN_MODIFY, BINOP_RSH},
961 static const struct token tokentab2[] =
963 {"+=", ASSIGN_MODIFY, BINOP_ADD},
964 {"-=", ASSIGN_MODIFY, BINOP_SUB},
965 {"*=", ASSIGN_MODIFY, BINOP_MUL},
966 {"/=", ASSIGN_MODIFY, BINOP_DIV},
967 {"%=", ASSIGN_MODIFY, BINOP_REM},
968 {"|=", ASSIGN_MODIFY, BINOP_BITWISE_IOR},
969 {"&=", ASSIGN_MODIFY, BINOP_BITWISE_AND},
970 {"^=", ASSIGN_MODIFY, BINOP_BITWISE_XOR},
971 {"++", INCREMENT, BINOP_END},
972 {"--", DECREMENT, BINOP_END},
973 {"&&", ANDAND, BINOP_END},
974 {"||", OROR, BINOP_END},
975 {"^^", HATHAT, BINOP_END},
976 {"<<", LSH, BINOP_END},
977 {">>", RSH, BINOP_END},
978 {"==", EQUAL, BINOP_END},
979 {"!=", NOTEQUAL, BINOP_END},
980 {"<=", LEQ, BINOP_END},
981 {">=", GEQ, BINOP_END},
982 {"..", DOTDOT, BINOP_END},
985 /* Identifier-like tokens. */
986 static const struct token ident_tokens[] =
988 {"is", IDENTITY, BINOP_END},
989 {"!is", NOTIDENTITY, BINOP_END},
991 {"cast", CAST_KEYWORD, OP_NULL},
992 {"const", CONST_KEYWORD, OP_NULL},
993 {"immutable", IMMUTABLE_KEYWORD, OP_NULL},
994 {"shared", SHARED_KEYWORD, OP_NULL},
995 {"super", SUPER_KEYWORD, OP_NULL},
997 {"null", NULL_KEYWORD, OP_NULL},
998 {"true", TRUE_KEYWORD, OP_NULL},
999 {"false", FALSE_KEYWORD, OP_NULL},
1001 {"init", INIT_KEYWORD, OP_NULL},
1002 {"sizeof", SIZEOF_KEYWORD, OP_NULL},
1003 {"typeof", TYPEOF_KEYWORD, OP_NULL},
1004 {"typeid", TYPEID_KEYWORD, OP_NULL},
1006 {"delegate", DELEGATE_KEYWORD, OP_NULL},
1007 {"function", FUNCTION_KEYWORD, OP_NULL},
1008 {"struct", STRUCT_KEYWORD, OP_NULL},
1009 {"union", UNION_KEYWORD, OP_NULL},
1010 {"class", CLASS_KEYWORD, OP_NULL},
1011 {"interface", INTERFACE_KEYWORD, OP_NULL},
1012 {"enum", ENUM_KEYWORD, OP_NULL},
1013 {"template", TEMPLATE_KEYWORD, OP_NULL},
1016 /* If NAME is a type name in this scope, return it. */
1018 static struct type *
1019 d_type_from_name (struct stoken name)
1022 char *copy = copy_name (name);
1024 sym = lookup_symbol (copy, expression_context_block,
1025 STRUCT_DOMAIN, NULL);
1027 return SYMBOL_TYPE (sym);
1032 /* If NAME is a module name in this scope, return it. */
1034 static struct type *
1035 d_module_from_name (struct stoken name)
1038 char *copy = copy_name (name);
1040 sym = lookup_symbol (copy, expression_context_block,
1041 MODULE_DOMAIN, NULL);
1043 return SYMBOL_TYPE (sym);
1048 /* If NAME is a valid variable name in this scope, push it and return 1.
1049 Otherwise, return 0. */
1052 push_variable (struct parser_state *ps, struct stoken name)
1054 char *copy = copy_name (name);
1055 struct field_of_this_result is_a_field_of_this;
1057 sym = lookup_symbol (copy, expression_context_block, VAR_DOMAIN,
1058 &is_a_field_of_this);
1059 if (sym && SYMBOL_CLASS (sym) != LOC_TYPEDEF)
1061 if (symbol_read_needs_frame (sym))
1063 if (innermost_block == 0 ||
1064 contained_in (block_found, innermost_block))
1065 innermost_block = block_found;
1068 write_exp_elt_opcode (ps, OP_VAR_VALUE);
1069 /* We want to use the selected frame, not another more inner frame
1070 which happens to be in the same block. */
1071 write_exp_elt_block (ps, NULL);
1072 write_exp_elt_sym (ps, sym);
1073 write_exp_elt_opcode (ps, OP_VAR_VALUE);
1076 if (is_a_field_of_this.type != NULL)
1078 /* It hangs off of `this'. Must not inadvertently convert from a
1079 method call to data ref. */
1080 if (innermost_block == 0 ||
1081 contained_in (block_found, innermost_block))
1082 innermost_block = block_found;
1083 write_exp_elt_opcode (ps, OP_THIS);
1084 write_exp_elt_opcode (ps, OP_THIS);
1085 write_exp_elt_opcode (ps, STRUCTOP_PTR);
1086 write_exp_string (ps, name);
1087 write_exp_elt_opcode (ps, STRUCTOP_PTR);
1093 /* Assuming a reference expression has been pushed, emit the
1094 STRUCTOP_PTR ops to access the field named NAME. If NAME is a
1095 qualified name (has '.'), generate a field access for each part. */
1098 push_fieldnames (struct parser_state *ps, struct stoken name)
1101 struct stoken token;
1102 token.ptr = name.ptr;
1105 if (i == name.length || name.ptr[i] == '.')
1107 /* token.ptr is start of current field name. */
1108 token.length = &name.ptr[i] - token.ptr;
1109 write_exp_elt_opcode (ps, STRUCTOP_PTR);
1110 write_exp_string (ps, token);
1111 write_exp_elt_opcode (ps, STRUCTOP_PTR);
1112 token.ptr += token.length + 1;
1114 if (i >= name.length)
1119 /* Helper routine for push_expression_name. Handle a TYPE symbol,
1120 where DOT_INDEX is the index of the first '.' if NAME is part of
1121 a qualified type. */
1124 push_type_name (struct parser_state *ps, struct type *type,
1125 struct stoken name, int dot_index)
1127 if (dot_index == name.length)
1129 write_exp_elt_opcode (ps, OP_TYPE);
1130 write_exp_elt_type (ps, type);
1131 write_exp_elt_opcode (ps, OP_TYPE);
1135 struct stoken token;
1137 token.ptr = name.ptr;
1138 token.length = dot_index;
1142 while (dot_index < name.length && name.ptr[dot_index] != '.')
1144 token.ptr = name.ptr;
1145 token.length = dot_index;
1147 write_exp_elt_opcode (ps, OP_SCOPE);
1148 write_exp_elt_type (ps, type);
1149 write_exp_string (ps, token);
1150 write_exp_elt_opcode (ps, OP_SCOPE);
1152 if (dot_index < name.length)
1155 name.ptr += dot_index;
1156 name.length -= dot_index;
1157 push_fieldnames (ps, name);
1162 /* Helper routine for push_expression_name. Like push_type_name,
1163 but used when TYPE is a module. Returns 1 on pushing the symbol. */
1166 push_module_name (struct parser_state *ps, struct type *module,
1167 struct stoken name, int dot_index)
1169 if (dot_index == name.length)
1171 write_exp_elt_opcode (ps, OP_TYPE);
1172 write_exp_elt_type (ps, module);
1173 write_exp_elt_opcode (ps, OP_TYPE);
1181 copy = copy_name (name);
1182 sym = lookup_symbol_in_static_block (copy, expression_context_block,
1185 sym = lookup_global_symbol (copy, expression_context_block,
1190 if (SYMBOL_CLASS (sym) != LOC_TYPEDEF)
1192 write_exp_elt_opcode (ps, OP_VAR_VALUE);
1193 write_exp_elt_block (ps, NULL);
1194 write_exp_elt_sym (ps, sym);
1195 write_exp_elt_opcode (ps, OP_VAR_VALUE);
1199 write_exp_elt_opcode (ps, OP_TYPE);
1200 write_exp_elt_type (ps, SYMBOL_TYPE (sym));
1201 write_exp_elt_opcode (ps, OP_TYPE);
1210 /* Handle NAME in an expression (or LHS), which could be a
1211 variable, type, or module. */
1214 push_expression_name (struct parser_state *ps, struct stoken name)
1216 struct stoken token;
1218 struct bound_minimal_symbol msymbol;
1222 /* Handle VAR, which could be local or global. */
1223 if (push_variable (ps, name) != 0)
1226 /* Handle MODULE. */
1227 typ = d_module_from_name (name);
1230 if (push_module_name (ps, typ, name, name.length) != 0)
1235 typ = d_type_from_name (name);
1238 push_type_name (ps, typ, name, name.length);
1242 /* Handle VAR.FIELD1..FIELDN. */
1243 for (doti = 0; doti < name.length; doti++)
1245 if (name.ptr[doti] == '.')
1247 token.ptr = name.ptr;
1248 token.length = doti;
1250 if (push_variable (ps, token) != 0)
1252 token.ptr = name.ptr + doti + 1;
1253 token.length = name.length - doti - 1;
1254 push_fieldnames (ps, token);
1261 /* Continue looking if we found a '.' in the name. */
1262 if (doti < name.length)
1264 token.ptr = name.ptr;
1267 token.length = doti;
1269 /* Handle PACKAGE.MODULE. */
1270 typ = d_module_from_name (token);
1273 if (push_module_name (ps, typ, name, doti) != 0)
1276 /* Handle TYPE.FIELD1..FIELDN. */
1277 typ = d_type_from_name (token);
1280 push_type_name (ps, typ, name, doti);
1284 if (doti >= name.length)
1286 doti++; /* Skip '.' */
1287 while (doti < name.length && name.ptr[doti] != '.')
1292 /* Lookup foreign name in global static symbols. */
1293 copy = copy_name (name);
1294 msymbol = lookup_bound_minimal_symbol (copy);
1295 if (msymbol.minsym != NULL)
1296 write_exp_msymbol (ps, msymbol);
1297 else if (!have_full_symbols () && !have_partial_symbols ())
1298 error (_("No symbol table is loaded. Use the \"file\" command"));
1300 error (_("No symbol \"%s\" in current context."), copy);
1303 /* This is set if a NAME token appeared at the very end of the input
1304 string, with no whitespace separating the name from the EOF. This
1305 is used only when parsing to do field name completion. */
1306 static int saw_name_at_eof;
1308 /* This is set if the previously-returned token was a structure operator.
1309 This is used only when parsing to do field name completion. */
1310 static int last_was_structop;
1312 /* Read one token, getting characters through lexptr. */
1320 const char *tokstart;
1321 int saw_structop = last_was_structop;
1324 last_was_structop = 0;
1328 prev_lexptr = lexptr;
1331 /* See if it is a special token of length 3. */
1332 for (i = 0; i < sizeof tokentab3 / sizeof tokentab3[0]; i++)
1333 if (strncmp (tokstart, tokentab3[i].oper, 3) == 0)
1336 yylval.opcode = tokentab3[i].opcode;
1337 return tokentab3[i].token;
1340 /* See if it is a special token of length 2. */
1341 for (i = 0; i < sizeof tokentab2 / sizeof tokentab2[0]; i++)
1342 if (strncmp (tokstart, tokentab2[i].oper, 2) == 0)
1345 yylval.opcode = tokentab2[i].opcode;
1346 return tokentab2[i].token;
1349 switch (c = *tokstart)
1352 /* If we're parsing for field name completion, and the previous
1353 token allows such completion, return a COMPLETE token.
1354 Otherwise, we were already scanning the original text, and
1355 we're really done. */
1356 if (saw_name_at_eof)
1358 saw_name_at_eof = 0;
1361 else if (saw_structop)
1380 if (paren_depth == 0)
1387 if (comma_terminates && paren_depth == 0)
1393 /* Might be a floating point number. */
1394 if (lexptr[1] < '0' || lexptr[1] > '9')
1396 if (parse_completion)
1397 last_was_structop = 1;
1398 goto symbol; /* Nope, must be a symbol. */
1400 /* FALL THRU into number case. */
1413 /* It's a number. */
1414 int got_dot = 0, got_e = 0, toktype;
1415 const char *p = tokstart;
1416 int hex = input_radix > 10;
1418 if (c == '0' && (p[1] == 'x' || p[1] == 'X'))
1426 /* Hex exponents start with 'p', because 'e' is a valid hex
1427 digit and thus does not indicate a floating point number
1428 when the radix is hex. */
1429 if ((!hex && !got_e && tolower (p[0]) == 'e')
1430 || (hex && !got_e && tolower (p[0] == 'p')))
1431 got_dot = got_e = 1;
1432 /* A '.' always indicates a decimal floating point number
1433 regardless of the radix. If we have a '..' then its the
1434 end of the number and the beginning of a slice. */
1435 else if (!got_dot && (p[0] == '.' && p[1] != '.'))
1437 /* This is the sign of the exponent, not the end of the number. */
1438 else if (got_e && (tolower (p[-1]) == 'e' || tolower (p[-1]) == 'p')
1439 && (*p == '-' || *p == '+'))
1441 /* We will take any letters or digits, ignoring any embedded '_'.
1442 parse_number will complain if past the radix, or if L or U are
1444 else if ((*p < '0' || *p > '9') && (*p != '_') &&
1445 ((*p < 'a' || *p > 'z') && (*p < 'A' || *p > 'Z')))
1449 toktype = parse_number (pstate, tokstart, p - tokstart,
1450 got_dot|got_e, &yylval);
1451 if (toktype == ERROR)
1453 char *err_copy = (char *) alloca (p - tokstart + 1);
1455 memcpy (err_copy, tokstart, p - tokstart);
1456 err_copy[p - tokstart] = 0;
1457 error (_("Invalid number \"%s\"."), err_copy);
1465 const char *p = &tokstart[1];
1466 size_t len = strlen ("entry");
1468 while (isspace (*p))
1470 if (strncmp (p, "entry", len) == 0 && !isalnum (p[len])
1504 int result = parse_string_or_char (tokstart, &lexptr, &yylval.tsval,
1506 if (result == CHARACTER_LITERAL)
1509 error (_("Empty character constant."));
1510 else if (host_len > 2 && c == '\'')
1513 namelen = lexptr - tokstart - 1;
1516 else if (host_len > 1)
1517 error (_("Invalid character constant."));
1523 if (!(c == '_' || c == '$'
1524 || (c >= 'a' && c <= 'z') || (c >= 'A' && c <= 'Z')))
1525 /* We must have come across a bad character (e.g. ';'). */
1526 error (_("Invalid character '%c' in expression"), c);
1528 /* It's a name. See how long it is. */
1530 for (c = tokstart[namelen];
1531 (c == '_' || c == '$' || (c >= '0' && c <= '9')
1532 || (c >= 'a' && c <= 'z') || (c >= 'A' && c <= 'Z'));)
1533 c = tokstart[++namelen];
1535 /* The token "if" terminates the expression and is NOT
1536 removed from the input stream. */
1537 if (namelen == 2 && tokstart[0] == 'i' && tokstart[1] == 'f')
1540 /* For the same reason (breakpoint conditions), "thread N"
1541 terminates the expression. "thread" could be an identifier, but
1542 an identifier is never followed by a number without intervening
1543 punctuation. "task" is similar. Handle abbreviations of these,
1544 similarly to breakpoint.c:find_condition_and_thread. */
1546 && (strncmp (tokstart, "thread", namelen) == 0
1547 || strncmp (tokstart, "task", namelen) == 0)
1548 && (tokstart[namelen] == ' ' || tokstart[namelen] == '\t'))
1550 const char *p = tokstart + namelen + 1;
1552 while (*p == ' ' || *p == '\t')
1554 if (*p >= '0' && *p <= '9')
1562 yylval.sval.ptr = tokstart;
1563 yylval.sval.length = namelen;
1565 /* Catch specific keywords. */
1566 copy = copy_name (yylval.sval);
1567 for (i = 0; i < sizeof ident_tokens / sizeof ident_tokens[0]; i++)
1568 if (strcmp (copy, ident_tokens[i].oper) == 0)
1570 /* It is ok to always set this, even though we don't always
1571 strictly need to. */
1572 yylval.opcode = ident_tokens[i].opcode;
1573 return ident_tokens[i].token;
1576 if (*tokstart == '$')
1577 return DOLLAR_VARIABLE;
1580 = language_lookup_primitive_type (parse_language (pstate),
1581 parse_gdbarch (pstate), copy);
1582 if (yylval.tsym.type != NULL)
1585 /* Input names that aren't symbols but ARE valid hex numbers,
1586 when the input radix permits them, can be names or numbers
1587 depending on the parse. Note we support radixes > 16 here. */
1588 if ((tokstart[0] >= 'a' && tokstart[0] < 'a' + input_radix - 10)
1589 || (tokstart[0] >= 'A' && tokstart[0] < 'A' + input_radix - 10))
1591 YYSTYPE newlval; /* Its value is ignored. */
1592 int hextype = parse_number (pstate, tokstart, namelen, 0, &newlval);
1593 if (hextype == INTEGER_LITERAL)
1597 if (parse_completion && *lexptr == '\0')
1598 saw_name_at_eof = 1;
1604 d_parse (struct parser_state *par_state)
1607 struct cleanup *back_to;
1609 /* Setting up the parser state. */
1610 gdb_assert (par_state != NULL);
1613 back_to = make_cleanup (null_cleanup, NULL);
1615 make_cleanup_restore_integer (&yydebug);
1616 make_cleanup_clear_parser_state (&pstate);
1617 yydebug = parser_debug;
1619 /* Initialize some state used by the lexer. */
1620 last_was_structop = 0;
1621 saw_name_at_eof = 0;
1623 result = yyparse ();
1624 do_cleanups (back_to);
1632 lexptr = prev_lexptr;
1634 error (_("A %s in expression, near `%s'."), (msg ? msg : "error"), lexptr);