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