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