Introduce dwarf2/public.h
[deliverable/binutils-gdb.git] / gdb / d-exp.y
index bcf62bad75293fac4faaa4145f51742cf8a0da5f..90c342e0e218e8e3b385abfdf41dddf4f5e21db8 100644 (file)
@@ -1,6 +1,6 @@
 /* YACC parser for D expressions, for GDB.
 
-   Copyright (C) 2014-2015 Free Software Foundation, Inc.
+   Copyright (C) 2014-2021 Free Software Foundation, Inc.
 
    This file is part of GDB.
 
 #include "objfiles.h" /* For have_full_symbols and have_partial_symbols */
 #include "charset.h"
 #include "block.h"
+#include "type-stack.h"
+#include "expop.h"
 
-#define parse_type(ps) builtin_type (parse_gdbarch (ps))
-#define parse_d_type(ps) builtin_d_type (parse_gdbarch (ps))
-
-/* Remap normal yacc parser interface names (yyparse, yylex, yyerror, etc),
-   as well as gratuitiously global symbol names, so we can have multiple
-   yacc generated parsers in gdb.  Note that these are only the variables
-   produced by yacc.  If other parser generators (bison, byacc, etc) produce
-   additional global names that conflict at link time, then those parser
-   generators need to be fixed instead of adding those names to this list.  */
-
-#define        yymaxdepth d_maxdepth
-#define        yyparse d_parse_internal
-#define        yylex   d_lex
-#define        yyerror d_error
-#define        yylval  d_lval
-#define        yychar  d_char
-#define        yydebug d_debug
-#define        yypact  d_pact
-#define        yyr1    d_r1
-#define        yyr2    d_r2
-#define        yydef   d_def
-#define        yychk   d_chk
-#define        yypgo   d_pgo
-#define        yyact   d_act
-#define        yyexca  d_exca
-#define        yyerrflag d_errflag
-#define        yynerrs d_nerrs
-#define        yyps    d_ps
-#define        yypv    d_pv
-#define        yys     d_s
-#define        yy_yys  d_yys
-#define        yystate d_state
-#define        yytmp   d_tmp
-#define        yyv     d_v
-#define        yy_yyv  d_yyv
-#define        yyval   d_val
-#define        yylloc  d_lloc
-#define        yyreds  d_reds  /* With YYDEBUG defined */
-#define        yytoks  d_toks  /* With YYDEBUG defined */
-#define        yyname  d_name  /* With YYDEBUG defined */
-#define        yyrule  d_rule  /* With YYDEBUG defined */
-#define        yylhs   d_yylhs
-#define        yylen   d_yylen
-#define        yydefre d_yydefred
-#define        yydgoto d_yydgoto
-#define        yysindex d_yysindex
-#define        yyrindex d_yyrindex
-#define        yygindex d_yygindex
-#define        yytable d_yytable
-#define        yycheck d_yycheck
-#define        yyss    d_yyss
-#define        yysslim d_yysslim
-#define        yyssp   d_yyssp
-#define        yystacksize d_yystacksize
-#define        yyvs    d_yyvs
-#define        yyvsp   d_yyvsp
-
-#ifndef YYDEBUG
-#define YYDEBUG 1      /* Default to yydebug support */
-#endif
-
-#define YYFPRINTF parser_fprintf
+#define parse_type(ps) builtin_type (ps->gdbarch ())
+#define parse_d_type(ps) builtin_d_type (ps->gdbarch ())
+
+/* Remap normal yacc parser interface names (yyparse, yylex, yyerror,
+   etc).  */
+#define GDB_YY_REMAP_PREFIX d_
+#include "yy-remap.h"
 
 /* The state of the parser, used internally when we are parsing the
    expression.  */
 
 static struct parser_state *pstate = NULL;
 
+/* The current type stack.  */
+static struct type_stack *type_stack;
+
 int yyparse (void);
 
 static int yylex (void);
 
-void yyerror (char *);
+static void yyerror (const char *);
+
+static int type_aggregate_p (struct type *);
+
+using namespace expr;
 
 %}
 
@@ -139,7 +93,7 @@ void yyerror (char *);
       struct type *type;
     } typed_val_int;
     struct {
-      DOUBLEST dval;
+      gdb_byte val[16];
       struct type *type;
     } typed_val_float;
     struct symbol *sym;
@@ -150,7 +104,6 @@ void yyerror (char *);
     struct symtoken ssym;
     int ival;
     int voidval;
-    struct block *bval;
     enum exp_opcode opcode;
     struct stoken_vector svec;
   }
@@ -241,53 +194,63 @@ Expression:
 CommaExpression:
        AssignExpression
 |      AssignExpression ',' CommaExpression
-               { write_exp_elt_opcode (pstate, BINOP_COMMA); }
+               { pstate->wrap2<comma_operation> (); }
 ;
 
 AssignExpression:
        ConditionalExpression
 |      ConditionalExpression '=' AssignExpression
-               { write_exp_elt_opcode (pstate, BINOP_ASSIGN); }
+               { pstate->wrap2<assign_operation> (); }
 |      ConditionalExpression ASSIGN_MODIFY AssignExpression
-               { write_exp_elt_opcode (pstate, BINOP_ASSIGN_MODIFY);
-                 write_exp_elt_opcode (pstate, $2);
-                 write_exp_elt_opcode (pstate, BINOP_ASSIGN_MODIFY); }
+               {
+                 operation_up rhs = pstate->pop ();
+                 operation_up lhs = pstate->pop ();
+                 pstate->push_new<assign_modify_operation>
+                   ($2, std::move (lhs), std::move (rhs));
+               }
 ;
 
 ConditionalExpression:
        OrOrExpression
 |      OrOrExpression '?' Expression ':' ConditionalExpression
-               { write_exp_elt_opcode (pstate, TERNOP_COND); }
+               {
+                 operation_up last = pstate->pop ();
+                 operation_up mid = pstate->pop ();
+                 operation_up first = pstate->pop ();
+                 pstate->push_new<ternop_cond_operation>
+                   (std::move (first), std::move (mid),
+                    std::move (last));
+               }
 ;
 
 OrOrExpression:
        AndAndExpression
 |      OrOrExpression OROR AndAndExpression
-               { write_exp_elt_opcode (pstate, BINOP_LOGICAL_OR); }
+               { pstate->wrap2<logical_or_operation> (); }
 ;
 
 AndAndExpression:
        OrExpression
 |      AndAndExpression ANDAND OrExpression
-               { write_exp_elt_opcode (pstate, BINOP_LOGICAL_AND); }
+               { pstate->wrap2<logical_and_operation> (); }
 ;
 
 OrExpression:
        XorExpression
 |      OrExpression '|' XorExpression
-               { write_exp_elt_opcode (pstate, BINOP_BITWISE_IOR); }
+               { pstate->wrap2<bitwise_ior_operation> (); }
 ;
 
 XorExpression:
        AndExpression
 |      XorExpression '^' AndExpression
-               { write_exp_elt_opcode (pstate, BINOP_BITWISE_XOR); }
+               { pstate->wrap2<bitwise_xor_operation> (); }
 ;
 
 AndExpression:
        CmpExpression
 |      AndExpression '&' CmpExpression
-               { write_exp_elt_opcode (pstate, BINOP_BITWISE_AND); }
+               { pstate->wrap2<bitwise_and_operation> (); }
 ;
 
 CmpExpression:
@@ -299,119 +262,121 @@ CmpExpression:
 
 EqualExpression:
        ShiftExpression EQUAL ShiftExpression
-               { write_exp_elt_opcode (pstate, BINOP_EQUAL); }
+               { pstate->wrap2<equal_operation> (); }
 |      ShiftExpression NOTEQUAL ShiftExpression
-               { write_exp_elt_opcode (pstate, BINOP_NOTEQUAL); }
+               { pstate->wrap2<notequal_operation> (); }
 ;
 
 IdentityExpression:
        ShiftExpression IDENTITY ShiftExpression
-               { write_exp_elt_opcode (pstate, BINOP_EQUAL); }
+               { pstate->wrap2<equal_operation> (); }
 |      ShiftExpression NOTIDENTITY ShiftExpression
-               { write_exp_elt_opcode (pstate, BINOP_NOTEQUAL); }
+               { pstate->wrap2<notequal_operation> (); }
 ;
 
 RelExpression:
        ShiftExpression '<' ShiftExpression
-               { write_exp_elt_opcode (pstate, BINOP_LESS); }
+               { pstate->wrap2<less_operation> (); }
 |      ShiftExpression LEQ ShiftExpression
-               { write_exp_elt_opcode (pstate, BINOP_LEQ); }
+               { pstate->wrap2<leq_operation> (); }
 |      ShiftExpression '>' ShiftExpression
-               { write_exp_elt_opcode (pstate, BINOP_GTR); }
+               { pstate->wrap2<gtr_operation> (); }
 |      ShiftExpression GEQ ShiftExpression
-               { write_exp_elt_opcode (pstate, BINOP_GEQ); }
+               { pstate->wrap2<geq_operation> (); }
 ;
 
 ShiftExpression:
        AddExpression
 |      ShiftExpression LSH AddExpression
-               { write_exp_elt_opcode (pstate, BINOP_LSH); }
+               { pstate->wrap2<lsh_operation> (); }
 |      ShiftExpression RSH AddExpression
-               { write_exp_elt_opcode (pstate, BINOP_RSH); }
+               { pstate->wrap2<rsh_operation> (); }
 ;
 
 AddExpression:
        MulExpression
 |      AddExpression '+' MulExpression
-               { write_exp_elt_opcode (pstate, BINOP_ADD); }
+               { pstate->wrap2<add_operation> (); }
 |      AddExpression '-' MulExpression
-               { write_exp_elt_opcode (pstate, BINOP_SUB); }
+               { pstate->wrap2<sub_operation> (); }
 |      AddExpression '~' MulExpression
-               { write_exp_elt_opcode (pstate, BINOP_CONCAT); }
+               { pstate->wrap2<concat_operation> (); }
 ;
 
 MulExpression:
        UnaryExpression
 |      MulExpression '*' UnaryExpression
-               { write_exp_elt_opcode (pstate, BINOP_MUL); }
+               { pstate->wrap2<mul_operation> (); }
 |      MulExpression '/' UnaryExpression
-               { write_exp_elt_opcode (pstate, BINOP_DIV); }
+               { pstate->wrap2<div_operation> (); }
 |      MulExpression '%' UnaryExpression
-               { write_exp_elt_opcode (pstate, BINOP_REM); }
+               { pstate->wrap2<rem_operation> (); }
 
 UnaryExpression:
        '&' UnaryExpression
-               { write_exp_elt_opcode (pstate, UNOP_ADDR); }
+               { pstate->wrap<unop_addr_operation> (); }
 |      INCREMENT UnaryExpression
-               { write_exp_elt_opcode (pstate, UNOP_PREINCREMENT); }
+               { pstate->wrap<preinc_operation> (); }
 |      DECREMENT UnaryExpression
-               { write_exp_elt_opcode (pstate, UNOP_PREDECREMENT); }
+               { pstate->wrap<predec_operation> (); }
 |      '*' UnaryExpression
-               { write_exp_elt_opcode (pstate, UNOP_IND); }
+               { pstate->wrap<unop_ind_operation> (); }
 |      '-' UnaryExpression
-               { write_exp_elt_opcode (pstate, UNOP_NEG); }
+               { pstate->wrap<unary_neg_operation> (); }
 |      '+' UnaryExpression
-               { write_exp_elt_opcode (pstate, UNOP_PLUS); }
+               { pstate->wrap<unary_plus_operation> (); }
 |      '!' UnaryExpression
-               { write_exp_elt_opcode (pstate, UNOP_LOGICAL_NOT); }
+               { pstate->wrap<unary_logical_not_operation> (); }
 |      '~' UnaryExpression
-               { write_exp_elt_opcode (pstate, UNOP_COMPLEMENT); }
+               { pstate->wrap<unary_complement_operation> (); }
+|      TypeExp '.' SIZEOF_KEYWORD
+               { pstate->wrap<unop_sizeof_operation> (); }
 |      CastExpression
 |      PowExpression
 ;
 
 CastExpression:
        CAST_KEYWORD '(' TypeExp ')' UnaryExpression
-               { write_exp_elt_opcode (pstate, UNOP_CAST);
-                 write_exp_elt_type (pstate, $3);
-                 write_exp_elt_opcode (pstate, UNOP_CAST); }
+               { pstate->wrap2<unop_cast_type_operation> (); }
        /* C style cast is illegal D, but is still recognised in
           the grammar, so we keep this around for convenience.  */
 |      '(' TypeExp ')' UnaryExpression
-               { write_exp_elt_opcode (pstate, UNOP_CAST);
-                 write_exp_elt_type (pstate, $2);
-                 write_exp_elt_opcode (pstate, UNOP_CAST); }
+               { pstate->wrap2<unop_cast_type_operation> (); }
 ;
 
 PowExpression:
        PostfixExpression
 |      PostfixExpression HATHAT UnaryExpression
-               { write_exp_elt_opcode (pstate, BINOP_EXP); }
+               { pstate->wrap2<exp_operation> (); }
 ;
 
 PostfixExpression:
        PrimaryExpression
 |      PostfixExpression '.' COMPLETE
-               { struct stoken s;
-                 mark_struct_expression (pstate);
-                 write_exp_elt_opcode (pstate, STRUCTOP_STRUCT);
-                 s.ptr = "";
-                 s.length = 0;
-                 write_exp_string (pstate, s);
-                 write_exp_elt_opcode (pstate, STRUCTOP_STRUCT); }
+               {
+                 structop_base_operation *op
+                   = new structop_ptr_operation (pstate->pop (), "");
+                 pstate->mark_struct_expression (op);
+                 pstate->push (operation_up (op));
+               }
 |      PostfixExpression '.' IDENTIFIER
-               { write_exp_elt_opcode (pstate, STRUCTOP_STRUCT);
-                 write_exp_string (pstate, $3);
-                 write_exp_elt_opcode (pstate, STRUCTOP_STRUCT); }
+               {
+                 pstate->push_new<structop_operation>
+                   (pstate->pop (), copy_name ($3));
+               }
 |      PostfixExpression '.' IDENTIFIER COMPLETE
-               { mark_struct_expression (pstate);
-                 write_exp_elt_opcode (pstate, STRUCTOP_STRUCT);
-                 write_exp_string (pstate, $3);
-                 write_exp_elt_opcode (pstate, STRUCTOP_STRUCT); }
+               {
+                 structop_base_operation *op
+                   = new structop_operation (pstate->pop (), copy_name ($3));
+                 pstate->mark_struct_expression (op);
+                 pstate->push (operation_up (op));
+               }
+|      PostfixExpression '.' SIZEOF_KEYWORD
+               { pstate->wrap<unop_sizeof_operation> (); }
 |      PostfixExpression INCREMENT
-               { write_exp_elt_opcode (pstate, UNOP_POSTINCREMENT); }
+               { pstate->wrap<postinc_operation> (); }
 |      PostfixExpression DECREMENT
-               { write_exp_elt_opcode (pstate, UNOP_POSTDECREMENT); }
+               { pstate->wrap<postdec_operation> (); }
 |      CallExpression
 |      IndexExpression
 |      SliceExpression
@@ -419,36 +384,40 @@ PostfixExpression:
 
 ArgumentList:
        AssignExpression
-               { arglist_len = 1; }
+               { pstate->arglist_len = 1; }
 |      ArgumentList ',' AssignExpression
-               { arglist_len++; }
+               { pstate->arglist_len++; }
 ;
 
 ArgumentList_opt:
        /* EMPTY */
-               { arglist_len = 0; }
+               { pstate->arglist_len = 0; }
 |      ArgumentList
 ;
 
 CallExpression:
        PostfixExpression '('
-               { start_arglist (); }
+               { pstate->start_arglist (); }
        ArgumentList_opt ')'
-               { write_exp_elt_opcode (pstate, OP_FUNCALL);
-                 write_exp_elt_longcst (pstate, (LONGEST) end_arglist ());
-                 write_exp_elt_opcode (pstate, OP_FUNCALL); }
+               {
+                 std::vector<operation_up> args
+                   = pstate->pop_vector (pstate->end_arglist ());
+                 pstate->push_new<funcall_operation>
+                   (pstate->pop (), std::move (args));
+               }
 ;
 
 IndexExpression:
        PostfixExpression '[' ArgumentList ']'
-               { if (arglist_len > 0)
+               { if (pstate->arglist_len > 0)
                    {
-                     write_exp_elt_opcode (pstate, MULTI_SUBSCRIPT);
-                     write_exp_elt_longcst (pstate, (LONGEST) arglist_len);
-                     write_exp_elt_opcode (pstate, MULTI_SUBSCRIPT);
+                     std::vector<operation_up> args
+                       = pstate->pop_vector (pstate->arglist_len);
+                     pstate->push_new<multi_subscript_operation>
+                       (pstate->pop (), std::move (args));
                    }
                  else
-                   write_exp_elt_opcode (pstate, BINOP_SUBSCRIPT);
+                   pstate->wrap2<subscript_operation> ();
                }
 ;
 
@@ -456,7 +425,14 @@ SliceExpression:
        PostfixExpression '[' ']'
                { /* Do nothing.  */ }
 |      PostfixExpression '[' AssignExpression DOTDOT AssignExpression ']'
-               { write_exp_elt_opcode (pstate, TERNOP_SLICE); }
+               {
+                 operation_up last = pstate->pop ();
+                 operation_up mid = pstate->pop ();
+                 operation_up first = pstate->pop ();
+                 pstate->push_new<ternop_slice_operation>
+                   (std::move (first), std::move (mid),
+                    std::move (last));
+               }
 ;
 
 PrimaryExpression:
@@ -464,52 +440,42 @@ PrimaryExpression:
                { /* Do nothing.  */ }
 |      IdentifierExp
                { struct bound_minimal_symbol msymbol;
-                 char *copy = copy_name ($1);
+                 std::string copy = copy_name ($1);
                  struct field_of_this_result is_a_field_of_this;
                  struct block_symbol sym;
 
                  /* Handle VAR, which could be local or global.  */
-                 sym = lookup_symbol (copy, expression_context_block, VAR_DOMAIN,
-                                      &is_a_field_of_this);
+                 sym = lookup_symbol (copy.c_str (),
+                                      pstate->expression_context_block,
+                                      VAR_DOMAIN, &is_a_field_of_this);
                  if (sym.symbol && SYMBOL_CLASS (sym.symbol) != LOC_TYPEDEF)
                    {
                      if (symbol_read_needs_frame (sym.symbol))
-                       {
-                         if (innermost_block == 0 ||
-                             contained_in (sym.block, innermost_block))
-                           innermost_block = sym.block;
-                       }
-
-                     write_exp_elt_opcode (pstate, OP_VAR_VALUE);
-                     /* We want to use the selected frame, not another more inner frame
-                        which happens to be in the same block.  */
-                     write_exp_elt_block (pstate, NULL);
-                     write_exp_elt_sym (pstate, sym.symbol);
-                     write_exp_elt_opcode (pstate, OP_VAR_VALUE);
+                       pstate->block_tracker->update (sym);
+                     pstate->push_new<var_value_operation> (sym.symbol,
+                                                            sym.block);
                    }
                  else if (is_a_field_of_this.type != NULL)
                     {
                      /* It hangs off of `this'.  Must not inadvertently convert from a
                         method call to data ref.  */
-                     if (innermost_block == 0 ||
-                         contained_in (sym.block, innermost_block))
-                       innermost_block = sym.block;
-                     write_exp_elt_opcode (pstate, OP_THIS);
-                     write_exp_elt_opcode (pstate, OP_THIS);
-                     write_exp_elt_opcode (pstate, STRUCTOP_PTR);
-                     write_exp_string (pstate, $1);
-                     write_exp_elt_opcode (pstate, STRUCTOP_PTR);
+                     pstate->block_tracker->update (sym);
+                     operation_up thisop
+                       = make_operation<op_this_operation> ();
+                     pstate->push_new<structop_ptr_operation>
+                       (std::move (thisop), std::move (copy));
                    }
                  else
                    {
                      /* Lookup foreign name in global static symbols.  */
-                     msymbol = lookup_bound_minimal_symbol (copy);
+                     msymbol = lookup_bound_minimal_symbol (copy.c_str ());
                      if (msymbol.minsym != NULL)
-                       write_exp_msymbol (pstate, msymbol);
+                       pstate->push_new<var_msym_value_operation> (msymbol);
                      else if (!have_full_symbols () && !have_partial_symbols ())
                        error (_("No symbol table is loaded.  Use the \"file\" command"));
                      else
-                       error (_("No symbol \"%s\" in current context."), copy);
+                       error (_("No symbol \"%s\" in current context."),
+                              copy.c_str ());
                    }
                  }
 |      TypeExp '.' IdentifierExp
@@ -518,108 +484,83 @@ PrimaryExpression:
                          /* Check if the qualified name is in the global
                             context.  However if the symbol has not already
                             been resolved, it's not likely to be found.  */
-                         if (TYPE_CODE (type) == TYPE_CODE_MODULE)
+                         if (type->code () == TYPE_CODE_MODULE)
                            {
-                             struct bound_minimal_symbol msymbol;
                              struct block_symbol sym;
-                             const char *typename = TYPE_SAFE_NAME (type);
-                             int typename_len = strlen (typename);
-                             char *name = malloc (typename_len + $3.length + 1);
-
-                             make_cleanup (free, name);
-                             sprintf (name, "%.*s.%.*s",
-                                      typename_len, typename, $3.length, $3.ptr);
+                             const char *type_name = TYPE_SAFE_NAME (type);
+                             int type_name_len = strlen (type_name);
+                             std::string name
+                               = string_printf ("%.*s.%.*s",
+                                                type_name_len, type_name,
+                                                $3.length, $3.ptr);
 
                              sym =
-                               lookup_symbol (name, (const struct block *) NULL,
+                               lookup_symbol (name.c_str (),
+                                              (const struct block *) NULL,
                                               VAR_DOMAIN, NULL);
-                             if (sym.symbol)
-                               {
-                                 write_exp_elt_opcode (pstate, OP_VAR_VALUE);
-                                 write_exp_elt_block (pstate, sym.block);
-                                 write_exp_elt_sym (pstate, sym.symbol);
-                                 write_exp_elt_opcode (pstate, OP_VAR_VALUE);
-                                 break;
-                               }
-
-                             msymbol = lookup_bound_minimal_symbol (name);
-                             if (msymbol.minsym != NULL)
-                               write_exp_msymbol (pstate, msymbol);
-                             else if (!have_full_symbols () && !have_partial_symbols ())
-                               error (_("No symbol table is loaded.  Use the \"file\" command."));
-                             else
-                               error (_("No symbol \"%s\" in current context."), name);
+                             pstate->push_symbol (name.c_str (), sym);
+                           }
+                         else
+                           {
+                             /* Check if the qualified name resolves as a member
+                                of an aggregate or an enum type.  */
+                             if (!type_aggregate_p (type))
+                               error (_("`%s' is not defined as an aggregate type."),
+                                      TYPE_SAFE_NAME (type));
+
+                             pstate->push_new<scope_operation>
+                               (type, copy_name ($3));
                            }
-
-                         /* Check if the qualified name resolves as a member
-                            of an aggregate or an enum type.  */
-                         if (!(TYPE_CODE (type) == TYPE_CODE_STRUCT
-                               || TYPE_CODE (type) == TYPE_CODE_UNION
-                               || TYPE_CODE (type) == TYPE_CODE_ENUM))
-                           error (_("`%s' is not defined as an aggregate type."),
-                                  TYPE_SAFE_NAME (type));
-
-                         write_exp_elt_opcode (pstate, OP_SCOPE);
-                         write_exp_elt_type (pstate, type);
-                         write_exp_string (pstate, $3);
-                         write_exp_elt_opcode (pstate, OP_SCOPE);
                        }
 |      DOLLAR_VARIABLE
-               { write_dollar_variable (pstate, $1); }
+               { pstate->push_dollar ($1); }
 |      NAME_OR_INT
                { YYSTYPE val;
-                  parse_number (pstate, $1.ptr, $1.length, 0, &val);
-                 write_exp_elt_opcode (pstate, OP_LONG);
-                 write_exp_elt_type (pstate, val.typed_val_int.type);
-                 write_exp_elt_longcst (pstate,
-                                        (LONGEST) val.typed_val_int.val);
-                 write_exp_elt_opcode (pstate, OP_LONG); }
+                 parse_number (pstate, $1.ptr, $1.length, 0, &val);
+                 pstate->push_new<long_const_operation>
+                   (val.typed_val_int.type, val.typed_val_int.val); }
 |      NULL_KEYWORD
                { struct type *type = parse_d_type (pstate)->builtin_void;
                  type = lookup_pointer_type (type);
-                 write_exp_elt_opcode (pstate, OP_LONG);
-                 write_exp_elt_type (pstate, type);
-                 write_exp_elt_longcst (pstate, (LONGEST) 0);
-                 write_exp_elt_opcode (pstate, OP_LONG); }
+                 pstate->push_new<long_const_operation> (type, 0); }
 |      TRUE_KEYWORD
-               { write_exp_elt_opcode (pstate, OP_BOOL);
-                 write_exp_elt_longcst (pstate, (LONGEST) 1);
-                 write_exp_elt_opcode (pstate, OP_BOOL); }
+               { pstate->push_new<bool_operation> (true); }
 |      FALSE_KEYWORD
-               { write_exp_elt_opcode (pstate, OP_BOOL);
-                 write_exp_elt_longcst (pstate, (LONGEST) 0);
-                 write_exp_elt_opcode (pstate, OP_BOOL); }
+               { pstate->push_new<bool_operation> (false); }
 |      INTEGER_LITERAL
-               { write_exp_elt_opcode (pstate, OP_LONG);
-                 write_exp_elt_type (pstate, $1.type);
-                 write_exp_elt_longcst (pstate, (LONGEST)($1.val));
-                 write_exp_elt_opcode (pstate, OP_LONG); }
+               { pstate->push_new<long_const_operation> ($1.type, $1.val); }
 |      FLOAT_LITERAL
-               { write_exp_elt_opcode (pstate, OP_DOUBLE);
-                 write_exp_elt_type (pstate, $1.type);
-                 write_exp_elt_dblcst (pstate, $1.dval);
-                 write_exp_elt_opcode (pstate, OP_DOUBLE); }
+               {
+                 float_data data;
+                 std::copy (std::begin ($1.val), std::end ($1.val),
+                            std::begin (data));
+                 pstate->push_new<float_const_operation> ($1.type, data);
+               }
 |      CHARACTER_LITERAL
                { struct stoken_vector vec;
                  vec.len = 1;
                  vec.tokens = &$1;
-                 write_exp_string_vector (pstate, $1.type, &vec); }
+                 pstate->push_c_string (0, &vec); }
 |      StringExp
                { int i;
-                 write_exp_string_vector (pstate, 0, &$1);
+                 pstate->push_c_string (0, &$1);
                  for (i = 0; i < $1.len; ++i)
                    free ($1.tokens[i].ptr);
                  free ($1.tokens); }
 |      ArrayLiteral
-               { write_exp_elt_opcode (pstate, OP_ARRAY);
-                 write_exp_elt_longcst (pstate, (LONGEST) 0);
-                 write_exp_elt_longcst (pstate, (LONGEST) $1 - 1);
-                 write_exp_elt_opcode (pstate, OP_ARRAY); }
+               {
+                 std::vector<operation_up> args
+                   = pstate->pop_vector ($1);
+                 pstate->push_new<array_operation>
+                   (0, $1 - 1, std::move (args));
+               }
+|      TYPEOF_KEYWORD '(' Expression ')'
+               { pstate->wrap<typeof_operation> (); }
 ;
 
 ArrayLiteral:
        '[' ArgumentList_opt ']'
-               { $$ = arglist_len; }
+               { $$ = pstate->arglist_len; }
 ;
 
 IdentifierExp:
@@ -639,7 +580,7 @@ StringExp:
 
                  vec->type = $1.type;
                  vec->length = $1.length;
-                 vec->ptr = malloc ($1.length + 1);
+                 vec->ptr = (char *) malloc ($1.length + 1);
                  memcpy (vec->ptr, $1.ptr, $1.length + 1);
                }
 |      StringExp STRING_LITERAL
@@ -647,10 +588,10 @@ StringExp:
                     for convenience.  */
                  char *p;
                  ++$$.len;
-                 $$.tokens = realloc ($$.tokens,
-                                      $$.len * sizeof (struct typed_stoken));
+                 $$.tokens
+                   = XRESIZEVEC (struct typed_stoken, $$.tokens, $$.len);
 
-                 p = malloc ($2.length + 1);
+                 p = (char *) malloc ($2.length + 1);
                  memcpy (p, $2.ptr, $2.length + 1);
 
                  $$.tokens[$$.len - 1].type = $2.type;
@@ -663,28 +604,24 @@ TypeExp:
        '(' TypeExp ')'
                { /* Do nothing.  */ }
 |      BasicType
-               { write_exp_elt_opcode (pstate, OP_TYPE);
-                 write_exp_elt_type (pstate, $1);
-                 write_exp_elt_opcode (pstate, OP_TYPE); }
+               { pstate->push_new<type_operation> ($1); }
 |      BasicType BasicType2
-               { $$ = follow_types ($1);
-                 write_exp_elt_opcode (pstate, OP_TYPE);
-                 write_exp_elt_type (pstate, $$);
-                 write_exp_elt_opcode (pstate, OP_TYPE);
+               { $$ = type_stack->follow_types ($1);
+                 pstate->push_new<type_operation> ($$);
                }
 ;
 
 BasicType2:
        '*'
-               { push_type (tp_pointer); }
+               { type_stack->push (tp_pointer); }
 |      '*' BasicType2
-               { push_type (tp_pointer); }
+               { type_stack->push (tp_pointer); }
 |      '[' INTEGER_LITERAL ']'
-               { push_type_int ($2.val);
-                 push_type (tp_array); }
+               { type_stack->push ($2.val);
+                 type_stack->push (tp_array); }
 |      '[' INTEGER_LITERAL ']' BasicType2
-               { push_type_int ($2.val);
-                 push_type (tp_array); }
+               { type_stack->push ($2.val);
+                 type_stack->push (tp_array); }
 ;
 
 BasicType:
@@ -694,6 +631,18 @@ BasicType:
 
 %%
 
+/* Return true if the type is aggregate-like.  */
+
+static int
+type_aggregate_p (struct type *type)
+{
+  return (type->code () == TYPE_CODE_STRUCT
+         || type->code () == TYPE_CODE_UNION
+         || type->code () == TYPE_CODE_MODULE
+         || (type->code () == TYPE_CODE_ENUM
+             && TYPE_DECLARED_CLASS (type)));
+}
+
 /* Take care of parsing a number (anything that starts with a digit).
    Set yylval and return the token type; update lexptr.
    LEN is the number of characters in it.  */
@@ -723,9 +672,6 @@ parse_number (struct parser_state *ps, const char *p,
 
   if (parsed_float)
     {
-      const struct builtin_d_type *builtin_d_types;
-      const char *suffix;
-      int suffix_len;
       char *s, *sp;
 
       /* Strip out all embedded '_' before passing to parse_float.  */
@@ -740,54 +686,51 @@ parse_number (struct parser_state *ps, const char *p,
       *sp = '\0';
       len = strlen (s);
 
-      if (! parse_float (s, len, &putithere->typed_val_float.dval, &suffix))
-       return ERROR;
-
-      suffix_len = s + len - suffix;
-
-      if (suffix_len == 0)
-       {
-         putithere->typed_val_float.type
-           = parse_d_type (ps)->builtin_double;
-       }
-      else if (suffix_len == 1)
+      /* Check suffix for `i' , `fi' or `li' (idouble, ifloat or ireal).  */
+      if (len >= 1 && tolower (s[len - 1]) == 'i')
        {
-         /* Check suffix for `f', `l', or `i' (float, real, or idouble).  */
-         if (tolower (*suffix) == 'f')
+         if (len >= 2 && tolower (s[len - 2]) == 'f')
            {
              putithere->typed_val_float.type
-               = parse_d_type (ps)->builtin_float;
+               = parse_d_type (ps)->builtin_ifloat;
+             len -= 2;
            }
-         else if (tolower (*suffix) == 'l')
+         else if (len >= 2 && tolower (s[len - 2]) == 'l')
            {
              putithere->typed_val_float.type
-               = parse_d_type (ps)->builtin_real;
+               = parse_d_type (ps)->builtin_ireal;
+             len -= 2;
            }
-         else if (tolower (*suffix) == 'i')
+         else
            {
              putithere->typed_val_float.type
                = parse_d_type (ps)->builtin_idouble;
+             len -= 1;
            }
-         else
-           return ERROR;
        }
-      else if (suffix_len == 2)
+      /* Check suffix for `f' or `l'' (float or real).  */
+      else if (len >= 1 && tolower (s[len - 1]) == 'f')
        {
-         /* Check suffix for `fi' or `li' (ifloat or ireal).  */
-         if (tolower (suffix[0]) == 'f' && tolower (suffix[1] == 'i'))
-           {
-             putithere->typed_val_float.type
-               = parse_d_type (ps)->builtin_ifloat;
-           }
-         else if (tolower (suffix[0]) == 'l' && tolower (suffix[1] == 'i'))
-           {
-             putithere->typed_val_float.type
-               = parse_d_type (ps)->builtin_ireal;
-           }
-         else
-           return ERROR;
+         putithere->typed_val_float.type
+           = parse_d_type (ps)->builtin_float;
+         len -= 1;
        }
+      else if (len >= 1 && tolower (s[len - 1]) == 'l')
+       {
+         putithere->typed_val_float.type
+           = parse_d_type (ps)->builtin_real;
+         len -= 1;
+       }
+      /* Default type if no suffix.  */
       else
+       {
+         putithere->typed_val_float.type
+           = parse_d_type (ps)->builtin_double;
+       }
+
+      if (!parse_float (s, len,
+                       putithere->typed_val_float.type,
+                       putithere->typed_val_float.val))
        return ERROR;
 
       return FLOAT_LITERAL;
@@ -842,7 +785,7 @@ parse_number (struct parser_state *ps, const char *p,
          if (base > 10 && c >= 'a' && c <= 'f')
            {
              if (found_suffix)
-               return ERROR;
+               return ERROR;
              n += i = c - 'a' + 10;
            }
          else if (c == 'l' && long_p == 0)
@@ -989,7 +932,7 @@ parse_string_or_char (const char *tokptr, const char **outptr,
   else
     value->type = C_STRING;
 
-  value->ptr = obstack_base (&tempbuf);
+  value->ptr = (char *) obstack_base (&tempbuf);
   value->length = obstack_object_size (&tempbuf);
 
   *outptr = tokptr;
@@ -999,7 +942,7 @@ parse_string_or_char (const char *tokptr, const char **outptr,
 
 struct token
 {
-  char *oper;
+  const char *oper;
   int token;
   enum exp_opcode opcode;
 };
@@ -1021,25 +964,25 @@ static const struct token tokentab2[] =
     {"|=", ASSIGN_MODIFY, BINOP_BITWISE_IOR},
     {"&=", ASSIGN_MODIFY, BINOP_BITWISE_AND},
     {"^=", ASSIGN_MODIFY, BINOP_BITWISE_XOR},
-    {"++", INCREMENT, BINOP_END},
-    {"--", DECREMENT, BINOP_END},
-    {"&&", ANDAND, BINOP_END},
-    {"||", OROR, BINOP_END},
-    {"^^", HATHAT, BINOP_END},
-    {"<<", LSH, BINOP_END},
-    {">>", RSH, BINOP_END},
-    {"==", EQUAL, BINOP_END},
-    {"!=", NOTEQUAL, BINOP_END},
-    {"<=", LEQ, BINOP_END},
-    {">=", GEQ, BINOP_END},
-    {"..", DOTDOT, BINOP_END},
+    {"++", INCREMENT, OP_NULL},
+    {"--", DECREMENT, OP_NULL},
+    {"&&", ANDAND, OP_NULL},
+    {"||", OROR, OP_NULL},
+    {"^^", HATHAT, OP_NULL},
+    {"<<", LSH, OP_NULL},
+    {">>", RSH, OP_NULL},
+    {"==", EQUAL, OP_NULL},
+    {"!=", NOTEQUAL, OP_NULL},
+    {"<=", LEQ, OP_NULL},
+    {">=", GEQ, OP_NULL},
+    {"..", DOTDOT, OP_NULL},
   };
 
 /* Identifier-like tokens.  */
 static const struct token ident_tokens[] =
   {
-    {"is", IDENTITY, BINOP_END},
-    {"!is", NOTIDENTITY, BINOP_END},
+    {"is", IDENTITY, OP_NULL},
+    {"!is", NOTIDENTITY, OP_NULL},
 
     {"cast", CAST_KEYWORD, OP_NULL},
     {"const", CONST_KEYWORD, OP_NULL},
@@ -1075,6 +1018,9 @@ static int saw_name_at_eof;
    This is used only when parsing to do field name completion.  */
 static int last_was_structop;
 
+/* Depth of parentheses.  */
+static int paren_depth;
+
 /* Read one token, getting characters through lexptr.  */
 
 static int
@@ -1085,20 +1031,19 @@ lex_one_token (struct parser_state *par_state)
   unsigned int i;
   const char *tokstart;
   int saw_structop = last_was_structop;
-  char *copy;
 
   last_was_structop = 0;
 
  retry:
 
-  prev_lexptr = lexptr;
+  pstate->prev_lexptr = pstate->lexptr;
 
-  tokstart = lexptr;
+  tokstart = pstate->lexptr;
   /* See if it is a special token of length 3.  */
   for (i = 0; i < sizeof tokentab3 / sizeof tokentab3[0]; i++)
     if (strncmp (tokstart, tokentab3[i].oper, 3) == 0)
       {
-       lexptr += 3;
+       pstate->lexptr += 3;
        yylval.opcode = tokentab3[i].opcode;
        return tokentab3[i].token;
       }
@@ -1107,7 +1052,7 @@ lex_one_token (struct parser_state *par_state)
   for (i = 0; i < sizeof tokentab2 / sizeof tokentab2[0]; i++)
     if (strncmp (tokstart, tokentab2[i].oper, 2) == 0)
       {
-       lexptr += 2;
+       pstate->lexptr += 2;
        yylval.opcode = tokentab2[i].opcode;
        return tokentab2[i].token;
       }
@@ -1127,18 +1072,18 @@ lex_one_token (struct parser_state *par_state)
       else if (saw_structop)
        return COMPLETE;
       else
-        return 0;
+       return 0;
 
     case ' ':
     case '\t':
     case '\n':
-      lexptr++;
+      pstate->lexptr++;
       goto retry;
 
     case '[':
     case '(':
       paren_depth++;
-      lexptr++;
+      pstate->lexptr++;
       return c;
 
     case ']':
@@ -1146,24 +1091,24 @@ lex_one_token (struct parser_state *par_state)
       if (paren_depth == 0)
        return 0;
       paren_depth--;
-      lexptr++;
+      pstate->lexptr++;
       return c;
 
     case ',':
-      if (comma_terminates && paren_depth == 0)
+      if (pstate->comma_terminates && paren_depth == 0)
        return 0;
-      lexptr++;
+      pstate->lexptr++;
       return c;
 
     case '.':
       /* Might be a floating point number.  */
-      if (lexptr[1] < '0' || lexptr[1] > '9')
+      if (pstate->lexptr[1] < '0' || pstate->lexptr[1] > '9')
        {
-         if (parse_completion)
+         if (pstate->parse_completion)
            last_was_structop = 1;
          goto symbol;          /* Nope, must be a symbol.  */
        }
-      /* FALL THRU into number case.  */
+      /* FALL THRU.  */
 
     case '0':
     case '1':
@@ -1207,8 +1152,8 @@ lex_one_token (struct parser_state *par_state)
            /* We will take any letters or digits, ignoring any embedded '_'.
               parse_number will complain if past the radix, or if L or U are
               not final.  */
-           else if ((*p < '0' || *p > '9') && (*p != '_') &&
-                    ((*p < 'a' || *p > 'z') && (*p < 'A' || *p > 'Z')))
+           else if ((*p < '0' || *p > '9') && (*p != '_')
+                    && ((*p < 'a' || *p > 'z') && (*p < 'A' || *p > 'Z')))
              break;
          }
 
@@ -1222,7 +1167,7 @@ lex_one_token (struct parser_state *par_state)
            err_copy[p - tokstart] = 0;
            error (_("Invalid number \"%s\"."), err_copy);
          }
-       lexptr = p;
+       pstate->lexptr = p;
        return toktype;
       }
 
@@ -1236,7 +1181,7 @@ lex_one_token (struct parser_state *par_state)
        if (strncmp (p, "entry", len) == 0 && !isalnum (p[len])
            && p[len] != '_')
          {
-           lexptr = &p[len];
+           pstate->lexptr = &p[len];
            return ENTRY;
          }
       }
@@ -1259,7 +1204,7 @@ lex_one_token (struct parser_state *par_state)
     case '{':
     case '}':
     symbol:
-      lexptr++;
+      pstate->lexptr++;
       return c;
 
     case '\'':
@@ -1267,8 +1212,8 @@ lex_one_token (struct parser_state *par_state)
     case '`':
       {
        int host_len;
-       int result = parse_string_or_char (tokstart, &lexptr, &yylval.tsval,
-                                          &host_len);
+       int result = parse_string_or_char (tokstart, &pstate->lexptr,
+                                          &yylval.tsval, &host_len);
        if (result == CHARACTER_LITERAL)
          {
            if (host_len == 0)
@@ -1276,7 +1221,7 @@ lex_one_token (struct parser_state *par_state)
            else if (host_len > 2 && c == '\'')
              {
                ++tokstart;
-               namelen = lexptr - tokstart - 1;
+               namelen = pstate->lexptr - tokstart - 1;
                goto tryname;
              }
            else if (host_len > 1)
@@ -1316,12 +1261,12 @@ lex_one_token (struct parser_state *par_state)
       const char *p = tokstart + namelen + 1;
 
       while (*p == ' ' || *p == '\t')
-        p++;
+       p++;
       if (*p >= '0' && *p <= '9')
-        return 0;
+       return 0;
     }
 
-  lexptr += namelen;
+  pstate->lexptr += namelen;
 
  tryname:
 
@@ -1329,9 +1274,9 @@ lex_one_token (struct parser_state *par_state)
   yylval.sval.length = namelen;
 
   /* Catch specific keywords.  */
-  copy = copy_name (yylval.sval);
+  std::string copy = copy_name (yylval.sval);
   for (i = 0; i < sizeof ident_tokens / sizeof ident_tokens[0]; i++)
-    if (strcmp (copy, ident_tokens[i].oper) == 0)
+    if (copy == ident_tokens[i].oper)
       {
        /* It is ok to always set this, even though we don't always
           strictly need to.  */
@@ -1343,8 +1288,8 @@ lex_one_token (struct parser_state *par_state)
     return DOLLAR_VARIABLE;
 
   yylval.tsym.type
-    = language_lookup_primitive_type (parse_language (par_state),
-                                     parse_gdbarch (par_state), copy);
+    = language_lookup_primitive_type (par_state->language (),
+                                     par_state->gdbarch (), copy.c_str ());
   if (yylval.tsym.type != NULL)
     return TYPENAME;
 
@@ -1360,31 +1305,30 @@ lex_one_token (struct parser_state *par_state)
        return NAME_OR_INT;
     }
 
-  if (parse_completion && *lexptr == '\0')
+  if (pstate->parse_completion && *pstate->lexptr == '\0')
     saw_name_at_eof = 1;
 
   return IDENTIFIER;
 }
 
 /* An object of this type is pushed on a FIFO by the "outer" lexer.  */
-typedef struct
+struct token_and_value
 {
   int token;
   YYSTYPE value;
-} token_and_value;
+};
 
-DEF_VEC_O (token_and_value);
 
 /* A FIFO of tokens that have been read but not yet returned to the
    parser.  */
-static VEC (token_and_value) *token_fifo;
+static std::vector<token_and_value> token_fifo;
 
 /* Non-zero if the lexer should return tokens from the FIFO.  */
 static int popping;
 
 /* Temporary storage for yylex; this holds symbol names as they are
    built up.  */
-static struct obstack name_obstack;
+static auto_obstack name_obstack;
 
 /* Classify an IDENTIFIER token.  The contents of the token are in `yylval'.
    Updates yylval and returns the new token type.  BLOCK is the block
@@ -1394,12 +1338,11 @@ static int
 classify_name (struct parser_state *par_state, const struct block *block)
 {
   struct block_symbol sym;
-  char *copy;
   struct field_of_this_result is_a_field_of_this;
 
-  copy = copy_name (yylval.sval);
+  std::string copy = copy_name (yylval.sval);
 
-  sym = lookup_symbol (copy, block, VAR_DOMAIN, &is_a_field_of_this);
+  sym = lookup_symbol (copy.c_str (), block, VAR_DOMAIN, &is_a_field_of_this);
   if (sym.symbol && SYMBOL_CLASS (sym.symbol) == LOC_TYPEDEF)
     {
       yylval.tsym.type = SYMBOL_TYPE (sym.symbol);
@@ -1408,9 +1351,9 @@ classify_name (struct parser_state *par_state, const struct block *block)
   else if (sym.symbol == NULL)
     {
       /* Look-up first for a module name, then a type.  */
-      sym = lookup_symbol (copy, block, MODULE_DOMAIN, NULL);
+      sym = lookup_symbol (copy.c_str (), block, MODULE_DOMAIN, NULL);
       if (sym.symbol == NULL)
-       sym = lookup_symbol (copy, block, STRUCT_DOMAIN, NULL);
+       sym = lookup_symbol (copy.c_str (), block, STRUCT_DOMAIN, NULL);
 
       if (sym.symbol != NULL)
        {
@@ -1433,15 +1376,16 @@ classify_inner_name (struct parser_state *par_state,
                     const struct block *block, struct type *context)
 {
   struct type *type;
-  char *copy;
 
   if (context == NULL)
     return classify_name (par_state, block);
 
   type = check_typedef (context);
+  if (!type_aggregate_p (type))
+    return ERROR;
 
-  copy = copy_name (yylval.ssym.stoken);
-  yylval.ssym.sym = d_lookup_nested_symbol (type, copy, block);
+  std::string copy = copy_name (yylval.ssym.stoken);
+  yylval.ssym.sym = d_lookup_nested_symbol (type, copy.c_str (), block);
 
   if (yylval.ssym.sym.symbol == NULL)
     return ERROR;
@@ -1471,7 +1415,7 @@ yylex (void)
   int last_to_examine, next_to_examine, checkpoint;
   const struct block *search_block;
 
-  if (popping && !VEC_empty (token_and_value, token_fifo))
+  if (popping && !token_fifo.empty ())
     goto do_pop;
   popping = 0;
 
@@ -1483,14 +1427,14 @@ yylex (void)
   /* Read any sequence of alternating "." and identifier tokens into
      the token FIFO.  */
   current.value = yylval;
-  VEC_safe_push (token_and_value, token_fifo, &current);
+  token_fifo.push_back (current);
   last_was_dot = current.token == '.';
 
   while (1)
     {
       current.token = lex_one_token (pstate);
       current.value = yylval;
-      VEC_safe_push (token_and_value, token_fifo, &current);
+      token_fifo.push_back (current);
 
       if ((last_was_dot && current.token != IDENTIFIER)
          || (!last_was_dot && current.token != '.'))
@@ -1502,17 +1446,17 @@ yylex (void)
 
   /* We always read one extra token, so compute the number of tokens
      to examine accordingly.  */
-  last_to_examine = VEC_length (token_and_value, token_fifo) - 2;
+  last_to_examine = token_fifo.size () - 2;
   next_to_examine = 0;
 
-  current = *VEC_index (token_and_value, token_fifo, next_to_examine);
+  current = token_fifo[next_to_examine];
   ++next_to_examine;
 
   /* If we are not dealing with a typename, now is the time to find out.  */
   if (current.token == IDENTIFIER)
     {
       yylval = current.value;
-      current.token = classify_name (pstate, expression_context_block);
+      current.token = classify_name (pstate, pstate->expression_context_block);
       current.value = yylval;
     }
 
@@ -1520,7 +1464,7 @@ yylex (void)
      first try building up a name until we find the qualified module.  */
   if (current.token == UNKNOWN_NAME)
     {
-      obstack_free (&name_obstack, obstack_base (&name_obstack));
+      name_obstack.clear ();
       obstack_grow (&name_obstack, current.value.sval.ptr,
                    current.value.sval.length);
 
@@ -1528,35 +1472,36 @@ yylex (void)
 
       while (next_to_examine <= last_to_examine)
        {
-         token_and_value *next;
+         token_and_value next;
 
-         next = VEC_index (token_and_value, token_fifo, next_to_examine);
+         next = token_fifo[next_to_examine];
          ++next_to_examine;
 
-         if (next->token == IDENTIFIER && last_was_dot)
+         if (next.token == IDENTIFIER && last_was_dot)
            {
              /* Update the partial name we are constructing.  */
-              obstack_grow_str (&name_obstack, ".");
-             obstack_grow (&name_obstack, next->value.sval.ptr,
-                           next->value.sval.length);
+             obstack_grow_str (&name_obstack, ".");
+             obstack_grow (&name_obstack, next.value.sval.ptr,
+                           next.value.sval.length);
 
-             yylval.sval.ptr = obstack_base (&name_obstack);
+             yylval.sval.ptr = (char *) obstack_base (&name_obstack);
              yylval.sval.length = obstack_object_size (&name_obstack);
 
-             current.token = classify_name (pstate, expression_context_block);
+             current.token = classify_name (pstate,
+                                            pstate->expression_context_block);
              current.value = yylval;
 
              /* We keep going until we find a TYPENAME.  */
              if (current.token == TYPENAME)
                {
                  /* Install it as the first token in the FIFO.  */
-                 VEC_replace (token_and_value, token_fifo, 0, &current);
-                 VEC_block_remove (token_and_value, token_fifo, 1,
-                                   next_to_examine - 1);
+                 token_fifo[0] = current;
+                 token_fifo.erase (token_fifo.begin () + 1,
+                                   token_fifo.begin () + next_to_examine);
                  break;
                }
            }
-         else if (next->token == '.' && !last_was_dot)
+         else if (next.token == '.' && !last_was_dot)
            last_was_dot = 1;
          else
            {
@@ -1567,20 +1512,20 @@ yylex (void)
 
       /* Reset our current token back to the start, if we found nothing
         this means that we will just jump to do pop.  */
-      current = *VEC_index (token_and_value, token_fifo, 0);
+      current = token_fifo[0];
       next_to_examine = 1;
     }
   if (current.token != TYPENAME && current.token != '.')
     goto do_pop;
 
-  obstack_free (&name_obstack, obstack_base (&name_obstack));
+  name_obstack.clear ();
   checkpoint = 0;
   if (current.token == '.')
     search_block = NULL;
   else
     {
       gdb_assert (current.token == TYPENAME);
-      search_block = expression_context_block;
+      search_block = pstate->expression_context_block;
       obstack_grow (&name_obstack, current.value.sval.ptr,
                    current.value.sval.length);
       context_type = current.value.tsym.type;
@@ -1591,16 +1536,16 @@ yylex (void)
 
   while (next_to_examine <= last_to_examine)
     {
-      token_and_value *next;
+      token_and_value next;
 
-      next = VEC_index (token_and_value, token_fifo, next_to_examine);
+      next = token_fifo[next_to_examine];
       ++next_to_examine;
 
-      if (next->token == IDENTIFIER && last_was_dot)
+      if (next.token == IDENTIFIER && last_was_dot)
        {
          int classification;
 
-         yylval = next->value;
+         yylval = next.value;
          classification = classify_inner_name (pstate, search_block,
                                                context_type);
          /* We keep going until we either run out of names, or until
@@ -1615,12 +1560,12 @@ yylex (void)
          if (context_type != NULL)
            {
              /* We don't want to put a leading "." into the name.  */
-              obstack_grow_str (&name_obstack, ".");
+             obstack_grow_str (&name_obstack, ".");
            }
-         obstack_grow (&name_obstack, next->value.sval.ptr,
-                       next->value.sval.length);
+         obstack_grow (&name_obstack, next.value.sval.ptr,
+                       next.value.sval.length);
 
-         yylval.sval.ptr = obstack_base (&name_obstack);
+         yylval.sval.ptr = (char *) obstack_base (&name_obstack);
          yylval.sval.length = obstack_object_size (&name_obstack);
          current.value = yylval;
          current.token = classification;
@@ -1632,7 +1577,7 @@ yylex (void)
 
          context_type = yylval.tsym.type;
        }
-      else if (next->token == '.' && !last_was_dot)
+      else if (next.token == '.' && !last_was_dot)
        last_was_dot = 1;
       else
        {
@@ -1645,14 +1590,15 @@ yylex (void)
      the FIFO, and delete the other constituent tokens.  */
   if (checkpoint > 0)
     {
-      VEC_replace (token_and_value, token_fifo, 0, &current);
+      token_fifo[0] = current;
       if (checkpoint > 1)
-       VEC_block_remove (token_and_value, token_fifo, 1, checkpoint - 1);
+       token_fifo.erase (token_fifo.begin () + 1,
+                         token_fifo.begin () + checkpoint);
     }
 
  do_pop:
-  current = *VEC_index (token_and_value, token_fifo, 0);
-  VEC_ordered_remove (token_and_value, token_fifo, 0);
+  current = token_fifo[0];
+  token_fifo.erase (token_fifo.begin ());
   yylval = current.value;
   return current.token;
 }
@@ -1660,39 +1606,39 @@ yylex (void)
 int
 d_parse (struct parser_state *par_state)
 {
-  int result;
-  struct cleanup *back_to;
-
   /* Setting up the parser state.  */
+  scoped_restore pstate_restore = make_scoped_restore (&pstate);
   gdb_assert (par_state != NULL);
   pstate = par_state;
 
-  back_to = make_cleanup (null_cleanup, NULL);
+  scoped_restore restore_yydebug = make_scoped_restore (&yydebug,
+                                                       parser_debug);
 
-  make_cleanup_restore_integer (&yydebug);
-  make_cleanup_clear_parser_state (&pstate);
-  yydebug = parser_debug;
+  struct type_stack stack;
+  scoped_restore restore_type_stack = make_scoped_restore (&type_stack,
+                                                          &stack);
 
   /* Initialize some state used by the lexer.  */
   last_was_structop = 0;
   saw_name_at_eof = 0;
+  paren_depth = 0;
 
-  VEC_free (token_and_value, token_fifo);
+  token_fifo.clear ();
   popping = 0;
-  obstack_init (&name_obstack);
-  make_cleanup_obstack_free (&name_obstack);
+  name_obstack.clear ();
 
-  result = yyparse ();
-  do_cleanups (back_to);
+  int result = yyparse ();
+  if (!result)
+    pstate->set_operation (pstate->pop ());
   return result;
 }
 
-void
-yyerror (char *msg)
+static void
+yyerror (const char *msg)
 {
-  if (prev_lexptr)
-    lexptr = prev_lexptr;
+  if (pstate->prev_lexptr)
+    pstate->lexptr = pstate->prev_lexptr;
 
-  error (_("A %s in expression, near `%s'."), (msg ? msg : "error"), lexptr);
+  error (_("A %s in expression, near `%s'."), msg, pstate->lexptr);
 }
 
This page took 0.051617 seconds and 4 git commands to generate.