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