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.
57 #include "expression.h"
59 #include "parser-defs.h"
63 #include "bfd.h" /* Required by objfiles.h. */
64 #include "symfile.h" /* Required by objfiles.h. */
65 #include "objfiles.h" /* For have_full_symbols and have_partial_symbols */
69 #define parse_type(ps) builtin_type (parse_gdbarch (ps))
71 /* Remap normal yacc parser interface names (yyparse, yylex, yyerror, etc),
72 as well as gratuitiously global symbol names, so we can have multiple
73 yacc generated parsers in gdb. Note that these are only the variables
74 produced by yacc. If other parser generators (bison, byacc, etc) produce
75 additional global names that conflict at link time, then those parser
76 generators need to be fixed instead of adding those names to this list. */
78 #define yymaxdepth go_maxdepth
79 #define yyparse go_parse_internal
81 #define yyerror go_error
82 #define yylval go_lval
83 #define yychar go_char
84 #define yydebug go_debug
85 #define yypact go_pact
92 #define yyexca go_exca
93 #define yyerrflag go_errflag
94 #define yynerrs go_nerrs
99 #define yystate go_state
102 #define yy_yyv go_yyv
104 #define yylloc go_lloc
105 #define yyreds go_reds /* With YYDEBUG defined */
106 #define yytoks go_toks /* With YYDEBUG defined */
107 #define yyname go_name /* With YYDEBUG defined */
108 #define yyrule go_rule /* With YYDEBUG defined */
109 #define yylhs go_yylhs
110 #define yylen go_yylen
111 #define yydefred go_yydefred
112 #define yydgoto go_yydgoto
113 #define yysindex go_yysindex
114 #define yyrindex go_yyrindex
115 #define yygindex go_yygindex
116 #define yytable go_yytable
117 #define yycheck go_yycheck
120 #define YYDEBUG 1 /* Default to yydebug support */
123 #define YYFPRINTF parser_fprintf
125 /* The state of the parser, used internally when we are parsing the
128 static struct parser_state *pstate = NULL;
132 static int yylex (void);
134 void yyerror (char *);
138 /* Although the yacc "value" of an expression is not used,
139 since the result is stored in the structure being created,
140 other node types do have values. */
154 struct symtoken ssym;
156 struct typed_stoken tsval;
159 enum exp_opcode opcode;
160 struct internalvar *ivar;
161 struct stoken_vector svec;
165 /* YYSTYPE gets defined by %union. */
166 static int parse_number (struct parser_state *,
167 const char *, int, int, YYSTYPE *);
168 static int parse_go_float (struct gdbarch *gdbarch, const char *p, int len,
169 DOUBLEST *d, struct type **t);
172 %type <voidval> exp exp1 type_exp start variable lcurly
176 %token <typed_val_int> INT
177 %token <typed_val_float> FLOAT
179 /* Both NAME and TYPENAME tokens represent symbols in the input,
180 and both convey their data as strings.
181 But a TYPENAME is a string that happens to be defined as a type
182 or builtin type name (such as int or char)
183 and a NAME is any other symbol.
184 Contexts where this distinction is not important can use the
185 nonterminal "name", which matches either NAME or TYPENAME. */
187 %token <tsval> RAW_STRING
188 %token <tsval> STRING
191 %token <tsym> TYPENAME /* Not TYPE_NAME cus already taken. */
192 %token <voidval> COMPLETE
193 /*%type <sval> name*/
194 %type <svec> string_exp
195 %type <ssym> name_not_typename
197 /* A NAME_OR_INT is a symbol which is not known in the symbol table,
198 but which would parse as a valid number in the current input radix.
199 E.g. "c" when input_radix==16. Depending on the parse, it will be
200 turned into a name or into a number. */
201 %token <ssym> NAME_OR_INT
203 %token <lval> TRUE_KEYWORD FALSE_KEYWORD
204 %token STRUCT_KEYWORD INTERFACE_KEYWORD TYPE_KEYWORD CHAN_KEYWORD
205 %token SIZEOF_KEYWORD
206 %token LEN_KEYWORD CAP_KEYWORD
208 %token IOTA_KEYWORD NIL_KEYWORD
214 /* Special type cases. */
215 %token BYTE_KEYWORD /* An alias of uint8. */
217 %token <sval> DOLLAR_VARIABLE
219 %token <opcode> ASSIGN_MODIFY
223 %right '=' ASSIGN_MODIFY
232 %left '<' '>' LEQ GEQ
237 %right UNARY INCREMENT DECREMENT
238 %right LEFT_ARROW '.' '[' '('
248 { write_exp_elt_opcode (pstate, OP_TYPE);
249 write_exp_elt_type (pstate, $1);
250 write_exp_elt_opcode (pstate, OP_TYPE); }
253 /* Expressions, including the comma operator. */
256 { write_exp_elt_opcode (pstate, BINOP_COMMA); }
259 /* Expressions, not including the comma operator. */
260 exp : '*' exp %prec UNARY
261 { write_exp_elt_opcode (pstate, UNOP_IND); }
264 exp : '&' exp %prec UNARY
265 { write_exp_elt_opcode (pstate, UNOP_ADDR); }
268 exp : '-' exp %prec UNARY
269 { write_exp_elt_opcode (pstate, UNOP_NEG); }
272 exp : '+' exp %prec UNARY
273 { write_exp_elt_opcode (pstate, UNOP_PLUS); }
276 exp : '!' exp %prec UNARY
277 { write_exp_elt_opcode (pstate, UNOP_LOGICAL_NOT); }
280 exp : '^' exp %prec UNARY
281 { write_exp_elt_opcode (pstate, UNOP_COMPLEMENT); }
284 exp : exp INCREMENT %prec UNARY
285 { write_exp_elt_opcode (pstate, UNOP_POSTINCREMENT); }
288 exp : exp DECREMENT %prec UNARY
289 { write_exp_elt_opcode (pstate, UNOP_POSTDECREMENT); }
292 /* foo->bar is not in Go. May want as a gdb extension. Later. */
294 exp : exp '.' name_not_typename
295 { write_exp_elt_opcode (pstate, STRUCTOP_STRUCT);
296 write_exp_string (pstate, $3.stoken);
297 write_exp_elt_opcode (pstate, STRUCTOP_STRUCT); }
300 exp : exp '.' name_not_typename COMPLETE
301 { mark_struct_expression (pstate);
302 write_exp_elt_opcode (pstate, STRUCTOP_STRUCT);
303 write_exp_string (pstate, $3.stoken);
304 write_exp_elt_opcode (pstate, STRUCTOP_STRUCT); }
307 exp : exp '.' COMPLETE
309 mark_struct_expression (pstate);
310 write_exp_elt_opcode (pstate, STRUCTOP_STRUCT);
313 write_exp_string (pstate, s);
314 write_exp_elt_opcode (pstate, STRUCTOP_STRUCT); }
317 exp : exp '[' exp1 ']'
318 { write_exp_elt_opcode (pstate, BINOP_SUBSCRIPT); }
322 /* This is to save the value of arglist_len
323 being accumulated by an outer function call. */
324 { start_arglist (); }
325 arglist ')' %prec LEFT_ARROW
326 { write_exp_elt_opcode (pstate, OP_FUNCALL);
327 write_exp_elt_longcst (pstate,
328 (LONGEST) end_arglist ());
329 write_exp_elt_opcode (pstate, OP_FUNCALL); }
333 { start_arglist (); }
343 arglist : arglist ',' exp %prec ABOVE_COMMA
348 { $$ = end_arglist () - 1; }
351 exp : lcurly type rcurly exp %prec UNARY
352 { write_exp_elt_opcode (pstate, UNOP_MEMVAL);
353 write_exp_elt_type (pstate, $2);
354 write_exp_elt_opcode (pstate, UNOP_MEMVAL); }
357 exp : type '(' exp ')' %prec UNARY
358 { write_exp_elt_opcode (pstate, UNOP_CAST);
359 write_exp_elt_type (pstate, $1);
360 write_exp_elt_opcode (pstate, UNOP_CAST); }
367 /* Binary operators in order of decreasing precedence. */
370 { write_exp_elt_opcode (pstate, BINOP_REPEAT); }
374 { write_exp_elt_opcode (pstate, BINOP_MUL); }
378 { write_exp_elt_opcode (pstate, BINOP_DIV); }
382 { write_exp_elt_opcode (pstate, BINOP_REM); }
386 { write_exp_elt_opcode (pstate, BINOP_ADD); }
390 { write_exp_elt_opcode (pstate, BINOP_SUB); }
394 { write_exp_elt_opcode (pstate, BINOP_LSH); }
398 { write_exp_elt_opcode (pstate, BINOP_RSH); }
402 { write_exp_elt_opcode (pstate, BINOP_EQUAL); }
405 exp : exp NOTEQUAL exp
406 { write_exp_elt_opcode (pstate, BINOP_NOTEQUAL); }
410 { write_exp_elt_opcode (pstate, BINOP_LEQ); }
414 { write_exp_elt_opcode (pstate, BINOP_GEQ); }
418 { write_exp_elt_opcode (pstate, BINOP_LESS); }
422 { write_exp_elt_opcode (pstate, BINOP_GTR); }
426 { write_exp_elt_opcode (pstate, BINOP_BITWISE_AND); }
430 { write_exp_elt_opcode (pstate, BINOP_BITWISE_XOR); }
434 { write_exp_elt_opcode (pstate, BINOP_BITWISE_IOR); }
438 { write_exp_elt_opcode (pstate, BINOP_LOGICAL_AND); }
442 { write_exp_elt_opcode (pstate, BINOP_LOGICAL_OR); }
445 exp : exp '?' exp ':' exp %prec '?'
446 { write_exp_elt_opcode (pstate, TERNOP_COND); }
450 { write_exp_elt_opcode (pstate, BINOP_ASSIGN); }
453 exp : exp ASSIGN_MODIFY exp
454 { write_exp_elt_opcode (pstate, BINOP_ASSIGN_MODIFY);
455 write_exp_elt_opcode (pstate, $2);
456 write_exp_elt_opcode (pstate, BINOP_ASSIGN_MODIFY); }
460 { write_exp_elt_opcode (pstate, OP_LONG);
461 write_exp_elt_type (pstate, $1.type);
462 write_exp_elt_longcst (pstate, (LONGEST)($1.val));
463 write_exp_elt_opcode (pstate, OP_LONG); }
468 struct stoken_vector vec;
471 write_exp_string_vector (pstate, $1.type, &vec);
477 parse_number (pstate, $1.stoken.ptr,
478 $1.stoken.length, 0, &val);
479 write_exp_elt_opcode (pstate, OP_LONG);
480 write_exp_elt_type (pstate, val.typed_val_int.type);
481 write_exp_elt_longcst (pstate, (LONGEST)
482 val.typed_val_int.val);
483 write_exp_elt_opcode (pstate, OP_LONG);
489 { write_exp_elt_opcode (pstate, OP_DOUBLE);
490 write_exp_elt_type (pstate, $1.type);
491 write_exp_elt_dblcst (pstate, $1.dval);
492 write_exp_elt_opcode (pstate, OP_DOUBLE); }
498 exp : DOLLAR_VARIABLE
500 write_dollar_variable (pstate, $1);
504 exp : SIZEOF_KEYWORD '(' type ')' %prec UNARY
506 /* TODO(dje): Go objects in structs. */
507 write_exp_elt_opcode (pstate, OP_LONG);
508 /* TODO(dje): What's the right type here? */
511 parse_type (pstate)->builtin_unsigned_int);
513 write_exp_elt_longcst (pstate,
514 (LONGEST) TYPE_LENGTH ($3));
515 write_exp_elt_opcode (pstate, OP_LONG);
519 exp : SIZEOF_KEYWORD '(' exp ')' %prec UNARY
521 /* TODO(dje): Go objects in structs. */
522 write_exp_elt_opcode (pstate, UNOP_SIZEOF);
528 /* We copy the string here, and not in the
529 lexer, to guarantee that we do not leak a
531 /* Note that we NUL-terminate here, but just
533 struct typed_stoken *vec = XNEW (struct typed_stoken);
538 vec->length = $1.length;
539 vec->ptr = malloc ($1.length + 1);
540 memcpy (vec->ptr, $1.ptr, $1.length + 1);
543 | string_exp '+' STRING
545 /* Note that we NUL-terminate here, but just
549 $$.tokens = realloc ($$.tokens,
550 $$.len * sizeof (struct typed_stoken));
552 p = malloc ($3.length + 1);
553 memcpy (p, $3.ptr, $3.length + 1);
555 $$.tokens[$$.len - 1].type = $3.type;
556 $$.tokens[$$.len - 1].length = $3.length;
557 $$.tokens[$$.len - 1].ptr = p;
561 exp : string_exp %prec ABOVE_COMMA
565 write_exp_string_vector (pstate, 0 /*always utf8*/,
567 for (i = 0; i < $1.len; ++i)
568 free ($1.tokens[i].ptr);
574 { write_exp_elt_opcode (pstate, OP_BOOL);
575 write_exp_elt_longcst (pstate, (LONGEST) $1);
576 write_exp_elt_opcode (pstate, OP_BOOL); }
580 { write_exp_elt_opcode (pstate, OP_BOOL);
581 write_exp_elt_longcst (pstate, (LONGEST) $1);
582 write_exp_elt_opcode (pstate, OP_BOOL); }
585 variable: name_not_typename ENTRY
586 { struct symbol *sym = $1.sym;
589 || !SYMBOL_IS_ARGUMENT (sym)
590 || !symbol_read_needs_frame (sym))
591 error (_("@entry can be used only for function "
592 "parameters, not for \"%s\""),
593 copy_name ($1.stoken));
595 write_exp_elt_opcode (pstate, OP_VAR_ENTRY_VALUE);
596 write_exp_elt_sym (pstate, sym);
597 write_exp_elt_opcode (pstate, OP_VAR_ENTRY_VALUE);
601 variable: name_not_typename
602 { struct symbol *sym = $1.sym;
606 if (symbol_read_needs_frame (sym))
608 if (innermost_block == 0
609 || contained_in (block_found,
611 innermost_block = block_found;
614 write_exp_elt_opcode (pstate, OP_VAR_VALUE);
615 /* We want to use the selected frame, not
616 another more inner frame which happens to
617 be in the same block. */
618 write_exp_elt_block (pstate, NULL);
619 write_exp_elt_sym (pstate, sym);
620 write_exp_elt_opcode (pstate, OP_VAR_VALUE);
622 else if ($1.is_a_field_of_this)
624 /* TODO(dje): Can we get here?
625 E.g., via a mix of c++ and go? */
626 gdb_assert_not_reached ("go with `this' field");
630 struct bound_minimal_symbol msymbol;
631 char *arg = copy_name ($1.stoken);
634 lookup_bound_minimal_symbol (arg);
635 if (msymbol.minsym != NULL)
636 write_exp_msymbol (pstate, msymbol);
637 else if (!have_full_symbols ()
638 && !have_partial_symbols ())
639 error (_("No symbol table is loaded. "
640 "Use the \"file\" command."));
642 error (_("No symbol \"%s\" in current context."),
643 copy_name ($1.stoken));
649 method_exp: PACKAGENAME '.' name '.' name
655 type /* Implements (approximately): [*] type-specifier */
657 { $$ = lookup_pointer_type ($2); }
661 | STRUCT_KEYWORD name
662 { $$ = lookup_struct (copy_name ($2),
663 expression_context_block); }
666 { $$ = builtin_go_type (parse_gdbarch (pstate))
671 name : NAME { $$ = $1.stoken; }
672 | TYPENAME { $$ = $1.stoken; }
673 | NAME_OR_INT { $$ = $1.stoken; }
679 /* These would be useful if name_not_typename was useful, but it is just
680 a fake for "variable", so these cause reduce/reduce conflicts because
681 the parser can't tell whether NAME_OR_INT is a name_not_typename (=variable,
682 =exp) or just an exp. If name_not_typename was ever used in an lvalue
683 context where only a name could occur, this might be useful.
690 /* Wrapper on parse_c_float to get the type right for Go. */
693 parse_go_float (struct gdbarch *gdbarch, const char *p, int len,
694 DOUBLEST *d, struct type **t)
696 int result = parse_c_float (gdbarch, p, len, d, t);
697 const struct builtin_type *builtin_types = builtin_type (gdbarch);
698 const struct builtin_go_type *builtin_go_types = builtin_go_type (gdbarch);
700 if (*t == builtin_types->builtin_float)
701 *t = builtin_go_types->builtin_float32;
702 else if (*t == builtin_types->builtin_double)
703 *t = builtin_go_types->builtin_float64;
708 /* Take care of parsing a number (anything that starts with a digit).
709 Set yylval and return the token type; update lexptr.
710 LEN is the number of characters in it. */
712 /* FIXME: Needs some error checking for the float case. */
713 /* FIXME(dje): IWBN to use c-exp.y's parse_number if we could.
714 That will require moving the guts into a function that we both call
715 as our YYSTYPE is different than c-exp.y's */
718 parse_number (struct parser_state *par_state,
719 const char *p, int len, int parsed_float, YYSTYPE *putithere)
721 /* FIXME: Shouldn't these be unsigned? We don't deal with negative values
722 here, and we do kind of silly things like cast to unsigned. */
729 int base = input_radix;
732 /* Number of "L" suffixes encountered. */
735 /* We have found a "L" or "U" suffix. */
736 int found_suffix = 0;
739 struct type *signed_type;
740 struct type *unsigned_type;
744 if (! parse_go_float (parse_gdbarch (par_state), p, len,
745 &putithere->typed_val_float.dval,
746 &putithere->typed_val_float.type))
751 /* Handle base-switching prefixes 0x, 0t, 0d, 0. */
795 if (c >= 'A' && c <= 'Z')
797 if (c != 'l' && c != 'u')
799 if (c >= '0' && c <= '9')
807 if (base > 10 && c >= 'a' && c <= 'f')
811 n += i = c - 'a' + 10;
824 return ERROR; /* Char not a digit */
827 return ERROR; /* Invalid digit in this base. */
829 /* Portably test for overflow (only works for nonzero values, so make
830 a second check for zero). FIXME: Can't we just make n and prevn
831 unsigned and avoid this? */
832 if (c != 'l' && c != 'u' && (prevn >= n) && n != 0)
833 unsigned_p = 1; /* Try something unsigned. */
835 /* Portably test for unsigned overflow.
836 FIXME: This check is wrong; for example it doesn't find overflow
837 on 0x123456789 when LONGEST is 32 bits. */
838 if (c != 'l' && c != 'u' && n != 0)
840 if ((unsigned_p && (ULONGEST) prevn >= (ULONGEST) n))
841 error (_("Numeric constant too large."));
846 /* An integer constant is an int, a long, or a long long. An L
847 suffix forces it to be long; an LL suffix forces it to be long
848 long. If not forced to a larger size, it gets the first type of
849 the above that it fits in. To figure out whether it fits, we
850 shift it right and see whether anything remains. Note that we
851 can't shift sizeof (LONGEST) * HOST_CHAR_BIT bits or more in one
852 operation, because many compilers will warn about such a shift
853 (which always produces a zero result). Sometimes gdbarch_int_bit
854 or gdbarch_long_bit will be that big, sometimes not. To deal with
855 the case where it is we just always shift the value more than
856 once, with fewer bits each time. */
858 un = (ULONGEST)n >> 2;
860 && (un >> (gdbarch_int_bit (parse_gdbarch (par_state)) - 2)) == 0)
863 = ((ULONGEST)1) << (gdbarch_int_bit (parse_gdbarch (par_state)) - 1);
865 /* A large decimal (not hex or octal) constant (between INT_MAX
866 and UINT_MAX) is a long or unsigned long, according to ANSI,
867 never an unsigned int, but this code treats it as unsigned
868 int. This probably should be fixed. GCC gives a warning on
871 unsigned_type = parse_type (par_state)->builtin_unsigned_int;
872 signed_type = parse_type (par_state)->builtin_int;
875 && (un >> (gdbarch_long_bit (parse_gdbarch (par_state)) - 2)) == 0)
878 = ((ULONGEST)1) << (gdbarch_long_bit (parse_gdbarch (par_state)) - 1);
879 unsigned_type = parse_type (par_state)->builtin_unsigned_long;
880 signed_type = parse_type (par_state)->builtin_long;
885 if (sizeof (ULONGEST) * HOST_CHAR_BIT
886 < gdbarch_long_long_bit (parse_gdbarch (par_state)))
887 /* A long long does not fit in a LONGEST. */
888 shift = (sizeof (ULONGEST) * HOST_CHAR_BIT - 1);
890 shift = (gdbarch_long_long_bit (parse_gdbarch (par_state)) - 1);
891 high_bit = (ULONGEST) 1 << shift;
892 unsigned_type = parse_type (par_state)->builtin_unsigned_long_long;
893 signed_type = parse_type (par_state)->builtin_long_long;
896 putithere->typed_val_int.val = n;
898 /* If the high bit of the worked out type is set then this number
899 has to be unsigned. */
901 if (unsigned_p || (n & high_bit))
903 putithere->typed_val_int.type = unsigned_type;
907 putithere->typed_val_int.type = signed_type;
913 /* Temporary obstack used for holding strings. */
914 static struct obstack tempbuf;
915 static int tempbuf_init;
917 /* Parse a string or character literal from TOKPTR. The string or
918 character may be wide or unicode. *OUTPTR is set to just after the
919 end of the literal in the input string. The resulting token is
920 stored in VALUE. This returns a token value, either STRING or
921 CHAR, depending on what was parsed. *HOST_CHARS is set to the
922 number of host characters in the literal. */
925 parse_string_or_char (const char *tokptr, const char **outptr,
926 struct typed_stoken *value, int *host_chars)
930 /* Build the gdb internal form of the input string in tempbuf. Note
931 that the buffer is null byte terminated *only* for the
932 convenience of debugging gdb itself and printing the buffer
933 contents when the buffer contains no embedded nulls. Gdb does
934 not depend upon the buffer being null byte terminated, it uses
935 the length string instead. This allows gdb to handle C strings
936 (as well as strings in other languages) with embedded null
942 obstack_free (&tempbuf, NULL);
943 obstack_init (&tempbuf);
945 /* Skip the quote. */
957 *host_chars += c_parse_escape (&tokptr, &tempbuf);
963 obstack_1grow (&tempbuf, c);
965 /* FIXME: this does the wrong thing with multi-byte host
966 characters. We could use mbrlen here, but that would
967 make "set host-charset" a bit less useful. */
972 if (*tokptr != quote)
975 error (_("Unterminated string in expression."));
977 error (_("Unmatched single quote."));
981 value->type = C_STRING | (quote == '\'' ? C_CHAR : 0); /*FIXME*/
982 value->ptr = obstack_base (&tempbuf);
983 value->length = obstack_object_size (&tempbuf);
987 return quote == '\'' ? CHAR : STRING;
994 enum exp_opcode opcode;
997 static const struct token tokentab3[] =
999 {">>=", ASSIGN_MODIFY, BINOP_RSH},
1000 {"<<=", ASSIGN_MODIFY, BINOP_LSH},
1001 /*{"&^=", ASSIGN_MODIFY, BINOP_BITWISE_ANDNOT}, TODO */
1002 {"...", DOTDOTDOT, OP_NULL},
1005 static const struct token tokentab2[] =
1007 {"+=", ASSIGN_MODIFY, BINOP_ADD},
1008 {"-=", ASSIGN_MODIFY, BINOP_SUB},
1009 {"*=", ASSIGN_MODIFY, BINOP_MUL},
1010 {"/=", ASSIGN_MODIFY, BINOP_DIV},
1011 {"%=", ASSIGN_MODIFY, BINOP_REM},
1012 {"|=", ASSIGN_MODIFY, BINOP_BITWISE_IOR},
1013 {"&=", ASSIGN_MODIFY, BINOP_BITWISE_AND},
1014 {"^=", ASSIGN_MODIFY, BINOP_BITWISE_XOR},
1015 {"++", INCREMENT, BINOP_END},
1016 {"--", DECREMENT, BINOP_END},
1017 /*{"->", RIGHT_ARROW, BINOP_END}, Doesn't exist in Go. */
1018 {"<-", LEFT_ARROW, BINOP_END},
1019 {"&&", ANDAND, BINOP_END},
1020 {"||", OROR, BINOP_END},
1021 {"<<", LSH, BINOP_END},
1022 {">>", RSH, BINOP_END},
1023 {"==", EQUAL, BINOP_END},
1024 {"!=", NOTEQUAL, BINOP_END},
1025 {"<=", LEQ, BINOP_END},
1026 {">=", GEQ, BINOP_END},
1027 /*{"&^", ANDNOT, BINOP_END}, TODO */
1030 /* Identifier-like tokens. */
1031 static const struct token ident_tokens[] =
1033 {"true", TRUE_KEYWORD, OP_NULL},
1034 {"false", FALSE_KEYWORD, OP_NULL},
1035 {"nil", NIL_KEYWORD, OP_NULL},
1036 {"const", CONST_KEYWORD, OP_NULL},
1037 {"struct", STRUCT_KEYWORD, OP_NULL},
1038 {"type", TYPE_KEYWORD, OP_NULL},
1039 {"interface", INTERFACE_KEYWORD, OP_NULL},
1040 {"chan", CHAN_KEYWORD, OP_NULL},
1041 {"byte", BYTE_KEYWORD, OP_NULL}, /* An alias of uint8. */
1042 {"len", LEN_KEYWORD, OP_NULL},
1043 {"cap", CAP_KEYWORD, OP_NULL},
1044 {"new", NEW_KEYWORD, OP_NULL},
1045 {"iota", IOTA_KEYWORD, OP_NULL},
1048 /* This is set if a NAME token appeared at the very end of the input
1049 string, with no whitespace separating the name from the EOF. This
1050 is used only when parsing to do field name completion. */
1051 static int saw_name_at_eof;
1053 /* This is set if the previously-returned token was a structure
1054 operator -- either '.' or ARROW. This is used only when parsing to
1055 do field name completion. */
1056 static int last_was_structop;
1058 /* Read one token, getting characters through lexptr. */
1061 lex_one_token (struct parser_state *par_state)
1066 const char *tokstart;
1067 int saw_structop = last_was_structop;
1070 last_was_structop = 0;
1074 prev_lexptr = lexptr;
1077 /* See if it is a special token of length 3. */
1078 for (i = 0; i < sizeof (tokentab3) / sizeof (tokentab3[0]); i++)
1079 if (strncmp (tokstart, tokentab3[i].operator, 3) == 0)
1082 yylval.opcode = tokentab3[i].opcode;
1083 return tokentab3[i].token;
1086 /* See if it is a special token of length 2. */
1087 for (i = 0; i < sizeof (tokentab2) / sizeof (tokentab2[0]); i++)
1088 if (strncmp (tokstart, tokentab2[i].operator, 2) == 0)
1091 yylval.opcode = tokentab2[i].opcode;
1092 /* NOTE: -> doesn't exist in Go, so we don't need to watch for
1093 setting last_was_structop here. */
1094 return tokentab2[i].token;
1097 switch (c = *tokstart)
1100 if (saw_name_at_eof)
1102 saw_name_at_eof = 0;
1105 else if (saw_structop)
1124 if (paren_depth == 0)
1131 if (comma_terminates
1132 && paren_depth == 0)
1138 /* Might be a floating point number. */
1139 if (lexptr[1] < '0' || lexptr[1] > '9')
1141 if (parse_completion)
1142 last_was_structop = 1;
1143 goto symbol; /* Nope, must be a symbol. */
1145 /* FALL THRU into number case. */
1158 /* It's a number. */
1159 int got_dot = 0, got_e = 0, toktype;
1160 const char *p = tokstart;
1161 int hex = input_radix > 10;
1163 if (c == '0' && (p[1] == 'x' || p[1] == 'X'))
1171 /* This test includes !hex because 'e' is a valid hex digit
1172 and thus does not indicate a floating point number when
1173 the radix is hex. */
1174 if (!hex && !got_e && (*p == 'e' || *p == 'E'))
1175 got_dot = got_e = 1;
1176 /* This test does not include !hex, because a '.' always indicates
1177 a decimal floating point number regardless of the radix. */
1178 else if (!got_dot && *p == '.')
1180 else if (got_e && (p[-1] == 'e' || p[-1] == 'E')
1181 && (*p == '-' || *p == '+'))
1182 /* This is the sign of the exponent, not the end of the
1185 /* We will take any letters or digits. parse_number will
1186 complain if past the radix, or if L or U are not final. */
1187 else if ((*p < '0' || *p > '9')
1188 && ((*p < 'a' || *p > 'z')
1189 && (*p < 'A' || *p > 'Z')))
1192 toktype = parse_number (par_state, tokstart, p - tokstart,
1193 got_dot|got_e, &yylval);
1194 if (toktype == ERROR)
1196 char *err_copy = (char *) alloca (p - tokstart + 1);
1198 memcpy (err_copy, tokstart, p - tokstart);
1199 err_copy[p - tokstart] = 0;
1200 error (_("Invalid number \"%s\"."), err_copy);
1208 const char *p = &tokstart[1];
1209 size_t len = strlen ("entry");
1211 while (isspace (*p))
1213 if (strncmp (p, "entry", len) == 0 && !isalnum (p[len])
1247 int result = parse_string_or_char (tokstart, &lexptr, &yylval.tsval,
1252 error (_("Empty character constant."));
1253 else if (host_len > 2 && c == '\'')
1256 namelen = lexptr - tokstart - 1;
1259 else if (host_len > 1)
1260 error (_("Invalid character constant."));
1266 if (!(c == '_' || c == '$'
1267 || (c >= 'a' && c <= 'z') || (c >= 'A' && c <= 'Z')))
1268 /* We must have come across a bad character (e.g. ';'). */
1269 error (_("Invalid character '%c' in expression."), c);
1271 /* It's a name. See how long it is. */
1273 for (c = tokstart[namelen];
1274 (c == '_' || c == '$' || (c >= '0' && c <= '9')
1275 || (c >= 'a' && c <= 'z') || (c >= 'A' && c <= 'Z'));)
1277 c = tokstart[++namelen];
1280 /* The token "if" terminates the expression and is NOT removed from
1281 the input stream. It doesn't count if it appears in the
1282 expansion of a macro. */
1284 && tokstart[0] == 'i'
1285 && tokstart[1] == 'f')
1290 /* For the same reason (breakpoint conditions), "thread N"
1291 terminates the expression. "thread" could be an identifier, but
1292 an identifier is never followed by a number without intervening
1294 Handle abbreviations of these, similarly to
1295 breakpoint.c:find_condition_and_thread.
1296 TODO: Watch for "goroutine" here? */
1298 && strncmp (tokstart, "thread", namelen) == 0
1299 && (tokstart[namelen] == ' ' || tokstart[namelen] == '\t'))
1301 const char *p = tokstart + namelen + 1;
1303 while (*p == ' ' || *p == '\t')
1305 if (*p >= '0' && *p <= '9')
1313 yylval.sval.ptr = tokstart;
1314 yylval.sval.length = namelen;
1316 /* Catch specific keywords. */
1317 copy = copy_name (yylval.sval);
1318 for (i = 0; i < sizeof (ident_tokens) / sizeof (ident_tokens[0]); i++)
1319 if (strcmp (copy, ident_tokens[i].operator) == 0)
1321 /* It is ok to always set this, even though we don't always
1322 strictly need to. */
1323 yylval.opcode = ident_tokens[i].opcode;
1324 return ident_tokens[i].token;
1327 if (*tokstart == '$')
1328 return DOLLAR_VARIABLE;
1330 if (parse_completion && *lexptr == '\0')
1331 saw_name_at_eof = 1;
1335 /* An object of this type is pushed on a FIFO by the "outer" lexer. */
1342 DEF_VEC_O (token_and_value);
1344 /* A FIFO of tokens that have been read but not yet returned to the
1346 static VEC (token_and_value) *token_fifo;
1348 /* Non-zero if the lexer should return tokens from the FIFO. */
1351 /* Temporary storage for yylex; this holds symbol names as they are
1353 static struct obstack name_obstack;
1355 /* Build "package.name" in name_obstack.
1356 For convenience of the caller, the name is NUL-terminated,
1357 but the NUL is not included in the recorded length. */
1359 static struct stoken
1360 build_packaged_name (const char *package, int package_len,
1361 const char *name, int name_len)
1363 struct stoken result;
1365 obstack_free (&name_obstack, obstack_base (&name_obstack));
1366 obstack_grow (&name_obstack, package, package_len);
1367 obstack_grow_str (&name_obstack, ".");
1368 obstack_grow (&name_obstack, name, name_len);
1369 obstack_grow (&name_obstack, "", 1);
1370 result.ptr = obstack_base (&name_obstack);
1371 result.length = obstack_object_size (&name_obstack) - 1;
1376 /* Return non-zero if NAME is a package name.
1377 BLOCK is the scope in which to interpret NAME; this can be NULL
1378 to mean the global scope. */
1381 package_name_p (const char *name, const struct block *block)
1384 struct field_of_this_result is_a_field_of_this;
1386 sym = lookup_symbol (name, block, STRUCT_DOMAIN, &is_a_field_of_this);
1389 && SYMBOL_CLASS (sym) == LOC_TYPEDEF
1390 && TYPE_CODE (SYMBOL_TYPE (sym)) == TYPE_CODE_MODULE)
1396 /* Classify a (potential) function in the "unsafe" package.
1397 We fold these into "keywords" to keep things simple, at least until
1398 something more complex is warranted. */
1401 classify_unsafe_function (struct stoken function_name)
1403 char *copy = copy_name (function_name);
1405 if (strcmp (copy, "Sizeof") == 0)
1407 yylval.sval = function_name;
1408 return SIZEOF_KEYWORD;
1411 error (_("Unknown function in `unsafe' package: %s"), copy);
1414 /* Classify token(s) "name1.name2" where name1 is known to be a package.
1415 The contents of the token are in `yylval'.
1416 Updates yylval and returns the new token type.
1418 The result is one of NAME, NAME_OR_INT, or TYPENAME. */
1421 classify_packaged_name (const struct block *block)
1425 struct field_of_this_result is_a_field_of_this;
1427 copy = copy_name (yylval.sval);
1429 sym = lookup_symbol (copy, block, VAR_DOMAIN, &is_a_field_of_this);
1433 yylval.ssym.sym = sym;
1434 yylval.ssym.is_a_field_of_this = is_a_field_of_this.type != NULL;
1440 /* Classify a NAME token.
1441 The contents of the token are in `yylval'.
1442 Updates yylval and returns the new token type.
1443 BLOCK is the block in which lookups start; this can be NULL
1444 to mean the global scope.
1446 The result is one of NAME, NAME_OR_INT, or TYPENAME. */
1449 classify_name (struct parser_state *par_state, const struct block *block)
1454 struct field_of_this_result is_a_field_of_this;
1456 copy = copy_name (yylval.sval);
1458 /* Try primitive types first so they win over bad/weird debug info. */
1459 type = language_lookup_primitive_type_by_name (parse_language (par_state),
1460 parse_gdbarch (par_state),
1464 /* NOTE: We take advantage of the fact that yylval coming in was a
1465 NAME, and that struct ttype is a compatible extension of struct
1466 stoken, so yylval.tsym.stoken is already filled in. */
1467 yylval.tsym.type = type;
1471 /* TODO: What about other types? */
1473 sym = lookup_symbol (copy, block, VAR_DOMAIN, &is_a_field_of_this);
1477 yylval.ssym.sym = sym;
1478 yylval.ssym.is_a_field_of_this = is_a_field_of_this.type != NULL;
1482 /* If we didn't find a symbol, look again in the current package.
1483 This is to, e.g., make "p global_var" work without having to specify
1484 the package name. We intentionally only looks for objects in the
1488 char *current_package_name = go_block_package_name (block);
1490 if (current_package_name != NULL)
1492 struct stoken sval =
1493 build_packaged_name (current_package_name,
1494 strlen (current_package_name),
1495 copy, strlen (copy));
1497 xfree (current_package_name);
1498 sym = lookup_symbol (sval.ptr, block, VAR_DOMAIN,
1499 &is_a_field_of_this);
1502 yylval.ssym.stoken = sval;
1503 yylval.ssym.sym = sym;
1504 yylval.ssym.is_a_field_of_this = is_a_field_of_this.type != NULL;
1510 /* Input names that aren't symbols but ARE valid hex numbers, when
1511 the input radix permits them, can be names or numbers depending
1512 on the parse. Note we support radixes > 16 here. */
1513 if ((copy[0] >= 'a' && copy[0] < 'a' + input_radix - 10)
1514 || (copy[0] >= 'A' && copy[0] < 'A' + input_radix - 10))
1516 YYSTYPE newlval; /* Its value is ignored. */
1517 int hextype = parse_number (par_state, copy, yylval.sval.length,
1521 yylval.ssym.sym = NULL;
1522 yylval.ssym.is_a_field_of_this = 0;
1527 yylval.ssym.sym = NULL;
1528 yylval.ssym.is_a_field_of_this = 0;
1532 /* This is taken from c-exp.y mostly to get something working.
1533 The basic structure has been kept because we may yet need some of it. */
1538 token_and_value current, next;
1540 if (popping && !VEC_empty (token_and_value, token_fifo))
1542 token_and_value tv = *VEC_index (token_and_value, token_fifo, 0);
1543 VEC_ordered_remove (token_and_value, token_fifo, 0);
1545 /* There's no need to fall through to handle package.name
1546 as that can never happen here. In theory. */
1551 current.token = lex_one_token (pstate);
1553 /* TODO: Need a way to force specifying name1 as a package.
1556 if (current.token != NAME)
1557 return current.token;
1559 /* See if we have "name1 . name2". */
1561 current.value = yylval;
1562 next.token = lex_one_token (pstate);
1563 next.value = yylval;
1565 if (next.token == '.')
1567 token_and_value name2;
1569 name2.token = lex_one_token (pstate);
1570 name2.value = yylval;
1572 if (name2.token == NAME)
1574 /* Ok, we have "name1 . name2". */
1577 copy = copy_name (current.value.sval);
1579 if (strcmp (copy, "unsafe") == 0)
1582 return classify_unsafe_function (name2.value.sval);
1585 if (package_name_p (copy, expression_context_block))
1588 yylval.sval = build_packaged_name (current.value.sval.ptr,
1589 current.value.sval.length,
1590 name2.value.sval.ptr,
1591 name2.value.sval.length);
1592 return classify_packaged_name (expression_context_block);
1596 VEC_safe_push (token_and_value, token_fifo, &next);
1597 VEC_safe_push (token_and_value, token_fifo, &name2);
1601 VEC_safe_push (token_and_value, token_fifo, &next);
1604 /* If we arrive here we don't have a package-qualified name. */
1607 yylval = current.value;
1608 return classify_name (pstate, expression_context_block);
1612 go_parse (struct parser_state *par_state)
1615 struct cleanup *back_to;
1617 /* Setting up the parser state. */
1618 gdb_assert (par_state != NULL);
1621 back_to = make_cleanup (null_cleanup, NULL);
1623 make_cleanup_restore_integer (&yydebug);
1624 make_cleanup_clear_parser_state (&pstate);
1625 yydebug = parser_debug;
1627 /* Initialize some state used by the lexer. */
1628 last_was_structop = 0;
1629 saw_name_at_eof = 0;
1631 VEC_free (token_and_value, token_fifo);
1633 obstack_init (&name_obstack);
1634 make_cleanup_obstack_free (&name_obstack);
1636 result = yyparse ();
1637 do_cleanups (back_to);
1645 lexptr = prev_lexptr;
1647 error (_("A %s in expression, near `%s'."), (msg ? msg : "error"), lexptr);