Update copyright year range in all GDB files
[external/binutils.git] / gdb / d-exp.y
1 /* YACC parser for D expressions, for GDB.
2
3    Copyright (C) 2014-2018 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       gdb_byte val[16];
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_FLOAT);
544                   write_exp_elt_type (pstate, $1.type);
545                   write_exp_elt_floatcst (pstate, $1.val);
546                   write_exp_elt_opcode (pstate, OP_FLOAT); }
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       char *s, *sp;
686
687       /* Strip out all embedded '_' before passing to parse_float.  */
688       s = (char *) alloca (len + 1);
689       sp = s;
690       while (len-- > 0)
691         {
692           if (*p != '_')
693             *sp++ = *p;
694           p++;
695         }
696       *sp = '\0';
697       len = strlen (s);
698
699       /* Check suffix for `i' , `fi' or `li' (idouble, ifloat or ireal).  */
700       if (len >= 1 && tolower (s[len - 1]) == 'i')
701         {
702           if (len >= 2 && tolower (s[len - 2]) == 'f')
703             {
704               putithere->typed_val_float.type
705                 = parse_d_type (ps)->builtin_ifloat;
706               len -= 2;
707             }
708           else if (len >= 2 && tolower (s[len - 2]) == 'l')
709             {
710               putithere->typed_val_float.type
711                 = parse_d_type (ps)->builtin_ireal;
712               len -= 2;
713             }
714           else
715             {
716               putithere->typed_val_float.type
717                 = parse_d_type (ps)->builtin_idouble;
718               len -= 1;
719             }
720         }
721       /* Check suffix for `f' or `l'' (float or real).  */
722       else if (len >= 1 && tolower (s[len - 1]) == 'f')
723         {
724           putithere->typed_val_float.type
725             = parse_d_type (ps)->builtin_float;
726           len -= 1;
727         }
728       else if (len >= 1 && tolower (s[len - 1]) == 'l')
729         {
730           putithere->typed_val_float.type
731             = parse_d_type (ps)->builtin_real;
732           len -= 1;
733         }
734       /* Default type if no suffix.  */
735       else
736         {
737           putithere->typed_val_float.type
738             = parse_d_type (ps)->builtin_double;
739         }
740
741       if (!parse_float (s, len,
742                         putithere->typed_val_float.type,
743                         putithere->typed_val_float.val))
744         return ERROR;
745
746       return FLOAT_LITERAL;
747     }
748
749   /* Handle base-switching prefixes 0x, 0b, 0 */
750   if (p[0] == '0')
751     switch (p[1])
752       {
753       case 'x':
754       case 'X':
755         if (len >= 3)
756           {
757             p += 2;
758             base = 16;
759             len -= 2;
760           }
761         break;
762
763       case 'b':
764       case 'B':
765         if (len >= 3)
766           {
767             p += 2;
768             base = 2;
769             len -= 2;
770           }
771         break;
772
773       default:
774         base = 8;
775         break;
776       }
777
778   while (len-- > 0)
779     {
780       c = *p++;
781       if (c == '_')
782         continue;       /* Ignore embedded '_'.  */
783       if (c >= 'A' && c <= 'Z')
784         c += 'a' - 'A';
785       if (c != 'l' && c != 'u')
786         n *= base;
787       if (c >= '0' && c <= '9')
788         {
789           if (found_suffix)
790             return ERROR;
791           n += i = c - '0';
792         }
793       else
794         {
795           if (base > 10 && c >= 'a' && c <= 'f')
796             {
797               if (found_suffix)
798                 return ERROR;
799               n += i = c - 'a' + 10;
800             }
801           else if (c == 'l' && long_p == 0)
802             {
803               long_p = 1;
804               found_suffix = 1;
805             }
806           else if (c == 'u' && unsigned_p == 0)
807             {
808               unsigned_p = 1;
809               found_suffix = 1;
810             }
811           else
812             return ERROR;       /* Char not a digit */
813         }
814       if (i >= base)
815         return ERROR;           /* Invalid digit in this base.  */
816       /* Portably test for integer overflow.  */
817       if (c != 'l' && c != 'u')
818         {
819           ULONGEST n2 = prevn * base;
820           if ((n2 / base != prevn) || (n2 + i < prevn))
821             error (_("Numeric constant too large."));
822         }
823       prevn = n;
824     }
825
826   /* An integer constant is an int or a long.  An L suffix forces it to
827      be long, and a U suffix forces it to be unsigned.  To figure out
828      whether it fits, we shift it right and see whether anything remains.
829      Note that we can't shift sizeof (LONGEST) * HOST_CHAR_BIT bits or
830      more in one operation, because many compilers will warn about such a
831      shift (which always produces a zero result).  To deal with the case
832      where it is we just always shift the value more than once, with fewer
833      bits each time.  */
834   un = (ULONGEST) n >> 2;
835   if (long_p == 0 && (un >> 30) == 0)
836     {
837       high_bit = ((ULONGEST) 1) << 31;
838       signed_type = parse_d_type (ps)->builtin_int;
839       /* For decimal notation, keep the sign of the worked out type.  */
840       if (base == 10 && !unsigned_p)
841         unsigned_type = parse_d_type (ps)->builtin_long;
842       else
843         unsigned_type = parse_d_type (ps)->builtin_uint;
844     }
845   else
846     {
847       int shift;
848       if (sizeof (ULONGEST) * HOST_CHAR_BIT < 64)
849         /* A long long does not fit in a LONGEST.  */
850         shift = (sizeof (ULONGEST) * HOST_CHAR_BIT - 1);
851       else
852         shift = 63;
853       high_bit = (ULONGEST) 1 << shift;
854       signed_type = parse_d_type (ps)->builtin_long;
855       unsigned_type = parse_d_type (ps)->builtin_ulong;
856     }
857
858   putithere->typed_val_int.val = n;
859
860   /* If the high bit of the worked out type is set then this number
861      has to be unsigned_type.  */
862   if (unsigned_p || (n & high_bit))
863     putithere->typed_val_int.type = unsigned_type;
864   else
865     putithere->typed_val_int.type = signed_type;
866
867   return INTEGER_LITERAL;
868 }
869
870 /* Temporary obstack used for holding strings.  */
871 static struct obstack tempbuf;
872 static int tempbuf_init;
873
874 /* Parse a string or character literal from TOKPTR.  The string or
875    character may be wide or unicode.  *OUTPTR is set to just after the
876    end of the literal in the input string.  The resulting token is
877    stored in VALUE.  This returns a token value, either STRING or
878    CHAR, depending on what was parsed.  *HOST_CHARS is set to the
879    number of host characters in the literal.  */
880
881 static int
882 parse_string_or_char (const char *tokptr, const char **outptr,
883                       struct typed_stoken *value, int *host_chars)
884 {
885   int quote;
886
887   /* Build the gdb internal form of the input string in tempbuf.  Note
888      that the buffer is null byte terminated *only* for the
889      convenience of debugging gdb itself and printing the buffer
890      contents when the buffer contains no embedded nulls.  Gdb does
891      not depend upon the buffer being null byte terminated, it uses
892      the length string instead.  This allows gdb to handle C strings
893      (as well as strings in other languages) with embedded null
894      bytes */
895
896   if (!tempbuf_init)
897     tempbuf_init = 1;
898   else
899     obstack_free (&tempbuf, NULL);
900   obstack_init (&tempbuf);
901
902   /* Skip the quote.  */
903   quote = *tokptr;
904   ++tokptr;
905
906   *host_chars = 0;
907
908   while (*tokptr)
909     {
910       char c = *tokptr;
911       if (c == '\\')
912         {
913            ++tokptr;
914            *host_chars += c_parse_escape (&tokptr, &tempbuf);
915         }
916       else if (c == quote)
917         break;
918       else
919         {
920           obstack_1grow (&tempbuf, c);
921           ++tokptr;
922           /* FIXME: this does the wrong thing with multi-byte host
923              characters.  We could use mbrlen here, but that would
924              make "set host-charset" a bit less useful.  */
925           ++*host_chars;
926         }
927     }
928
929   if (*tokptr != quote)
930     {
931       if (quote == '"' || quote == '`')
932         error (_("Unterminated string in expression."));
933       else
934         error (_("Unmatched single quote."));
935     }
936   ++tokptr;
937
938   /* FIXME: should instead use own language string_type enum
939      and handle D-specific string suffixes here. */
940   if (quote == '\'')
941     value->type = C_CHAR;
942   else
943     value->type = C_STRING;
944
945   value->ptr = (char *) obstack_base (&tempbuf);
946   value->length = obstack_object_size (&tempbuf);
947
948   *outptr = tokptr;
949
950   return quote == '\'' ? CHARACTER_LITERAL : STRING_LITERAL;
951 }
952
953 struct token
954 {
955   const char *oper;
956   int token;
957   enum exp_opcode opcode;
958 };
959
960 static const struct token tokentab3[] =
961   {
962     {"^^=", ASSIGN_MODIFY, BINOP_EXP},
963     {"<<=", ASSIGN_MODIFY, BINOP_LSH},
964     {">>=", ASSIGN_MODIFY, BINOP_RSH},
965   };
966
967 static const struct token tokentab2[] =
968   {
969     {"+=", ASSIGN_MODIFY, BINOP_ADD},
970     {"-=", ASSIGN_MODIFY, BINOP_SUB},
971     {"*=", ASSIGN_MODIFY, BINOP_MUL},
972     {"/=", ASSIGN_MODIFY, BINOP_DIV},
973     {"%=", ASSIGN_MODIFY, BINOP_REM},
974     {"|=", ASSIGN_MODIFY, BINOP_BITWISE_IOR},
975     {"&=", ASSIGN_MODIFY, BINOP_BITWISE_AND},
976     {"^=", ASSIGN_MODIFY, BINOP_BITWISE_XOR},
977     {"++", INCREMENT, BINOP_END},
978     {"--", DECREMENT, BINOP_END},
979     {"&&", ANDAND, BINOP_END},
980     {"||", OROR, BINOP_END},
981     {"^^", HATHAT, BINOP_END},
982     {"<<", LSH, BINOP_END},
983     {">>", RSH, BINOP_END},
984     {"==", EQUAL, BINOP_END},
985     {"!=", NOTEQUAL, BINOP_END},
986     {"<=", LEQ, BINOP_END},
987     {">=", GEQ, BINOP_END},
988     {"..", DOTDOT, BINOP_END},
989   };
990
991 /* Identifier-like tokens.  */
992 static const struct token ident_tokens[] =
993   {
994     {"is", IDENTITY, BINOP_END},
995     {"!is", NOTIDENTITY, BINOP_END},
996
997     {"cast", CAST_KEYWORD, OP_NULL},
998     {"const", CONST_KEYWORD, OP_NULL},
999     {"immutable", IMMUTABLE_KEYWORD, OP_NULL},
1000     {"shared", SHARED_KEYWORD, OP_NULL},
1001     {"super", SUPER_KEYWORD, OP_NULL},
1002
1003     {"null", NULL_KEYWORD, OP_NULL},
1004     {"true", TRUE_KEYWORD, OP_NULL},
1005     {"false", FALSE_KEYWORD, OP_NULL},
1006
1007     {"init", INIT_KEYWORD, OP_NULL},
1008     {"sizeof", SIZEOF_KEYWORD, OP_NULL},
1009     {"typeof", TYPEOF_KEYWORD, OP_NULL},
1010     {"typeid", TYPEID_KEYWORD, OP_NULL},
1011
1012     {"delegate", DELEGATE_KEYWORD, OP_NULL},
1013     {"function", FUNCTION_KEYWORD, OP_NULL},
1014     {"struct", STRUCT_KEYWORD, OP_NULL},
1015     {"union", UNION_KEYWORD, OP_NULL},
1016     {"class", CLASS_KEYWORD, OP_NULL},
1017     {"interface", INTERFACE_KEYWORD, OP_NULL},
1018     {"enum", ENUM_KEYWORD, OP_NULL},
1019     {"template", TEMPLATE_KEYWORD, OP_NULL},
1020   };
1021
1022 /* This is set if a NAME token appeared at the very end of the input
1023    string, with no whitespace separating the name from the EOF.  This
1024    is used only when parsing to do field name completion.  */
1025 static int saw_name_at_eof;
1026
1027 /* This is set if the previously-returned token was a structure operator.
1028    This is used only when parsing to do field name completion.  */
1029 static int last_was_structop;
1030
1031 /* Read one token, getting characters through lexptr.  */
1032
1033 static int
1034 lex_one_token (struct parser_state *par_state)
1035 {
1036   int c;
1037   int namelen;
1038   unsigned int i;
1039   const char *tokstart;
1040   int saw_structop = last_was_structop;
1041   char *copy;
1042
1043   last_was_structop = 0;
1044
1045  retry:
1046
1047   prev_lexptr = lexptr;
1048
1049   tokstart = lexptr;
1050   /* See if it is a special token of length 3.  */
1051   for (i = 0; i < sizeof tokentab3 / sizeof tokentab3[0]; i++)
1052     if (strncmp (tokstart, tokentab3[i].oper, 3) == 0)
1053       {
1054         lexptr += 3;
1055         yylval.opcode = tokentab3[i].opcode;
1056         return tokentab3[i].token;
1057       }
1058
1059   /* See if it is a special token of length 2.  */
1060   for (i = 0; i < sizeof tokentab2 / sizeof tokentab2[0]; i++)
1061     if (strncmp (tokstart, tokentab2[i].oper, 2) == 0)
1062       {
1063         lexptr += 2;
1064         yylval.opcode = tokentab2[i].opcode;
1065         return tokentab2[i].token;
1066       }
1067
1068   switch (c = *tokstart)
1069     {
1070     case 0:
1071       /* If we're parsing for field name completion, and the previous
1072          token allows such completion, return a COMPLETE token.
1073          Otherwise, we were already scanning the original text, and
1074          we're really done.  */
1075       if (saw_name_at_eof)
1076         {
1077           saw_name_at_eof = 0;
1078           return COMPLETE;
1079         }
1080       else if (saw_structop)
1081         return COMPLETE;
1082       else
1083         return 0;
1084
1085     case ' ':
1086     case '\t':
1087     case '\n':
1088       lexptr++;
1089       goto retry;
1090
1091     case '[':
1092     case '(':
1093       paren_depth++;
1094       lexptr++;
1095       return c;
1096
1097     case ']':
1098     case ')':
1099       if (paren_depth == 0)
1100         return 0;
1101       paren_depth--;
1102       lexptr++;
1103       return c;
1104
1105     case ',':
1106       if (comma_terminates && paren_depth == 0)
1107         return 0;
1108       lexptr++;
1109       return c;
1110
1111     case '.':
1112       /* Might be a floating point number.  */
1113       if (lexptr[1] < '0' || lexptr[1] > '9')
1114         {
1115           if (parse_completion)
1116             last_was_structop = 1;
1117           goto symbol;          /* Nope, must be a symbol.  */
1118         }
1119       /* FALL THRU into number case.  */
1120
1121     case '0':
1122     case '1':
1123     case '2':
1124     case '3':
1125     case '4':
1126     case '5':
1127     case '6':
1128     case '7':
1129     case '8':
1130     case '9':
1131       {
1132         /* It's a number.  */
1133         int got_dot = 0, got_e = 0, toktype;
1134         const char *p = tokstart;
1135         int hex = input_radix > 10;
1136
1137         if (c == '0' && (p[1] == 'x' || p[1] == 'X'))
1138           {
1139             p += 2;
1140             hex = 1;
1141           }
1142
1143         for (;; ++p)
1144           {
1145             /* Hex exponents start with 'p', because 'e' is a valid hex
1146                digit and thus does not indicate a floating point number
1147                when the radix is hex.  */
1148             if ((!hex && !got_e && tolower (p[0]) == 'e')
1149                 || (hex && !got_e && tolower (p[0] == 'p')))
1150               got_dot = got_e = 1;
1151             /* A '.' always indicates a decimal floating point number
1152                regardless of the radix.  If we have a '..' then its the
1153                end of the number and the beginning of a slice.  */
1154             else if (!got_dot && (p[0] == '.' && p[1] != '.'))
1155                 got_dot = 1;
1156             /* This is the sign of the exponent, not the end of the number.  */
1157             else if (got_e && (tolower (p[-1]) == 'e' || tolower (p[-1]) == 'p')
1158                      && (*p == '-' || *p == '+'))
1159               continue;
1160             /* We will take any letters or digits, ignoring any embedded '_'.
1161                parse_number will complain if past the radix, or if L or U are
1162                not final.  */
1163             else if ((*p < '0' || *p > '9') && (*p != '_')
1164                      && ((*p < 'a' || *p > 'z') && (*p < 'A' || *p > 'Z')))
1165               break;
1166           }
1167
1168         toktype = parse_number (par_state, tokstart, p - tokstart,
1169                                 got_dot|got_e, &yylval);
1170         if (toktype == ERROR)
1171           {
1172             char *err_copy = (char *) alloca (p - tokstart + 1);
1173
1174             memcpy (err_copy, tokstart, p - tokstart);
1175             err_copy[p - tokstart] = 0;
1176             error (_("Invalid number \"%s\"."), err_copy);
1177           }
1178         lexptr = p;
1179         return toktype;
1180       }
1181
1182     case '@':
1183       {
1184         const char *p = &tokstart[1];
1185         size_t len = strlen ("entry");
1186
1187         while (isspace (*p))
1188           p++;
1189         if (strncmp (p, "entry", len) == 0 && !isalnum (p[len])
1190             && p[len] != '_')
1191           {
1192             lexptr = &p[len];
1193             return ENTRY;
1194           }
1195       }
1196       /* FALLTHRU */
1197     case '+':
1198     case '-':
1199     case '*':
1200     case '/':
1201     case '%':
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     symbol:
1215       lexptr++;
1216       return c;
1217
1218     case '\'':
1219     case '"':
1220     case '`':
1221       {
1222         int host_len;
1223         int result = parse_string_or_char (tokstart, &lexptr, &yylval.tsval,
1224                                            &host_len);
1225         if (result == CHARACTER_LITERAL)
1226           {
1227             if (host_len == 0)
1228               error (_("Empty character constant."));
1229             else if (host_len > 2 && c == '\'')
1230               {
1231                 ++tokstart;
1232                 namelen = lexptr - tokstart - 1;
1233                 goto tryname;
1234               }
1235             else if (host_len > 1)
1236               error (_("Invalid character constant."));
1237           }
1238         return result;
1239       }
1240     }
1241
1242   if (!(c == '_' || c == '$'
1243         || (c >= 'a' && c <= 'z') || (c >= 'A' && c <= 'Z')))
1244     /* We must have come across a bad character (e.g. ';').  */
1245     error (_("Invalid character '%c' in expression"), c);
1246
1247   /* It's a name.  See how long it is.  */
1248   namelen = 0;
1249   for (c = tokstart[namelen];
1250        (c == '_' || c == '$' || (c >= '0' && c <= '9')
1251         || (c >= 'a' && c <= 'z') || (c >= 'A' && c <= 'Z'));)
1252     c = tokstart[++namelen];
1253
1254   /* The token "if" terminates the expression and is NOT
1255      removed from the input stream.  */
1256   if (namelen == 2 && tokstart[0] == 'i' && tokstart[1] == 'f')
1257     return 0;
1258
1259   /* For the same reason (breakpoint conditions), "thread N"
1260      terminates the expression.  "thread" could be an identifier, but
1261      an identifier is never followed by a number without intervening
1262      punctuation.  "task" is similar.  Handle abbreviations of these,
1263      similarly to breakpoint.c:find_condition_and_thread.  */
1264   if (namelen >= 1
1265       && (strncmp (tokstart, "thread", namelen) == 0
1266           || strncmp (tokstart, "task", namelen) == 0)
1267       && (tokstart[namelen] == ' ' || tokstart[namelen] == '\t'))
1268     {
1269       const char *p = tokstart + namelen + 1;
1270
1271       while (*p == ' ' || *p == '\t')
1272         p++;
1273       if (*p >= '0' && *p <= '9')
1274         return 0;
1275     }
1276
1277   lexptr += namelen;
1278
1279  tryname:
1280
1281   yylval.sval.ptr = tokstart;
1282   yylval.sval.length = namelen;
1283
1284   /* Catch specific keywords.  */
1285   copy = copy_name (yylval.sval);
1286   for (i = 0; i < sizeof ident_tokens / sizeof ident_tokens[0]; i++)
1287     if (strcmp (copy, ident_tokens[i].oper) == 0)
1288       {
1289         /* It is ok to always set this, even though we don't always
1290            strictly need to.  */
1291         yylval.opcode = ident_tokens[i].opcode;
1292         return ident_tokens[i].token;
1293       }
1294
1295   if (*tokstart == '$')
1296     return DOLLAR_VARIABLE;
1297
1298   yylval.tsym.type
1299     = language_lookup_primitive_type (parse_language (par_state),
1300                                       parse_gdbarch (par_state), copy);
1301   if (yylval.tsym.type != NULL)
1302     return TYPENAME;
1303
1304   /* Input names that aren't symbols but ARE valid hex numbers,
1305      when the input radix permits them, can be names or numbers
1306      depending on the parse.  Note we support radixes > 16 here.  */
1307   if ((tokstart[0] >= 'a' && tokstart[0] < 'a' + input_radix - 10)
1308       || (tokstart[0] >= 'A' && tokstart[0] < 'A' + input_radix - 10))
1309     {
1310       YYSTYPE newlval;  /* Its value is ignored.  */
1311       int hextype = parse_number (par_state, tokstart, namelen, 0, &newlval);
1312       if (hextype == INTEGER_LITERAL)
1313         return NAME_OR_INT;
1314     }
1315
1316   if (parse_completion && *lexptr == '\0')
1317     saw_name_at_eof = 1;
1318
1319   return IDENTIFIER;
1320 }
1321
1322 /* An object of this type is pushed on a FIFO by the "outer" lexer.  */
1323 typedef struct
1324 {
1325   int token;
1326   YYSTYPE value;
1327 } token_and_value;
1328
1329 DEF_VEC_O (token_and_value);
1330
1331 /* A FIFO of tokens that have been read but not yet returned to the
1332    parser.  */
1333 static VEC (token_and_value) *token_fifo;
1334
1335 /* Non-zero if the lexer should return tokens from the FIFO.  */
1336 static int popping;
1337
1338 /* Temporary storage for yylex; this holds symbol names as they are
1339    built up.  */
1340 static auto_obstack name_obstack;
1341
1342 /* Classify an IDENTIFIER token.  The contents of the token are in `yylval'.
1343    Updates yylval and returns the new token type.  BLOCK is the block
1344    in which lookups start; this can be NULL to mean the global scope.  */
1345
1346 static int
1347 classify_name (struct parser_state *par_state, const struct block *block)
1348 {
1349   struct block_symbol sym;
1350   char *copy;
1351   struct field_of_this_result is_a_field_of_this;
1352
1353   copy = copy_name (yylval.sval);
1354
1355   sym = lookup_symbol (copy, block, VAR_DOMAIN, &is_a_field_of_this);
1356   if (sym.symbol && SYMBOL_CLASS (sym.symbol) == LOC_TYPEDEF)
1357     {
1358       yylval.tsym.type = SYMBOL_TYPE (sym.symbol);
1359       return TYPENAME;
1360     }
1361   else if (sym.symbol == NULL)
1362     {
1363       /* Look-up first for a module name, then a type.  */
1364       sym = lookup_symbol (copy, block, MODULE_DOMAIN, NULL);
1365       if (sym.symbol == NULL)
1366         sym = lookup_symbol (copy, block, STRUCT_DOMAIN, NULL);
1367
1368       if (sym.symbol != NULL)
1369         {
1370           yylval.tsym.type = SYMBOL_TYPE (sym.symbol);
1371           return TYPENAME;
1372         }
1373
1374       return UNKNOWN_NAME;
1375     }
1376
1377   return IDENTIFIER;
1378 }
1379
1380 /* Like classify_name, but used by the inner loop of the lexer, when a
1381    name might have already been seen.  CONTEXT is the context type, or
1382    NULL if this is the first component of a name.  */
1383
1384 static int
1385 classify_inner_name (struct parser_state *par_state,
1386                      const struct block *block, struct type *context)
1387 {
1388   struct type *type;
1389   char *copy;
1390
1391   if (context == NULL)
1392     return classify_name (par_state, block);
1393
1394   type = check_typedef (context);
1395   if (!type_aggregate_p (type))
1396     return ERROR;
1397
1398   copy = copy_name (yylval.ssym.stoken);
1399   yylval.ssym.sym = d_lookup_nested_symbol (type, copy, block);
1400
1401   if (yylval.ssym.sym.symbol == NULL)
1402     return ERROR;
1403
1404   if (SYMBOL_CLASS (yylval.ssym.sym.symbol) == LOC_TYPEDEF)
1405     {
1406       yylval.tsym.type = SYMBOL_TYPE (yylval.ssym.sym.symbol);
1407       return TYPENAME;
1408     }
1409
1410   return IDENTIFIER;
1411 }
1412
1413 /* The outer level of a two-level lexer.  This calls the inner lexer
1414    to return tokens.  It then either returns these tokens, or
1415    aggregates them into a larger token.  This lets us work around a
1416    problem in our parsing approach, where the parser could not
1417    distinguish between qualified names and qualified types at the
1418    right point.  */
1419
1420 static int
1421 yylex (void)
1422 {
1423   token_and_value current;
1424   int last_was_dot;
1425   struct type *context_type = NULL;
1426   int last_to_examine, next_to_examine, checkpoint;
1427   const struct block *search_block;
1428
1429   if (popping && !VEC_empty (token_and_value, token_fifo))
1430     goto do_pop;
1431   popping = 0;
1432
1433   /* Read the first token and decide what to do.  */
1434   current.token = lex_one_token (pstate);
1435   if (current.token != IDENTIFIER && current.token != '.')
1436     return current.token;
1437
1438   /* Read any sequence of alternating "." and identifier tokens into
1439      the token FIFO.  */
1440   current.value = yylval;
1441   VEC_safe_push (token_and_value, token_fifo, &current);
1442   last_was_dot = current.token == '.';
1443
1444   while (1)
1445     {
1446       current.token = lex_one_token (pstate);
1447       current.value = yylval;
1448       VEC_safe_push (token_and_value, token_fifo, &current);
1449
1450       if ((last_was_dot && current.token != IDENTIFIER)
1451           || (!last_was_dot && current.token != '.'))
1452         break;
1453
1454       last_was_dot = !last_was_dot;
1455     }
1456   popping = 1;
1457
1458   /* We always read one extra token, so compute the number of tokens
1459      to examine accordingly.  */
1460   last_to_examine = VEC_length (token_and_value, token_fifo) - 2;
1461   next_to_examine = 0;
1462
1463   current = *VEC_index (token_and_value, token_fifo, next_to_examine);
1464   ++next_to_examine;
1465
1466   /* If we are not dealing with a typename, now is the time to find out.  */
1467   if (current.token == IDENTIFIER)
1468     {
1469       yylval = current.value;
1470       current.token = classify_name (pstate, expression_context_block);
1471       current.value = yylval;
1472     }
1473
1474   /* If the IDENTIFIER is not known, it could be a package symbol,
1475      first try building up a name until we find the qualified module.  */
1476   if (current.token == UNKNOWN_NAME)
1477     {
1478       name_obstack.clear ();
1479       obstack_grow (&name_obstack, current.value.sval.ptr,
1480                     current.value.sval.length);
1481
1482       last_was_dot = 0;
1483
1484       while (next_to_examine <= last_to_examine)
1485         {
1486           token_and_value *next;
1487
1488           next = VEC_index (token_and_value, token_fifo, next_to_examine);
1489           ++next_to_examine;
1490
1491           if (next->token == IDENTIFIER && last_was_dot)
1492             {
1493               /* Update the partial name we are constructing.  */
1494               obstack_grow_str (&name_obstack, ".");
1495               obstack_grow (&name_obstack, next->value.sval.ptr,
1496                             next->value.sval.length);
1497
1498               yylval.sval.ptr = (char *) obstack_base (&name_obstack);
1499               yylval.sval.length = obstack_object_size (&name_obstack);
1500
1501               current.token = classify_name (pstate, expression_context_block);
1502               current.value = yylval;
1503
1504               /* We keep going until we find a TYPENAME.  */
1505               if (current.token == TYPENAME)
1506                 {
1507                   /* Install it as the first token in the FIFO.  */
1508                   VEC_replace (token_and_value, token_fifo, 0, &current);
1509                   VEC_block_remove (token_and_value, token_fifo, 1,
1510                                     next_to_examine - 1);
1511                   break;
1512                 }
1513             }
1514           else if (next->token == '.' && !last_was_dot)
1515             last_was_dot = 1;
1516           else
1517             {
1518               /* We've reached the end of the name.  */
1519               break;
1520             }
1521         }
1522
1523       /* Reset our current token back to the start, if we found nothing
1524          this means that we will just jump to do pop.  */
1525       current = *VEC_index (token_and_value, token_fifo, 0);
1526       next_to_examine = 1;
1527     }
1528   if (current.token != TYPENAME && current.token != '.')
1529     goto do_pop;
1530
1531   name_obstack.clear ();
1532   checkpoint = 0;
1533   if (current.token == '.')
1534     search_block = NULL;
1535   else
1536     {
1537       gdb_assert (current.token == TYPENAME);
1538       search_block = expression_context_block;
1539       obstack_grow (&name_obstack, current.value.sval.ptr,
1540                     current.value.sval.length);
1541       context_type = current.value.tsym.type;
1542       checkpoint = 1;
1543     }
1544
1545   last_was_dot = current.token == '.';
1546
1547   while (next_to_examine <= last_to_examine)
1548     {
1549       token_and_value *next;
1550
1551       next = VEC_index (token_and_value, token_fifo, next_to_examine);
1552       ++next_to_examine;
1553
1554       if (next->token == IDENTIFIER && last_was_dot)
1555         {
1556           int classification;
1557
1558           yylval = next->value;
1559           classification = classify_inner_name (pstate, search_block,
1560                                                 context_type);
1561           /* We keep going until we either run out of names, or until
1562              we have a qualified name which is not a type.  */
1563           if (classification != TYPENAME && classification != IDENTIFIER)
1564             break;
1565
1566           /* Accept up to this token.  */
1567           checkpoint = next_to_examine;
1568
1569           /* Update the partial name we are constructing.  */
1570           if (context_type != NULL)
1571             {
1572               /* We don't want to put a leading "." into the name.  */
1573               obstack_grow_str (&name_obstack, ".");
1574             }
1575           obstack_grow (&name_obstack, next->value.sval.ptr,
1576                         next->value.sval.length);
1577
1578           yylval.sval.ptr = (char *) obstack_base (&name_obstack);
1579           yylval.sval.length = obstack_object_size (&name_obstack);
1580           current.value = yylval;
1581           current.token = classification;
1582
1583           last_was_dot = 0;
1584
1585           if (classification == IDENTIFIER)
1586             break;
1587
1588           context_type = yylval.tsym.type;
1589         }
1590       else if (next->token == '.' && !last_was_dot)
1591         last_was_dot = 1;
1592       else
1593         {
1594           /* We've reached the end of the name.  */
1595           break;
1596         }
1597     }
1598
1599   /* If we have a replacement token, install it as the first token in
1600      the FIFO, and delete the other constituent tokens.  */
1601   if (checkpoint > 0)
1602     {
1603       VEC_replace (token_and_value, token_fifo, 0, &current);
1604       if (checkpoint > 1)
1605         VEC_block_remove (token_and_value, token_fifo, 1, checkpoint - 1);
1606     }
1607
1608  do_pop:
1609   current = *VEC_index (token_and_value, token_fifo, 0);
1610   VEC_ordered_remove (token_and_value, token_fifo, 0);
1611   yylval = current.value;
1612   return current.token;
1613 }
1614
1615 int
1616 d_parse (struct parser_state *par_state)
1617 {
1618   /* Setting up the parser state.  */
1619   scoped_restore pstate_restore = make_scoped_restore (&pstate);
1620   gdb_assert (par_state != NULL);
1621   pstate = par_state;
1622
1623   scoped_restore restore_yydebug = make_scoped_restore (&yydebug,
1624                                                         parser_debug);
1625
1626   /* Initialize some state used by the lexer.  */
1627   last_was_structop = 0;
1628   saw_name_at_eof = 0;
1629
1630   VEC_free (token_and_value, token_fifo);
1631   popping = 0;
1632   name_obstack.clear ();
1633
1634   return yyparse ();
1635 }
1636
1637 void
1638 yyerror (const char *msg)
1639 {
1640   if (prev_lexptr)
1641     lexptr = prev_lexptr;
1642
1643   error (_("A %s in expression, near `%s'."), (msg ? msg : "error"), lexptr);
1644 }
1645