1 /* YACC parser for Go expressions, for GDB.
3 Copyright (C) 2012-2014 Free Software Foundation, Inc.
5 This file is part of GDB.
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.
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.
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/>. */
20 /* This file is derived from c-exp.y, p-exp.y. */
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.
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. */
39 /* Known bugs or limitations:
43 - '_' (blank identifier)
44 - automatic deref of pointers
46 - interfaces, channels, etc.
48 And lots of other things.
49 I'm sure there's some cleanup to do.
56 #include "expression.h"
58 #include "parser-defs.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 */
68 #define parse_type(ps) builtin_type (parse_gdbarch (ps))
70 /* Remap normal yacc parser interface names (yyparse, yylex, yyerror, etc),
71 as well as gratuitiously global symbol names, so we can have multiple
72 yacc generated parsers in gdb. Note that these are only the variables
73 produced by yacc. If other parser generators (bison, byacc, etc) produce
74 additional global names that conflict at link time, then those parser
75 generators need to be fixed instead of adding those names to this list. */
77 #define yymaxdepth go_maxdepth
78 #define yyparse go_parse_internal
80 #define yyerror go_error
81 #define yylval go_lval
82 #define yychar go_char
83 #define yydebug go_debug
84 #define yypact go_pact
91 #define yyexca go_exca
92 #define yyerrflag go_errflag
93 #define yynerrs go_nerrs
98 #define yystate go_state
101 #define yy_yyv go_yyv
103 #define yylloc go_lloc
104 #define yyreds go_reds /* With YYDEBUG defined */
105 #define yytoks go_toks /* With YYDEBUG defined */
106 #define yyname go_name /* With YYDEBUG defined */
107 #define yyrule go_rule /* With YYDEBUG defined */
108 #define yylhs go_yylhs
109 #define yylen go_yylen
110 #define yydefred go_yydefred
111 #define yydgoto go_yydgoto
112 #define yysindex go_yysindex
113 #define yyrindex go_yyrindex
114 #define yygindex go_yygindex
115 #define yytable go_yytable
116 #define yycheck go_yycheck
119 #define YYDEBUG 1 /* Default to yydebug support */
122 #define YYFPRINTF parser_fprintf
124 /* The state of the parser, used internally when we are parsing the
127 static struct parser_state *pstate = NULL;
131 static int yylex (void);
133 void yyerror (char *);
137 /* Although the yacc "value" of an expression is not used,
138 since the result is stored in the structure being created,
139 other node types do have values. */
153 struct symtoken ssym;
155 struct typed_stoken tsval;
158 enum exp_opcode opcode;
159 struct internalvar *ivar;
160 struct stoken_vector svec;
164 /* YYSTYPE gets defined by %union. */
165 static int parse_number (struct parser_state *,
166 const char *, int, int, YYSTYPE *);
167 static int parse_go_float (struct gdbarch *gdbarch, const char *p, int len,
168 DOUBLEST *d, struct type **t);
171 %type <voidval> exp exp1 type_exp start variable lcurly
175 %token <typed_val_int> INT
176 %token <typed_val_float> FLOAT
178 /* Both NAME and TYPENAME tokens represent symbols in the input,
179 and both convey their data as strings.
180 But a TYPENAME is a string that happens to be defined as a type
181 or builtin type name (such as int or char)
182 and a NAME is any other symbol.
183 Contexts where this distinction is not important can use the
184 nonterminal "name", which matches either NAME or TYPENAME. */
186 %token <tsval> RAW_STRING
187 %token <tsval> STRING
190 %token <tsym> TYPENAME /* Not TYPE_NAME cus already taken. */
191 %token <voidval> COMPLETE
192 /*%type <sval> name*/
193 %type <svec> string_exp
194 %type <ssym> name_not_typename
196 /* A NAME_OR_INT is a symbol which is not known in the symbol table,
197 but which would parse as a valid number in the current input radix.
198 E.g. "c" when input_radix==16. Depending on the parse, it will be
199 turned into a name or into a number. */
200 %token <ssym> NAME_OR_INT
202 %token <lval> TRUE_KEYWORD FALSE_KEYWORD
203 %token STRUCT_KEYWORD INTERFACE_KEYWORD TYPE_KEYWORD CHAN_KEYWORD
204 %token SIZEOF_KEYWORD
205 %token LEN_KEYWORD CAP_KEYWORD
207 %token IOTA_KEYWORD NIL_KEYWORD
213 /* Special type cases. */
214 %token BYTE_KEYWORD /* An alias of uint8. */
216 %token <sval> DOLLAR_VARIABLE
218 %token <opcode> ASSIGN_MODIFY
222 %right '=' ASSIGN_MODIFY
231 %left '<' '>' LEQ GEQ
236 %right UNARY INCREMENT DECREMENT
237 %right LEFT_ARROW '.' '[' '('
247 { write_exp_elt_opcode (pstate, OP_TYPE);
248 write_exp_elt_type (pstate, $1);
249 write_exp_elt_opcode (pstate, OP_TYPE); }
252 /* Expressions, including the comma operator. */
255 { write_exp_elt_opcode (pstate, BINOP_COMMA); }
258 /* Expressions, not including the comma operator. */
259 exp : '*' exp %prec UNARY
260 { write_exp_elt_opcode (pstate, UNOP_IND); }
263 exp : '&' exp %prec UNARY
264 { write_exp_elt_opcode (pstate, UNOP_ADDR); }
267 exp : '-' exp %prec UNARY
268 { write_exp_elt_opcode (pstate, UNOP_NEG); }
271 exp : '+' exp %prec UNARY
272 { write_exp_elt_opcode (pstate, UNOP_PLUS); }
275 exp : '!' exp %prec UNARY
276 { write_exp_elt_opcode (pstate, UNOP_LOGICAL_NOT); }
279 exp : '^' exp %prec UNARY
280 { write_exp_elt_opcode (pstate, UNOP_COMPLEMENT); }
283 exp : exp INCREMENT %prec UNARY
284 { write_exp_elt_opcode (pstate, UNOP_POSTINCREMENT); }
287 exp : exp DECREMENT %prec UNARY
288 { write_exp_elt_opcode (pstate, UNOP_POSTDECREMENT); }
291 /* foo->bar is not in Go. May want as a gdb extension. Later. */
293 exp : exp '.' name_not_typename
294 { write_exp_elt_opcode (pstate, STRUCTOP_STRUCT);
295 write_exp_string (pstate, $3.stoken);
296 write_exp_elt_opcode (pstate, STRUCTOP_STRUCT); }
299 exp : exp '.' name_not_typename COMPLETE
300 { mark_struct_expression (pstate);
301 write_exp_elt_opcode (pstate, STRUCTOP_STRUCT);
302 write_exp_string (pstate, $3.stoken);
303 write_exp_elt_opcode (pstate, STRUCTOP_STRUCT); }
306 exp : exp '.' COMPLETE
308 mark_struct_expression (pstate);
309 write_exp_elt_opcode (pstate, STRUCTOP_STRUCT);
312 write_exp_string (pstate, s);
313 write_exp_elt_opcode (pstate, STRUCTOP_STRUCT); }
316 exp : exp '[' exp1 ']'
317 { write_exp_elt_opcode (pstate, BINOP_SUBSCRIPT); }
321 /* This is to save the value of arglist_len
322 being accumulated by an outer function call. */
323 { start_arglist (); }
324 arglist ')' %prec LEFT_ARROW
325 { write_exp_elt_opcode (pstate, OP_FUNCALL);
326 write_exp_elt_longcst (pstate,
327 (LONGEST) end_arglist ());
328 write_exp_elt_opcode (pstate, OP_FUNCALL); }
332 { start_arglist (); }
342 arglist : arglist ',' exp %prec ABOVE_COMMA
347 { $$ = end_arglist () - 1; }
350 exp : lcurly type rcurly exp %prec UNARY
351 { write_exp_elt_opcode (pstate, UNOP_MEMVAL);
352 write_exp_elt_type (pstate, $2);
353 write_exp_elt_opcode (pstate, UNOP_MEMVAL); }
356 exp : type '(' exp ')' %prec UNARY
357 { write_exp_elt_opcode (pstate, UNOP_CAST);
358 write_exp_elt_type (pstate, $1);
359 write_exp_elt_opcode (pstate, UNOP_CAST); }
366 /* Binary operators in order of decreasing precedence. */
369 { write_exp_elt_opcode (pstate, BINOP_REPEAT); }
373 { write_exp_elt_opcode (pstate, BINOP_MUL); }
377 { write_exp_elt_opcode (pstate, BINOP_DIV); }
381 { write_exp_elt_opcode (pstate, BINOP_REM); }
385 { write_exp_elt_opcode (pstate, BINOP_ADD); }
389 { write_exp_elt_opcode (pstate, BINOP_SUB); }
393 { write_exp_elt_opcode (pstate, BINOP_LSH); }
397 { write_exp_elt_opcode (pstate, BINOP_RSH); }
401 { write_exp_elt_opcode (pstate, BINOP_EQUAL); }
404 exp : exp NOTEQUAL exp
405 { write_exp_elt_opcode (pstate, BINOP_NOTEQUAL); }
409 { write_exp_elt_opcode (pstate, BINOP_LEQ); }
413 { write_exp_elt_opcode (pstate, BINOP_GEQ); }
417 { write_exp_elt_opcode (pstate, BINOP_LESS); }
421 { write_exp_elt_opcode (pstate, BINOP_GTR); }
425 { write_exp_elt_opcode (pstate, BINOP_BITWISE_AND); }
429 { write_exp_elt_opcode (pstate, BINOP_BITWISE_XOR); }
433 { write_exp_elt_opcode (pstate, BINOP_BITWISE_IOR); }
437 { write_exp_elt_opcode (pstate, BINOP_LOGICAL_AND); }
441 { write_exp_elt_opcode (pstate, BINOP_LOGICAL_OR); }
444 exp : exp '?' exp ':' exp %prec '?'
445 { write_exp_elt_opcode (pstate, TERNOP_COND); }
449 { write_exp_elt_opcode (pstate, BINOP_ASSIGN); }
452 exp : exp ASSIGN_MODIFY exp
453 { write_exp_elt_opcode (pstate, BINOP_ASSIGN_MODIFY);
454 write_exp_elt_opcode (pstate, $2);
455 write_exp_elt_opcode (pstate, BINOP_ASSIGN_MODIFY); }
459 { write_exp_elt_opcode (pstate, OP_LONG);
460 write_exp_elt_type (pstate, $1.type);
461 write_exp_elt_longcst (pstate, (LONGEST)($1.val));
462 write_exp_elt_opcode (pstate, OP_LONG); }
467 struct stoken_vector vec;
470 write_exp_string_vector (pstate, $1.type, &vec);
476 parse_number (pstate, $1.stoken.ptr,
477 $1.stoken.length, 0, &val);
478 write_exp_elt_opcode (pstate, OP_LONG);
479 write_exp_elt_type (pstate, val.typed_val_int.type);
480 write_exp_elt_longcst (pstate, (LONGEST)
481 val.typed_val_int.val);
482 write_exp_elt_opcode (pstate, OP_LONG);
488 { write_exp_elt_opcode (pstate, OP_DOUBLE);
489 write_exp_elt_type (pstate, $1.type);
490 write_exp_elt_dblcst (pstate, $1.dval);
491 write_exp_elt_opcode (pstate, OP_DOUBLE); }
497 exp : DOLLAR_VARIABLE
499 write_dollar_variable (pstate, $1);
503 exp : SIZEOF_KEYWORD '(' type ')' %prec UNARY
505 /* TODO(dje): Go objects in structs. */
506 write_exp_elt_opcode (pstate, OP_LONG);
507 /* TODO(dje): What's the right type here? */
510 parse_type (pstate)->builtin_unsigned_int);
512 write_exp_elt_longcst (pstate,
513 (LONGEST) TYPE_LENGTH ($3));
514 write_exp_elt_opcode (pstate, OP_LONG);
518 exp : SIZEOF_KEYWORD '(' exp ')' %prec UNARY
520 /* TODO(dje): Go objects in structs. */
521 write_exp_elt_opcode (pstate, UNOP_SIZEOF);
527 /* We copy the string here, and not in the
528 lexer, to guarantee that we do not leak a
530 /* Note that we NUL-terminate here, but just
532 struct typed_stoken *vec = XNEW (struct typed_stoken);
537 vec->length = $1.length;
538 vec->ptr = malloc ($1.length + 1);
539 memcpy (vec->ptr, $1.ptr, $1.length + 1);
542 | string_exp '+' STRING
544 /* Note that we NUL-terminate here, but just
548 $$.tokens = realloc ($$.tokens,
549 $$.len * sizeof (struct typed_stoken));
551 p = malloc ($3.length + 1);
552 memcpy (p, $3.ptr, $3.length + 1);
554 $$.tokens[$$.len - 1].type = $3.type;
555 $$.tokens[$$.len - 1].length = $3.length;
556 $$.tokens[$$.len - 1].ptr = p;
560 exp : string_exp %prec ABOVE_COMMA
564 write_exp_string_vector (pstate, 0 /*always utf8*/,
566 for (i = 0; i < $1.len; ++i)
567 free ($1.tokens[i].ptr);
573 { write_exp_elt_opcode (pstate, OP_BOOL);
574 write_exp_elt_longcst (pstate, (LONGEST) $1);
575 write_exp_elt_opcode (pstate, OP_BOOL); }
579 { write_exp_elt_opcode (pstate, OP_BOOL);
580 write_exp_elt_longcst (pstate, (LONGEST) $1);
581 write_exp_elt_opcode (pstate, OP_BOOL); }
584 variable: name_not_typename ENTRY
585 { struct symbol *sym = $1.sym;
588 || !SYMBOL_IS_ARGUMENT (sym)
589 || !symbol_read_needs_frame (sym))
590 error (_("@entry can be used only for function "
591 "parameters, not for \"%s\""),
592 copy_name ($1.stoken));
594 write_exp_elt_opcode (pstate, OP_VAR_ENTRY_VALUE);
595 write_exp_elt_sym (pstate, sym);
596 write_exp_elt_opcode (pstate, OP_VAR_ENTRY_VALUE);
600 variable: name_not_typename
601 { struct symbol *sym = $1.sym;
605 if (symbol_read_needs_frame (sym))
607 if (innermost_block == 0
608 || contained_in (block_found,
610 innermost_block = block_found;
613 write_exp_elt_opcode (pstate, OP_VAR_VALUE);
614 /* We want to use the selected frame, not
615 another more inner frame which happens to
616 be in the same block. */
617 write_exp_elt_block (pstate, NULL);
618 write_exp_elt_sym (pstate, sym);
619 write_exp_elt_opcode (pstate, OP_VAR_VALUE);
621 else if ($1.is_a_field_of_this)
623 /* TODO(dje): Can we get here?
624 E.g., via a mix of c++ and go? */
625 gdb_assert_not_reached ("go with `this' field");
629 struct bound_minimal_symbol msymbol;
630 char *arg = copy_name ($1.stoken);
633 lookup_bound_minimal_symbol (arg);
634 if (msymbol.minsym != NULL)
635 write_exp_msymbol (pstate, msymbol);
636 else if (!have_full_symbols ()
637 && !have_partial_symbols ())
638 error (_("No symbol table is loaded. "
639 "Use the \"file\" command."));
641 error (_("No symbol \"%s\" in current context."),
642 copy_name ($1.stoken));
648 method_exp: PACKAGENAME '.' name '.' name
654 type /* Implements (approximately): [*] type-specifier */
656 { $$ = lookup_pointer_type ($2); }
660 | STRUCT_KEYWORD name
661 { $$ = lookup_struct (copy_name ($2),
662 expression_context_block); }
665 { $$ = builtin_go_type (parse_gdbarch (pstate))
670 name : NAME { $$ = $1.stoken; }
671 | TYPENAME { $$ = $1.stoken; }
672 | NAME_OR_INT { $$ = $1.stoken; }
678 /* These would be useful if name_not_typename was useful, but it is just
679 a fake for "variable", so these cause reduce/reduce conflicts because
680 the parser can't tell whether NAME_OR_INT is a name_not_typename (=variable,
681 =exp) or just an exp. If name_not_typename was ever used in an lvalue
682 context where only a name could occur, this might be useful.
689 /* Wrapper on parse_c_float to get the type right for Go. */
692 parse_go_float (struct gdbarch *gdbarch, const char *p, int len,
693 DOUBLEST *d, struct type **t)
695 int result = parse_c_float (gdbarch, p, len, d, t);
696 const struct builtin_type *builtin_types = builtin_type (gdbarch);
697 const struct builtin_go_type *builtin_go_types = builtin_go_type (gdbarch);
699 if (*t == builtin_types->builtin_float)
700 *t = builtin_go_types->builtin_float32;
701 else if (*t == builtin_types->builtin_double)
702 *t = builtin_go_types->builtin_float64;
707 /* Take care of parsing a number (anything that starts with a digit).
708 Set yylval and return the token type; update lexptr.
709 LEN is the number of characters in it. */
711 /* FIXME: Needs some error checking for the float case. */
712 /* FIXME(dje): IWBN to use c-exp.y's parse_number if we could.
713 That will require moving the guts into a function that we both call
714 as our YYSTYPE is different than c-exp.y's */
717 parse_number (struct parser_state *par_state,
718 const char *p, int len, int parsed_float, YYSTYPE *putithere)
720 /* FIXME: Shouldn't these be unsigned? We don't deal with negative values
721 here, and we do kind of silly things like cast to unsigned. */
728 int base = input_radix;
731 /* Number of "L" suffixes encountered. */
734 /* We have found a "L" or "U" suffix. */
735 int found_suffix = 0;
738 struct type *signed_type;
739 struct type *unsigned_type;
743 if (! parse_go_float (parse_gdbarch (par_state), p, len,
744 &putithere->typed_val_float.dval,
745 &putithere->typed_val_float.type))
750 /* Handle base-switching prefixes 0x, 0t, 0d, 0. */
794 if (c >= 'A' && c <= 'Z')
796 if (c != 'l' && c != 'u')
798 if (c >= '0' && c <= '9')
806 if (base > 10 && c >= 'a' && c <= 'f')
810 n += i = c - 'a' + 10;
823 return ERROR; /* Char not a digit */
826 return ERROR; /* Invalid digit in this base. */
828 /* Portably test for overflow (only works for nonzero values, so make
829 a second check for zero). FIXME: Can't we just make n and prevn
830 unsigned and avoid this? */
831 if (c != 'l' && c != 'u' && (prevn >= n) && n != 0)
832 unsigned_p = 1; /* Try something unsigned. */
834 /* Portably test for unsigned overflow.
835 FIXME: This check is wrong; for example it doesn't find overflow
836 on 0x123456789 when LONGEST is 32 bits. */
837 if (c != 'l' && c != 'u' && n != 0)
839 if ((unsigned_p && (ULONGEST) prevn >= (ULONGEST) n))
840 error (_("Numeric constant too large."));
845 /* An integer constant is an int, a long, or a long long. An L
846 suffix forces it to be long; an LL suffix forces it to be long
847 long. If not forced to a larger size, it gets the first type of
848 the above that it fits in. To figure out whether it fits, we
849 shift it right and see whether anything remains. Note that we
850 can't shift sizeof (LONGEST) * HOST_CHAR_BIT bits or more in one
851 operation, because many compilers will warn about such a shift
852 (which always produces a zero result). Sometimes gdbarch_int_bit
853 or gdbarch_long_bit will be that big, sometimes not. To deal with
854 the case where it is we just always shift the value more than
855 once, with fewer bits each time. */
857 un = (ULONGEST)n >> 2;
859 && (un >> (gdbarch_int_bit (parse_gdbarch (par_state)) - 2)) == 0)
862 = ((ULONGEST)1) << (gdbarch_int_bit (parse_gdbarch (par_state)) - 1);
864 /* A large decimal (not hex or octal) constant (between INT_MAX
865 and UINT_MAX) is a long or unsigned long, according to ANSI,
866 never an unsigned int, but this code treats it as unsigned
867 int. This probably should be fixed. GCC gives a warning on
870 unsigned_type = parse_type (par_state)->builtin_unsigned_int;
871 signed_type = parse_type (par_state)->builtin_int;
874 && (un >> (gdbarch_long_bit (parse_gdbarch (par_state)) - 2)) == 0)
877 = ((ULONGEST)1) << (gdbarch_long_bit (parse_gdbarch (par_state)) - 1);
878 unsigned_type = parse_type (par_state)->builtin_unsigned_long;
879 signed_type = parse_type (par_state)->builtin_long;
884 if (sizeof (ULONGEST) * HOST_CHAR_BIT
885 < gdbarch_long_long_bit (parse_gdbarch (par_state)))
886 /* A long long does not fit in a LONGEST. */
887 shift = (sizeof (ULONGEST) * HOST_CHAR_BIT - 1);
889 shift = (gdbarch_long_long_bit (parse_gdbarch (par_state)) - 1);
890 high_bit = (ULONGEST) 1 << shift;
891 unsigned_type = parse_type (par_state)->builtin_unsigned_long_long;
892 signed_type = parse_type (par_state)->builtin_long_long;
895 putithere->typed_val_int.val = n;
897 /* If the high bit of the worked out type is set then this number
898 has to be unsigned. */
900 if (unsigned_p || (n & high_bit))
902 putithere->typed_val_int.type = unsigned_type;
906 putithere->typed_val_int.type = signed_type;
912 /* Temporary obstack used for holding strings. */
913 static struct obstack tempbuf;
914 static int tempbuf_init;
916 /* Parse a string or character literal from TOKPTR. The string or
917 character may be wide or unicode. *OUTPTR is set to just after the
918 end of the literal in the input string. The resulting token is
919 stored in VALUE. This returns a token value, either STRING or
920 CHAR, depending on what was parsed. *HOST_CHARS is set to the
921 number of host characters in the literal. */
924 parse_string_or_char (const char *tokptr, const char **outptr,
925 struct typed_stoken *value, int *host_chars)
929 /* Build the gdb internal form of the input string in tempbuf. Note
930 that the buffer is null byte terminated *only* for the
931 convenience of debugging gdb itself and printing the buffer
932 contents when the buffer contains no embedded nulls. Gdb does
933 not depend upon the buffer being null byte terminated, it uses
934 the length string instead. This allows gdb to handle C strings
935 (as well as strings in other languages) with embedded null
941 obstack_free (&tempbuf, NULL);
942 obstack_init (&tempbuf);
944 /* Skip the quote. */
956 *host_chars += c_parse_escape (&tokptr, &tempbuf);
962 obstack_1grow (&tempbuf, c);
964 /* FIXME: this does the wrong thing with multi-byte host
965 characters. We could use mbrlen here, but that would
966 make "set host-charset" a bit less useful. */
971 if (*tokptr != quote)
974 error (_("Unterminated string in expression."));
976 error (_("Unmatched single quote."));
980 value->type = C_STRING | (quote == '\'' ? C_CHAR : 0); /*FIXME*/
981 value->ptr = obstack_base (&tempbuf);
982 value->length = obstack_object_size (&tempbuf);
986 return quote == '\'' ? CHAR : STRING;
993 enum exp_opcode opcode;
996 static const struct token tokentab3[] =
998 {">>=", ASSIGN_MODIFY, BINOP_RSH},
999 {"<<=", ASSIGN_MODIFY, BINOP_LSH},
1000 /*{"&^=", ASSIGN_MODIFY, BINOP_BITWISE_ANDNOT}, TODO */
1001 {"...", DOTDOTDOT, OP_NULL},
1004 static const struct token tokentab2[] =
1006 {"+=", ASSIGN_MODIFY, BINOP_ADD},
1007 {"-=", ASSIGN_MODIFY, BINOP_SUB},
1008 {"*=", ASSIGN_MODIFY, BINOP_MUL},
1009 {"/=", ASSIGN_MODIFY, BINOP_DIV},
1010 {"%=", ASSIGN_MODIFY, BINOP_REM},
1011 {"|=", ASSIGN_MODIFY, BINOP_BITWISE_IOR},
1012 {"&=", ASSIGN_MODIFY, BINOP_BITWISE_AND},
1013 {"^=", ASSIGN_MODIFY, BINOP_BITWISE_XOR},
1014 {"++", INCREMENT, BINOP_END},
1015 {"--", DECREMENT, BINOP_END},
1016 /*{"->", RIGHT_ARROW, BINOP_END}, Doesn't exist in Go. */
1017 {"<-", LEFT_ARROW, BINOP_END},
1018 {"&&", ANDAND, BINOP_END},
1019 {"||", OROR, BINOP_END},
1020 {"<<", LSH, BINOP_END},
1021 {">>", RSH, BINOP_END},
1022 {"==", EQUAL, BINOP_END},
1023 {"!=", NOTEQUAL, BINOP_END},
1024 {"<=", LEQ, BINOP_END},
1025 {">=", GEQ, BINOP_END},
1026 /*{"&^", ANDNOT, BINOP_END}, TODO */
1029 /* Identifier-like tokens. */
1030 static const struct token ident_tokens[] =
1032 {"true", TRUE_KEYWORD, OP_NULL},
1033 {"false", FALSE_KEYWORD, OP_NULL},
1034 {"nil", NIL_KEYWORD, OP_NULL},
1035 {"const", CONST_KEYWORD, OP_NULL},
1036 {"struct", STRUCT_KEYWORD, OP_NULL},
1037 {"type", TYPE_KEYWORD, OP_NULL},
1038 {"interface", INTERFACE_KEYWORD, OP_NULL},
1039 {"chan", CHAN_KEYWORD, OP_NULL},
1040 {"byte", BYTE_KEYWORD, OP_NULL}, /* An alias of uint8. */
1041 {"len", LEN_KEYWORD, OP_NULL},
1042 {"cap", CAP_KEYWORD, OP_NULL},
1043 {"new", NEW_KEYWORD, OP_NULL},
1044 {"iota", IOTA_KEYWORD, OP_NULL},
1047 /* This is set if a NAME token appeared at the very end of the input
1048 string, with no whitespace separating the name from the EOF. This
1049 is used only when parsing to do field name completion. */
1050 static int saw_name_at_eof;
1052 /* This is set if the previously-returned token was a structure
1053 operator -- either '.' or ARROW. This is used only when parsing to
1054 do field name completion. */
1055 static int last_was_structop;
1057 /* Read one token, getting characters through lexptr. */
1060 lex_one_token (struct parser_state *par_state)
1065 const char *tokstart;
1066 int saw_structop = last_was_structop;
1069 last_was_structop = 0;
1073 prev_lexptr = lexptr;
1076 /* See if it is a special token of length 3. */
1077 for (i = 0; i < sizeof (tokentab3) / sizeof (tokentab3[0]); i++)
1078 if (strncmp (tokstart, tokentab3[i].operator, 3) == 0)
1081 yylval.opcode = tokentab3[i].opcode;
1082 return tokentab3[i].token;
1085 /* See if it is a special token of length 2. */
1086 for (i = 0; i < sizeof (tokentab2) / sizeof (tokentab2[0]); i++)
1087 if (strncmp (tokstart, tokentab2[i].operator, 2) == 0)
1090 yylval.opcode = tokentab2[i].opcode;
1091 /* NOTE: -> doesn't exist in Go, so we don't need to watch for
1092 setting last_was_structop here. */
1093 return tokentab2[i].token;
1096 switch (c = *tokstart)
1099 if (saw_name_at_eof)
1101 saw_name_at_eof = 0;
1104 else if (saw_structop)
1123 if (paren_depth == 0)
1130 if (comma_terminates
1131 && paren_depth == 0)
1137 /* Might be a floating point number. */
1138 if (lexptr[1] < '0' || lexptr[1] > '9')
1140 if (parse_completion)
1141 last_was_structop = 1;
1142 goto symbol; /* Nope, must be a symbol. */
1144 /* FALL THRU into number case. */
1157 /* It's a number. */
1158 int got_dot = 0, got_e = 0, toktype;
1159 const char *p = tokstart;
1160 int hex = input_radix > 10;
1162 if (c == '0' && (p[1] == 'x' || p[1] == 'X'))
1170 /* This test includes !hex because 'e' is a valid hex digit
1171 and thus does not indicate a floating point number when
1172 the radix is hex. */
1173 if (!hex && !got_e && (*p == 'e' || *p == 'E'))
1174 got_dot = got_e = 1;
1175 /* This test does not include !hex, because a '.' always indicates
1176 a decimal floating point number regardless of the radix. */
1177 else if (!got_dot && *p == '.')
1179 else if (got_e && (p[-1] == 'e' || p[-1] == 'E')
1180 && (*p == '-' || *p == '+'))
1181 /* This is the sign of the exponent, not the end of the
1184 /* We will take any letters or digits. parse_number will
1185 complain if past the radix, or if L or U are not final. */
1186 else if ((*p < '0' || *p > '9')
1187 && ((*p < 'a' || *p > 'z')
1188 && (*p < 'A' || *p > 'Z')))
1191 toktype = parse_number (par_state, tokstart, p - tokstart,
1192 got_dot|got_e, &yylval);
1193 if (toktype == ERROR)
1195 char *err_copy = (char *) alloca (p - tokstart + 1);
1197 memcpy (err_copy, tokstart, p - tokstart);
1198 err_copy[p - tokstart] = 0;
1199 error (_("Invalid number \"%s\"."), err_copy);
1207 const char *p = &tokstart[1];
1208 size_t len = strlen ("entry");
1210 while (isspace (*p))
1212 if (strncmp (p, "entry", len) == 0 && !isalnum (p[len])
1246 int result = parse_string_or_char (tokstart, &lexptr, &yylval.tsval,
1251 error (_("Empty character constant."));
1252 else if (host_len > 2 && c == '\'')
1255 namelen = lexptr - tokstart - 1;
1258 else if (host_len > 1)
1259 error (_("Invalid character constant."));
1265 if (!(c == '_' || c == '$'
1266 || (c >= 'a' && c <= 'z') || (c >= 'A' && c <= 'Z')))
1267 /* We must have come across a bad character (e.g. ';'). */
1268 error (_("Invalid character '%c' in expression."), c);
1270 /* It's a name. See how long it is. */
1272 for (c = tokstart[namelen];
1273 (c == '_' || c == '$' || (c >= '0' && c <= '9')
1274 || (c >= 'a' && c <= 'z') || (c >= 'A' && c <= 'Z'));)
1276 c = tokstart[++namelen];
1279 /* The token "if" terminates the expression and is NOT removed from
1280 the input stream. It doesn't count if it appears in the
1281 expansion of a macro. */
1283 && tokstart[0] == 'i'
1284 && tokstart[1] == 'f')
1289 /* For the same reason (breakpoint conditions), "thread N"
1290 terminates the expression. "thread" could be an identifier, but
1291 an identifier is never followed by a number without intervening
1293 Handle abbreviations of these, similarly to
1294 breakpoint.c:find_condition_and_thread.
1295 TODO: Watch for "goroutine" here? */
1297 && strncmp (tokstart, "thread", namelen) == 0
1298 && (tokstart[namelen] == ' ' || tokstart[namelen] == '\t'))
1300 const char *p = tokstart + namelen + 1;
1302 while (*p == ' ' || *p == '\t')
1304 if (*p >= '0' && *p <= '9')
1312 yylval.sval.ptr = tokstart;
1313 yylval.sval.length = namelen;
1315 /* Catch specific keywords. */
1316 copy = copy_name (yylval.sval);
1317 for (i = 0; i < sizeof (ident_tokens) / sizeof (ident_tokens[0]); i++)
1318 if (strcmp (copy, ident_tokens[i].operator) == 0)
1320 /* It is ok to always set this, even though we don't always
1321 strictly need to. */
1322 yylval.opcode = ident_tokens[i].opcode;
1323 return ident_tokens[i].token;
1326 if (*tokstart == '$')
1327 return DOLLAR_VARIABLE;
1329 if (parse_completion && *lexptr == '\0')
1330 saw_name_at_eof = 1;
1334 /* An object of this type is pushed on a FIFO by the "outer" lexer. */
1341 DEF_VEC_O (token_and_value);
1343 /* A FIFO of tokens that have been read but not yet returned to the
1345 static VEC (token_and_value) *token_fifo;
1347 /* Non-zero if the lexer should return tokens from the FIFO. */
1350 /* Temporary storage for yylex; this holds symbol names as they are
1352 static struct obstack name_obstack;
1354 /* Build "package.name" in name_obstack.
1355 For convenience of the caller, the name is NUL-terminated,
1356 but the NUL is not included in the recorded length. */
1358 static struct stoken
1359 build_packaged_name (const char *package, int package_len,
1360 const char *name, int name_len)
1362 struct stoken result;
1364 obstack_free (&name_obstack, obstack_base (&name_obstack));
1365 obstack_grow (&name_obstack, package, package_len);
1366 obstack_grow_str (&name_obstack, ".");
1367 obstack_grow (&name_obstack, name, name_len);
1368 obstack_grow (&name_obstack, "", 1);
1369 result.ptr = obstack_base (&name_obstack);
1370 result.length = obstack_object_size (&name_obstack) - 1;
1375 /* Return non-zero if NAME is a package name.
1376 BLOCK is the scope in which to interpret NAME; this can be NULL
1377 to mean the global scope. */
1380 package_name_p (const char *name, const struct block *block)
1383 struct field_of_this_result is_a_field_of_this;
1385 sym = lookup_symbol (name, block, STRUCT_DOMAIN, &is_a_field_of_this);
1388 && SYMBOL_CLASS (sym) == LOC_TYPEDEF
1389 && TYPE_CODE (SYMBOL_TYPE (sym)) == TYPE_CODE_MODULE)
1395 /* Classify a (potential) function in the "unsafe" package.
1396 We fold these into "keywords" to keep things simple, at least until
1397 something more complex is warranted. */
1400 classify_unsafe_function (struct stoken function_name)
1402 char *copy = copy_name (function_name);
1404 if (strcmp (copy, "Sizeof") == 0)
1406 yylval.sval = function_name;
1407 return SIZEOF_KEYWORD;
1410 error (_("Unknown function in `unsafe' package: %s"), copy);
1413 /* Classify token(s) "name1.name2" where name1 is known to be a package.
1414 The contents of the token are in `yylval'.
1415 Updates yylval and returns the new token type.
1417 The result is one of NAME, NAME_OR_INT, or TYPENAME. */
1420 classify_packaged_name (const struct block *block)
1424 struct field_of_this_result is_a_field_of_this;
1426 copy = copy_name (yylval.sval);
1428 sym = lookup_symbol (copy, block, VAR_DOMAIN, &is_a_field_of_this);
1432 yylval.ssym.sym = sym;
1433 yylval.ssym.is_a_field_of_this = is_a_field_of_this.type != NULL;
1439 /* Classify a NAME token.
1440 The contents of the token are in `yylval'.
1441 Updates yylval and returns the new token type.
1442 BLOCK is the block in which lookups start; this can be NULL
1443 to mean the global scope.
1445 The result is one of NAME, NAME_OR_INT, or TYPENAME. */
1448 classify_name (struct parser_state *par_state, const struct block *block)
1453 struct field_of_this_result is_a_field_of_this;
1455 copy = copy_name (yylval.sval);
1457 /* Try primitive types first so they win over bad/weird debug info. */
1458 type = language_lookup_primitive_type (parse_language (par_state),
1459 parse_gdbarch (par_state),
1463 /* NOTE: We take advantage of the fact that yylval coming in was a
1464 NAME, and that struct ttype is a compatible extension of struct
1465 stoken, so yylval.tsym.stoken is already filled in. */
1466 yylval.tsym.type = type;
1470 /* TODO: What about other types? */
1472 sym = lookup_symbol (copy, block, VAR_DOMAIN, &is_a_field_of_this);
1476 yylval.ssym.sym = sym;
1477 yylval.ssym.is_a_field_of_this = is_a_field_of_this.type != NULL;
1481 /* If we didn't find a symbol, look again in the current package.
1482 This is to, e.g., make "p global_var" work without having to specify
1483 the package name. We intentionally only looks for objects in the
1487 char *current_package_name = go_block_package_name (block);
1489 if (current_package_name != NULL)
1491 struct stoken sval =
1492 build_packaged_name (current_package_name,
1493 strlen (current_package_name),
1494 copy, strlen (copy));
1496 xfree (current_package_name);
1497 sym = lookup_symbol (sval.ptr, block, VAR_DOMAIN,
1498 &is_a_field_of_this);
1501 yylval.ssym.stoken = sval;
1502 yylval.ssym.sym = sym;
1503 yylval.ssym.is_a_field_of_this = is_a_field_of_this.type != NULL;
1509 /* Input names that aren't symbols but ARE valid hex numbers, when
1510 the input radix permits them, can be names or numbers depending
1511 on the parse. Note we support radixes > 16 here. */
1512 if ((copy[0] >= 'a' && copy[0] < 'a' + input_radix - 10)
1513 || (copy[0] >= 'A' && copy[0] < 'A' + input_radix - 10))
1515 YYSTYPE newlval; /* Its value is ignored. */
1516 int hextype = parse_number (par_state, copy, yylval.sval.length,
1520 yylval.ssym.sym = NULL;
1521 yylval.ssym.is_a_field_of_this = 0;
1526 yylval.ssym.sym = NULL;
1527 yylval.ssym.is_a_field_of_this = 0;
1531 /* This is taken from c-exp.y mostly to get something working.
1532 The basic structure has been kept because we may yet need some of it. */
1537 token_and_value current, next;
1539 if (popping && !VEC_empty (token_and_value, token_fifo))
1541 token_and_value tv = *VEC_index (token_and_value, token_fifo, 0);
1542 VEC_ordered_remove (token_and_value, token_fifo, 0);
1544 /* There's no need to fall through to handle package.name
1545 as that can never happen here. In theory. */
1550 current.token = lex_one_token (pstate);
1552 /* TODO: Need a way to force specifying name1 as a package.
1555 if (current.token != NAME)
1556 return current.token;
1558 /* See if we have "name1 . name2". */
1560 current.value = yylval;
1561 next.token = lex_one_token (pstate);
1562 next.value = yylval;
1564 if (next.token == '.')
1566 token_and_value name2;
1568 name2.token = lex_one_token (pstate);
1569 name2.value = yylval;
1571 if (name2.token == NAME)
1573 /* Ok, we have "name1 . name2". */
1576 copy = copy_name (current.value.sval);
1578 if (strcmp (copy, "unsafe") == 0)
1581 return classify_unsafe_function (name2.value.sval);
1584 if (package_name_p (copy, expression_context_block))
1587 yylval.sval = build_packaged_name (current.value.sval.ptr,
1588 current.value.sval.length,
1589 name2.value.sval.ptr,
1590 name2.value.sval.length);
1591 return classify_packaged_name (expression_context_block);
1595 VEC_safe_push (token_and_value, token_fifo, &next);
1596 VEC_safe_push (token_and_value, token_fifo, &name2);
1600 VEC_safe_push (token_and_value, token_fifo, &next);
1603 /* If we arrive here we don't have a package-qualified name. */
1606 yylval = current.value;
1607 return classify_name (pstate, expression_context_block);
1611 go_parse (struct parser_state *par_state)
1614 struct cleanup *back_to;
1616 /* Setting up the parser state. */
1617 gdb_assert (par_state != NULL);
1620 back_to = make_cleanup (null_cleanup, NULL);
1622 make_cleanup_restore_integer (&yydebug);
1623 make_cleanup_clear_parser_state (&pstate);
1624 yydebug = parser_debug;
1626 /* Initialize some state used by the lexer. */
1627 last_was_structop = 0;
1628 saw_name_at_eof = 0;
1630 VEC_free (token_and_value, token_fifo);
1632 obstack_init (&name_obstack);
1633 make_cleanup_obstack_free (&name_obstack);
1635 result = yyparse ();
1636 do_cleanups (back_to);
1644 lexptr = prev_lexptr;
1646 error (_("A %s in expression, near `%s'."), (msg ? msg : "error"), lexptr);