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