More block constification
[deliverable/binutils-gdb.git] / gdb / d-exp.y
1 /* YACC parser for D expressions, for GDB.
2
3 Copyright (C) 2014-2019 Free Software Foundation, Inc.
4
5 This file is part of GDB.
6
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.
11
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.
16
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/>. */
19
20 /* This file is derived from c-exp.y, jv-exp.y. */
21
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.
30
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. */
38
39 %{
40
41 #include "defs.h"
42 #include <ctype.h>
43 #include "expression.h"
44 #include "value.h"
45 #include "parser-defs.h"
46 #include "language.h"
47 #include "c-lang.h"
48 #include "d-lang.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 */
52 #include "charset.h"
53 #include "block.h"
54
55 #define parse_type(ps) builtin_type (parse_gdbarch (ps))
56 #define parse_d_type(ps) builtin_d_type (parse_gdbarch (ps))
57
58 /* Remap normal yacc parser interface names (yyparse, yylex, yyerror,
59 etc). */
60 #define GDB_YY_REMAP_PREFIX d_
61 #include "yy-remap.h"
62
63 /* The state of the parser, used internally when we are parsing the
64 expression. */
65
66 static struct parser_state *pstate = NULL;
67
68 int yyparse (void);
69
70 static int yylex (void);
71
72 static void yyerror (const char *);
73
74 static int type_aggregate_p (struct type *);
75
76 %}
77
78 /* Although the yacc "value" of an expression is not used,
79 since the result is stored in the structure being created,
80 other node types do have values. */
81
82 %union
83 {
84 struct {
85 LONGEST val;
86 struct type *type;
87 } typed_val_int;
88 struct {
89 gdb_byte val[16];
90 struct type *type;
91 } typed_val_float;
92 struct symbol *sym;
93 struct type *tval;
94 struct typed_stoken tsval;
95 struct stoken sval;
96 struct ttype tsym;
97 struct symtoken ssym;
98 int ival;
99 int voidval;
100 enum exp_opcode opcode;
101 struct stoken_vector svec;
102 }
103
104 %{
105 /* YYSTYPE gets defined by %union */
106 static int parse_number (struct parser_state *, const char *,
107 int, int, YYSTYPE *);
108 %}
109
110 %token <sval> IDENTIFIER UNKNOWN_NAME
111 %token <tsym> TYPENAME
112 %token <voidval> COMPLETE
113
114 /* A NAME_OR_INT is a symbol which is not known in the symbol table,
115 but which would parse as a valid number in the current input radix.
116 E.g. "c" when input_radix==16. Depending on the parse, it will be
117 turned into a name or into a number. */
118
119 %token <sval> NAME_OR_INT
120
121 %token <typed_val_int> INTEGER_LITERAL
122 %token <typed_val_float> FLOAT_LITERAL
123 %token <tsval> CHARACTER_LITERAL
124 %token <tsval> STRING_LITERAL
125
126 %type <svec> StringExp
127 %type <tval> BasicType TypeExp
128 %type <sval> IdentifierExp
129 %type <ival> ArrayLiteral
130
131 %token ENTRY
132 %token ERROR
133
134 /* Keywords that have a constant value. */
135 %token TRUE_KEYWORD FALSE_KEYWORD NULL_KEYWORD
136 /* Class 'super' accessor. */
137 %token SUPER_KEYWORD
138 /* Properties. */
139 %token CAST_KEYWORD SIZEOF_KEYWORD
140 %token TYPEOF_KEYWORD TYPEID_KEYWORD
141 %token INIT_KEYWORD
142 /* Comparison keywords. */
143 /* Type storage classes. */
144 %token IMMUTABLE_KEYWORD CONST_KEYWORD SHARED_KEYWORD
145 /* Non-scalar type keywords. */
146 %token STRUCT_KEYWORD UNION_KEYWORD
147 %token CLASS_KEYWORD INTERFACE_KEYWORD
148 %token ENUM_KEYWORD TEMPLATE_KEYWORD
149 %token DELEGATE_KEYWORD FUNCTION_KEYWORD
150
151 %token <sval> DOLLAR_VARIABLE
152
153 %token <opcode> ASSIGN_MODIFY
154
155 %left ','
156 %right '=' ASSIGN_MODIFY
157 %right '?'
158 %left OROR
159 %left ANDAND
160 %left '|'
161 %left '^'
162 %left '&'
163 %left EQUAL NOTEQUAL '<' '>' LEQ GEQ
164 %right LSH RSH
165 %left '+' '-'
166 %left '*' '/' '%'
167 %right HATHAT
168 %left IDENTITY NOTIDENTITY
169 %right INCREMENT DECREMENT
170 %right '.' '[' '('
171 %token DOTDOT
172
173 \f
174 %%
175
176 start :
177 Expression
178 | TypeExp
179 ;
180
181 /* Expressions, including the comma operator. */
182
183 Expression:
184 CommaExpression
185 ;
186
187 CommaExpression:
188 AssignExpression
189 | AssignExpression ',' CommaExpression
190 { write_exp_elt_opcode (pstate, BINOP_COMMA); }
191 ;
192
193 AssignExpression:
194 ConditionalExpression
195 | ConditionalExpression '=' AssignExpression
196 { write_exp_elt_opcode (pstate, BINOP_ASSIGN); }
197 | ConditionalExpression ASSIGN_MODIFY AssignExpression
198 { write_exp_elt_opcode (pstate, BINOP_ASSIGN_MODIFY);
199 write_exp_elt_opcode (pstate, $2);
200 write_exp_elt_opcode (pstate, BINOP_ASSIGN_MODIFY); }
201 ;
202
203 ConditionalExpression:
204 OrOrExpression
205 | OrOrExpression '?' Expression ':' ConditionalExpression
206 { write_exp_elt_opcode (pstate, TERNOP_COND); }
207 ;
208
209 OrOrExpression:
210 AndAndExpression
211 | OrOrExpression OROR AndAndExpression
212 { write_exp_elt_opcode (pstate, BINOP_LOGICAL_OR); }
213 ;
214
215 AndAndExpression:
216 OrExpression
217 | AndAndExpression ANDAND OrExpression
218 { write_exp_elt_opcode (pstate, BINOP_LOGICAL_AND); }
219 ;
220
221 OrExpression:
222 XorExpression
223 | OrExpression '|' XorExpression
224 { write_exp_elt_opcode (pstate, BINOP_BITWISE_IOR); }
225 ;
226
227 XorExpression:
228 AndExpression
229 | XorExpression '^' AndExpression
230 { write_exp_elt_opcode (pstate, BINOP_BITWISE_XOR); }
231 ;
232
233 AndExpression:
234 CmpExpression
235 | AndExpression '&' CmpExpression
236 { write_exp_elt_opcode (pstate, BINOP_BITWISE_AND); }
237 ;
238
239 CmpExpression:
240 ShiftExpression
241 | EqualExpression
242 | IdentityExpression
243 | RelExpression
244 ;
245
246 EqualExpression:
247 ShiftExpression EQUAL ShiftExpression
248 { write_exp_elt_opcode (pstate, BINOP_EQUAL); }
249 | ShiftExpression NOTEQUAL ShiftExpression
250 { write_exp_elt_opcode (pstate, BINOP_NOTEQUAL); }
251 ;
252
253 IdentityExpression:
254 ShiftExpression IDENTITY ShiftExpression
255 { write_exp_elt_opcode (pstate, BINOP_EQUAL); }
256 | ShiftExpression NOTIDENTITY ShiftExpression
257 { write_exp_elt_opcode (pstate, BINOP_NOTEQUAL); }
258 ;
259
260 RelExpression:
261 ShiftExpression '<' ShiftExpression
262 { write_exp_elt_opcode (pstate, BINOP_LESS); }
263 | ShiftExpression LEQ ShiftExpression
264 { write_exp_elt_opcode (pstate, BINOP_LEQ); }
265 | ShiftExpression '>' ShiftExpression
266 { write_exp_elt_opcode (pstate, BINOP_GTR); }
267 | ShiftExpression GEQ ShiftExpression
268 { write_exp_elt_opcode (pstate, BINOP_GEQ); }
269 ;
270
271 ShiftExpression:
272 AddExpression
273 | ShiftExpression LSH AddExpression
274 { write_exp_elt_opcode (pstate, BINOP_LSH); }
275 | ShiftExpression RSH AddExpression
276 { write_exp_elt_opcode (pstate, BINOP_RSH); }
277 ;
278
279 AddExpression:
280 MulExpression
281 | AddExpression '+' MulExpression
282 { write_exp_elt_opcode (pstate, BINOP_ADD); }
283 | AddExpression '-' MulExpression
284 { write_exp_elt_opcode (pstate, BINOP_SUB); }
285 | AddExpression '~' MulExpression
286 { write_exp_elt_opcode (pstate, BINOP_CONCAT); }
287 ;
288
289 MulExpression:
290 UnaryExpression
291 | MulExpression '*' UnaryExpression
292 { write_exp_elt_opcode (pstate, BINOP_MUL); }
293 | MulExpression '/' UnaryExpression
294 { write_exp_elt_opcode (pstate, BINOP_DIV); }
295 | MulExpression '%' UnaryExpression
296 { write_exp_elt_opcode (pstate, BINOP_REM); }
297
298 UnaryExpression:
299 '&' UnaryExpression
300 { write_exp_elt_opcode (pstate, UNOP_ADDR); }
301 | INCREMENT UnaryExpression
302 { write_exp_elt_opcode (pstate, UNOP_PREINCREMENT); }
303 | DECREMENT UnaryExpression
304 { write_exp_elt_opcode (pstate, UNOP_PREDECREMENT); }
305 | '*' UnaryExpression
306 { write_exp_elt_opcode (pstate, UNOP_IND); }
307 | '-' UnaryExpression
308 { write_exp_elt_opcode (pstate, UNOP_NEG); }
309 | '+' UnaryExpression
310 { write_exp_elt_opcode (pstate, UNOP_PLUS); }
311 | '!' UnaryExpression
312 { write_exp_elt_opcode (pstate, UNOP_LOGICAL_NOT); }
313 | '~' UnaryExpression
314 { write_exp_elt_opcode (pstate, UNOP_COMPLEMENT); }
315 | TypeExp '.' SIZEOF_KEYWORD
316 { write_exp_elt_opcode (pstate, UNOP_SIZEOF); }
317 | CastExpression
318 | PowExpression
319 ;
320
321 CastExpression:
322 CAST_KEYWORD '(' TypeExp ')' UnaryExpression
323 { write_exp_elt_opcode (pstate, UNOP_CAST_TYPE); }
324 /* C style cast is illegal D, but is still recognised in
325 the grammar, so we keep this around for convenience. */
326 | '(' TypeExp ')' UnaryExpression
327 { write_exp_elt_opcode (pstate, UNOP_CAST_TYPE); }
328
329 ;
330
331 PowExpression:
332 PostfixExpression
333 | PostfixExpression HATHAT UnaryExpression
334 { write_exp_elt_opcode (pstate, BINOP_EXP); }
335 ;
336
337 PostfixExpression:
338 PrimaryExpression
339 | PostfixExpression '.' COMPLETE
340 { struct stoken s;
341 mark_struct_expression (pstate);
342 write_exp_elt_opcode (pstate, STRUCTOP_STRUCT);
343 s.ptr = "";
344 s.length = 0;
345 write_exp_string (pstate, s);
346 write_exp_elt_opcode (pstate, STRUCTOP_STRUCT); }
347 | PostfixExpression '.' IDENTIFIER
348 { write_exp_elt_opcode (pstate, STRUCTOP_STRUCT);
349 write_exp_string (pstate, $3);
350 write_exp_elt_opcode (pstate, STRUCTOP_STRUCT); }
351 | PostfixExpression '.' IDENTIFIER COMPLETE
352 { mark_struct_expression (pstate);
353 write_exp_elt_opcode (pstate, STRUCTOP_STRUCT);
354 write_exp_string (pstate, $3);
355 write_exp_elt_opcode (pstate, STRUCTOP_STRUCT); }
356 | PostfixExpression '.' SIZEOF_KEYWORD
357 { write_exp_elt_opcode (pstate, UNOP_SIZEOF); }
358 | PostfixExpression INCREMENT
359 { write_exp_elt_opcode (pstate, UNOP_POSTINCREMENT); }
360 | PostfixExpression DECREMENT
361 { write_exp_elt_opcode (pstate, UNOP_POSTDECREMENT); }
362 | CallExpression
363 | IndexExpression
364 | SliceExpression
365 ;
366
367 ArgumentList:
368 AssignExpression
369 { arglist_len = 1; }
370 | ArgumentList ',' AssignExpression
371 { arglist_len++; }
372 ;
373
374 ArgumentList_opt:
375 /* EMPTY */
376 { arglist_len = 0; }
377 | ArgumentList
378 ;
379
380 CallExpression:
381 PostfixExpression '('
382 { start_arglist (); }
383 ArgumentList_opt ')'
384 { write_exp_elt_opcode (pstate, OP_FUNCALL);
385 write_exp_elt_longcst (pstate, (LONGEST) end_arglist ());
386 write_exp_elt_opcode (pstate, OP_FUNCALL); }
387 ;
388
389 IndexExpression:
390 PostfixExpression '[' ArgumentList ']'
391 { if (arglist_len > 0)
392 {
393 write_exp_elt_opcode (pstate, MULTI_SUBSCRIPT);
394 write_exp_elt_longcst (pstate, (LONGEST) arglist_len);
395 write_exp_elt_opcode (pstate, MULTI_SUBSCRIPT);
396 }
397 else
398 write_exp_elt_opcode (pstate, BINOP_SUBSCRIPT);
399 }
400 ;
401
402 SliceExpression:
403 PostfixExpression '[' ']'
404 { /* Do nothing. */ }
405 | PostfixExpression '[' AssignExpression DOTDOT AssignExpression ']'
406 { write_exp_elt_opcode (pstate, TERNOP_SLICE); }
407 ;
408
409 PrimaryExpression:
410 '(' Expression ')'
411 { /* Do nothing. */ }
412 | IdentifierExp
413 { struct bound_minimal_symbol msymbol;
414 char *copy = copy_name ($1);
415 struct field_of_this_result is_a_field_of_this;
416 struct block_symbol sym;
417
418 /* Handle VAR, which could be local or global. */
419 sym = lookup_symbol (copy, expression_context_block, VAR_DOMAIN,
420 &is_a_field_of_this);
421 if (sym.symbol && SYMBOL_CLASS (sym.symbol) != LOC_TYPEDEF)
422 {
423 if (symbol_read_needs_frame (sym.symbol))
424 innermost_block.update (sym);
425 write_exp_elt_opcode (pstate, OP_VAR_VALUE);
426 write_exp_elt_block (pstate, sym.block);
427 write_exp_elt_sym (pstate, sym.symbol);
428 write_exp_elt_opcode (pstate, OP_VAR_VALUE);
429 }
430 else if (is_a_field_of_this.type != NULL)
431 {
432 /* It hangs off of `this'. Must not inadvertently convert from a
433 method call to data ref. */
434 innermost_block.update (sym);
435 write_exp_elt_opcode (pstate, OP_THIS);
436 write_exp_elt_opcode (pstate, OP_THIS);
437 write_exp_elt_opcode (pstate, STRUCTOP_PTR);
438 write_exp_string (pstate, $1);
439 write_exp_elt_opcode (pstate, STRUCTOP_PTR);
440 }
441 else
442 {
443 /* Lookup foreign name in global static symbols. */
444 msymbol = lookup_bound_minimal_symbol (copy);
445 if (msymbol.minsym != NULL)
446 write_exp_msymbol (pstate, msymbol);
447 else if (!have_full_symbols () && !have_partial_symbols ())
448 error (_("No symbol table is loaded. Use the \"file\" command"));
449 else
450 error (_("No symbol \"%s\" in current context."), copy);
451 }
452 }
453 | TypeExp '.' IdentifierExp
454 { struct type *type = check_typedef ($1);
455
456 /* Check if the qualified name is in the global
457 context. However if the symbol has not already
458 been resolved, it's not likely to be found. */
459 if (TYPE_CODE (type) == TYPE_CODE_MODULE)
460 {
461 struct bound_minimal_symbol msymbol;
462 struct block_symbol sym;
463 const char *type_name = TYPE_SAFE_NAME (type);
464 int type_name_len = strlen (type_name);
465 std::string name
466 = string_printf ("%.*s.%.*s",
467 type_name_len, type_name,
468 $3.length, $3.ptr);
469
470 sym =
471 lookup_symbol (name.c_str (),
472 (const struct block *) NULL,
473 VAR_DOMAIN, NULL);
474 if (sym.symbol)
475 {
476 write_exp_elt_opcode (pstate, OP_VAR_VALUE);
477 write_exp_elt_block (pstate, sym.block);
478 write_exp_elt_sym (pstate, sym.symbol);
479 write_exp_elt_opcode (pstate, OP_VAR_VALUE);
480 break;
481 }
482
483 msymbol = lookup_bound_minimal_symbol (name.c_str ());
484 if (msymbol.minsym != NULL)
485 write_exp_msymbol (pstate, msymbol);
486 else if (!have_full_symbols () && !have_partial_symbols ())
487 error (_("No symbol table is loaded. Use the \"file\" command."));
488 else
489 error (_("No symbol \"%s\" in current context."),
490 name.c_str ());
491 }
492
493 /* Check if the qualified name resolves as a member
494 of an aggregate or an enum type. */
495 if (!type_aggregate_p (type))
496 error (_("`%s' is not defined as an aggregate type."),
497 TYPE_SAFE_NAME (type));
498
499 write_exp_elt_opcode (pstate, OP_SCOPE);
500 write_exp_elt_type (pstate, type);
501 write_exp_string (pstate, $3);
502 write_exp_elt_opcode (pstate, OP_SCOPE);
503 }
504 | DOLLAR_VARIABLE
505 { write_dollar_variable (pstate, $1); }
506 | NAME_OR_INT
507 { YYSTYPE val;
508 parse_number (pstate, $1.ptr, $1.length, 0, &val);
509 write_exp_elt_opcode (pstate, OP_LONG);
510 write_exp_elt_type (pstate, val.typed_val_int.type);
511 write_exp_elt_longcst (pstate,
512 (LONGEST) val.typed_val_int.val);
513 write_exp_elt_opcode (pstate, OP_LONG); }
514 | NULL_KEYWORD
515 { struct type *type = parse_d_type (pstate)->builtin_void;
516 type = lookup_pointer_type (type);
517 write_exp_elt_opcode (pstate, OP_LONG);
518 write_exp_elt_type (pstate, type);
519 write_exp_elt_longcst (pstate, (LONGEST) 0);
520 write_exp_elt_opcode (pstate, OP_LONG); }
521 | TRUE_KEYWORD
522 { write_exp_elt_opcode (pstate, OP_BOOL);
523 write_exp_elt_longcst (pstate, (LONGEST) 1);
524 write_exp_elt_opcode (pstate, OP_BOOL); }
525 | FALSE_KEYWORD
526 { write_exp_elt_opcode (pstate, OP_BOOL);
527 write_exp_elt_longcst (pstate, (LONGEST) 0);
528 write_exp_elt_opcode (pstate, OP_BOOL); }
529 | INTEGER_LITERAL
530 { write_exp_elt_opcode (pstate, OP_LONG);
531 write_exp_elt_type (pstate, $1.type);
532 write_exp_elt_longcst (pstate, (LONGEST)($1.val));
533 write_exp_elt_opcode (pstate, OP_LONG); }
534 | FLOAT_LITERAL
535 { write_exp_elt_opcode (pstate, OP_FLOAT);
536 write_exp_elt_type (pstate, $1.type);
537 write_exp_elt_floatcst (pstate, $1.val);
538 write_exp_elt_opcode (pstate, OP_FLOAT); }
539 | CHARACTER_LITERAL
540 { struct stoken_vector vec;
541 vec.len = 1;
542 vec.tokens = &$1;
543 write_exp_string_vector (pstate, $1.type, &vec); }
544 | StringExp
545 { int i;
546 write_exp_string_vector (pstate, 0, &$1);
547 for (i = 0; i < $1.len; ++i)
548 free ($1.tokens[i].ptr);
549 free ($1.tokens); }
550 | ArrayLiteral
551 { write_exp_elt_opcode (pstate, OP_ARRAY);
552 write_exp_elt_longcst (pstate, (LONGEST) 0);
553 write_exp_elt_longcst (pstate, (LONGEST) $1 - 1);
554 write_exp_elt_opcode (pstate, OP_ARRAY); }
555 | TYPEOF_KEYWORD '(' Expression ')'
556 { write_exp_elt_opcode (pstate, OP_TYPEOF); }
557 ;
558
559 ArrayLiteral:
560 '[' ArgumentList_opt ']'
561 { $$ = arglist_len; }
562 ;
563
564 IdentifierExp:
565 IDENTIFIER
566 ;
567
568 StringExp:
569 STRING_LITERAL
570 { /* We copy the string here, and not in the
571 lexer, to guarantee that we do not leak a
572 string. Note that we follow the
573 NUL-termination convention of the
574 lexer. */
575 struct typed_stoken *vec = XNEW (struct typed_stoken);
576 $$.len = 1;
577 $$.tokens = vec;
578
579 vec->type = $1.type;
580 vec->length = $1.length;
581 vec->ptr = (char *) malloc ($1.length + 1);
582 memcpy (vec->ptr, $1.ptr, $1.length + 1);
583 }
584 | StringExp STRING_LITERAL
585 { /* Note that we NUL-terminate here, but just
586 for convenience. */
587 char *p;
588 ++$$.len;
589 $$.tokens
590 = XRESIZEVEC (struct typed_stoken, $$.tokens, $$.len);
591
592 p = (char *) malloc ($2.length + 1);
593 memcpy (p, $2.ptr, $2.length + 1);
594
595 $$.tokens[$$.len - 1].type = $2.type;
596 $$.tokens[$$.len - 1].length = $2.length;
597 $$.tokens[$$.len - 1].ptr = p;
598 }
599 ;
600
601 TypeExp:
602 '(' TypeExp ')'
603 { /* Do nothing. */ }
604 | BasicType
605 { write_exp_elt_opcode (pstate, OP_TYPE);
606 write_exp_elt_type (pstate, $1);
607 write_exp_elt_opcode (pstate, OP_TYPE); }
608 | BasicType BasicType2
609 { $$ = follow_types ($1);
610 write_exp_elt_opcode (pstate, OP_TYPE);
611 write_exp_elt_type (pstate, $$);
612 write_exp_elt_opcode (pstate, OP_TYPE);
613 }
614 ;
615
616 BasicType2:
617 '*'
618 { push_type (tp_pointer); }
619 | '*' BasicType2
620 { push_type (tp_pointer); }
621 | '[' INTEGER_LITERAL ']'
622 { push_type_int ($2.val);
623 push_type (tp_array); }
624 | '[' INTEGER_LITERAL ']' BasicType2
625 { push_type_int ($2.val);
626 push_type (tp_array); }
627 ;
628
629 BasicType:
630 TYPENAME
631 { $$ = $1.type; }
632 ;
633
634 %%
635
636 /* Return true if the type is aggregate-like. */
637
638 static int
639 type_aggregate_p (struct type *type)
640 {
641 return (TYPE_CODE (type) == TYPE_CODE_STRUCT
642 || TYPE_CODE (type) == TYPE_CODE_UNION
643 || TYPE_CODE (type) == TYPE_CODE_MODULE
644 || (TYPE_CODE (type) == TYPE_CODE_ENUM
645 && TYPE_DECLARED_CLASS (type)));
646 }
647
648 /* Take care of parsing a number (anything that starts with a digit).
649 Set yylval and return the token type; update lexptr.
650 LEN is the number of characters in it. */
651
652 /*** Needs some error checking for the float case ***/
653
654 static int
655 parse_number (struct parser_state *ps, const char *p,
656 int len, int parsed_float, YYSTYPE *putithere)
657 {
658 ULONGEST n = 0;
659 ULONGEST prevn = 0;
660 ULONGEST un;
661
662 int i = 0;
663 int c;
664 int base = input_radix;
665 int unsigned_p = 0;
666 int long_p = 0;
667
668 /* We have found a "L" or "U" suffix. */
669 int found_suffix = 0;
670
671 ULONGEST high_bit;
672 struct type *signed_type;
673 struct type *unsigned_type;
674
675 if (parsed_float)
676 {
677 char *s, *sp;
678
679 /* Strip out all embedded '_' before passing to parse_float. */
680 s = (char *) alloca (len + 1);
681 sp = s;
682 while (len-- > 0)
683 {
684 if (*p != '_')
685 *sp++ = *p;
686 p++;
687 }
688 *sp = '\0';
689 len = strlen (s);
690
691 /* Check suffix for `i' , `fi' or `li' (idouble, ifloat or ireal). */
692 if (len >= 1 && tolower (s[len - 1]) == 'i')
693 {
694 if (len >= 2 && tolower (s[len - 2]) == 'f')
695 {
696 putithere->typed_val_float.type
697 = parse_d_type (ps)->builtin_ifloat;
698 len -= 2;
699 }
700 else if (len >= 2 && tolower (s[len - 2]) == 'l')
701 {
702 putithere->typed_val_float.type
703 = parse_d_type (ps)->builtin_ireal;
704 len -= 2;
705 }
706 else
707 {
708 putithere->typed_val_float.type
709 = parse_d_type (ps)->builtin_idouble;
710 len -= 1;
711 }
712 }
713 /* Check suffix for `f' or `l'' (float or real). */
714 else if (len >= 1 && tolower (s[len - 1]) == 'f')
715 {
716 putithere->typed_val_float.type
717 = parse_d_type (ps)->builtin_float;
718 len -= 1;
719 }
720 else if (len >= 1 && tolower (s[len - 1]) == 'l')
721 {
722 putithere->typed_val_float.type
723 = parse_d_type (ps)->builtin_real;
724 len -= 1;
725 }
726 /* Default type if no suffix. */
727 else
728 {
729 putithere->typed_val_float.type
730 = parse_d_type (ps)->builtin_double;
731 }
732
733 if (!parse_float (s, len,
734 putithere->typed_val_float.type,
735 putithere->typed_val_float.val))
736 return ERROR;
737
738 return FLOAT_LITERAL;
739 }
740
741 /* Handle base-switching prefixes 0x, 0b, 0 */
742 if (p[0] == '0')
743 switch (p[1])
744 {
745 case 'x':
746 case 'X':
747 if (len >= 3)
748 {
749 p += 2;
750 base = 16;
751 len -= 2;
752 }
753 break;
754
755 case 'b':
756 case 'B':
757 if (len >= 3)
758 {
759 p += 2;
760 base = 2;
761 len -= 2;
762 }
763 break;
764
765 default:
766 base = 8;
767 break;
768 }
769
770 while (len-- > 0)
771 {
772 c = *p++;
773 if (c == '_')
774 continue; /* Ignore embedded '_'. */
775 if (c >= 'A' && c <= 'Z')
776 c += 'a' - 'A';
777 if (c != 'l' && c != 'u')
778 n *= base;
779 if (c >= '0' && c <= '9')
780 {
781 if (found_suffix)
782 return ERROR;
783 n += i = c - '0';
784 }
785 else
786 {
787 if (base > 10 && c >= 'a' && c <= 'f')
788 {
789 if (found_suffix)
790 return ERROR;
791 n += i = c - 'a' + 10;
792 }
793 else if (c == 'l' && long_p == 0)
794 {
795 long_p = 1;
796 found_suffix = 1;
797 }
798 else if (c == 'u' && unsigned_p == 0)
799 {
800 unsigned_p = 1;
801 found_suffix = 1;
802 }
803 else
804 return ERROR; /* Char not a digit */
805 }
806 if (i >= base)
807 return ERROR; /* Invalid digit in this base. */
808 /* Portably test for integer overflow. */
809 if (c != 'l' && c != 'u')
810 {
811 ULONGEST n2 = prevn * base;
812 if ((n2 / base != prevn) || (n2 + i < prevn))
813 error (_("Numeric constant too large."));
814 }
815 prevn = n;
816 }
817
818 /* An integer constant is an int or a long. An L suffix forces it to
819 be long, and a U suffix forces it to be unsigned. To figure out
820 whether it fits, we shift it right and see whether anything remains.
821 Note that we can't shift sizeof (LONGEST) * HOST_CHAR_BIT bits or
822 more in one operation, because many compilers will warn about such a
823 shift (which always produces a zero result). To deal with the case
824 where it is we just always shift the value more than once, with fewer
825 bits each time. */
826 un = (ULONGEST) n >> 2;
827 if (long_p == 0 && (un >> 30) == 0)
828 {
829 high_bit = ((ULONGEST) 1) << 31;
830 signed_type = parse_d_type (ps)->builtin_int;
831 /* For decimal notation, keep the sign of the worked out type. */
832 if (base == 10 && !unsigned_p)
833 unsigned_type = parse_d_type (ps)->builtin_long;
834 else
835 unsigned_type = parse_d_type (ps)->builtin_uint;
836 }
837 else
838 {
839 int shift;
840 if (sizeof (ULONGEST) * HOST_CHAR_BIT < 64)
841 /* A long long does not fit in a LONGEST. */
842 shift = (sizeof (ULONGEST) * HOST_CHAR_BIT - 1);
843 else
844 shift = 63;
845 high_bit = (ULONGEST) 1 << shift;
846 signed_type = parse_d_type (ps)->builtin_long;
847 unsigned_type = parse_d_type (ps)->builtin_ulong;
848 }
849
850 putithere->typed_val_int.val = n;
851
852 /* If the high bit of the worked out type is set then this number
853 has to be unsigned_type. */
854 if (unsigned_p || (n & high_bit))
855 putithere->typed_val_int.type = unsigned_type;
856 else
857 putithere->typed_val_int.type = signed_type;
858
859 return INTEGER_LITERAL;
860 }
861
862 /* Temporary obstack used for holding strings. */
863 static struct obstack tempbuf;
864 static int tempbuf_init;
865
866 /* Parse a string or character literal from TOKPTR. The string or
867 character may be wide or unicode. *OUTPTR is set to just after the
868 end of the literal in the input string. The resulting token is
869 stored in VALUE. This returns a token value, either STRING or
870 CHAR, depending on what was parsed. *HOST_CHARS is set to the
871 number of host characters in the literal. */
872
873 static int
874 parse_string_or_char (const char *tokptr, const char **outptr,
875 struct typed_stoken *value, int *host_chars)
876 {
877 int quote;
878
879 /* Build the gdb internal form of the input string in tempbuf. Note
880 that the buffer is null byte terminated *only* for the
881 convenience of debugging gdb itself and printing the buffer
882 contents when the buffer contains no embedded nulls. Gdb does
883 not depend upon the buffer being null byte terminated, it uses
884 the length string instead. This allows gdb to handle C strings
885 (as well as strings in other languages) with embedded null
886 bytes */
887
888 if (!tempbuf_init)
889 tempbuf_init = 1;
890 else
891 obstack_free (&tempbuf, NULL);
892 obstack_init (&tempbuf);
893
894 /* Skip the quote. */
895 quote = *tokptr;
896 ++tokptr;
897
898 *host_chars = 0;
899
900 while (*tokptr)
901 {
902 char c = *tokptr;
903 if (c == '\\')
904 {
905 ++tokptr;
906 *host_chars += c_parse_escape (&tokptr, &tempbuf);
907 }
908 else if (c == quote)
909 break;
910 else
911 {
912 obstack_1grow (&tempbuf, c);
913 ++tokptr;
914 /* FIXME: this does the wrong thing with multi-byte host
915 characters. We could use mbrlen here, but that would
916 make "set host-charset" a bit less useful. */
917 ++*host_chars;
918 }
919 }
920
921 if (*tokptr != quote)
922 {
923 if (quote == '"' || quote == '`')
924 error (_("Unterminated string in expression."));
925 else
926 error (_("Unmatched single quote."));
927 }
928 ++tokptr;
929
930 /* FIXME: should instead use own language string_type enum
931 and handle D-specific string suffixes here. */
932 if (quote == '\'')
933 value->type = C_CHAR;
934 else
935 value->type = C_STRING;
936
937 value->ptr = (char *) obstack_base (&tempbuf);
938 value->length = obstack_object_size (&tempbuf);
939
940 *outptr = tokptr;
941
942 return quote == '\'' ? CHARACTER_LITERAL : STRING_LITERAL;
943 }
944
945 struct token
946 {
947 const char *oper;
948 int token;
949 enum exp_opcode opcode;
950 };
951
952 static const struct token tokentab3[] =
953 {
954 {"^^=", ASSIGN_MODIFY, BINOP_EXP},
955 {"<<=", ASSIGN_MODIFY, BINOP_LSH},
956 {">>=", ASSIGN_MODIFY, BINOP_RSH},
957 };
958
959 static const struct token tokentab2[] =
960 {
961 {"+=", ASSIGN_MODIFY, BINOP_ADD},
962 {"-=", ASSIGN_MODIFY, BINOP_SUB},
963 {"*=", ASSIGN_MODIFY, BINOP_MUL},
964 {"/=", ASSIGN_MODIFY, BINOP_DIV},
965 {"%=", ASSIGN_MODIFY, BINOP_REM},
966 {"|=", ASSIGN_MODIFY, BINOP_BITWISE_IOR},
967 {"&=", ASSIGN_MODIFY, BINOP_BITWISE_AND},
968 {"^=", ASSIGN_MODIFY, BINOP_BITWISE_XOR},
969 {"++", INCREMENT, BINOP_END},
970 {"--", DECREMENT, BINOP_END},
971 {"&&", ANDAND, BINOP_END},
972 {"||", OROR, BINOP_END},
973 {"^^", HATHAT, BINOP_END},
974 {"<<", LSH, BINOP_END},
975 {">>", RSH, BINOP_END},
976 {"==", EQUAL, BINOP_END},
977 {"!=", NOTEQUAL, BINOP_END},
978 {"<=", LEQ, BINOP_END},
979 {">=", GEQ, BINOP_END},
980 {"..", DOTDOT, BINOP_END},
981 };
982
983 /* Identifier-like tokens. */
984 static const struct token ident_tokens[] =
985 {
986 {"is", IDENTITY, BINOP_END},
987 {"!is", NOTIDENTITY, BINOP_END},
988
989 {"cast", CAST_KEYWORD, OP_NULL},
990 {"const", CONST_KEYWORD, OP_NULL},
991 {"immutable", IMMUTABLE_KEYWORD, OP_NULL},
992 {"shared", SHARED_KEYWORD, OP_NULL},
993 {"super", SUPER_KEYWORD, OP_NULL},
994
995 {"null", NULL_KEYWORD, OP_NULL},
996 {"true", TRUE_KEYWORD, OP_NULL},
997 {"false", FALSE_KEYWORD, OP_NULL},
998
999 {"init", INIT_KEYWORD, OP_NULL},
1000 {"sizeof", SIZEOF_KEYWORD, OP_NULL},
1001 {"typeof", TYPEOF_KEYWORD, OP_NULL},
1002 {"typeid", TYPEID_KEYWORD, OP_NULL},
1003
1004 {"delegate", DELEGATE_KEYWORD, OP_NULL},
1005 {"function", FUNCTION_KEYWORD, OP_NULL},
1006 {"struct", STRUCT_KEYWORD, OP_NULL},
1007 {"union", UNION_KEYWORD, OP_NULL},
1008 {"class", CLASS_KEYWORD, OP_NULL},
1009 {"interface", INTERFACE_KEYWORD, OP_NULL},
1010 {"enum", ENUM_KEYWORD, OP_NULL},
1011 {"template", TEMPLATE_KEYWORD, OP_NULL},
1012 };
1013
1014 /* This is set if a NAME token appeared at the very end of the input
1015 string, with no whitespace separating the name from the EOF. This
1016 is used only when parsing to do field name completion. */
1017 static int saw_name_at_eof;
1018
1019 /* This is set if the previously-returned token was a structure operator.
1020 This is used only when parsing to do field name completion. */
1021 static int last_was_structop;
1022
1023 /* Read one token, getting characters through lexptr. */
1024
1025 static int
1026 lex_one_token (struct parser_state *par_state)
1027 {
1028 int c;
1029 int namelen;
1030 unsigned int i;
1031 const char *tokstart;
1032 int saw_structop = last_was_structop;
1033 char *copy;
1034
1035 last_was_structop = 0;
1036
1037 retry:
1038
1039 prev_lexptr = lexptr;
1040
1041 tokstart = lexptr;
1042 /* See if it is a special token of length 3. */
1043 for (i = 0; i < sizeof tokentab3 / sizeof tokentab3[0]; i++)
1044 if (strncmp (tokstart, tokentab3[i].oper, 3) == 0)
1045 {
1046 lexptr += 3;
1047 yylval.opcode = tokentab3[i].opcode;
1048 return tokentab3[i].token;
1049 }
1050
1051 /* See if it is a special token of length 2. */
1052 for (i = 0; i < sizeof tokentab2 / sizeof tokentab2[0]; i++)
1053 if (strncmp (tokstart, tokentab2[i].oper, 2) == 0)
1054 {
1055 lexptr += 2;
1056 yylval.opcode = tokentab2[i].opcode;
1057 return tokentab2[i].token;
1058 }
1059
1060 switch (c = *tokstart)
1061 {
1062 case 0:
1063 /* If we're parsing for field name completion, and the previous
1064 token allows such completion, return a COMPLETE token.
1065 Otherwise, we were already scanning the original text, and
1066 we're really done. */
1067 if (saw_name_at_eof)
1068 {
1069 saw_name_at_eof = 0;
1070 return COMPLETE;
1071 }
1072 else if (saw_structop)
1073 return COMPLETE;
1074 else
1075 return 0;
1076
1077 case ' ':
1078 case '\t':
1079 case '\n':
1080 lexptr++;
1081 goto retry;
1082
1083 case '[':
1084 case '(':
1085 paren_depth++;
1086 lexptr++;
1087 return c;
1088
1089 case ']':
1090 case ')':
1091 if (paren_depth == 0)
1092 return 0;
1093 paren_depth--;
1094 lexptr++;
1095 return c;
1096
1097 case ',':
1098 if (comma_terminates && paren_depth == 0)
1099 return 0;
1100 lexptr++;
1101 return c;
1102
1103 case '.':
1104 /* Might be a floating point number. */
1105 if (lexptr[1] < '0' || lexptr[1] > '9')
1106 {
1107 if (parse_completion)
1108 last_was_structop = 1;
1109 goto symbol; /* Nope, must be a symbol. */
1110 }
1111 /* FALL THRU. */
1112
1113 case '0':
1114 case '1':
1115 case '2':
1116 case '3':
1117 case '4':
1118 case '5':
1119 case '6':
1120 case '7':
1121 case '8':
1122 case '9':
1123 {
1124 /* It's a number. */
1125 int got_dot = 0, got_e = 0, toktype;
1126 const char *p = tokstart;
1127 int hex = input_radix > 10;
1128
1129 if (c == '0' && (p[1] == 'x' || p[1] == 'X'))
1130 {
1131 p += 2;
1132 hex = 1;
1133 }
1134
1135 for (;; ++p)
1136 {
1137 /* Hex exponents start with 'p', because 'e' is a valid hex
1138 digit and thus does not indicate a floating point number
1139 when the radix is hex. */
1140 if ((!hex && !got_e && tolower (p[0]) == 'e')
1141 || (hex && !got_e && tolower (p[0] == 'p')))
1142 got_dot = got_e = 1;
1143 /* A '.' always indicates a decimal floating point number
1144 regardless of the radix. If we have a '..' then its the
1145 end of the number and the beginning of a slice. */
1146 else if (!got_dot && (p[0] == '.' && p[1] != '.'))
1147 got_dot = 1;
1148 /* This is the sign of the exponent, not the end of the number. */
1149 else if (got_e && (tolower (p[-1]) == 'e' || tolower (p[-1]) == 'p')
1150 && (*p == '-' || *p == '+'))
1151 continue;
1152 /* We will take any letters or digits, ignoring any embedded '_'.
1153 parse_number will complain if past the radix, or if L or U are
1154 not final. */
1155 else if ((*p < '0' || *p > '9') && (*p != '_')
1156 && ((*p < 'a' || *p > 'z') && (*p < 'A' || *p > 'Z')))
1157 break;
1158 }
1159
1160 toktype = parse_number (par_state, tokstart, p - tokstart,
1161 got_dot|got_e, &yylval);
1162 if (toktype == ERROR)
1163 {
1164 char *err_copy = (char *) alloca (p - tokstart + 1);
1165
1166 memcpy (err_copy, tokstart, p - tokstart);
1167 err_copy[p - tokstart] = 0;
1168 error (_("Invalid number \"%s\"."), err_copy);
1169 }
1170 lexptr = p;
1171 return toktype;
1172 }
1173
1174 case '@':
1175 {
1176 const char *p = &tokstart[1];
1177 size_t len = strlen ("entry");
1178
1179 while (isspace (*p))
1180 p++;
1181 if (strncmp (p, "entry", len) == 0 && !isalnum (p[len])
1182 && p[len] != '_')
1183 {
1184 lexptr = &p[len];
1185 return ENTRY;
1186 }
1187 }
1188 /* FALLTHRU */
1189 case '+':
1190 case '-':
1191 case '*':
1192 case '/':
1193 case '%':
1194 case '|':
1195 case '&':
1196 case '^':
1197 case '~':
1198 case '!':
1199 case '<':
1200 case '>':
1201 case '?':
1202 case ':':
1203 case '=':
1204 case '{':
1205 case '}':
1206 symbol:
1207 lexptr++;
1208 return c;
1209
1210 case '\'':
1211 case '"':
1212 case '`':
1213 {
1214 int host_len;
1215 int result = parse_string_or_char (tokstart, &lexptr, &yylval.tsval,
1216 &host_len);
1217 if (result == CHARACTER_LITERAL)
1218 {
1219 if (host_len == 0)
1220 error (_("Empty character constant."));
1221 else if (host_len > 2 && c == '\'')
1222 {
1223 ++tokstart;
1224 namelen = lexptr - tokstart - 1;
1225 goto tryname;
1226 }
1227 else if (host_len > 1)
1228 error (_("Invalid character constant."));
1229 }
1230 return result;
1231 }
1232 }
1233
1234 if (!(c == '_' || c == '$'
1235 || (c >= 'a' && c <= 'z') || (c >= 'A' && c <= 'Z')))
1236 /* We must have come across a bad character (e.g. ';'). */
1237 error (_("Invalid character '%c' in expression"), c);
1238
1239 /* It's a name. See how long it is. */
1240 namelen = 0;
1241 for (c = tokstart[namelen];
1242 (c == '_' || c == '$' || (c >= '0' && c <= '9')
1243 || (c >= 'a' && c <= 'z') || (c >= 'A' && c <= 'Z'));)
1244 c = tokstart[++namelen];
1245
1246 /* The token "if" terminates the expression and is NOT
1247 removed from the input stream. */
1248 if (namelen == 2 && tokstart[0] == 'i' && tokstart[1] == 'f')
1249 return 0;
1250
1251 /* For the same reason (breakpoint conditions), "thread N"
1252 terminates the expression. "thread" could be an identifier, but
1253 an identifier is never followed by a number without intervening
1254 punctuation. "task" is similar. Handle abbreviations of these,
1255 similarly to breakpoint.c:find_condition_and_thread. */
1256 if (namelen >= 1
1257 && (strncmp (tokstart, "thread", namelen) == 0
1258 || strncmp (tokstart, "task", namelen) == 0)
1259 && (tokstart[namelen] == ' ' || tokstart[namelen] == '\t'))
1260 {
1261 const char *p = tokstart + namelen + 1;
1262
1263 while (*p == ' ' || *p == '\t')
1264 p++;
1265 if (*p >= '0' && *p <= '9')
1266 return 0;
1267 }
1268
1269 lexptr += namelen;
1270
1271 tryname:
1272
1273 yylval.sval.ptr = tokstart;
1274 yylval.sval.length = namelen;
1275
1276 /* Catch specific keywords. */
1277 copy = copy_name (yylval.sval);
1278 for (i = 0; i < sizeof ident_tokens / sizeof ident_tokens[0]; i++)
1279 if (strcmp (copy, ident_tokens[i].oper) == 0)
1280 {
1281 /* It is ok to always set this, even though we don't always
1282 strictly need to. */
1283 yylval.opcode = ident_tokens[i].opcode;
1284 return ident_tokens[i].token;
1285 }
1286
1287 if (*tokstart == '$')
1288 return DOLLAR_VARIABLE;
1289
1290 yylval.tsym.type
1291 = language_lookup_primitive_type (parse_language (par_state),
1292 parse_gdbarch (par_state), copy);
1293 if (yylval.tsym.type != NULL)
1294 return TYPENAME;
1295
1296 /* Input names that aren't symbols but ARE valid hex numbers,
1297 when the input radix permits them, can be names or numbers
1298 depending on the parse. Note we support radixes > 16 here. */
1299 if ((tokstart[0] >= 'a' && tokstart[0] < 'a' + input_radix - 10)
1300 || (tokstart[0] >= 'A' && tokstart[0] < 'A' + input_radix - 10))
1301 {
1302 YYSTYPE newlval; /* Its value is ignored. */
1303 int hextype = parse_number (par_state, tokstart, namelen, 0, &newlval);
1304 if (hextype == INTEGER_LITERAL)
1305 return NAME_OR_INT;
1306 }
1307
1308 if (parse_completion && *lexptr == '\0')
1309 saw_name_at_eof = 1;
1310
1311 return IDENTIFIER;
1312 }
1313
1314 /* An object of this type is pushed on a FIFO by the "outer" lexer. */
1315 struct token_and_value
1316 {
1317 int token;
1318 YYSTYPE value;
1319 };
1320
1321
1322 /* A FIFO of tokens that have been read but not yet returned to the
1323 parser. */
1324 static std::vector<token_and_value> token_fifo;
1325
1326 /* Non-zero if the lexer should return tokens from the FIFO. */
1327 static int popping;
1328
1329 /* Temporary storage for yylex; this holds symbol names as they are
1330 built up. */
1331 static auto_obstack name_obstack;
1332
1333 /* Classify an IDENTIFIER token. The contents of the token are in `yylval'.
1334 Updates yylval and returns the new token type. BLOCK is the block
1335 in which lookups start; this can be NULL to mean the global scope. */
1336
1337 static int
1338 classify_name (struct parser_state *par_state, const struct block *block)
1339 {
1340 struct block_symbol sym;
1341 char *copy;
1342 struct field_of_this_result is_a_field_of_this;
1343
1344 copy = copy_name (yylval.sval);
1345
1346 sym = lookup_symbol (copy, block, VAR_DOMAIN, &is_a_field_of_this);
1347 if (sym.symbol && SYMBOL_CLASS (sym.symbol) == LOC_TYPEDEF)
1348 {
1349 yylval.tsym.type = SYMBOL_TYPE (sym.symbol);
1350 return TYPENAME;
1351 }
1352 else if (sym.symbol == NULL)
1353 {
1354 /* Look-up first for a module name, then a type. */
1355 sym = lookup_symbol (copy, block, MODULE_DOMAIN, NULL);
1356 if (sym.symbol == NULL)
1357 sym = lookup_symbol (copy, block, STRUCT_DOMAIN, NULL);
1358
1359 if (sym.symbol != NULL)
1360 {
1361 yylval.tsym.type = SYMBOL_TYPE (sym.symbol);
1362 return TYPENAME;
1363 }
1364
1365 return UNKNOWN_NAME;
1366 }
1367
1368 return IDENTIFIER;
1369 }
1370
1371 /* Like classify_name, but used by the inner loop of the lexer, when a
1372 name might have already been seen. CONTEXT is the context type, or
1373 NULL if this is the first component of a name. */
1374
1375 static int
1376 classify_inner_name (struct parser_state *par_state,
1377 const struct block *block, struct type *context)
1378 {
1379 struct type *type;
1380 char *copy;
1381
1382 if (context == NULL)
1383 return classify_name (par_state, block);
1384
1385 type = check_typedef (context);
1386 if (!type_aggregate_p (type))
1387 return ERROR;
1388
1389 copy = copy_name (yylval.ssym.stoken);
1390 yylval.ssym.sym = d_lookup_nested_symbol (type, copy, block);
1391
1392 if (yylval.ssym.sym.symbol == NULL)
1393 return ERROR;
1394
1395 if (SYMBOL_CLASS (yylval.ssym.sym.symbol) == LOC_TYPEDEF)
1396 {
1397 yylval.tsym.type = SYMBOL_TYPE (yylval.ssym.sym.symbol);
1398 return TYPENAME;
1399 }
1400
1401 return IDENTIFIER;
1402 }
1403
1404 /* The outer level of a two-level lexer. This calls the inner lexer
1405 to return tokens. It then either returns these tokens, or
1406 aggregates them into a larger token. This lets us work around a
1407 problem in our parsing approach, where the parser could not
1408 distinguish between qualified names and qualified types at the
1409 right point. */
1410
1411 static int
1412 yylex (void)
1413 {
1414 token_and_value current;
1415 int last_was_dot;
1416 struct type *context_type = NULL;
1417 int last_to_examine, next_to_examine, checkpoint;
1418 const struct block *search_block;
1419
1420 if (popping && !token_fifo.empty ())
1421 goto do_pop;
1422 popping = 0;
1423
1424 /* Read the first token and decide what to do. */
1425 current.token = lex_one_token (pstate);
1426 if (current.token != IDENTIFIER && current.token != '.')
1427 return current.token;
1428
1429 /* Read any sequence of alternating "." and identifier tokens into
1430 the token FIFO. */
1431 current.value = yylval;
1432 token_fifo.push_back (current);
1433 last_was_dot = current.token == '.';
1434
1435 while (1)
1436 {
1437 current.token = lex_one_token (pstate);
1438 current.value = yylval;
1439 token_fifo.push_back (current);
1440
1441 if ((last_was_dot && current.token != IDENTIFIER)
1442 || (!last_was_dot && current.token != '.'))
1443 break;
1444
1445 last_was_dot = !last_was_dot;
1446 }
1447 popping = 1;
1448
1449 /* We always read one extra token, so compute the number of tokens
1450 to examine accordingly. */
1451 last_to_examine = token_fifo.size () - 2;
1452 next_to_examine = 0;
1453
1454 current = token_fifo[next_to_examine];
1455 ++next_to_examine;
1456
1457 /* If we are not dealing with a typename, now is the time to find out. */
1458 if (current.token == IDENTIFIER)
1459 {
1460 yylval = current.value;
1461 current.token = classify_name (pstate, expression_context_block);
1462 current.value = yylval;
1463 }
1464
1465 /* If the IDENTIFIER is not known, it could be a package symbol,
1466 first try building up a name until we find the qualified module. */
1467 if (current.token == UNKNOWN_NAME)
1468 {
1469 name_obstack.clear ();
1470 obstack_grow (&name_obstack, current.value.sval.ptr,
1471 current.value.sval.length);
1472
1473 last_was_dot = 0;
1474
1475 while (next_to_examine <= last_to_examine)
1476 {
1477 token_and_value next;
1478
1479 next = token_fifo[next_to_examine];
1480 ++next_to_examine;
1481
1482 if (next.token == IDENTIFIER && last_was_dot)
1483 {
1484 /* Update the partial name we are constructing. */
1485 obstack_grow_str (&name_obstack, ".");
1486 obstack_grow (&name_obstack, next.value.sval.ptr,
1487 next.value.sval.length);
1488
1489 yylval.sval.ptr = (char *) obstack_base (&name_obstack);
1490 yylval.sval.length = obstack_object_size (&name_obstack);
1491
1492 current.token = classify_name (pstate, expression_context_block);
1493 current.value = yylval;
1494
1495 /* We keep going until we find a TYPENAME. */
1496 if (current.token == TYPENAME)
1497 {
1498 /* Install it as the first token in the FIFO. */
1499 token_fifo[0] = current;
1500 token_fifo.erase (token_fifo.begin () + 1,
1501 token_fifo.begin () + next_to_examine);
1502 break;
1503 }
1504 }
1505 else if (next.token == '.' && !last_was_dot)
1506 last_was_dot = 1;
1507 else
1508 {
1509 /* We've reached the end of the name. */
1510 break;
1511 }
1512 }
1513
1514 /* Reset our current token back to the start, if we found nothing
1515 this means that we will just jump to do pop. */
1516 current = token_fifo[0];
1517 next_to_examine = 1;
1518 }
1519 if (current.token != TYPENAME && current.token != '.')
1520 goto do_pop;
1521
1522 name_obstack.clear ();
1523 checkpoint = 0;
1524 if (current.token == '.')
1525 search_block = NULL;
1526 else
1527 {
1528 gdb_assert (current.token == TYPENAME);
1529 search_block = expression_context_block;
1530 obstack_grow (&name_obstack, current.value.sval.ptr,
1531 current.value.sval.length);
1532 context_type = current.value.tsym.type;
1533 checkpoint = 1;
1534 }
1535
1536 last_was_dot = current.token == '.';
1537
1538 while (next_to_examine <= last_to_examine)
1539 {
1540 token_and_value next;
1541
1542 next = token_fifo[next_to_examine];
1543 ++next_to_examine;
1544
1545 if (next.token == IDENTIFIER && last_was_dot)
1546 {
1547 int classification;
1548
1549 yylval = next.value;
1550 classification = classify_inner_name (pstate, search_block,
1551 context_type);
1552 /* We keep going until we either run out of names, or until
1553 we have a qualified name which is not a type. */
1554 if (classification != TYPENAME && classification != IDENTIFIER)
1555 break;
1556
1557 /* Accept up to this token. */
1558 checkpoint = next_to_examine;
1559
1560 /* Update the partial name we are constructing. */
1561 if (context_type != NULL)
1562 {
1563 /* We don't want to put a leading "." into the name. */
1564 obstack_grow_str (&name_obstack, ".");
1565 }
1566 obstack_grow (&name_obstack, next.value.sval.ptr,
1567 next.value.sval.length);
1568
1569 yylval.sval.ptr = (char *) obstack_base (&name_obstack);
1570 yylval.sval.length = obstack_object_size (&name_obstack);
1571 current.value = yylval;
1572 current.token = classification;
1573
1574 last_was_dot = 0;
1575
1576 if (classification == IDENTIFIER)
1577 break;
1578
1579 context_type = yylval.tsym.type;
1580 }
1581 else if (next.token == '.' && !last_was_dot)
1582 last_was_dot = 1;
1583 else
1584 {
1585 /* We've reached the end of the name. */
1586 break;
1587 }
1588 }
1589
1590 /* If we have a replacement token, install it as the first token in
1591 the FIFO, and delete the other constituent tokens. */
1592 if (checkpoint > 0)
1593 {
1594 token_fifo[0] = current;
1595 if (checkpoint > 1)
1596 token_fifo.erase (token_fifo.begin () + 1,
1597 token_fifo.begin () + checkpoint);
1598 }
1599
1600 do_pop:
1601 current = token_fifo[0];
1602 token_fifo.erase (token_fifo.begin ());
1603 yylval = current.value;
1604 return current.token;
1605 }
1606
1607 int
1608 d_parse (struct parser_state *par_state)
1609 {
1610 /* Setting up the parser state. */
1611 scoped_restore pstate_restore = make_scoped_restore (&pstate);
1612 gdb_assert (par_state != NULL);
1613 pstate = par_state;
1614
1615 scoped_restore restore_yydebug = make_scoped_restore (&yydebug,
1616 parser_debug);
1617
1618 /* Initialize some state used by the lexer. */
1619 last_was_structop = 0;
1620 saw_name_at_eof = 0;
1621
1622 token_fifo.clear ();
1623 popping = 0;
1624 name_obstack.clear ();
1625
1626 return yyparse ();
1627 }
1628
1629 static void
1630 yyerror (const char *msg)
1631 {
1632 if (prev_lexptr)
1633 lexptr = prev_lexptr;
1634
1635 error (_("A %s in expression, near `%s'."), msg, lexptr);
1636 }
1637
This page took 0.069563 seconds and 5 git commands to generate.