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