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