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