Convert generic probe interface to C++ (and perform some cleanups)
[external/binutils.git] / gdb / go-exp.y
1 /* YACC parser for Go expressions, for GDB.
2
3    Copyright (C) 2012-2017 Free Software Foundation, Inc.
4
5    This file is part of GDB.
6
7    This program is free software; you can redistribute it and/or modify
8    it under the terms of the GNU General Public License as published by
9    the Free Software Foundation; either version 3 of the License, or
10    (at your option) any later version.
11
12    This program is distributed in the hope that it will be useful,
13    but WITHOUT ANY WARRANTY; without even the implied warranty of
14    MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE.  See the
15    GNU General Public License for more details.
16
17    You should have received a copy of the GNU General Public License
18    along with this program.  If not, see <http://www.gnu.org/licenses/>.  */
19
20 /* This file is derived from c-exp.y, p-exp.y.  */
21
22 /* Parse a Go 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 /* Known bugs or limitations:
40
41    - Unicode
42    - &^
43    - '_' (blank identifier)
44    - automatic deref of pointers
45    - method expressions
46    - interfaces, channels, etc.
47
48    And lots of other things.
49    I'm sure there's some cleanup to do.
50 */
51
52 %{
53
54 #include "defs.h"
55 #include <ctype.h>
56 #include "expression.h"
57 #include "value.h"
58 #include "parser-defs.h"
59 #include "language.h"
60 #include "c-lang.h"
61 #include "go-lang.h"
62 #include "bfd.h" /* Required by objfiles.h.  */
63 #include "symfile.h" /* Required by objfiles.h.  */
64 #include "objfiles.h" /* For have_full_symbols and have_partial_symbols */
65 #include "charset.h"
66 #include "block.h"
67
68 #define parse_type(ps) builtin_type (parse_gdbarch (ps))
69
70 /* Remap normal yacc parser interface names (yyparse, yylex, yyerror,
71    etc).  */
72 #define GDB_YY_REMAP_PREFIX go_
73 #include "yy-remap.h"
74
75 /* The state of the parser, used internally when we are parsing the
76    expression.  */
77
78 static struct parser_state *pstate = NULL;
79
80 int yyparse (void);
81
82 static int yylex (void);
83
84 void yyerror (const char *);
85
86 %}
87
88 /* Although the yacc "value" of an expression is not used,
89    since the result is stored in the structure being created,
90    other node types do have values.  */
91
92 %union
93   {
94     LONGEST lval;
95     struct {
96       LONGEST val;
97       struct type *type;
98     } typed_val_int;
99     struct {
100       gdb_byte val[16];
101       struct type *type;
102     } typed_val_float;
103     struct stoken sval;
104     struct symtoken ssym;
105     struct type *tval;
106     struct typed_stoken tsval;
107     struct ttype tsym;
108     int voidval;
109     enum exp_opcode opcode;
110     struct internalvar *ivar;
111     struct stoken_vector svec;
112   }
113
114 %{
115 /* YYSTYPE gets defined by %union.  */
116 static int parse_number (struct parser_state *,
117                          const char *, int, int, YYSTYPE *);
118 %}
119
120 %type <voidval> exp exp1 type_exp start variable lcurly
121 %type <lval> rcurly
122 %type <tval> type
123
124 %token <typed_val_int> INT
125 %token <typed_val_float> FLOAT
126
127 /* Both NAME and TYPENAME tokens represent symbols in the input,
128    and both convey their data as strings.
129    But a TYPENAME is a string that happens to be defined as a type
130    or builtin type name (such as int or char)
131    and a NAME is any other symbol.
132    Contexts where this distinction is not important can use the
133    nonterminal "name", which matches either NAME or TYPENAME.  */
134
135 %token <tsval> RAW_STRING
136 %token <tsval> STRING
137 %token <tsval> CHAR
138 %token <ssym> NAME
139 %token <tsym> TYPENAME /* Not TYPE_NAME cus already taken.  */
140 %token <voidval> COMPLETE
141 /*%type <sval> name*/
142 %type <svec> string_exp
143 %type <ssym> name_not_typename
144
145 /* A NAME_OR_INT is a symbol which is not known in the symbol table,
146    but which would parse as a valid number in the current input radix.
147    E.g. "c" when input_radix==16.  Depending on the parse, it will be
148    turned into a name or into a number.  */
149 %token <ssym> NAME_OR_INT
150
151 %token <lval> TRUE_KEYWORD FALSE_KEYWORD
152 %token STRUCT_KEYWORD INTERFACE_KEYWORD TYPE_KEYWORD CHAN_KEYWORD
153 %token SIZEOF_KEYWORD
154 %token LEN_KEYWORD CAP_KEYWORD
155 %token NEW_KEYWORD
156 %token IOTA_KEYWORD NIL_KEYWORD
157 %token CONST_KEYWORD
158 %token DOTDOTDOT
159 %token ENTRY
160 %token ERROR
161
162 /* Special type cases.  */
163 %token BYTE_KEYWORD /* An alias of uint8.  */
164
165 %token <sval> DOLLAR_VARIABLE
166
167 %token <opcode> ASSIGN_MODIFY
168
169 %left ','
170 %left ABOVE_COMMA
171 %right '=' ASSIGN_MODIFY
172 %right '?'
173 %left OROR
174 %left ANDAND
175 %left '|'
176 %left '^'
177 %left '&'
178 %left ANDNOT
179 %left EQUAL NOTEQUAL
180 %left '<' '>' LEQ GEQ
181 %left LSH RSH
182 %left '@'
183 %left '+' '-'
184 %left '*' '/' '%'
185 %right UNARY INCREMENT DECREMENT
186 %right LEFT_ARROW '.' '[' '('
187
188 \f
189 %%
190
191 start   :       exp1
192         |       type_exp
193         ;
194
195 type_exp:       type
196                         { write_exp_elt_opcode (pstate, OP_TYPE);
197                           write_exp_elt_type (pstate, $1);
198                           write_exp_elt_opcode (pstate, OP_TYPE); }
199         ;
200
201 /* Expressions, including the comma operator.  */
202 exp1    :       exp
203         |       exp1 ',' exp
204                         { write_exp_elt_opcode (pstate, BINOP_COMMA); }
205         ;
206
207 /* Expressions, not including the comma operator.  */
208 exp     :       '*' exp    %prec UNARY
209                         { write_exp_elt_opcode (pstate, UNOP_IND); }
210         ;
211
212 exp     :       '&' exp    %prec UNARY
213                         { write_exp_elt_opcode (pstate, UNOP_ADDR); }
214         ;
215
216 exp     :       '-' exp    %prec UNARY
217                         { write_exp_elt_opcode (pstate, UNOP_NEG); }
218         ;
219
220 exp     :       '+' exp    %prec UNARY
221                         { write_exp_elt_opcode (pstate, UNOP_PLUS); }
222         ;
223
224 exp     :       '!' exp    %prec UNARY
225                         { write_exp_elt_opcode (pstate, UNOP_LOGICAL_NOT); }
226         ;
227
228 exp     :       '^' exp    %prec UNARY
229                         { write_exp_elt_opcode (pstate, UNOP_COMPLEMENT); }
230         ;
231
232 exp     :       exp INCREMENT    %prec UNARY
233                         { write_exp_elt_opcode (pstate, UNOP_POSTINCREMENT); }
234         ;
235
236 exp     :       exp DECREMENT    %prec UNARY
237                         { write_exp_elt_opcode (pstate, UNOP_POSTDECREMENT); }
238         ;
239
240 /* foo->bar is not in Go.  May want as a gdb extension.  Later.  */
241
242 exp     :       exp '.' name_not_typename
243                         { write_exp_elt_opcode (pstate, STRUCTOP_STRUCT);
244                           write_exp_string (pstate, $3.stoken);
245                           write_exp_elt_opcode (pstate, STRUCTOP_STRUCT); }
246         ;
247
248 exp     :       exp '.' name_not_typename COMPLETE
249                         { mark_struct_expression (pstate);
250                           write_exp_elt_opcode (pstate, STRUCTOP_STRUCT);
251                           write_exp_string (pstate, $3.stoken);
252                           write_exp_elt_opcode (pstate, STRUCTOP_STRUCT); }
253         ;
254
255 exp     :       exp '.' COMPLETE
256                         { struct stoken s;
257                           mark_struct_expression (pstate);
258                           write_exp_elt_opcode (pstate, STRUCTOP_STRUCT);
259                           s.ptr = "";
260                           s.length = 0;
261                           write_exp_string (pstate, s);
262                           write_exp_elt_opcode (pstate, STRUCTOP_STRUCT); }
263         ;
264
265 exp     :       exp '[' exp1 ']'
266                         { write_exp_elt_opcode (pstate, BINOP_SUBSCRIPT); }
267         ;
268
269 exp     :       exp '('
270                         /* This is to save the value of arglist_len
271                            being accumulated by an outer function call.  */
272                         { start_arglist (); }
273                 arglist ')'     %prec LEFT_ARROW
274                         { write_exp_elt_opcode (pstate, OP_FUNCALL);
275                           write_exp_elt_longcst (pstate,
276                                                  (LONGEST) end_arglist ());
277                           write_exp_elt_opcode (pstate, OP_FUNCALL); }
278         ;
279
280 lcurly  :       '{'
281                         { start_arglist (); }
282         ;
283
284 arglist :
285         ;
286
287 arglist :       exp
288                         { arglist_len = 1; }
289         ;
290
291 arglist :       arglist ',' exp   %prec ABOVE_COMMA
292                         { arglist_len++; }
293         ;
294
295 rcurly  :       '}'
296                         { $$ = end_arglist () - 1; }
297         ;
298
299 exp     :       lcurly type rcurly exp  %prec UNARY
300                         { write_exp_elt_opcode (pstate, UNOP_MEMVAL);
301                           write_exp_elt_type (pstate, $2);
302                           write_exp_elt_opcode (pstate, UNOP_MEMVAL); }
303         ;
304
305 exp     :       type '(' exp ')'  %prec UNARY
306                         { write_exp_elt_opcode (pstate, UNOP_CAST);
307                           write_exp_elt_type (pstate, $1);
308                           write_exp_elt_opcode (pstate, UNOP_CAST); }
309         ;
310
311 exp     :       '(' exp1 ')'
312                         { }
313         ;
314
315 /* Binary operators in order of decreasing precedence.  */
316
317 exp     :       exp '@' exp
318                         { write_exp_elt_opcode (pstate, BINOP_REPEAT); }
319         ;
320
321 exp     :       exp '*' exp
322                         { write_exp_elt_opcode (pstate, BINOP_MUL); }
323         ;
324
325 exp     :       exp '/' exp
326                         { write_exp_elt_opcode (pstate, BINOP_DIV); }
327         ;
328
329 exp     :       exp '%' exp
330                         { write_exp_elt_opcode (pstate, BINOP_REM); }
331         ;
332
333 exp     :       exp '+' exp
334                         { write_exp_elt_opcode (pstate, BINOP_ADD); }
335         ;
336
337 exp     :       exp '-' exp
338                         { write_exp_elt_opcode (pstate, BINOP_SUB); }
339         ;
340
341 exp     :       exp LSH exp
342                         { write_exp_elt_opcode (pstate, BINOP_LSH); }
343         ;
344
345 exp     :       exp RSH exp
346                         { write_exp_elt_opcode (pstate, BINOP_RSH); }
347         ;
348
349 exp     :       exp EQUAL exp
350                         { write_exp_elt_opcode (pstate, BINOP_EQUAL); }
351         ;
352
353 exp     :       exp NOTEQUAL exp
354                         { write_exp_elt_opcode (pstate, BINOP_NOTEQUAL); }
355         ;
356
357 exp     :       exp LEQ exp
358                         { write_exp_elt_opcode (pstate, BINOP_LEQ); }
359         ;
360
361 exp     :       exp GEQ exp
362                         { write_exp_elt_opcode (pstate, BINOP_GEQ); }
363         ;
364
365 exp     :       exp '<' exp
366                         { write_exp_elt_opcode (pstate, BINOP_LESS); }
367         ;
368
369 exp     :       exp '>' exp
370                         { write_exp_elt_opcode (pstate, BINOP_GTR); }
371         ;
372
373 exp     :       exp '&' exp
374                         { write_exp_elt_opcode (pstate, BINOP_BITWISE_AND); }
375         ;
376
377 exp     :       exp '^' exp
378                         { write_exp_elt_opcode (pstate, BINOP_BITWISE_XOR); }
379         ;
380
381 exp     :       exp '|' exp
382                         { write_exp_elt_opcode (pstate, BINOP_BITWISE_IOR); }
383         ;
384
385 exp     :       exp ANDAND exp
386                         { write_exp_elt_opcode (pstate, BINOP_LOGICAL_AND); }
387         ;
388
389 exp     :       exp OROR exp
390                         { write_exp_elt_opcode (pstate, BINOP_LOGICAL_OR); }
391         ;
392
393 exp     :       exp '?' exp ':' exp     %prec '?'
394                         { write_exp_elt_opcode (pstate, TERNOP_COND); }
395         ;
396
397 exp     :       exp '=' exp
398                         { write_exp_elt_opcode (pstate, BINOP_ASSIGN); }
399         ;
400
401 exp     :       exp ASSIGN_MODIFY exp
402                         { write_exp_elt_opcode (pstate, BINOP_ASSIGN_MODIFY);
403                           write_exp_elt_opcode (pstate, $2);
404                           write_exp_elt_opcode (pstate, BINOP_ASSIGN_MODIFY); }
405         ;
406
407 exp     :       INT
408                         { write_exp_elt_opcode (pstate, OP_LONG);
409                           write_exp_elt_type (pstate, $1.type);
410                           write_exp_elt_longcst (pstate, (LONGEST)($1.val));
411                           write_exp_elt_opcode (pstate, OP_LONG); }
412         ;
413
414 exp     :       CHAR
415                         {
416                           struct stoken_vector vec;
417                           vec.len = 1;
418                           vec.tokens = &$1;
419                           write_exp_string_vector (pstate, $1.type, &vec);
420                         }
421         ;
422
423 exp     :       NAME_OR_INT
424                         { YYSTYPE val;
425                           parse_number (pstate, $1.stoken.ptr,
426                                         $1.stoken.length, 0, &val);
427                           write_exp_elt_opcode (pstate, OP_LONG);
428                           write_exp_elt_type (pstate, val.typed_val_int.type);
429                           write_exp_elt_longcst (pstate, (LONGEST)
430                                                  val.typed_val_int.val);
431                           write_exp_elt_opcode (pstate, OP_LONG);
432                         }
433         ;
434
435
436 exp     :       FLOAT
437                         { write_exp_elt_opcode (pstate, OP_FLOAT);
438                           write_exp_elt_type (pstate, $1.type);
439                           write_exp_elt_floatcst (pstate, $1.val);
440                           write_exp_elt_opcode (pstate, OP_FLOAT); }
441         ;
442
443 exp     :       variable
444         ;
445
446 exp     :       DOLLAR_VARIABLE
447                         {
448                           write_dollar_variable (pstate, $1);
449                         }
450         ;
451
452 exp     :       SIZEOF_KEYWORD '(' type ')'  %prec UNARY
453                         {
454                           /* TODO(dje): Go objects in structs.  */
455                           write_exp_elt_opcode (pstate, OP_LONG);
456                           /* TODO(dje): What's the right type here?  */
457                           write_exp_elt_type
458                             (pstate,
459                              parse_type (pstate)->builtin_unsigned_int);
460                           $3 = check_typedef ($3);
461                           write_exp_elt_longcst (pstate,
462                                                  (LONGEST) TYPE_LENGTH ($3));
463                           write_exp_elt_opcode (pstate, OP_LONG);
464                         }
465         ;
466
467 exp     :       SIZEOF_KEYWORD  '(' exp ')'  %prec UNARY
468                         {
469                           /* TODO(dje): Go objects in structs.  */
470                           write_exp_elt_opcode (pstate, UNOP_SIZEOF);
471                         }
472
473 string_exp:
474                 STRING
475                         {
476                           /* We copy the string here, and not in the
477                              lexer, to guarantee that we do not leak a
478                              string.  */
479                           /* Note that we NUL-terminate here, but just
480                              for convenience.  */
481                           struct typed_stoken *vec = XNEW (struct typed_stoken);
482                           $$.len = 1;
483                           $$.tokens = vec;
484
485                           vec->type = $1.type;
486                           vec->length = $1.length;
487                           vec->ptr = (char *) malloc ($1.length + 1);
488                           memcpy (vec->ptr, $1.ptr, $1.length + 1);
489                         }
490
491         |       string_exp '+' STRING
492                         {
493                           /* Note that we NUL-terminate here, but just
494                              for convenience.  */
495                           char *p;
496                           ++$$.len;
497                           $$.tokens = XRESIZEVEC (struct typed_stoken,
498                                                   $$.tokens, $$.len);
499
500                           p = (char *) malloc ($3.length + 1);
501                           memcpy (p, $3.ptr, $3.length + 1);
502
503                           $$.tokens[$$.len - 1].type = $3.type;
504                           $$.tokens[$$.len - 1].length = $3.length;
505                           $$.tokens[$$.len - 1].ptr = p;
506                         }
507         ;
508
509 exp     :       string_exp  %prec ABOVE_COMMA
510                         {
511                           int i;
512
513                           write_exp_string_vector (pstate, 0 /*always utf8*/,
514                                                    &$1);
515                           for (i = 0; i < $1.len; ++i)
516                             free ($1.tokens[i].ptr);
517                           free ($1.tokens);
518                         }
519         ;
520
521 exp     :       TRUE_KEYWORD
522                         { write_exp_elt_opcode (pstate, OP_BOOL);
523                           write_exp_elt_longcst (pstate, (LONGEST) $1);
524                           write_exp_elt_opcode (pstate, OP_BOOL); }
525         ;
526
527 exp     :       FALSE_KEYWORD
528                         { write_exp_elt_opcode (pstate, OP_BOOL);
529                           write_exp_elt_longcst (pstate, (LONGEST) $1);
530                           write_exp_elt_opcode (pstate, OP_BOOL); }
531         ;
532
533 variable:       name_not_typename ENTRY
534                         { struct symbol *sym = $1.sym.symbol;
535
536                           if (sym == NULL
537                               || !SYMBOL_IS_ARGUMENT (sym)
538                               || !symbol_read_needs_frame (sym))
539                             error (_("@entry can be used only for function "
540                                      "parameters, not for \"%s\""),
541                                    copy_name ($1.stoken));
542
543                           write_exp_elt_opcode (pstate, OP_VAR_ENTRY_VALUE);
544                           write_exp_elt_sym (pstate, sym);
545                           write_exp_elt_opcode (pstate, OP_VAR_ENTRY_VALUE);
546                         }
547         ;
548
549 variable:       name_not_typename
550                         { struct block_symbol sym = $1.sym;
551
552                           if (sym.symbol)
553                             {
554                               if (symbol_read_needs_frame (sym.symbol))
555                                 {
556                                   if (innermost_block == 0
557                                       || contained_in (sym.block,
558                                                        innermost_block))
559                                     innermost_block = sym.block;
560                                 }
561
562                               write_exp_elt_opcode (pstate, OP_VAR_VALUE);
563                               write_exp_elt_block (pstate, sym.block);
564                               write_exp_elt_sym (pstate, sym.symbol);
565                               write_exp_elt_opcode (pstate, OP_VAR_VALUE);
566                             }
567                           else if ($1.is_a_field_of_this)
568                             {
569                               /* TODO(dje): Can we get here?
570                                  E.g., via a mix of c++ and go?  */
571                               gdb_assert_not_reached ("go with `this' field");
572                             }
573                           else
574                             {
575                               struct bound_minimal_symbol msymbol;
576                               char *arg = copy_name ($1.stoken);
577
578                               msymbol =
579                                 lookup_bound_minimal_symbol (arg);
580                               if (msymbol.minsym != NULL)
581                                 write_exp_msymbol (pstate, msymbol);
582                               else if (!have_full_symbols ()
583                                        && !have_partial_symbols ())
584                                 error (_("No symbol table is loaded.  "
585                                        "Use the \"file\" command."));
586                               else
587                                 error (_("No symbol \"%s\" in current context."),
588                                        copy_name ($1.stoken));
589                             }
590                         }
591         ;
592
593 /* TODO
594 method_exp: PACKAGENAME '.' name '.' name
595                         {
596                         }
597         ;
598 */
599
600 type  /* Implements (approximately): [*] type-specifier */
601         :       '*' type
602                         { $$ = lookup_pointer_type ($2); }
603         |       TYPENAME
604                         { $$ = $1.type; }
605 /*
606         |       STRUCT_KEYWORD name
607                         { $$ = lookup_struct (copy_name ($2),
608                                               expression_context_block); }
609 */
610         |       BYTE_KEYWORD
611                         { $$ = builtin_go_type (parse_gdbarch (pstate))
612                             ->builtin_uint8; }
613         ;
614
615 /* TODO
616 name    :       NAME { $$ = $1.stoken; }
617         |       TYPENAME { $$ = $1.stoken; }
618         |       NAME_OR_INT  { $$ = $1.stoken; }
619         ;
620 */
621
622 name_not_typename
623         :       NAME
624 /* These would be useful if name_not_typename was useful, but it is just
625    a fake for "variable", so these cause reduce/reduce conflicts because
626    the parser can't tell whether NAME_OR_INT is a name_not_typename (=variable,
627    =exp) or just an exp.  If name_not_typename was ever used in an lvalue
628    context where only a name could occur, this might be useful.
629         |       NAME_OR_INT
630 */
631         ;
632
633 %%
634
635 /* Take care of parsing a number (anything that starts with a digit).
636    Set yylval and return the token type; update lexptr.
637    LEN is the number of characters in it.  */
638
639 /* FIXME: Needs some error checking for the float case.  */
640 /* FIXME(dje): IWBN to use c-exp.y's parse_number if we could.
641    That will require moving the guts into a function that we both call
642    as our YYSTYPE is different than c-exp.y's  */
643
644 static int
645 parse_number (struct parser_state *par_state,
646               const char *p, int len, int parsed_float, YYSTYPE *putithere)
647 {
648   /* FIXME: Shouldn't these be unsigned?  We don't deal with negative values
649      here, and we do kind of silly things like cast to unsigned.  */
650   LONGEST n = 0;
651   LONGEST prevn = 0;
652   ULONGEST un;
653
654   int i = 0;
655   int c;
656   int base = input_radix;
657   int unsigned_p = 0;
658
659   /* Number of "L" suffixes encountered.  */
660   int long_p = 0;
661
662   /* We have found a "L" or "U" suffix.  */
663   int found_suffix = 0;
664
665   ULONGEST high_bit;
666   struct type *signed_type;
667   struct type *unsigned_type;
668
669   if (parsed_float)
670     {
671       const struct builtin_go_type *builtin_go_types
672         = builtin_go_type (parse_gdbarch (par_state));
673
674       /* Handle suffixes: 'f' for float32, 'l' for long double.
675          FIXME: This appears to be an extension -- do we want this?  */
676       if (len >= 1 && tolower (p[len - 1]) == 'f')
677         {
678           putithere->typed_val_float.type
679             = builtin_go_types->builtin_float32;
680           len--;
681         }
682       else if (len >= 1 && tolower (p[len - 1]) == 'l')
683         {
684           putithere->typed_val_float.type
685             = parse_type (par_state)->builtin_long_double;
686           len--;
687         }
688       /* Default type for floating-point literals is float64.  */
689       else
690         {
691           putithere->typed_val_float.type
692             = builtin_go_types->builtin_float64;
693         }
694
695       if (!parse_float (p, len,
696                         putithere->typed_val_float.type,
697                         putithere->typed_val_float.val))
698         return ERROR;
699       return FLOAT;
700     }
701
702   /* Handle base-switching prefixes 0x, 0t, 0d, 0.  */
703   if (p[0] == '0')
704     switch (p[1])
705       {
706       case 'x':
707       case 'X':
708         if (len >= 3)
709           {
710             p += 2;
711             base = 16;
712             len -= 2;
713           }
714         break;
715
716       case 'b':
717       case 'B':
718         if (len >= 3)
719           {
720             p += 2;
721             base = 2;
722             len -= 2;
723           }
724         break;
725
726       case 't':
727       case 'T':
728       case 'd':
729       case 'D':
730         if (len >= 3)
731           {
732             p += 2;
733             base = 10;
734             len -= 2;
735           }
736         break;
737
738       default:
739         base = 8;
740         break;
741       }
742
743   while (len-- > 0)
744     {
745       c = *p++;
746       if (c >= 'A' && c <= 'Z')
747         c += 'a' - 'A';
748       if (c != 'l' && c != 'u')
749         n *= base;
750       if (c >= '0' && c <= '9')
751         {
752           if (found_suffix)
753             return ERROR;
754           n += i = c - '0';
755         }
756       else
757         {
758           if (base > 10 && c >= 'a' && c <= 'f')
759             {
760               if (found_suffix)
761                 return ERROR;
762               n += i = c - 'a' + 10;
763             }
764           else if (c == 'l')
765             {
766               ++long_p;
767               found_suffix = 1;
768             }
769           else if (c == 'u')
770             {
771               unsigned_p = 1;
772               found_suffix = 1;
773             }
774           else
775             return ERROR;       /* Char not a digit */
776         }
777       if (i >= base)
778         return ERROR;           /* Invalid digit in this base.  */
779
780       /* Portably test for overflow (only works for nonzero values, so make
781          a second check for zero).  FIXME: Can't we just make n and prevn
782          unsigned and avoid this?  */
783       if (c != 'l' && c != 'u' && (prevn >= n) && n != 0)
784         unsigned_p = 1;         /* Try something unsigned.  */
785
786       /* Portably test for unsigned overflow.
787          FIXME: This check is wrong; for example it doesn't find overflow
788          on 0x123456789 when LONGEST is 32 bits.  */
789       if (c != 'l' && c != 'u' && n != 0)
790         {
791           if ((unsigned_p && (ULONGEST) prevn >= (ULONGEST) n))
792             error (_("Numeric constant too large."));
793         }
794       prevn = n;
795     }
796
797   /* An integer constant is an int, a long, or a long long.  An L
798      suffix forces it to be long; an LL suffix forces it to be long
799      long.  If not forced to a larger size, it gets the first type of
800      the above that it fits in.  To figure out whether it fits, we
801      shift it right and see whether anything remains.  Note that we
802      can't shift sizeof (LONGEST) * HOST_CHAR_BIT bits or more in one
803      operation, because many compilers will warn about such a shift
804      (which always produces a zero result).  Sometimes gdbarch_int_bit
805      or gdbarch_long_bit will be that big, sometimes not.  To deal with
806      the case where it is we just always shift the value more than
807      once, with fewer bits each time.  */
808
809   un = (ULONGEST)n >> 2;
810   if (long_p == 0
811       && (un >> (gdbarch_int_bit (parse_gdbarch (par_state)) - 2)) == 0)
812     {
813       high_bit
814         = ((ULONGEST)1) << (gdbarch_int_bit (parse_gdbarch (par_state)) - 1);
815
816       /* A large decimal (not hex or octal) constant (between INT_MAX
817          and UINT_MAX) is a long or unsigned long, according to ANSI,
818          never an unsigned int, but this code treats it as unsigned
819          int.  This probably should be fixed.  GCC gives a warning on
820          such constants.  */
821
822       unsigned_type = parse_type (par_state)->builtin_unsigned_int;
823       signed_type = parse_type (par_state)->builtin_int;
824     }
825   else if (long_p <= 1
826            && (un >> (gdbarch_long_bit (parse_gdbarch (par_state)) - 2)) == 0)
827     {
828       high_bit
829         = ((ULONGEST)1) << (gdbarch_long_bit (parse_gdbarch (par_state)) - 1);
830       unsigned_type = parse_type (par_state)->builtin_unsigned_long;
831       signed_type = parse_type (par_state)->builtin_long;
832     }
833   else
834     {
835       int shift;
836       if (sizeof (ULONGEST) * HOST_CHAR_BIT
837           < gdbarch_long_long_bit (parse_gdbarch (par_state)))
838         /* A long long does not fit in a LONGEST.  */
839         shift = (sizeof (ULONGEST) * HOST_CHAR_BIT - 1);
840       else
841         shift = (gdbarch_long_long_bit (parse_gdbarch (par_state)) - 1);
842       high_bit = (ULONGEST) 1 << shift;
843       unsigned_type = parse_type (par_state)->builtin_unsigned_long_long;
844       signed_type = parse_type (par_state)->builtin_long_long;
845     }
846
847    putithere->typed_val_int.val = n;
848
849    /* If the high bit of the worked out type is set then this number
850       has to be unsigned.  */
851
852    if (unsigned_p || (n & high_bit))
853      {
854        putithere->typed_val_int.type = unsigned_type;
855      }
856    else
857      {
858        putithere->typed_val_int.type = signed_type;
859      }
860
861    return INT;
862 }
863
864 /* Temporary obstack used for holding strings.  */
865 static struct obstack tempbuf;
866 static int tempbuf_init;
867
868 /* Parse a string or character literal from TOKPTR.  The string or
869    character may be wide or unicode.  *OUTPTR is set to just after the
870    end of the literal in the input string.  The resulting token is
871    stored in VALUE.  This returns a token value, either STRING or
872    CHAR, depending on what was parsed.  *HOST_CHARS is set to the
873    number of host characters in the literal.  */
874
875 static int
876 parse_string_or_char (const char *tokptr, const char **outptr,
877                       struct typed_stoken *value, int *host_chars)
878 {
879   int quote;
880
881   /* Build the gdb internal form of the input string in tempbuf.  Note
882      that the buffer is null byte terminated *only* for the
883      convenience of debugging gdb itself and printing the buffer
884      contents when the buffer contains no embedded nulls.  Gdb does
885      not depend upon the buffer being null byte terminated, it uses
886      the length string instead.  This allows gdb to handle C strings
887      (as well as strings in other languages) with embedded null
888      bytes */
889
890   if (!tempbuf_init)
891     tempbuf_init = 1;
892   else
893     obstack_free (&tempbuf, NULL);
894   obstack_init (&tempbuf);
895
896   /* Skip the quote.  */
897   quote = *tokptr;
898   ++tokptr;
899
900   *host_chars = 0;
901
902   while (*tokptr)
903     {
904       char c = *tokptr;
905       if (c == '\\')
906         {
907           ++tokptr;
908           *host_chars += c_parse_escape (&tokptr, &tempbuf);
909         }
910       else if (c == quote)
911         break;
912       else
913         {
914           obstack_1grow (&tempbuf, c);
915           ++tokptr;
916           /* FIXME: this does the wrong thing with multi-byte host
917              characters.  We could use mbrlen here, but that would
918              make "set host-charset" a bit less useful.  */
919           ++*host_chars;
920         }
921     }
922
923   if (*tokptr != quote)
924     {
925       if (quote == '"')
926         error (_("Unterminated string in expression."));
927       else
928         error (_("Unmatched single quote."));
929     }
930   ++tokptr;
931
932   value->type = C_STRING | (quote == '\'' ? C_CHAR : 0); /*FIXME*/
933   value->ptr = (char *) obstack_base (&tempbuf);
934   value->length = obstack_object_size (&tempbuf);
935
936   *outptr = tokptr;
937
938   return quote == '\'' ? CHAR : STRING;
939 }
940
941 struct token
942 {
943   const char *oper;
944   int token;
945   enum exp_opcode opcode;
946 };
947
948 static const struct token tokentab3[] =
949   {
950     {">>=", ASSIGN_MODIFY, BINOP_RSH},
951     {"<<=", ASSIGN_MODIFY, BINOP_LSH},
952     /*{"&^=", ASSIGN_MODIFY, BINOP_BITWISE_ANDNOT}, TODO */
953     {"...", DOTDOTDOT, OP_NULL},
954   };
955
956 static const struct token tokentab2[] =
957   {
958     {"+=", ASSIGN_MODIFY, BINOP_ADD},
959     {"-=", ASSIGN_MODIFY, BINOP_SUB},
960     {"*=", ASSIGN_MODIFY, BINOP_MUL},
961     {"/=", ASSIGN_MODIFY, BINOP_DIV},
962     {"%=", ASSIGN_MODIFY, BINOP_REM},
963     {"|=", ASSIGN_MODIFY, BINOP_BITWISE_IOR},
964     {"&=", ASSIGN_MODIFY, BINOP_BITWISE_AND},
965     {"^=", ASSIGN_MODIFY, BINOP_BITWISE_XOR},
966     {"++", INCREMENT, BINOP_END},
967     {"--", DECREMENT, BINOP_END},
968     /*{"->", RIGHT_ARROW, BINOP_END}, Doesn't exist in Go.  */
969     {"<-", LEFT_ARROW, BINOP_END},
970     {"&&", ANDAND, BINOP_END},
971     {"||", OROR, BINOP_END},
972     {"<<", LSH, BINOP_END},
973     {">>", RSH, BINOP_END},
974     {"==", EQUAL, BINOP_END},
975     {"!=", NOTEQUAL, BINOP_END},
976     {"<=", LEQ, BINOP_END},
977     {">=", GEQ, BINOP_END},
978     /*{"&^", ANDNOT, BINOP_END}, TODO */
979   };
980
981 /* Identifier-like tokens.  */
982 static const struct token ident_tokens[] =
983   {
984     {"true", TRUE_KEYWORD, OP_NULL},
985     {"false", FALSE_KEYWORD, OP_NULL},
986     {"nil", NIL_KEYWORD, OP_NULL},
987     {"const", CONST_KEYWORD, OP_NULL},
988     {"struct", STRUCT_KEYWORD, OP_NULL},
989     {"type", TYPE_KEYWORD, OP_NULL},
990     {"interface", INTERFACE_KEYWORD, OP_NULL},
991     {"chan", CHAN_KEYWORD, OP_NULL},
992     {"byte", BYTE_KEYWORD, OP_NULL}, /* An alias of uint8.  */
993     {"len", LEN_KEYWORD, OP_NULL},
994     {"cap", CAP_KEYWORD, OP_NULL},
995     {"new", NEW_KEYWORD, OP_NULL},
996     {"iota", IOTA_KEYWORD, OP_NULL},
997   };
998
999 /* This is set if a NAME token appeared at the very end of the input
1000    string, with no whitespace separating the name from the EOF.  This
1001    is used only when parsing to do field name completion.  */
1002 static int saw_name_at_eof;
1003
1004 /* This is set if the previously-returned token was a structure
1005    operator -- either '.' or ARROW.  This is used only when parsing to
1006    do field name completion.  */
1007 static int last_was_structop;
1008
1009 /* Read one token, getting characters through lexptr.  */
1010
1011 static int
1012 lex_one_token (struct parser_state *par_state)
1013 {
1014   int c;
1015   int namelen;
1016   unsigned int i;
1017   const char *tokstart;
1018   int saw_structop = last_was_structop;
1019   char *copy;
1020
1021   last_was_structop = 0;
1022
1023  retry:
1024
1025   prev_lexptr = lexptr;
1026
1027   tokstart = lexptr;
1028   /* See if it is a special token of length 3.  */
1029   for (i = 0; i < sizeof (tokentab3) / sizeof (tokentab3[0]); i++)
1030     if (strncmp (tokstart, tokentab3[i].oper, 3) == 0)
1031       {
1032         lexptr += 3;
1033         yylval.opcode = tokentab3[i].opcode;
1034         return tokentab3[i].token;
1035       }
1036
1037   /* See if it is a special token of length 2.  */
1038   for (i = 0; i < sizeof (tokentab2) / sizeof (tokentab2[0]); i++)
1039     if (strncmp (tokstart, tokentab2[i].oper, 2) == 0)
1040       {
1041         lexptr += 2;
1042         yylval.opcode = tokentab2[i].opcode;
1043         /* NOTE: -> doesn't exist in Go, so we don't need to watch for
1044            setting last_was_structop here.  */
1045         return tokentab2[i].token;
1046       }
1047
1048   switch (c = *tokstart)
1049     {
1050     case 0:
1051       if (saw_name_at_eof)
1052         {
1053           saw_name_at_eof = 0;
1054           return COMPLETE;
1055         }
1056       else if (saw_structop)
1057         return COMPLETE;
1058       else
1059         return 0;
1060
1061     case ' ':
1062     case '\t':
1063     case '\n':
1064       lexptr++;
1065       goto retry;
1066
1067     case '[':
1068     case '(':
1069       paren_depth++;
1070       lexptr++;
1071       return c;
1072
1073     case ']':
1074     case ')':
1075       if (paren_depth == 0)
1076         return 0;
1077       paren_depth--;
1078       lexptr++;
1079       return c;
1080
1081     case ',':
1082       if (comma_terminates
1083           && paren_depth == 0)
1084         return 0;
1085       lexptr++;
1086       return c;
1087
1088     case '.':
1089       /* Might be a floating point number.  */
1090       if (lexptr[1] < '0' || lexptr[1] > '9')
1091         {
1092           if (parse_completion)
1093             last_was_structop = 1;
1094           goto symbol;          /* Nope, must be a symbol. */
1095         }
1096       /* FALL THRU into number case.  */
1097
1098     case '0':
1099     case '1':
1100     case '2':
1101     case '3':
1102     case '4':
1103     case '5':
1104     case '6':
1105     case '7':
1106     case '8':
1107     case '9':
1108       {
1109         /* It's a number.  */
1110         int got_dot = 0, got_e = 0, toktype;
1111         const char *p = tokstart;
1112         int hex = input_radix > 10;
1113
1114         if (c == '0' && (p[1] == 'x' || p[1] == 'X'))
1115           {
1116             p += 2;
1117             hex = 1;
1118           }
1119
1120         for (;; ++p)
1121           {
1122             /* This test includes !hex because 'e' is a valid hex digit
1123                and thus does not indicate a floating point number when
1124                the radix is hex.  */
1125             if (!hex && !got_e && (*p == 'e' || *p == 'E'))
1126               got_dot = got_e = 1;
1127             /* This test does not include !hex, because a '.' always indicates
1128                a decimal floating point number regardless of the radix.  */
1129             else if (!got_dot && *p == '.')
1130               got_dot = 1;
1131             else if (got_e && (p[-1] == 'e' || p[-1] == 'E')
1132                      && (*p == '-' || *p == '+'))
1133               /* This is the sign of the exponent, not the end of the
1134                  number.  */
1135               continue;
1136             /* We will take any letters or digits.  parse_number will
1137                complain if past the radix, or if L or U are not final.  */
1138             else if ((*p < '0' || *p > '9')
1139                      && ((*p < 'a' || *p > 'z')
1140                                   && (*p < 'A' || *p > 'Z')))
1141               break;
1142           }
1143         toktype = parse_number (par_state, tokstart, p - tokstart,
1144                                 got_dot|got_e, &yylval);
1145         if (toktype == ERROR)
1146           {
1147             char *err_copy = (char *) alloca (p - tokstart + 1);
1148
1149             memcpy (err_copy, tokstart, p - tokstart);
1150             err_copy[p - tokstart] = 0;
1151             error (_("Invalid number \"%s\"."), err_copy);
1152           }
1153         lexptr = p;
1154         return toktype;
1155       }
1156
1157     case '@':
1158       {
1159         const char *p = &tokstart[1];
1160         size_t len = strlen ("entry");
1161
1162         while (isspace (*p))
1163           p++;
1164         if (strncmp (p, "entry", len) == 0 && !isalnum (p[len])
1165             && p[len] != '_')
1166           {
1167             lexptr = &p[len];
1168             return ENTRY;
1169           }
1170       }
1171       /* FALLTHRU */
1172     case '+':
1173     case '-':
1174     case '*':
1175     case '/':
1176     case '%':
1177     case '|':
1178     case '&':
1179     case '^':
1180     case '~':
1181     case '!':
1182     case '<':
1183     case '>':
1184     case '?':
1185     case ':':
1186     case '=':
1187     case '{':
1188     case '}':
1189     symbol:
1190       lexptr++;
1191       return c;
1192
1193     case '\'':
1194     case '"':
1195     case '`':
1196       {
1197         int host_len;
1198         int result = parse_string_or_char (tokstart, &lexptr, &yylval.tsval,
1199                                            &host_len);
1200         if (result == CHAR)
1201           {
1202             if (host_len == 0)
1203               error (_("Empty character constant."));
1204             else if (host_len > 2 && c == '\'')
1205               {
1206                 ++tokstart;
1207                 namelen = lexptr - tokstart - 1;
1208                 goto tryname;
1209               }
1210             else if (host_len > 1)
1211               error (_("Invalid character constant."));
1212           }
1213         return result;
1214       }
1215     }
1216
1217   if (!(c == '_' || c == '$'
1218         || (c >= 'a' && c <= 'z') || (c >= 'A' && c <= 'Z')))
1219     /* We must have come across a bad character (e.g. ';').  */
1220     error (_("Invalid character '%c' in expression."), c);
1221
1222   /* It's a name.  See how long it is.  */
1223   namelen = 0;
1224   for (c = tokstart[namelen];
1225        (c == '_' || c == '$' || (c >= '0' && c <= '9')
1226         || (c >= 'a' && c <= 'z') || (c >= 'A' && c <= 'Z'));)
1227     {
1228       c = tokstart[++namelen];
1229     }
1230
1231   /* The token "if" terminates the expression and is NOT removed from
1232      the input stream.  It doesn't count if it appears in the
1233      expansion of a macro.  */
1234   if (namelen == 2
1235       && tokstart[0] == 'i'
1236       && tokstart[1] == 'f')
1237     {
1238       return 0;
1239     }
1240
1241   /* For the same reason (breakpoint conditions), "thread N"
1242      terminates the expression.  "thread" could be an identifier, but
1243      an identifier is never followed by a number without intervening
1244      punctuation.
1245      Handle abbreviations of these, similarly to
1246      breakpoint.c:find_condition_and_thread.
1247      TODO: Watch for "goroutine" here?  */
1248   if (namelen >= 1
1249       && strncmp (tokstart, "thread", namelen) == 0
1250       && (tokstart[namelen] == ' ' || tokstart[namelen] == '\t'))
1251     {
1252       const char *p = tokstart + namelen + 1;
1253
1254       while (*p == ' ' || *p == '\t')
1255         p++;
1256       if (*p >= '0' && *p <= '9')
1257         return 0;
1258     }
1259
1260   lexptr += namelen;
1261
1262   tryname:
1263
1264   yylval.sval.ptr = tokstart;
1265   yylval.sval.length = namelen;
1266
1267   /* Catch specific keywords.  */
1268   copy = copy_name (yylval.sval);
1269   for (i = 0; i < sizeof (ident_tokens) / sizeof (ident_tokens[0]); i++)
1270     if (strcmp (copy, ident_tokens[i].oper) == 0)
1271       {
1272         /* It is ok to always set this, even though we don't always
1273            strictly need to.  */
1274         yylval.opcode = ident_tokens[i].opcode;
1275         return ident_tokens[i].token;
1276       }
1277
1278   if (*tokstart == '$')
1279     return DOLLAR_VARIABLE;
1280
1281   if (parse_completion && *lexptr == '\0')
1282     saw_name_at_eof = 1;
1283   return NAME;
1284 }
1285
1286 /* An object of this type is pushed on a FIFO by the "outer" lexer.  */
1287 typedef struct
1288 {
1289   int token;
1290   YYSTYPE value;
1291 } token_and_value;
1292
1293 DEF_VEC_O (token_and_value);
1294
1295 /* A FIFO of tokens that have been read but not yet returned to the
1296    parser.  */
1297 static VEC (token_and_value) *token_fifo;
1298
1299 /* Non-zero if the lexer should return tokens from the FIFO.  */
1300 static int popping;
1301
1302 /* Temporary storage for yylex; this holds symbol names as they are
1303    built up.  */
1304 static auto_obstack name_obstack;
1305
1306 /* Build "package.name" in name_obstack.
1307    For convenience of the caller, the name is NUL-terminated,
1308    but the NUL is not included in the recorded length.  */
1309
1310 static struct stoken
1311 build_packaged_name (const char *package, int package_len,
1312                      const char *name, int name_len)
1313 {
1314   struct stoken result;
1315
1316   name_obstack.clear ();
1317   obstack_grow (&name_obstack, package, package_len);
1318   obstack_grow_str (&name_obstack, ".");
1319   obstack_grow (&name_obstack, name, name_len);
1320   obstack_grow (&name_obstack, "", 1);
1321   result.ptr = (char *) obstack_base (&name_obstack);
1322   result.length = obstack_object_size (&name_obstack) - 1;
1323
1324   return result;
1325 }
1326
1327 /* Return non-zero if NAME is a package name.
1328    BLOCK is the scope in which to interpret NAME; this can be NULL
1329    to mean the global scope.  */
1330
1331 static int
1332 package_name_p (const char *name, const struct block *block)
1333 {
1334   struct symbol *sym;
1335   struct field_of_this_result is_a_field_of_this;
1336
1337   sym = lookup_symbol (name, block, STRUCT_DOMAIN, &is_a_field_of_this).symbol;
1338
1339   if (sym
1340       && SYMBOL_CLASS (sym) == LOC_TYPEDEF
1341       && TYPE_CODE (SYMBOL_TYPE (sym)) == TYPE_CODE_MODULE)
1342     return 1;
1343
1344   return 0;
1345 }
1346
1347 /* Classify a (potential) function in the "unsafe" package.
1348    We fold these into "keywords" to keep things simple, at least until
1349    something more complex is warranted.  */
1350
1351 static int
1352 classify_unsafe_function (struct stoken function_name)
1353 {
1354   char *copy = copy_name (function_name);
1355
1356   if (strcmp (copy, "Sizeof") == 0)
1357     {
1358       yylval.sval = function_name;
1359       return SIZEOF_KEYWORD;
1360     }
1361
1362   error (_("Unknown function in `unsafe' package: %s"), copy);
1363 }
1364
1365 /* Classify token(s) "name1.name2" where name1 is known to be a package.
1366    The contents of the token are in `yylval'.
1367    Updates yylval and returns the new token type.
1368
1369    The result is one of NAME, NAME_OR_INT, or TYPENAME.  */
1370
1371 static int
1372 classify_packaged_name (const struct block *block)
1373 {
1374   char *copy;
1375   struct block_symbol sym;
1376   struct field_of_this_result is_a_field_of_this;
1377
1378   copy = copy_name (yylval.sval);
1379
1380   sym = lookup_symbol (copy, block, VAR_DOMAIN, &is_a_field_of_this);
1381
1382   if (sym.symbol)
1383     {
1384       yylval.ssym.sym = sym;
1385       yylval.ssym.is_a_field_of_this = is_a_field_of_this.type != NULL;
1386     }
1387
1388   return NAME;
1389 }
1390
1391 /* Classify a NAME token.
1392    The contents of the token are in `yylval'.
1393    Updates yylval and returns the new token type.
1394    BLOCK is the block in which lookups start; this can be NULL
1395    to mean the global scope.
1396
1397    The result is one of NAME, NAME_OR_INT, or TYPENAME.  */
1398
1399 static int
1400 classify_name (struct parser_state *par_state, const struct block *block)
1401 {
1402   struct type *type;
1403   struct block_symbol sym;
1404   char *copy;
1405   struct field_of_this_result is_a_field_of_this;
1406
1407   copy = copy_name (yylval.sval);
1408
1409   /* Try primitive types first so they win over bad/weird debug info.  */
1410   type = language_lookup_primitive_type (parse_language (par_state),
1411                                          parse_gdbarch (par_state),
1412                                          copy);
1413   if (type != NULL)
1414     {
1415       /* NOTE: We take advantage of the fact that yylval coming in was a
1416          NAME, and that struct ttype is a compatible extension of struct
1417          stoken, so yylval.tsym.stoken is already filled in.  */
1418       yylval.tsym.type = type;
1419       return TYPENAME;
1420     }
1421
1422   /* TODO: What about other types?  */
1423
1424   sym = lookup_symbol (copy, block, VAR_DOMAIN, &is_a_field_of_this);
1425
1426   if (sym.symbol)
1427     {
1428       yylval.ssym.sym = sym;
1429       yylval.ssym.is_a_field_of_this = is_a_field_of_this.type != NULL;
1430       return NAME;
1431     }
1432
1433   /* If we didn't find a symbol, look again in the current package.
1434      This is to, e.g., make "p global_var" work without having to specify
1435      the package name.  We intentionally only looks for objects in the
1436      current package.  */
1437
1438   {
1439     char *current_package_name = go_block_package_name (block);
1440
1441     if (current_package_name != NULL)
1442       {
1443         struct stoken sval =
1444           build_packaged_name (current_package_name,
1445                                strlen (current_package_name),
1446                                copy, strlen (copy));
1447
1448         xfree (current_package_name);
1449         sym = lookup_symbol (sval.ptr, block, VAR_DOMAIN,
1450                              &is_a_field_of_this);
1451         if (sym.symbol)
1452           {
1453             yylval.ssym.stoken = sval;
1454             yylval.ssym.sym = sym;
1455             yylval.ssym.is_a_field_of_this = is_a_field_of_this.type != NULL;
1456             return NAME;
1457           }
1458       }
1459   }
1460
1461   /* Input names that aren't symbols but ARE valid hex numbers, when
1462      the input radix permits them, can be names or numbers depending
1463      on the parse.  Note we support radixes > 16 here.  */
1464   if ((copy[0] >= 'a' && copy[0] < 'a' + input_radix - 10)
1465       || (copy[0] >= 'A' && copy[0] < 'A' + input_radix - 10))
1466     {
1467       YYSTYPE newlval;  /* Its value is ignored.  */
1468       int hextype = parse_number (par_state, copy, yylval.sval.length,
1469                                   0, &newlval);
1470       if (hextype == INT)
1471         {
1472           yylval.ssym.sym.symbol = NULL;
1473           yylval.ssym.sym.block = NULL;
1474           yylval.ssym.is_a_field_of_this = 0;
1475           return NAME_OR_INT;
1476         }
1477     }
1478
1479   yylval.ssym.sym.symbol = NULL;
1480   yylval.ssym.sym.block = NULL;
1481   yylval.ssym.is_a_field_of_this = 0;
1482   return NAME;
1483 }
1484
1485 /* This is taken from c-exp.y mostly to get something working.
1486    The basic structure has been kept because we may yet need some of it.  */
1487
1488 static int
1489 yylex (void)
1490 {
1491   token_and_value current, next;
1492
1493   if (popping && !VEC_empty (token_and_value, token_fifo))
1494     {
1495       token_and_value tv = *VEC_index (token_and_value, token_fifo, 0);
1496       VEC_ordered_remove (token_and_value, token_fifo, 0);
1497       yylval = tv.value;
1498       /* There's no need to fall through to handle package.name
1499          as that can never happen here.  In theory.  */
1500       return tv.token;
1501     }
1502   popping = 0;
1503
1504   current.token = lex_one_token (pstate);
1505
1506   /* TODO: Need a way to force specifying name1 as a package.
1507      .name1.name2 ?  */
1508
1509   if (current.token != NAME)
1510     return current.token;
1511
1512   /* See if we have "name1 . name2".  */
1513
1514   current.value = yylval;
1515   next.token = lex_one_token (pstate);
1516   next.value = yylval;
1517
1518   if (next.token == '.')
1519     {
1520       token_and_value name2;
1521
1522       name2.token = lex_one_token (pstate);
1523       name2.value = yylval;
1524
1525       if (name2.token == NAME)
1526         {
1527           /* Ok, we have "name1 . name2".  */
1528           char *copy;
1529
1530           copy = copy_name (current.value.sval);
1531
1532           if (strcmp (copy, "unsafe") == 0)
1533             {
1534               popping = 1;
1535               return classify_unsafe_function (name2.value.sval);
1536             }
1537
1538           if (package_name_p (copy, expression_context_block))
1539             {
1540               popping = 1;
1541               yylval.sval = build_packaged_name (current.value.sval.ptr,
1542                                                  current.value.sval.length,
1543                                                  name2.value.sval.ptr,
1544                                                  name2.value.sval.length);
1545               return classify_packaged_name (expression_context_block);
1546             }
1547         }
1548
1549       VEC_safe_push (token_and_value, token_fifo, &next);
1550       VEC_safe_push (token_and_value, token_fifo, &name2);
1551     }
1552   else
1553     {
1554       VEC_safe_push (token_and_value, token_fifo, &next);
1555     }
1556
1557   /* If we arrive here we don't have a package-qualified name.  */
1558
1559   popping = 1;
1560   yylval = current.value;
1561   return classify_name (pstate, expression_context_block);
1562 }
1563
1564 int
1565 go_parse (struct parser_state *par_state)
1566 {
1567   /* Setting up the parser state.  */
1568   scoped_restore pstate_restore = make_scoped_restore (&pstate);
1569   gdb_assert (par_state != NULL);
1570   pstate = par_state;
1571
1572   scoped_restore restore_yydebug = make_scoped_restore (&yydebug,
1573                                                         parser_debug);
1574
1575   /* Initialize some state used by the lexer.  */
1576   last_was_structop = 0;
1577   saw_name_at_eof = 0;
1578
1579   VEC_free (token_and_value, token_fifo);
1580   popping = 0;
1581   name_obstack.clear ();
1582
1583   return yyparse ();
1584 }
1585
1586 void
1587 yyerror (const char *msg)
1588 {
1589   if (prev_lexptr)
1590     lexptr = prev_lexptr;
1591
1592   error (_("A %s in expression, near `%s'."), (msg ? msg : "error"), lexptr);
1593 }