1 /* YACC parser for D expressions, for GDB.
3 Copyright (C) 2014-2023 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"
51 #include "type-stack.h"
54 #define parse_type(ps) builtin_type (ps->gdbarch ())
55 #define parse_d_type(ps) builtin_d_type (ps->gdbarch ())
57 /* Remap normal yacc parser interface names (yyparse, yylex, yyerror,
59 #define GDB_YY_REMAP_PREFIX d_
62 /* The state of the parser, used internally when we are parsing the
65 static struct parser_state
*pstate
= NULL
;
67 /* The current type stack. */
68 static struct type_stack
*type_stack
;
72 static int yylex (void);
74 static void yyerror (const char *);
76 static int type_aggregate_p
(struct type
*);
82 /* Although the yacc "value" of an expression is not used,
83 since the result is stored in the structure being created,
84 other node types do have values. */
98 struct typed_stoken tsval
;
101 struct symtoken ssym
;
104 enum exp_opcode opcode
;
105 struct stoken_vector svec
;
109 /* YYSTYPE gets defined by %union */
110 static int parse_number
(struct parser_state
*, const char *,
111 int, int, YYSTYPE *);
114 %token
<sval
> IDENTIFIER UNKNOWN_NAME
115 %token
<tsym
> TYPENAME
116 %token
<voidval
> COMPLETE
118 /* A NAME_OR_INT is a symbol which is not known in the symbol table,
119 but which would parse as a valid number in the current input radix.
120 E.g. "c" when input_radix==16. Depending on the parse, it will be
121 turned into a name or into a number. */
123 %token
<sval
> NAME_OR_INT
125 %token
<typed_val_int
> INTEGER_LITERAL
126 %token
<typed_val_float
> FLOAT_LITERAL
127 %token
<tsval
> CHARACTER_LITERAL
128 %token
<tsval
> STRING_LITERAL
130 %type
<svec
> StringExp
131 %type
<tval
> BasicType TypeExp
132 %type
<sval
> IdentifierExp
133 %type
<ival
> ArrayLiteral
138 /* Keywords that have a constant value. */
139 %token TRUE_KEYWORD FALSE_KEYWORD NULL_KEYWORD
140 /* Class 'super' accessor. */
143 %token CAST_KEYWORD SIZEOF_KEYWORD
144 %token TYPEOF_KEYWORD TYPEID_KEYWORD
146 /* Comparison keywords. */
147 /* Type storage classes. */
148 %token IMMUTABLE_KEYWORD CONST_KEYWORD SHARED_KEYWORD
149 /* Non-scalar type keywords. */
150 %token STRUCT_KEYWORD UNION_KEYWORD
151 %token CLASS_KEYWORD INTERFACE_KEYWORD
152 %token ENUM_KEYWORD TEMPLATE_KEYWORD
153 %token DELEGATE_KEYWORD FUNCTION_KEYWORD
155 %token
<sval
> DOLLAR_VARIABLE
157 %token
<opcode
> ASSIGN_MODIFY
160 %right
'=' ASSIGN_MODIFY
167 %left EQUAL NOTEQUAL
'<' '>' LEQ GEQ
172 %left IDENTITY NOTIDENTITY
173 %right INCREMENT DECREMENT
185 /* Expressions, including the comma operator. */
193 | AssignExpression
',' CommaExpression
194 { pstate
->wrap2
<comma_operation
> (); }
198 ConditionalExpression
199 | ConditionalExpression
'=' AssignExpression
200 { pstate
->wrap2
<assign_operation
> (); }
201 | ConditionalExpression ASSIGN_MODIFY AssignExpression
203 operation_up rhs
= pstate
->pop
();
204 operation_up lhs
= pstate
->pop
();
205 pstate
->push_new
<assign_modify_operation
>
206 ($2, std
::move
(lhs
), std
::move
(rhs
));
210 ConditionalExpression:
212 | OrOrExpression
'?' Expression
':' ConditionalExpression
214 operation_up last
= pstate
->pop
();
215 operation_up mid
= pstate
->pop
();
216 operation_up first
= pstate
->pop
();
217 pstate
->push_new
<ternop_cond_operation
>
218 (std
::move
(first
), std
::move
(mid
),
225 | OrOrExpression OROR AndAndExpression
226 { pstate
->wrap2
<logical_or_operation
> (); }
231 | AndAndExpression ANDAND OrExpression
232 { pstate
->wrap2
<logical_and_operation
> (); }
237 | OrExpression
'|' XorExpression
238 { pstate
->wrap2
<bitwise_ior_operation
> (); }
243 | XorExpression
'^' AndExpression
244 { pstate
->wrap2
<bitwise_xor_operation
> (); }
249 | AndExpression
'&' CmpExpression
250 { pstate
->wrap2
<bitwise_and_operation
> (); }
261 ShiftExpression EQUAL ShiftExpression
262 { pstate
->wrap2
<equal_operation
> (); }
263 | ShiftExpression NOTEQUAL ShiftExpression
264 { pstate
->wrap2
<notequal_operation
> (); }
268 ShiftExpression IDENTITY ShiftExpression
269 { pstate
->wrap2
<equal_operation
> (); }
270 | ShiftExpression NOTIDENTITY ShiftExpression
271 { pstate
->wrap2
<notequal_operation
> (); }
275 ShiftExpression
'<' ShiftExpression
276 { pstate
->wrap2
<less_operation
> (); }
277 | ShiftExpression LEQ ShiftExpression
278 { pstate
->wrap2
<leq_operation
> (); }
279 | ShiftExpression
'>' ShiftExpression
280 { pstate
->wrap2
<gtr_operation
> (); }
281 | ShiftExpression GEQ ShiftExpression
282 { pstate
->wrap2
<geq_operation
> (); }
287 | ShiftExpression LSH AddExpression
288 { pstate
->wrap2
<lsh_operation
> (); }
289 | ShiftExpression RSH AddExpression
290 { pstate
->wrap2
<rsh_operation
> (); }
295 | AddExpression
'+' MulExpression
296 { pstate
->wrap2
<add_operation
> (); }
297 | AddExpression
'-' MulExpression
298 { pstate
->wrap2
<sub_operation
> (); }
299 | AddExpression
'~' MulExpression
300 { pstate
->wrap2
<concat_operation
> (); }
305 | MulExpression
'*' UnaryExpression
306 { pstate
->wrap2
<mul_operation
> (); }
307 | MulExpression
'/' UnaryExpression
308 { pstate
->wrap2
<div_operation
> (); }
309 | MulExpression
'%' UnaryExpression
310 { pstate
->wrap2
<rem_operation
> (); }
314 { pstate
->wrap
<unop_addr_operation
> (); }
315 | INCREMENT UnaryExpression
316 { pstate
->wrap
<preinc_operation
> (); }
317 | DECREMENT UnaryExpression
318 { pstate
->wrap
<predec_operation
> (); }
319 |
'*' UnaryExpression
320 { pstate
->wrap
<unop_ind_operation
> (); }
321 |
'-' UnaryExpression
322 { pstate
->wrap
<unary_neg_operation
> (); }
323 |
'+' UnaryExpression
324 { pstate
->wrap
<unary_plus_operation
> (); }
325 |
'!' UnaryExpression
326 { pstate
->wrap
<unary_logical_not_operation
> (); }
327 |
'~' UnaryExpression
328 { pstate
->wrap
<unary_complement_operation
> (); }
329 | TypeExp
'.' SIZEOF_KEYWORD
330 { pstate
->wrap
<unop_sizeof_operation
> (); }
336 CAST_KEYWORD
'(' TypeExp
')' UnaryExpression
337 { pstate
->wrap2
<unop_cast_type_operation
> (); }
338 /* C style cast is illegal D, but is still recognised in
339 the grammar, so we keep this around for convenience. */
340 |
'(' TypeExp
')' UnaryExpression
341 { pstate
->wrap2
<unop_cast_type_operation
> (); }
346 | PostfixExpression HATHAT UnaryExpression
347 { pstate
->wrap2
<exp_operation
> (); }
352 | PostfixExpression
'.' COMPLETE
354 structop_base_operation
*op
355 = new structop_ptr_operation
(pstate
->pop
(), "");
356 pstate
->mark_struct_expression
(op
);
357 pstate
->push
(operation_up
(op
));
359 | PostfixExpression
'.' IDENTIFIER
361 pstate
->push_new
<structop_operation
>
362 (pstate
->pop
(), copy_name
($3));
364 | PostfixExpression
'.' IDENTIFIER COMPLETE
366 structop_base_operation
*op
367 = new structop_operation
(pstate
->pop
(), copy_name
($3));
368 pstate
->mark_struct_expression
(op
);
369 pstate
->push
(operation_up
(op
));
371 | PostfixExpression
'.' SIZEOF_KEYWORD
372 { pstate
->wrap
<unop_sizeof_operation
> (); }
373 | PostfixExpression INCREMENT
374 { pstate
->wrap
<postinc_operation
> (); }
375 | PostfixExpression DECREMENT
376 { pstate
->wrap
<postdec_operation
> (); }
384 { pstate
->arglist_len
= 1; }
385 | ArgumentList
',' AssignExpression
386 { pstate
->arglist_len
++; }
391 { pstate
->arglist_len
= 0; }
396 PostfixExpression
'('
397 { pstate
->start_arglist
(); }
400 std
::vector
<operation_up
> args
401 = pstate
->pop_vector
(pstate
->end_arglist
());
402 pstate
->push_new
<funcall_operation
>
403 (pstate
->pop
(), std
::move
(args
));
408 PostfixExpression
'[' ArgumentList
']'
409 { if
(pstate
->arglist_len
> 0)
411 std
::vector
<operation_up
> args
412 = pstate
->pop_vector
(pstate
->arglist_len
);
413 pstate
->push_new
<multi_subscript_operation
>
414 (pstate
->pop
(), std
::move
(args
));
417 pstate
->wrap2
<subscript_operation
> ();
422 PostfixExpression
'[' ']'
423 { /* Do nothing. */ }
424 | PostfixExpression
'[' AssignExpression DOTDOT AssignExpression
']'
426 operation_up last
= pstate
->pop
();
427 operation_up mid
= pstate
->pop
();
428 operation_up first
= pstate
->pop
();
429 pstate
->push_new
<ternop_slice_operation
>
430 (std
::move
(first
), std
::move
(mid
),
437 { /* Do nothing. */ }
439 { struct bound_minimal_symbol msymbol
;
440 std
::string copy
= copy_name
($1);
441 struct field_of_this_result is_a_field_of_this
;
442 struct block_symbol sym
;
444 /* Handle VAR, which could be local or global. */
445 sym
= lookup_symbol
(copy.c_str
(),
446 pstate
->expression_context_block
,
447 VAR_DOMAIN
, &is_a_field_of_this
);
448 if
(sym.symbol
&& sym.symbol
->aclass
() != LOC_TYPEDEF
)
450 if
(symbol_read_needs_frame
(sym.symbol
))
451 pstate
->block_tracker
->update
(sym
);
452 pstate
->push_new
<var_value_operation
> (sym
);
454 else if
(is_a_field_of_this.type
!= NULL
)
456 /* It hangs off of `this'. Must not inadvertently convert from a
457 method call to data ref. */
458 pstate
->block_tracker
->update
(sym
);
460 = make_operation
<op_this_operation
> ();
461 pstate
->push_new
<structop_ptr_operation
>
462 (std
::move
(thisop
), std
::move
(copy
));
466 /* Lookup foreign name in global static symbols. */
467 msymbol
= lookup_bound_minimal_symbol
(copy.c_str
());
468 if
(msymbol.minsym
!= NULL
)
469 pstate
->push_new
<var_msym_value_operation
> (msymbol
);
470 else if
(!have_full_symbols
() && !have_partial_symbols
())
471 error (_
("No symbol table is loaded. Use the \"file\" command"));
473 error (_
("No symbol \"%s\" in current context."),
477 | TypeExp
'.' IdentifierExp
478 { struct type
*type
= check_typedef
($1);
480 /* Check if the qualified name is in the global
481 context. However if the symbol has not already
482 been resolved, it's not likely to be found. */
483 if
(type
->code
() == TYPE_CODE_MODULE
)
485 struct block_symbol sym
;
486 const char *type_name
= TYPE_SAFE_NAME
(type
);
487 int type_name_len
= strlen
(type_name
);
489 = string_printf
("%.*s.%.*s",
490 type_name_len
, type_name
,
494 lookup_symbol
(name.c_str
(),
495 (const struct block
*) NULL
,
497 pstate
->push_symbol
(name.c_str
(), sym
);
501 /* Check if the qualified name resolves as a member
502 of an aggregate or an enum type. */
503 if
(!type_aggregate_p
(type
))
504 error (_
("`%s' is not defined as an aggregate type."),
505 TYPE_SAFE_NAME
(type
));
507 pstate
->push_new
<scope_operation
>
508 (type
, copy_name
($3));
512 { pstate
->push_dollar
($1); }
515 parse_number
(pstate
, $1.ptr
, $1.length
, 0, &val
);
516 pstate
->push_new
<long_const_operation
>
517 (val.typed_val_int.type
, val.typed_val_int.val
); }
519 { struct type
*type
= parse_d_type
(pstate
)->builtin_void
;
520 type
= lookup_pointer_type
(type
);
521 pstate
->push_new
<long_const_operation
> (type
, 0); }
523 { pstate
->push_new
<bool_operation
> (true
); }
525 { pstate
->push_new
<bool_operation
> (false
); }
527 { pstate
->push_new
<long_const_operation
> ($1.type
, $1.val
); }
531 std
::copy
(std
::begin
($1.val
), std
::end
($1.val
),
533 pstate
->push_new
<float_const_operation
> ($1.type
, data
);
536 { struct stoken_vector vec
;
539 pstate
->push_c_string
(0, &vec
); }
542 pstate
->push_c_string
(0, &$1);
543 for
(i
= 0; i
< $1.len
; ++i
)
544 free
($1.tokens
[i
].ptr
);
548 std
::vector
<operation_up
> args
549 = pstate
->pop_vector
($1);
550 pstate
->push_new
<array_operation
>
551 (0, $1 - 1, std
::move
(args
));
553 | TYPEOF_KEYWORD
'(' Expression
')'
554 { pstate
->wrap
<typeof_operation
> (); }
558 '[' ArgumentList_opt
']'
559 { $$
= pstate
->arglist_len
; }
568 { /* We copy the string here, and not in the
569 lexer, to guarantee that we do not leak a
570 string. Note that we follow the
571 NUL-termination convention of the
573 struct typed_stoken
*vec
= XNEW
(struct typed_stoken
);
578 vec
->length
= $1.length
;
579 vec
->ptr
= (char *) malloc
($1.length
+ 1);
580 memcpy
(vec
->ptr
, $1.ptr
, $1.length
+ 1);
582 | StringExp STRING_LITERAL
583 { /* Note that we NUL-terminate here, but just
588 = XRESIZEVEC
(struct typed_stoken
, $$.tokens
, $$.len
);
590 p
= (char *) malloc
($2.length
+ 1);
591 memcpy
(p
, $2.ptr
, $2.length
+ 1);
593 $$.tokens
[$$.len
- 1].type
= $2.type
;
594 $$.tokens
[$$.len
- 1].length
= $2.length
;
595 $$.tokens
[$$.len
- 1].ptr
= p
;
601 { /* Do nothing. */ }
603 { pstate
->push_new
<type_operation
> ($1); }
604 | BasicType BasicType2
605 { $$
= type_stack
->follow_types
($1);
606 pstate
->push_new
<type_operation
> ($$
);
612 { type_stack
->push
(tp_pointer
); }
614 { type_stack
->push
(tp_pointer
); }
615 |
'[' INTEGER_LITERAL
']'
616 { type_stack
->push
($2.val
);
617 type_stack
->push
(tp_array
); }
618 |
'[' INTEGER_LITERAL
']' BasicType2
619 { type_stack
->push
($2.val
);
620 type_stack
->push
(tp_array
); }
630 /* Return true if the type is aggregate-like. */
633 type_aggregate_p
(struct type
*type
)
635 return
(type
->code
() == TYPE_CODE_STRUCT
636 || type
->code
() == TYPE_CODE_UNION
637 || type
->code
() == TYPE_CODE_MODULE
638 ||
(type
->code
() == TYPE_CODE_ENUM
639 && type
->is_declared_class
()));
642 /* Take care of parsing a number (anything that starts with a digit).
643 Set yylval and return the token type; update lexptr.
644 LEN is the number of characters in it. */
646 /*** Needs some error checking for the float case ***/
649 parse_number
(struct parser_state
*ps
, const char *p
,
650 int len
, int parsed_float
, YYSTYPE *putithere
)
658 int base
= input_radix
;
662 /* We have found a "L" or "U" suffix. */
663 int found_suffix
= 0;
666 struct type
*signed_type
;
667 struct type
*unsigned_type
;
673 /* Strip out all embedded '_' before passing to parse_float. */
674 s
= (char *) alloca
(len
+ 1);
685 /* Check suffix for `i' , `fi' or `li' (idouble, ifloat or ireal). */
686 if
(len
>= 1 && tolower
(s
[len
- 1]) == 'i')
688 if
(len
>= 2 && tolower
(s
[len
- 2]) == 'f')
690 putithere
->typed_val_float.type
691 = parse_d_type
(ps
)->builtin_ifloat
;
694 else if
(len
>= 2 && tolower
(s
[len
- 2]) == 'l')
696 putithere
->typed_val_float.type
697 = parse_d_type
(ps
)->builtin_ireal
;
702 putithere
->typed_val_float.type
703 = parse_d_type
(ps
)->builtin_idouble
;
707 /* Check suffix for `f' or `l'' (float or real). */
708 else if
(len
>= 1 && tolower
(s
[len
- 1]) == 'f')
710 putithere
->typed_val_float.type
711 = parse_d_type
(ps
)->builtin_float
;
714 else if
(len
>= 1 && tolower
(s
[len
- 1]) == 'l')
716 putithere
->typed_val_float.type
717 = parse_d_type
(ps
)->builtin_real
;
720 /* Default type if no suffix. */
723 putithere
->typed_val_float.type
724 = parse_d_type
(ps
)->builtin_double
;
727 if
(!parse_float
(s
, len
,
728 putithere
->typed_val_float.type
,
729 putithere
->typed_val_float.val
))
732 return FLOAT_LITERAL
;
735 /* Handle base-switching prefixes 0x, 0b, 0 */
768 continue
; /* Ignore embedded '_'. */
769 if
(c
>= 'A' && c
<= 'Z')
771 if
(c
!= 'l' && c
!= 'u')
773 if
(c
>= '0' && c
<= '9')
781 if
(base
> 10 && c
>= 'a' && c
<= 'f')
785 n
+= i
= c
- 'a' + 10;
787 else if
(c
== 'l' && long_p
== 0)
792 else if
(c
== 'u' && unsigned_p
== 0)
798 return ERROR
; /* Char not a digit */
801 return ERROR
; /* Invalid digit in this base. */
802 /* Portably test for integer overflow. */
803 if
(c
!= 'l' && c
!= 'u')
805 ULONGEST n2
= prevn
* base
;
806 if
((n2
/ base
!= prevn
) ||
(n2
+ i
< prevn
))
807 error (_
("Numeric constant too large."));
812 /* An integer constant is an int or a long. An L suffix forces it to
813 be long, and a U suffix forces it to be unsigned. To figure out
814 whether it fits, we shift it right and see whether anything remains.
815 Note that we can't shift sizeof (LONGEST) * HOST_CHAR_BIT bits or
816 more in one operation, because many compilers will warn about such a
817 shift (which always produces a zero result). To deal with the case
818 where it is we just always shift the value more than once, with fewer
820 un
= (ULONGEST
) n
>> 2;
821 if
(long_p
== 0 && (un
>> 30) == 0)
823 high_bit
= ((ULONGEST
) 1) << 31;
824 signed_type
= parse_d_type
(ps
)->builtin_int
;
825 /* For decimal notation, keep the sign of the worked out type. */
826 if
(base
== 10 && !unsigned_p
)
827 unsigned_type
= parse_d_type
(ps
)->builtin_long
;
829 unsigned_type
= parse_d_type
(ps
)->builtin_uint
;
834 if
(sizeof
(ULONGEST
) * HOST_CHAR_BIT
< 64)
835 /* A long long does not fit in a LONGEST. */
836 shift
= (sizeof
(ULONGEST
) * HOST_CHAR_BIT
- 1);
839 high_bit
= (ULONGEST
) 1 << shift
;
840 signed_type
= parse_d_type
(ps
)->builtin_long
;
841 unsigned_type
= parse_d_type
(ps
)->builtin_ulong
;
844 putithere
->typed_val_int.val
= n
;
846 /* If the high bit of the worked out type is set then this number
847 has to be unsigned_type. */
848 if
(unsigned_p ||
(n
& high_bit
))
849 putithere
->typed_val_int.type
= unsigned_type
;
851 putithere
->typed_val_int.type
= signed_type
;
853 return INTEGER_LITERAL
;
856 /* Temporary obstack used for holding strings. */
857 static struct obstack tempbuf
;
858 static int tempbuf_init
;
860 /* Parse a string or character literal from TOKPTR. The string or
861 character may be wide or unicode. *OUTPTR is set to just after the
862 end of the literal in the input string. The resulting token is
863 stored in VALUE. This returns a token value, either STRING or
864 CHAR, depending on what was parsed. *HOST_CHARS is set to the
865 number of host characters in the literal. */
868 parse_string_or_char
(const char *tokptr
, const char **outptr
,
869 struct typed_stoken
*value
, int *host_chars
)
873 /* Build the gdb internal form of the input string in tempbuf. Note
874 that the buffer is null byte terminated *only* for the
875 convenience of debugging gdb itself and printing the buffer
876 contents when the buffer contains no embedded nulls. Gdb does
877 not depend upon the buffer being null byte terminated, it uses
878 the length string instead. This allows gdb to handle C strings
879 (as well as strings in other languages) with embedded null
885 obstack_free
(&tempbuf
, NULL
);
886 obstack_init
(&tempbuf
);
888 /* Skip the quote. */
900 *host_chars
+= c_parse_escape
(&tokptr
, &tempbuf
);
906 obstack_1grow
(&tempbuf
, c
);
908 /* FIXME: this does the wrong thing with multi-byte host
909 characters. We could use mbrlen here, but that would
910 make "set host-charset" a bit less useful. */
915 if
(*tokptr
!= quote
)
917 if
(quote
== '"' || quote
== '`')
918 error (_
("Unterminated string in expression."));
920 error (_
("Unmatched single quote."));
924 /* FIXME: should instead use own language string_type enum
925 and handle D-specific string suffixes here. */
927 value
->type
= C_CHAR
;
929 value
->type
= C_STRING
;
931 value
->ptr
= (char *) obstack_base
(&tempbuf
);
932 value
->length
= obstack_object_size
(&tempbuf
);
936 return quote
== '\'' ? CHARACTER_LITERAL
: STRING_LITERAL
;
943 enum exp_opcode opcode
;
946 static const struct d_token tokentab3
[] =
948 {"^^=", ASSIGN_MODIFY
, BINOP_EXP
},
949 {"<<=", ASSIGN_MODIFY
, BINOP_LSH
},
950 {">>=", ASSIGN_MODIFY
, BINOP_RSH
},
953 static const struct d_token tokentab2
[] =
955 {"+=", ASSIGN_MODIFY
, BINOP_ADD
},
956 {"-=", ASSIGN_MODIFY
, BINOP_SUB
},
957 {"*=", ASSIGN_MODIFY
, BINOP_MUL
},
958 {"/=", ASSIGN_MODIFY
, BINOP_DIV
},
959 {"%=", ASSIGN_MODIFY
, BINOP_REM
},
960 {"|=", ASSIGN_MODIFY
, BINOP_BITWISE_IOR
},
961 {"&=", ASSIGN_MODIFY
, BINOP_BITWISE_AND
},
962 {"^=", ASSIGN_MODIFY
, BINOP_BITWISE_XOR
},
963 {"++", INCREMENT
, OP_NULL
},
964 {"--", DECREMENT
, OP_NULL
},
965 {"&&", ANDAND
, OP_NULL
},
966 {"||", OROR
, OP_NULL
},
967 {"^^", HATHAT
, OP_NULL
},
968 {"<<", LSH
, OP_NULL
},
969 {">>", RSH
, OP_NULL
},
970 {"==", EQUAL
, OP_NULL
},
971 {"!=", NOTEQUAL
, OP_NULL
},
972 {"<=", LEQ
, OP_NULL
},
973 {">=", GEQ
, OP_NULL
},
974 {"..", DOTDOT
, OP_NULL
},
977 /* Identifier-like tokens. */
978 static const struct d_token ident_tokens
[] =
980 {"is", IDENTITY
, OP_NULL
},
981 {"!is", NOTIDENTITY
, OP_NULL
},
983 {"cast", CAST_KEYWORD
, OP_NULL
},
984 {"const", CONST_KEYWORD
, OP_NULL
},
985 {"immutable", IMMUTABLE_KEYWORD
, OP_NULL
},
986 {"shared", SHARED_KEYWORD
, OP_NULL
},
987 {"super", SUPER_KEYWORD
, OP_NULL
},
989 {"null", NULL_KEYWORD
, OP_NULL
},
990 {"true", TRUE_KEYWORD
, OP_NULL
},
991 {"false", FALSE_KEYWORD
, OP_NULL
},
993 {"init", INIT_KEYWORD
, OP_NULL
},
994 {"sizeof", SIZEOF_KEYWORD
, OP_NULL
},
995 {"typeof", TYPEOF_KEYWORD
, OP_NULL
},
996 {"typeid", TYPEID_KEYWORD
, OP_NULL
},
998 {"delegate", DELEGATE_KEYWORD
, OP_NULL
},
999 {"function", FUNCTION_KEYWORD
, OP_NULL
},
1000 {"struct", STRUCT_KEYWORD
, OP_NULL
},
1001 {"union", UNION_KEYWORD
, OP_NULL
},
1002 {"class", CLASS_KEYWORD
, OP_NULL
},
1003 {"interface", INTERFACE_KEYWORD
, OP_NULL
},
1004 {"enum", ENUM_KEYWORD
, OP_NULL
},
1005 {"template", TEMPLATE_KEYWORD
, OP_NULL
},
1008 /* This is set if a NAME token appeared at the very end of the input
1009 string, with no whitespace separating the name from the EOF. This
1010 is used only when parsing to do field name completion. */
1011 static int saw_name_at_eof
;
1013 /* This is set if the previously-returned token was a structure operator.
1014 This is used only when parsing to do field name completion. */
1015 static int last_was_structop
;
1017 /* Depth of parentheses. */
1018 static int paren_depth
;
1020 /* Read one token, getting characters through lexptr. */
1023 lex_one_token
(struct parser_state
*par_state
)
1027 const char *tokstart
;
1028 int saw_structop
= last_was_structop
;
1030 last_was_structop
= 0;
1034 pstate
->prev_lexptr
= pstate
->lexptr
;
1036 tokstart
= pstate
->lexptr
;
1037 /* See if it is a special token of length 3. */
1038 for
(const auto
&token
: tokentab3
)
1039 if
(strncmp
(tokstart
, token.oper
, 3) == 0)
1041 pstate
->lexptr
+= 3;
1042 yylval.opcode
= token.opcode
;
1046 /* See if it is a special token of length 2. */
1047 for
(const auto
&token
: tokentab2
)
1048 if
(strncmp
(tokstart
, token.oper
, 2) == 0)
1050 pstate
->lexptr
+= 2;
1051 yylval.opcode
= token.opcode
;
1055 switch
(c
= *tokstart
)
1058 /* If we're parsing for field name completion, and the previous
1059 token allows such completion, return a COMPLETE token.
1060 Otherwise, we were already scanning the original text, and
1061 we're really done. */
1062 if
(saw_name_at_eof
)
1064 saw_name_at_eof
= 0;
1067 else if
(saw_structop
)
1086 if
(paren_depth
== 0)
1093 if
(pstate
->comma_terminates
&& paren_depth
== 0)
1099 /* Might be a floating point number. */
1100 if
(pstate
->lexptr
[1] < '0' || pstate
->lexptr
[1] > '9')
1102 if
(pstate
->parse_completion
)
1103 last_was_structop
= 1;
1104 goto symbol
; /* Nope, must be a symbol. */
1119 /* It's a number. */
1120 int got_dot
= 0, got_e
= 0, toktype
;
1121 const char *p
= tokstart
;
1122 int hex
= input_radix
> 10;
1124 if
(c
== '0' && (p
[1] == 'x' || p
[1] == 'X'))
1132 /* Hex exponents start with 'p', because 'e' is a valid hex
1133 digit and thus does not indicate a floating point number
1134 when the radix is hex. */
1135 if
((!hex
&& !got_e
&& tolower
(p
[0]) == 'e')
1136 ||
(hex
&& !got_e
&& tolower
(p
[0] == 'p')))
1137 got_dot
= got_e
= 1;
1138 /* A '.' always indicates a decimal floating point number
1139 regardless of the radix. If we have a '..' then its the
1140 end of the number and the beginning of a slice. */
1141 else if
(!got_dot
&& (p
[0] == '.' && p
[1] != '.'))
1143 /* This is the sign of the exponent, not the end of the number. */
1144 else if
(got_e
&& (tolower
(p
[-1]) == 'e' || tolower
(p
[-1]) == 'p')
1145 && (*p
== '-' ||
*p
== '+'))
1147 /* We will take any letters or digits, ignoring any embedded '_'.
1148 parse_number will complain if past the radix, or if L or U are
1150 else if
((*p
< '0' ||
*p
> '9') && (*p
!= '_')
1151 && ((*p
< 'a' ||
*p
> 'z') && (*p
< 'A' ||
*p
> 'Z')))
1155 toktype
= parse_number
(par_state
, tokstart
, p
- tokstart
,
1156 got_dot|got_e
, &yylval);
1157 if
(toktype
== ERROR
)
1159 char *err_copy
= (char *) alloca
(p
- tokstart
+ 1);
1161 memcpy
(err_copy
, tokstart
, p
- tokstart
);
1162 err_copy
[p
- tokstart
] = 0;
1163 error (_
("Invalid number \"%s\"."), err_copy
);
1171 const char *p
= &tokstart
[1];
1172 size_t len
= strlen
("entry");
1174 while
(isspace
(*p
))
1176 if
(strncmp
(p
, "entry", len
) == 0 && !isalnum
(p
[len
])
1179 pstate
->lexptr
= &p
[len
];
1210 int result
= parse_string_or_char
(tokstart
, &pstate
->lexptr
,
1211 &yylval.tsval
, &host_len
);
1212 if
(result
== CHARACTER_LITERAL
)
1215 error (_
("Empty character constant."));
1216 else if
(host_len
> 2 && c
== '\'')
1219 namelen
= pstate
->lexptr
- tokstart
- 1;
1222 else if
(host_len
> 1)
1223 error (_
("Invalid character constant."));
1229 if
(!(c
== '_' || c
== '$'
1230 ||
(c
>= 'a' && c
<= 'z') ||
(c
>= 'A' && c
<= 'Z')))
1231 /* We must have come across a bad character (e.g. ';'). */
1232 error (_
("Invalid character '%c' in expression"), c
);
1234 /* It's a name. See how long it is. */
1236 for
(c
= tokstart
[namelen
];
1237 (c
== '_' || c
== '$' ||
(c
>= '0' && c
<= '9')
1238 ||
(c
>= 'a' && c
<= 'z') ||
(c
>= 'A' && c
<= 'Z'));)
1239 c
= tokstart
[++namelen
];
1241 /* The token "if" terminates the expression and is NOT
1242 removed from the input stream. */
1243 if
(namelen
== 2 && tokstart
[0] == 'i' && tokstart
[1] == 'f')
1246 /* For the same reason (breakpoint conditions), "thread N"
1247 terminates the expression. "thread" could be an identifier, but
1248 an identifier is never followed by a number without intervening
1249 punctuation. "task" is similar. Handle abbreviations of these,
1250 similarly to breakpoint.c:find_condition_and_thread. */
1252 && (strncmp
(tokstart
, "thread", namelen
) == 0
1253 || strncmp
(tokstart
, "task", namelen
) == 0)
1254 && (tokstart
[namelen
] == ' ' || tokstart
[namelen
] == '\t'))
1256 const char *p
= tokstart
+ namelen
+ 1;
1258 while
(*p
== ' ' ||
*p
== '\t')
1260 if
(*p
>= '0' && *p
<= '9')
1264 pstate
->lexptr
+= namelen
;
1268 yylval.sval.ptr
= tokstart
;
1269 yylval.sval.length
= namelen
;
1271 /* Catch specific keywords. */
1272 std
::string copy
= copy_name
(yylval.sval
);
1273 for
(const auto
&token
: ident_tokens
)
1274 if
(copy
== token.oper
)
1276 /* It is ok to always set this, even though we don't always
1277 strictly need to. */
1278 yylval.opcode
= token.opcode
;
1282 if
(*tokstart
== '$')
1283 return DOLLAR_VARIABLE
;
1286 = language_lookup_primitive_type
(par_state
->language
(),
1287 par_state
->gdbarch
(), copy.c_str
());
1288 if
(yylval.tsym.type
!= NULL
)
1291 /* Input names that aren't symbols but ARE valid hex numbers,
1292 when the input radix permits them, can be names or numbers
1293 depending on the parse. Note we support radixes > 16 here. */
1294 if
((tokstart
[0] >= 'a' && tokstart
[0] < 'a' + input_radix
- 10)
1295 ||
(tokstart
[0] >= 'A' && tokstart
[0] < 'A' + input_radix
- 10))
1297 YYSTYPE newlval
; /* Its value is ignored. */
1298 int hextype
= parse_number
(par_state
, tokstart
, namelen
, 0, &newlval
);
1299 if
(hextype
== INTEGER_LITERAL
)
1303 if
(pstate
->parse_completion
&& *pstate
->lexptr
== '\0')
1304 saw_name_at_eof
= 1;
1309 /* An object of this type is pushed on a FIFO by the "outer" lexer. */
1310 struct d_token_and_value
1317 /* A FIFO of tokens that have been read but not yet returned to the
1319 static std
::vector
<d_token_and_value
> token_fifo
;
1321 /* Non-zero if the lexer should return tokens from the FIFO. */
1324 /* Temporary storage for yylex; this holds symbol names as they are
1326 static auto_obstack name_obstack
;
1328 /* Classify an IDENTIFIER token. The contents of the token are in `yylval'.
1329 Updates yylval and returns the new token type. BLOCK is the block
1330 in which lookups start; this can be NULL to mean the global scope. */
1333 classify_name
(struct parser_state
*par_state
, const struct block
*block
)
1335 struct block_symbol sym
;
1336 struct field_of_this_result is_a_field_of_this
;
1338 std
::string copy
= copy_name
(yylval.sval
);
1340 sym
= lookup_symbol
(copy.c_str
(), block
, VAR_DOMAIN
, &is_a_field_of_this
);
1341 if
(sym.symbol
&& sym.symbol
->aclass
() == LOC_TYPEDEF
)
1343 yylval.tsym.type
= sym.symbol
->type
();
1346 else if
(sym.symbol
== NULL
)
1348 /* Look-up first for a module name, then a type. */
1349 sym
= lookup_symbol
(copy.c_str
(), block
, MODULE_DOMAIN
, NULL
);
1350 if
(sym.symbol
== NULL
)
1351 sym
= lookup_symbol
(copy.c_str
(), block
, STRUCT_DOMAIN
, NULL
);
1353 if
(sym.symbol
!= NULL
)
1355 yylval.tsym.type
= sym.symbol
->type
();
1359 return UNKNOWN_NAME
;
1365 /* Like classify_name, but used by the inner loop of the lexer, when a
1366 name might have already been seen. CONTEXT is the context type, or
1367 NULL if this is the first component of a name. */
1370 classify_inner_name
(struct parser_state
*par_state
,
1371 const struct block
*block
, struct type
*context
)
1375 if
(context
== NULL
)
1376 return classify_name
(par_state
, block
);
1378 type
= check_typedef
(context
);
1379 if
(!type_aggregate_p
(type
))
1382 std
::string copy
= copy_name
(yylval.ssym.stoken
);
1383 yylval.ssym.sym
= d_lookup_nested_symbol
(type
, copy.c_str
(), block
);
1385 if
(yylval.ssym.sym.symbol
== NULL
)
1388 if
(yylval.ssym.sym.symbol
->aclass
() == LOC_TYPEDEF
)
1390 yylval.tsym.type
= yylval.ssym.sym.symbol
->type
();
1397 /* The outer level of a two-level lexer. This calls the inner lexer
1398 to return tokens. It then either returns these tokens, or
1399 aggregates them into a larger token. This lets us work around a
1400 problem in our parsing approach, where the parser could not
1401 distinguish between qualified names and qualified types at the
1407 d_token_and_value current
;
1409 struct type
*context_type
= NULL
;
1410 int last_to_examine
, next_to_examine
, checkpoint
;
1411 const struct block
*search_block
;
1413 if
(popping
&& !token_fifo.empty
())
1417 /* Read the first token and decide what to do. */
1418 current.token
= lex_one_token
(pstate
);
1419 if
(current.token
!= IDENTIFIER
&& current.token
!= '.')
1420 return current.token
;
1422 /* Read any sequence of alternating "." and identifier tokens into
1424 current.value
= yylval;
1425 token_fifo.push_back
(current
);
1426 last_was_dot
= current.token
== '.';
1430 current.token
= lex_one_token
(pstate
);
1431 current.value
= yylval;
1432 token_fifo.push_back
(current
);
1434 if
((last_was_dot
&& current.token
!= IDENTIFIER
)
1435 ||
(!last_was_dot
&& current.token
!= '.'))
1438 last_was_dot
= !last_was_dot
;
1442 /* We always read one extra token, so compute the number of tokens
1443 to examine accordingly. */
1444 last_to_examine
= token_fifo.size
() - 2;
1445 next_to_examine
= 0;
1447 current
= token_fifo
[next_to_examine
];
1450 /* If we are not dealing with a typename, now is the time to find out. */
1451 if
(current.token
== IDENTIFIER
)
1453 yylval = current.value
;
1454 current.token
= classify_name
(pstate
, pstate
->expression_context_block
);
1455 current.value
= yylval;
1458 /* If the IDENTIFIER is not known, it could be a package symbol,
1459 first try building up a name until we find the qualified module. */
1460 if
(current.token
== UNKNOWN_NAME
)
1462 name_obstack.clear
();
1463 obstack_grow
(&name_obstack
, current.value.sval.ptr
,
1464 current.value.sval.length
);
1468 while
(next_to_examine
<= last_to_examine
)
1470 d_token_and_value next
;
1472 next
= token_fifo
[next_to_examine
];
1475 if
(next.token
== IDENTIFIER
&& last_was_dot
)
1477 /* Update the partial name we are constructing. */
1478 obstack_grow_str
(&name_obstack
, ".");
1479 obstack_grow
(&name_obstack
, next.value.sval.ptr
,
1480 next.value.sval.length
);
1482 yylval.sval.ptr
= (char *) obstack_base
(&name_obstack
);
1483 yylval.sval.length
= obstack_object_size
(&name_obstack
);
1485 current.token
= classify_name
(pstate
,
1486 pstate
->expression_context_block
);
1487 current.value
= yylval;
1489 /* We keep going until we find a TYPENAME. */
1490 if
(current.token
== TYPENAME
)
1492 /* Install it as the first token in the FIFO. */
1493 token_fifo
[0] = current
;
1494 token_fifo.erase
(token_fifo.begin
() + 1,
1495 token_fifo.begin
() + next_to_examine
);
1499 else if
(next.token
== '.' && !last_was_dot
)
1503 /* We've reached the end of the name. */
1508 /* Reset our current token back to the start, if we found nothing
1509 this means that we will just jump to do pop. */
1510 current
= token_fifo
[0];
1511 next_to_examine
= 1;
1513 if
(current.token
!= TYPENAME
&& current.token
!= '.')
1516 name_obstack.clear
();
1518 if
(current.token
== '.')
1519 search_block
= NULL
;
1522 gdb_assert
(current.token
== TYPENAME
);
1523 search_block
= pstate
->expression_context_block
;
1524 obstack_grow
(&name_obstack
, current.value.sval.ptr
,
1525 current.value.sval.length
);
1526 context_type
= current.value.tsym.type
;
1530 last_was_dot
= current.token
== '.';
1532 while
(next_to_examine
<= last_to_examine
)
1534 d_token_and_value next
;
1536 next
= token_fifo
[next_to_examine
];
1539 if
(next.token
== IDENTIFIER
&& last_was_dot
)
1543 yylval = next.value
;
1544 classification
= classify_inner_name
(pstate
, search_block
,
1546 /* We keep going until we either run out of names, or until
1547 we have a qualified name which is not a type. */
1548 if
(classification
!= TYPENAME
&& classification
!= IDENTIFIER
)
1551 /* Accept up to this token. */
1552 checkpoint
= next_to_examine
;
1554 /* Update the partial name we are constructing. */
1555 if
(context_type
!= NULL
)
1557 /* We don't want to put a leading "." into the name. */
1558 obstack_grow_str
(&name_obstack
, ".");
1560 obstack_grow
(&name_obstack
, next.value.sval.ptr
,
1561 next.value.sval.length
);
1563 yylval.sval.ptr
= (char *) obstack_base
(&name_obstack
);
1564 yylval.sval.length
= obstack_object_size
(&name_obstack
);
1565 current.value
= yylval;
1566 current.token
= classification
;
1570 if
(classification
== IDENTIFIER
)
1573 context_type
= yylval.tsym.type
;
1575 else if
(next.token
== '.' && !last_was_dot
)
1579 /* We've reached the end of the name. */
1584 /* If we have a replacement token, install it as the first token in
1585 the FIFO, and delete the other constituent tokens. */
1588 token_fifo
[0] = current
;
1590 token_fifo.erase
(token_fifo.begin
() + 1,
1591 token_fifo.begin
() + checkpoint
);
1595 current
= token_fifo
[0];
1596 token_fifo.erase
(token_fifo.begin
());
1597 yylval = current.value
;
1598 return current.token
;
1602 d_parse
(struct parser_state
*par_state
)
1604 /* Setting up the parser state. */
1605 scoped_restore pstate_restore
= make_scoped_restore
(&pstate
);
1606 gdb_assert
(par_state
!= NULL
);
1609 scoped_restore restore_yydebug
= make_scoped_restore
(&yydebug,
1612 struct type_stack stack
;
1613 scoped_restore restore_type_stack
= make_scoped_restore
(&type_stack
,
1616 /* Initialize some state used by the lexer. */
1617 last_was_structop
= 0;
1618 saw_name_at_eof
= 0;
1621 token_fifo.clear
();
1623 name_obstack.clear
();
1625 int result
= yyparse ();
1627 pstate
->set_operation
(pstate
->pop
());
1632 yyerror (const char *msg
)
1634 if
(pstate
->prev_lexptr
)
1635 pstate
->lexptr
= pstate
->prev_lexptr
;
1637 error (_
("A %s in expression, near `%s'."), msg
, pstate
->lexptr
);