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