1 /* YACC parser for D expressions, for GDB.
3 Copyright (C) 2014-2022 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
&& sym.symbol
->aclass
() != LOC_TYPEDEF
)
453 if
(symbol_read_needs_frame
(sym.symbol
))
454 pstate
->block_tracker
->update
(sym
);
455 pstate
->push_new
<var_value_operation
> (sym
);
457 else if
(is_a_field_of_this.type
!= NULL
)
459 /* It hangs off of `this'. Must not inadvertently convert from a
460 method call to data ref. */
461 pstate
->block_tracker
->update
(sym
);
463 = make_operation
<op_this_operation
> ();
464 pstate
->push_new
<structop_ptr_operation
>
465 (std
::move
(thisop
), std
::move
(copy
));
469 /* Lookup foreign name in global static symbols. */
470 msymbol
= lookup_bound_minimal_symbol
(copy.c_str
());
471 if
(msymbol.minsym
!= NULL
)
472 pstate
->push_new
<var_msym_value_operation
> (msymbol
);
473 else if
(!have_full_symbols
() && !have_partial_symbols
())
474 error (_
("No symbol table is loaded. Use the \"file\" command"));
476 error (_
("No symbol \"%s\" in current context."),
480 | TypeExp
'.' IdentifierExp
481 { struct type
*type
= check_typedef
($1);
483 /* Check if the qualified name is in the global
484 context. However if the symbol has not already
485 been resolved, it's not likely to be found. */
486 if
(type
->code
() == TYPE_CODE_MODULE
)
488 struct block_symbol sym
;
489 const char *type_name
= TYPE_SAFE_NAME
(type
);
490 int type_name_len
= strlen
(type_name
);
492 = string_printf
("%.*s.%.*s",
493 type_name_len
, type_name
,
497 lookup_symbol
(name.c_str
(),
498 (const struct block
*) NULL
,
500 pstate
->push_symbol
(name.c_str
(), sym
);
504 /* Check if the qualified name resolves as a member
505 of an aggregate or an enum type. */
506 if
(!type_aggregate_p
(type
))
507 error (_
("`%s' is not defined as an aggregate type."),
508 TYPE_SAFE_NAME
(type
));
510 pstate
->push_new
<scope_operation
>
511 (type
, copy_name
($3));
515 { pstate
->push_dollar
($1); }
518 parse_number
(pstate
, $1.ptr
, $1.length
, 0, &val
);
519 pstate
->push_new
<long_const_operation
>
520 (val.typed_val_int.type
, val.typed_val_int.val
); }
522 { struct type
*type
= parse_d_type
(pstate
)->builtin_void
;
523 type
= lookup_pointer_type
(type
);
524 pstate
->push_new
<long_const_operation
> (type
, 0); }
526 { pstate
->push_new
<bool_operation
> (true
); }
528 { pstate
->push_new
<bool_operation
> (false
); }
530 { pstate
->push_new
<long_const_operation
> ($1.type
, $1.val
); }
534 std
::copy
(std
::begin
($1.val
), std
::end
($1.val
),
536 pstate
->push_new
<float_const_operation
> ($1.type
, data
);
539 { struct stoken_vector vec
;
542 pstate
->push_c_string
(0, &vec
); }
545 pstate
->push_c_string
(0, &$1);
546 for
(i
= 0; i
< $1.len
; ++i
)
547 free
($1.tokens
[i
].ptr
);
551 std
::vector
<operation_up
> args
552 = pstate
->pop_vector
($1);
553 pstate
->push_new
<array_operation
>
554 (0, $1 - 1, std
::move
(args
));
556 | TYPEOF_KEYWORD
'(' Expression
')'
557 { pstate
->wrap
<typeof_operation
> (); }
561 '[' ArgumentList_opt
']'
562 { $$
= pstate
->arglist_len
; }
571 { /* We copy the string here, and not in the
572 lexer, to guarantee that we do not leak a
573 string. Note that we follow the
574 NUL-termination convention of the
576 struct typed_stoken
*vec
= XNEW
(struct typed_stoken
);
581 vec
->length
= $1.length
;
582 vec
->ptr
= (char *) malloc
($1.length
+ 1);
583 memcpy
(vec
->ptr
, $1.ptr
, $1.length
+ 1);
585 | StringExp STRING_LITERAL
586 { /* Note that we NUL-terminate here, but just
591 = XRESIZEVEC
(struct typed_stoken
, $$.tokens
, $$.len
);
593 p
= (char *) malloc
($2.length
+ 1);
594 memcpy
(p
, $2.ptr
, $2.length
+ 1);
596 $$.tokens
[$$.len
- 1].type
= $2.type
;
597 $$.tokens
[$$.len
- 1].length
= $2.length
;
598 $$.tokens
[$$.len
- 1].ptr
= p
;
604 { /* Do nothing. */ }
606 { pstate
->push_new
<type_operation
> ($1); }
607 | BasicType BasicType2
608 { $$
= type_stack
->follow_types
($1);
609 pstate
->push_new
<type_operation
> ($$
);
615 { type_stack
->push
(tp_pointer
); }
617 { type_stack
->push
(tp_pointer
); }
618 |
'[' INTEGER_LITERAL
']'
619 { type_stack
->push
($2.val
);
620 type_stack
->push
(tp_array
); }
621 |
'[' INTEGER_LITERAL
']' BasicType2
622 { type_stack
->push
($2.val
);
623 type_stack
->push
(tp_array
); }
633 /* Return true if the type is aggregate-like. */
636 type_aggregate_p
(struct type
*type
)
638 return
(type
->code
() == TYPE_CODE_STRUCT
639 || type
->code
() == TYPE_CODE_UNION
640 || type
->code
() == TYPE_CODE_MODULE
641 ||
(type
->code
() == TYPE_CODE_ENUM
642 && type
->is_declared_class
()));
645 /* Take care of parsing a number (anything that starts with a digit).
646 Set yylval and return the token type; update lexptr.
647 LEN is the number of characters in it. */
649 /*** Needs some error checking for the float case ***/
652 parse_number
(struct parser_state
*ps
, const char *p
,
653 int len
, int parsed_float
, YYSTYPE *putithere
)
661 int base
= input_radix
;
665 /* We have found a "L" or "U" suffix. */
666 int found_suffix
= 0;
669 struct type
*signed_type
;
670 struct type
*unsigned_type
;
676 /* Strip out all embedded '_' before passing to parse_float. */
677 s
= (char *) alloca
(len
+ 1);
688 /* Check suffix for `i' , `fi' or `li' (idouble, ifloat or ireal). */
689 if
(len
>= 1 && tolower
(s
[len
- 1]) == 'i')
691 if
(len
>= 2 && tolower
(s
[len
- 2]) == 'f')
693 putithere
->typed_val_float.type
694 = parse_d_type
(ps
)->builtin_ifloat
;
697 else if
(len
>= 2 && tolower
(s
[len
- 2]) == 'l')
699 putithere
->typed_val_float.type
700 = parse_d_type
(ps
)->builtin_ireal
;
705 putithere
->typed_val_float.type
706 = parse_d_type
(ps
)->builtin_idouble
;
710 /* Check suffix for `f' or `l'' (float or real). */
711 else if
(len
>= 1 && tolower
(s
[len
- 1]) == 'f')
713 putithere
->typed_val_float.type
714 = parse_d_type
(ps
)->builtin_float
;
717 else if
(len
>= 1 && tolower
(s
[len
- 1]) == 'l')
719 putithere
->typed_val_float.type
720 = parse_d_type
(ps
)->builtin_real
;
723 /* Default type if no suffix. */
726 putithere
->typed_val_float.type
727 = parse_d_type
(ps
)->builtin_double
;
730 if
(!parse_float
(s
, len
,
731 putithere
->typed_val_float.type
,
732 putithere
->typed_val_float.val
))
735 return FLOAT_LITERAL
;
738 /* Handle base-switching prefixes 0x, 0b, 0 */
771 continue
; /* Ignore embedded '_'. */
772 if
(c
>= 'A' && c
<= 'Z')
774 if
(c
!= 'l' && c
!= 'u')
776 if
(c
>= '0' && c
<= '9')
784 if
(base
> 10 && c
>= 'a' && c
<= 'f')
788 n
+= i
= c
- 'a' + 10;
790 else if
(c
== 'l' && long_p
== 0)
795 else if
(c
== 'u' && unsigned_p
== 0)
801 return ERROR
; /* Char not a digit */
804 return ERROR
; /* Invalid digit in this base. */
805 /* Portably test for integer overflow. */
806 if
(c
!= 'l' && c
!= 'u')
808 ULONGEST n2
= prevn
* base
;
809 if
((n2
/ base
!= prevn
) ||
(n2
+ i
< prevn
))
810 error (_
("Numeric constant too large."));
815 /* An integer constant is an int or a long. An L suffix forces it to
816 be long, and a U suffix forces it to be unsigned. To figure out
817 whether it fits, we shift it right and see whether anything remains.
818 Note that we can't shift sizeof (LONGEST) * HOST_CHAR_BIT bits or
819 more in one operation, because many compilers will warn about such a
820 shift (which always produces a zero result). To deal with the case
821 where it is we just always shift the value more than once, with fewer
823 un
= (ULONGEST
) n
>> 2;
824 if
(long_p
== 0 && (un
>> 30) == 0)
826 high_bit
= ((ULONGEST
) 1) << 31;
827 signed_type
= parse_d_type
(ps
)->builtin_int
;
828 /* For decimal notation, keep the sign of the worked out type. */
829 if
(base
== 10 && !unsigned_p
)
830 unsigned_type
= parse_d_type
(ps
)->builtin_long
;
832 unsigned_type
= parse_d_type
(ps
)->builtin_uint
;
837 if
(sizeof
(ULONGEST
) * HOST_CHAR_BIT
< 64)
838 /* A long long does not fit in a LONGEST. */
839 shift
= (sizeof
(ULONGEST
) * HOST_CHAR_BIT
- 1);
842 high_bit
= (ULONGEST
) 1 << shift
;
843 signed_type
= parse_d_type
(ps
)->builtin_long
;
844 unsigned_type
= parse_d_type
(ps
)->builtin_ulong
;
847 putithere
->typed_val_int.val
= n
;
849 /* If the high bit of the worked out type is set then this number
850 has to be unsigned_type. */
851 if
(unsigned_p ||
(n
& high_bit
))
852 putithere
->typed_val_int.type
= unsigned_type
;
854 putithere
->typed_val_int.type
= signed_type
;
856 return INTEGER_LITERAL
;
859 /* Temporary obstack used for holding strings. */
860 static struct obstack tempbuf
;
861 static int tempbuf_init
;
863 /* Parse a string or character literal from TOKPTR. The string or
864 character may be wide or unicode. *OUTPTR is set to just after the
865 end of the literal in the input string. The resulting token is
866 stored in VALUE. This returns a token value, either STRING or
867 CHAR, depending on what was parsed. *HOST_CHARS is set to the
868 number of host characters in the literal. */
871 parse_string_or_char
(const char *tokptr
, const char **outptr
,
872 struct typed_stoken
*value
, int *host_chars
)
876 /* Build the gdb internal form of the input string in tempbuf. Note
877 that the buffer is null byte terminated *only* for the
878 convenience of debugging gdb itself and printing the buffer
879 contents when the buffer contains no embedded nulls. Gdb does
880 not depend upon the buffer being null byte terminated, it uses
881 the length string instead. This allows gdb to handle C strings
882 (as well as strings in other languages) with embedded null
888 obstack_free
(&tempbuf
, NULL
);
889 obstack_init
(&tempbuf
);
891 /* Skip the quote. */
903 *host_chars
+= c_parse_escape
(&tokptr
, &tempbuf
);
909 obstack_1grow
(&tempbuf
, c
);
911 /* FIXME: this does the wrong thing with multi-byte host
912 characters. We could use mbrlen here, but that would
913 make "set host-charset" a bit less useful. */
918 if
(*tokptr
!= quote
)
920 if
(quote
== '"' || quote
== '`')
921 error (_
("Unterminated string in expression."));
923 error (_
("Unmatched single quote."));
927 /* FIXME: should instead use own language string_type enum
928 and handle D-specific string suffixes here. */
930 value
->type
= C_CHAR
;
932 value
->type
= C_STRING
;
934 value
->ptr
= (char *) obstack_base
(&tempbuf
);
935 value
->length
= obstack_object_size
(&tempbuf
);
939 return quote
== '\'' ? CHARACTER_LITERAL
: STRING_LITERAL
;
946 enum exp_opcode opcode
;
949 static const struct token tokentab3
[] =
951 {"^^=", ASSIGN_MODIFY
, BINOP_EXP
},
952 {"<<=", ASSIGN_MODIFY
, BINOP_LSH
},
953 {">>=", ASSIGN_MODIFY
, BINOP_RSH
},
956 static const struct token tokentab2
[] =
958 {"+=", ASSIGN_MODIFY
, BINOP_ADD
},
959 {"-=", ASSIGN_MODIFY
, BINOP_SUB
},
960 {"*=", ASSIGN_MODIFY
, BINOP_MUL
},
961 {"/=", ASSIGN_MODIFY
, BINOP_DIV
},
962 {"%=", ASSIGN_MODIFY
, BINOP_REM
},
963 {"|=", ASSIGN_MODIFY
, BINOP_BITWISE_IOR
},
964 {"&=", ASSIGN_MODIFY
, BINOP_BITWISE_AND
},
965 {"^=", ASSIGN_MODIFY
, BINOP_BITWISE_XOR
},
966 {"++", INCREMENT
, OP_NULL
},
967 {"--", DECREMENT
, OP_NULL
},
968 {"&&", ANDAND
, OP_NULL
},
969 {"||", OROR
, OP_NULL
},
970 {"^^", HATHAT
, OP_NULL
},
971 {"<<", LSH
, OP_NULL
},
972 {">>", RSH
, OP_NULL
},
973 {"==", EQUAL
, OP_NULL
},
974 {"!=", NOTEQUAL
, OP_NULL
},
975 {"<=", LEQ
, OP_NULL
},
976 {">=", GEQ
, OP_NULL
},
977 {"..", DOTDOT
, OP_NULL
},
980 /* Identifier-like tokens. */
981 static const struct token ident_tokens
[] =
983 {"is", IDENTITY
, OP_NULL
},
984 {"!is", NOTIDENTITY
, OP_NULL
},
986 {"cast", CAST_KEYWORD
, OP_NULL
},
987 {"const", CONST_KEYWORD
, OP_NULL
},
988 {"immutable", IMMUTABLE_KEYWORD
, OP_NULL
},
989 {"shared", SHARED_KEYWORD
, OP_NULL
},
990 {"super", SUPER_KEYWORD
, OP_NULL
},
992 {"null", NULL_KEYWORD
, OP_NULL
},
993 {"true", TRUE_KEYWORD
, OP_NULL
},
994 {"false", FALSE_KEYWORD
, OP_NULL
},
996 {"init", INIT_KEYWORD
, OP_NULL
},
997 {"sizeof", SIZEOF_KEYWORD
, OP_NULL
},
998 {"typeof", TYPEOF_KEYWORD
, OP_NULL
},
999 {"typeid", TYPEID_KEYWORD
, OP_NULL
},
1001 {"delegate", DELEGATE_KEYWORD
, OP_NULL
},
1002 {"function", FUNCTION_KEYWORD
, OP_NULL
},
1003 {"struct", STRUCT_KEYWORD
, OP_NULL
},
1004 {"union", UNION_KEYWORD
, OP_NULL
},
1005 {"class", CLASS_KEYWORD
, OP_NULL
},
1006 {"interface", INTERFACE_KEYWORD
, OP_NULL
},
1007 {"enum", ENUM_KEYWORD
, OP_NULL
},
1008 {"template", TEMPLATE_KEYWORD
, OP_NULL
},
1011 /* This is set if a NAME token appeared at the very end of the input
1012 string, with no whitespace separating the name from the EOF. This
1013 is used only when parsing to do field name completion. */
1014 static int saw_name_at_eof
;
1016 /* This is set if the previously-returned token was a structure operator.
1017 This is used only when parsing to do field name completion. */
1018 static int last_was_structop
;
1020 /* Depth of parentheses. */
1021 static int paren_depth
;
1023 /* Read one token, getting characters through lexptr. */
1026 lex_one_token
(struct parser_state
*par_state
)
1030 const char *tokstart
;
1031 int saw_structop
= last_was_structop
;
1033 last_was_structop
= 0;
1037 pstate
->prev_lexptr
= pstate
->lexptr
;
1039 tokstart
= pstate
->lexptr
;
1040 /* See if it is a special token of length 3. */
1041 for
(const auto
&token
: tokentab3
)
1042 if
(strncmp
(tokstart
, token.oper
, 3) == 0)
1044 pstate
->lexptr
+= 3;
1045 yylval.opcode
= token.opcode
;
1049 /* See if it is a special token of length 2. */
1050 for
(const auto
&token
: tokentab2
)
1051 if
(strncmp
(tokstart
, token.oper
, 2) == 0)
1053 pstate
->lexptr
+= 2;
1054 yylval.opcode
= token.opcode
;
1058 switch
(c
= *tokstart
)
1061 /* If we're parsing for field name completion, and the previous
1062 token allows such completion, return a COMPLETE token.
1063 Otherwise, we were already scanning the original text, and
1064 we're really done. */
1065 if
(saw_name_at_eof
)
1067 saw_name_at_eof
= 0;
1070 else if
(saw_structop
)
1089 if
(paren_depth
== 0)
1096 if
(pstate
->comma_terminates
&& paren_depth
== 0)
1102 /* Might be a floating point number. */
1103 if
(pstate
->lexptr
[1] < '0' || pstate
->lexptr
[1] > '9')
1105 if
(pstate
->parse_completion
)
1106 last_was_structop
= 1;
1107 goto symbol
; /* Nope, must be a symbol. */
1122 /* It's a number. */
1123 int got_dot
= 0, got_e
= 0, toktype
;
1124 const char *p
= tokstart
;
1125 int hex
= input_radix
> 10;
1127 if
(c
== '0' && (p
[1] == 'x' || p
[1] == 'X'))
1135 /* Hex exponents start with 'p', because 'e' is a valid hex
1136 digit and thus does not indicate a floating point number
1137 when the radix is hex. */
1138 if
((!hex
&& !got_e
&& tolower
(p
[0]) == 'e')
1139 ||
(hex
&& !got_e
&& tolower
(p
[0] == 'p')))
1140 got_dot
= got_e
= 1;
1141 /* A '.' always indicates a decimal floating point number
1142 regardless of the radix. If we have a '..' then its the
1143 end of the number and the beginning of a slice. */
1144 else if
(!got_dot
&& (p
[0] == '.' && p
[1] != '.'))
1146 /* This is the sign of the exponent, not the end of the number. */
1147 else if
(got_e
&& (tolower
(p
[-1]) == 'e' || tolower
(p
[-1]) == 'p')
1148 && (*p
== '-' ||
*p
== '+'))
1150 /* We will take any letters or digits, ignoring any embedded '_'.
1151 parse_number will complain if past the radix, or if L or U are
1153 else if
((*p
< '0' ||
*p
> '9') && (*p
!= '_')
1154 && ((*p
< 'a' ||
*p
> 'z') && (*p
< 'A' ||
*p
> 'Z')))
1158 toktype
= parse_number
(par_state
, tokstart
, p
- tokstart
,
1159 got_dot|got_e
, &yylval);
1160 if
(toktype
== ERROR
)
1162 char *err_copy
= (char *) alloca
(p
- tokstart
+ 1);
1164 memcpy
(err_copy
, tokstart
, p
- tokstart
);
1165 err_copy
[p
- tokstart
] = 0;
1166 error (_
("Invalid number \"%s\"."), err_copy
);
1174 const char *p
= &tokstart
[1];
1175 size_t len
= strlen
("entry");
1177 while
(isspace
(*p
))
1179 if
(strncmp
(p
, "entry", len
) == 0 && !isalnum
(p
[len
])
1182 pstate
->lexptr
= &p
[len
];
1213 int result
= parse_string_or_char
(tokstart
, &pstate
->lexptr
,
1214 &yylval.tsval
, &host_len
);
1215 if
(result
== CHARACTER_LITERAL
)
1218 error (_
("Empty character constant."));
1219 else if
(host_len
> 2 && c
== '\'')
1222 namelen
= pstate
->lexptr
- tokstart
- 1;
1225 else if
(host_len
> 1)
1226 error (_
("Invalid character constant."));
1232 if
(!(c
== '_' || c
== '$'
1233 ||
(c
>= 'a' && c
<= 'z') ||
(c
>= 'A' && c
<= 'Z')))
1234 /* We must have come across a bad character (e.g. ';'). */
1235 error (_
("Invalid character '%c' in expression"), c
);
1237 /* It's a name. See how long it is. */
1239 for
(c
= tokstart
[namelen
];
1240 (c
== '_' || c
== '$' ||
(c
>= '0' && c
<= '9')
1241 ||
(c
>= 'a' && c
<= 'z') ||
(c
>= 'A' && c
<= 'Z'));)
1242 c
= tokstart
[++namelen
];
1244 /* The token "if" terminates the expression and is NOT
1245 removed from the input stream. */
1246 if
(namelen
== 2 && tokstart
[0] == 'i' && tokstart
[1] == 'f')
1249 /* For the same reason (breakpoint conditions), "thread N"
1250 terminates the expression. "thread" could be an identifier, but
1251 an identifier is never followed by a number without intervening
1252 punctuation. "task" is similar. Handle abbreviations of these,
1253 similarly to breakpoint.c:find_condition_and_thread. */
1255 && (strncmp
(tokstart
, "thread", namelen
) == 0
1256 || strncmp
(tokstart
, "task", namelen
) == 0)
1257 && (tokstart
[namelen
] == ' ' || tokstart
[namelen
] == '\t'))
1259 const char *p
= tokstart
+ namelen
+ 1;
1261 while
(*p
== ' ' ||
*p
== '\t')
1263 if
(*p
>= '0' && *p
<= '9')
1267 pstate
->lexptr
+= namelen
;
1271 yylval.sval.ptr
= tokstart
;
1272 yylval.sval.length
= namelen
;
1274 /* Catch specific keywords. */
1275 std
::string copy
= copy_name
(yylval.sval
);
1276 for
(const auto
&token
: ident_tokens
)
1277 if
(copy
== token.oper
)
1279 /* It is ok to always set this, even though we don't always
1280 strictly need to. */
1281 yylval.opcode
= token.opcode
;
1285 if
(*tokstart
== '$')
1286 return DOLLAR_VARIABLE
;
1289 = language_lookup_primitive_type
(par_state
->language
(),
1290 par_state
->gdbarch
(), copy.c_str
());
1291 if
(yylval.tsym.type
!= NULL
)
1294 /* Input names that aren't symbols but ARE valid hex numbers,
1295 when the input radix permits them, can be names or numbers
1296 depending on the parse. Note we support radixes > 16 here. */
1297 if
((tokstart
[0] >= 'a' && tokstart
[0] < 'a' + input_radix
- 10)
1298 ||
(tokstart
[0] >= 'A' && tokstart
[0] < 'A' + input_radix
- 10))
1300 YYSTYPE newlval
; /* Its value is ignored. */
1301 int hextype
= parse_number
(par_state
, tokstart
, namelen
, 0, &newlval
);
1302 if
(hextype
== INTEGER_LITERAL
)
1306 if
(pstate
->parse_completion
&& *pstate
->lexptr
== '\0')
1307 saw_name_at_eof
= 1;
1312 /* An object of this type is pushed on a FIFO by the "outer" lexer. */
1313 struct token_and_value
1320 /* A FIFO of tokens that have been read but not yet returned to the
1322 static std
::vector
<token_and_value
> token_fifo
;
1324 /* Non-zero if the lexer should return tokens from the FIFO. */
1327 /* Temporary storage for yylex; this holds symbol names as they are
1329 static auto_obstack name_obstack
;
1331 /* Classify an IDENTIFIER token. The contents of the token are in `yylval'.
1332 Updates yylval and returns the new token type. BLOCK is the block
1333 in which lookups start; this can be NULL to mean the global scope. */
1336 classify_name
(struct parser_state
*par_state
, const struct block
*block
)
1338 struct block_symbol sym
;
1339 struct field_of_this_result is_a_field_of_this
;
1341 std
::string copy
= copy_name
(yylval.sval
);
1343 sym
= lookup_symbol
(copy.c_str
(), block
, VAR_DOMAIN
, &is_a_field_of_this
);
1344 if
(sym.symbol
&& sym.symbol
->aclass
() == LOC_TYPEDEF
)
1346 yylval.tsym.type
= sym.symbol
->type
();
1349 else if
(sym.symbol
== NULL
)
1351 /* Look-up first for a module name, then a type. */
1352 sym
= lookup_symbol
(copy.c_str
(), block
, MODULE_DOMAIN
, NULL
);
1353 if
(sym.symbol
== NULL
)
1354 sym
= lookup_symbol
(copy.c_str
(), block
, STRUCT_DOMAIN
, NULL
);
1356 if
(sym.symbol
!= NULL
)
1358 yylval.tsym.type
= sym.symbol
->type
();
1362 return UNKNOWN_NAME
;
1368 /* Like classify_name, but used by the inner loop of the lexer, when a
1369 name might have already been seen. CONTEXT is the context type, or
1370 NULL if this is the first component of a name. */
1373 classify_inner_name
(struct parser_state
*par_state
,
1374 const struct block
*block
, struct type
*context
)
1378 if
(context
== NULL
)
1379 return classify_name
(par_state
, block
);
1381 type
= check_typedef
(context
);
1382 if
(!type_aggregate_p
(type
))
1385 std
::string copy
= copy_name
(yylval.ssym.stoken
);
1386 yylval.ssym.sym
= d_lookup_nested_symbol
(type
, copy.c_str
(), block
);
1388 if
(yylval.ssym.sym.symbol
== NULL
)
1391 if
(yylval.ssym.sym.symbol
->aclass
() == LOC_TYPEDEF
)
1393 yylval.tsym.type
= yylval.ssym.sym.symbol
->type
();
1400 /* The outer level of a two-level lexer. This calls the inner lexer
1401 to return tokens. It then either returns these tokens, or
1402 aggregates them into a larger token. This lets us work around a
1403 problem in our parsing approach, where the parser could not
1404 distinguish between qualified names and qualified types at the
1410 token_and_value current
;
1412 struct type
*context_type
= NULL
;
1413 int last_to_examine
, next_to_examine
, checkpoint
;
1414 const struct block
*search_block
;
1416 if
(popping
&& !token_fifo.empty
())
1420 /* Read the first token and decide what to do. */
1421 current.token
= lex_one_token
(pstate
);
1422 if
(current.token
!= IDENTIFIER
&& current.token
!= '.')
1423 return current.token
;
1425 /* Read any sequence of alternating "." and identifier tokens into
1427 current.value
= yylval;
1428 token_fifo.push_back
(current
);
1429 last_was_dot
= current.token
== '.';
1433 current.token
= lex_one_token
(pstate
);
1434 current.value
= yylval;
1435 token_fifo.push_back
(current
);
1437 if
((last_was_dot
&& current.token
!= IDENTIFIER
)
1438 ||
(!last_was_dot
&& current.token
!= '.'))
1441 last_was_dot
= !last_was_dot
;
1445 /* We always read one extra token, so compute the number of tokens
1446 to examine accordingly. */
1447 last_to_examine
= token_fifo.size
() - 2;
1448 next_to_examine
= 0;
1450 current
= token_fifo
[next_to_examine
];
1453 /* If we are not dealing with a typename, now is the time to find out. */
1454 if
(current.token
== IDENTIFIER
)
1456 yylval = current.value
;
1457 current.token
= classify_name
(pstate
, pstate
->expression_context_block
);
1458 current.value
= yylval;
1461 /* If the IDENTIFIER is not known, it could be a package symbol,
1462 first try building up a name until we find the qualified module. */
1463 if
(current.token
== UNKNOWN_NAME
)
1465 name_obstack.clear
();
1466 obstack_grow
(&name_obstack
, current.value.sval.ptr
,
1467 current.value.sval.length
);
1471 while
(next_to_examine
<= last_to_examine
)
1473 token_and_value next
;
1475 next
= token_fifo
[next_to_examine
];
1478 if
(next.token
== IDENTIFIER
&& last_was_dot
)
1480 /* Update the partial name we are constructing. */
1481 obstack_grow_str
(&name_obstack
, ".");
1482 obstack_grow
(&name_obstack
, next.value.sval.ptr
,
1483 next.value.sval.length
);
1485 yylval.sval.ptr
= (char *) obstack_base
(&name_obstack
);
1486 yylval.sval.length
= obstack_object_size
(&name_obstack
);
1488 current.token
= classify_name
(pstate
,
1489 pstate
->expression_context_block
);
1490 current.value
= yylval;
1492 /* We keep going until we find a TYPENAME. */
1493 if
(current.token
== TYPENAME
)
1495 /* Install it as the first token in the FIFO. */
1496 token_fifo
[0] = current
;
1497 token_fifo.erase
(token_fifo.begin
() + 1,
1498 token_fifo.begin
() + next_to_examine
);
1502 else if
(next.token
== '.' && !last_was_dot
)
1506 /* We've reached the end of the name. */
1511 /* Reset our current token back to the start, if we found nothing
1512 this means that we will just jump to do pop. */
1513 current
= token_fifo
[0];
1514 next_to_examine
= 1;
1516 if
(current.token
!= TYPENAME
&& current.token
!= '.')
1519 name_obstack.clear
();
1521 if
(current.token
== '.')
1522 search_block
= NULL
;
1525 gdb_assert
(current.token
== TYPENAME
);
1526 search_block
= pstate
->expression_context_block
;
1527 obstack_grow
(&name_obstack
, current.value.sval.ptr
,
1528 current.value.sval.length
);
1529 context_type
= current.value.tsym.type
;
1533 last_was_dot
= current.token
== '.';
1535 while
(next_to_examine
<= last_to_examine
)
1537 token_and_value next
;
1539 next
= token_fifo
[next_to_examine
];
1542 if
(next.token
== IDENTIFIER
&& last_was_dot
)
1546 yylval = next.value
;
1547 classification
= classify_inner_name
(pstate
, search_block
,
1549 /* We keep going until we either run out of names, or until
1550 we have a qualified name which is not a type. */
1551 if
(classification
!= TYPENAME
&& classification
!= IDENTIFIER
)
1554 /* Accept up to this token. */
1555 checkpoint
= next_to_examine
;
1557 /* Update the partial name we are constructing. */
1558 if
(context_type
!= NULL
)
1560 /* We don't want to put a leading "." into the name. */
1561 obstack_grow_str
(&name_obstack
, ".");
1563 obstack_grow
(&name_obstack
, next.value.sval.ptr
,
1564 next.value.sval.length
);
1566 yylval.sval.ptr
= (char *) obstack_base
(&name_obstack
);
1567 yylval.sval.length
= obstack_object_size
(&name_obstack
);
1568 current.value
= yylval;
1569 current.token
= classification
;
1573 if
(classification
== IDENTIFIER
)
1576 context_type
= yylval.tsym.type
;
1578 else if
(next.token
== '.' && !last_was_dot
)
1582 /* We've reached the end of the name. */
1587 /* If we have a replacement token, install it as the first token in
1588 the FIFO, and delete the other constituent tokens. */
1591 token_fifo
[0] = current
;
1593 token_fifo.erase
(token_fifo.begin
() + 1,
1594 token_fifo.begin
() + checkpoint
);
1598 current
= token_fifo
[0];
1599 token_fifo.erase
(token_fifo.begin
());
1600 yylval = current.value
;
1601 return current.token
;
1605 d_parse
(struct parser_state
*par_state
)
1607 /* Setting up the parser state. */
1608 scoped_restore pstate_restore
= make_scoped_restore
(&pstate
);
1609 gdb_assert
(par_state
!= NULL
);
1612 scoped_restore restore_yydebug
= make_scoped_restore
(&yydebug,
1615 struct type_stack stack
;
1616 scoped_restore restore_type_stack
= make_scoped_restore
(&type_stack
,
1619 /* Initialize some state used by the lexer. */
1620 last_was_structop
= 0;
1621 saw_name_at_eof
= 0;
1624 token_fifo.clear
();
1626 name_obstack.clear
();
1628 int result
= yyparse ();
1630 pstate
->set_operation
(pstate
->pop
());
1635 yyerror (const char *msg
)
1637 if
(pstate
->prev_lexptr
)
1638 pstate
->lexptr
= pstate
->prev_lexptr
;
1640 error (_
("A %s in expression, near `%s'."), msg
, pstate
->lexptr
);