1 /* YACC parser for Go expressions, for GDB.
3 Copyright (C) 2012-2021 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 */
69 #define parse_type(ps) builtin_type (ps->gdbarch ())
71 /* Remap normal yacc parser interface names (yyparse, yylex, yyerror,
73 #define GDB_YY_REMAP_PREFIX go_
76 /* The state of the parser, used internally when we are parsing the
79 static struct parser_state *pstate = NULL;
83 static int yylex (void);
85 static void yyerror (const char *);
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. */
105 struct symtoken ssym;
107 struct typed_stoken tsval;
110 enum exp_opcode opcode;
111 struct internalvar *ivar;
112 struct stoken_vector svec;
116 /* YYSTYPE gets defined by %union. */
117 static int parse_number (struct parser_state *,
118 const char *, int, int, YYSTYPE *);
120 using namespace expr;
123 %type <voidval> exp exp1 type_exp start variable lcurly
127 %token <typed_val_int> INT
128 %token <typed_val_float> FLOAT
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. */
138 %token <tsval> RAW_STRING
139 %token <tsval> STRING
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
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
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
159 %token IOTA_KEYWORD NIL_KEYWORD
165 /* Special type cases. */
166 %token BYTE_KEYWORD /* An alias of uint8. */
168 %token <sval> DOLLAR_VARIABLE
170 %token <opcode> ASSIGN_MODIFY
174 %right '=' ASSIGN_MODIFY
183 %left '<' '>' LEQ GEQ
188 %right UNARY INCREMENT DECREMENT
189 %right LEFT_ARROW '.' '[' '('
199 { pstate->push_new<type_operation> ($1); }
202 /* Expressions, including the comma operator. */
205 { pstate->wrap2<comma_operation> (); }
208 /* Expressions, not including the comma operator. */
209 exp : '*' exp %prec UNARY
210 { pstate->wrap<unop_ind_operation> (); }
213 exp : '&' exp %prec UNARY
214 { pstate->wrap<unop_addr_operation> (); }
217 exp : '-' exp %prec UNARY
218 { pstate->wrap<unary_neg_operation> (); }
221 exp : '+' exp %prec UNARY
222 { pstate->wrap<unary_plus_operation> (); }
225 exp : '!' exp %prec UNARY
226 { pstate->wrap<unary_logical_not_operation> (); }
229 exp : '^' exp %prec UNARY
230 { pstate->wrap<unary_complement_operation> (); }
233 exp : exp INCREMENT %prec UNARY
234 { pstate->wrap<postinc_operation> (); }
237 exp : exp DECREMENT %prec UNARY
238 { pstate->wrap<postdec_operation> (); }
241 /* foo->bar is not in Go. May want as a gdb extension. Later. */
243 exp : exp '.' name_not_typename
245 pstate->push_new<structop_operation>
246 (pstate->pop (), copy_name ($3.stoken));
250 exp : exp '.' name_not_typename COMPLETE
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));
260 exp : exp '.' COMPLETE
262 structop_base_operation *op
263 = new structop_operation (pstate->pop (), "");
264 pstate->mark_struct_expression (op);
265 pstate->push (operation_up (op));
269 exp : exp '[' exp1 ']'
270 { pstate->wrap2<subscript_operation> (); }
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
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));
287 { pstate->start_arglist (); }
294 { pstate->arglist_len = 1; }
297 arglist : arglist ',' exp %prec ABOVE_COMMA
298 { pstate->arglist_len++; }
302 { $$ = pstate->end_arglist () - 1; }
305 exp : lcurly type rcurly exp %prec UNARY
307 pstate->push_new<unop_memval_operation>
308 (pstate->pop (), $2);
312 exp : type '(' exp ')' %prec UNARY
314 pstate->push_new<unop_cast_operation>
315 (pstate->pop (), $1);
323 /* Binary operators in order of decreasing precedence. */
326 { pstate->wrap2<repeat_operation> (); }
330 { pstate->wrap2<mul_operation> (); }
334 { pstate->wrap2<div_operation> (); }
338 { pstate->wrap2<rem_operation> (); }
342 { pstate->wrap2<add_operation> (); }
346 { pstate->wrap2<sub_operation> (); }
350 { pstate->wrap2<lsh_operation> (); }
354 { pstate->wrap2<rsh_operation> (); }
358 { pstate->wrap2<equal_operation> (); }
361 exp : exp NOTEQUAL exp
362 { pstate->wrap2<notequal_operation> (); }
366 { pstate->wrap2<leq_operation> (); }
370 { pstate->wrap2<geq_operation> (); }
374 { pstate->wrap2<less_operation> (); }
378 { pstate->wrap2<gtr_operation> (); }
382 { pstate->wrap2<bitwise_and_operation> (); }
386 { pstate->wrap2<bitwise_xor_operation> (); }
390 { pstate->wrap2<bitwise_ior_operation> (); }
394 { pstate->wrap2<logical_and_operation> (); }
398 { pstate->wrap2<logical_or_operation> (); }
401 exp : exp '?' exp ':' exp %prec '?'
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),
413 { pstate->wrap2<assign_operation> (); }
416 exp : exp ASSIGN_MODIFY exp
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));
427 pstate->push_new<long_const_operation>
434 struct stoken_vector vec;
437 pstate->push_c_string ($1.type, &vec);
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);
455 std::copy (std::begin ($1.val), std::end ($1.val),
457 pstate->push_new<float_const_operation> ($1.type, data);
464 exp : DOLLAR_VARIABLE
466 pstate->push_dollar ($1);
470 exp : SIZEOF_KEYWORD '(' type ')' %prec UNARY
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));
482 exp : SIZEOF_KEYWORD '(' exp ')' %prec UNARY
484 /* TODO(dje): Go objects in structs. */
485 pstate->wrap<unop_sizeof_operation> ();
491 /* We copy the string here, and not in the
492 lexer, to guarantee that we do not leak a
494 /* Note that we NUL-terminate here, but just
496 struct typed_stoken *vec = XNEW (struct typed_stoken);
501 vec->length = $1.length;
502 vec->ptr = (char *) malloc ($1.length + 1);
503 memcpy (vec->ptr, $1.ptr, $1.length + 1);
506 | string_exp '+' STRING
508 /* Note that we NUL-terminate here, but just
512 $$.tokens = XRESIZEVEC (struct typed_stoken,
515 p = (char *) malloc ($3.length + 1);
516 memcpy (p, $3.ptr, $3.length + 1);
518 $$.tokens[$$.len - 1].type = $3.type;
519 $$.tokens[$$.len - 1].length = $3.length;
520 $$.tokens[$$.len - 1].ptr = p;
524 exp : string_exp %prec ABOVE_COMMA
529 pstate->push_c_string (0, &$1);
530 for (i = 0; i < $1.len; ++i)
531 free ($1.tokens[i].ptr);
537 { pstate->push_new<bool_operation> ($1); }
541 { pstate->push_new<bool_operation> ($1); }
544 variable: name_not_typename ENTRY
545 { struct symbol *sym = $1.sym.symbol;
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 ());
554 pstate->push_new<var_entry_value_operation> (sym);
558 variable: name_not_typename
559 { struct block_symbol sym = $1.sym;
563 if (symbol_read_needs_frame (sym.symbol))
564 pstate->block_tracker->update (sym);
566 pstate->push_new<var_value_operation>
567 (sym.symbol, sym.block);
569 else if ($1.is_a_field_of_this)
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");
577 struct bound_minimal_symbol msymbol;
578 std::string arg = copy_name ($1.stoken);
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."));
590 error (_("No symbol \"%s\" in current context."),
597 method_exp: PACKAGENAME '.' name '.' name
603 type /* Implements (approximately): [*] type-specifier */
605 { $$ = lookup_pointer_type ($2); }
609 | STRUCT_KEYWORD name
610 { $$ = lookup_struct (copy_name ($2),
611 expression_context_block); }
614 { $$ = builtin_go_type (pstate->gdbarch ())
619 name : NAME { $$ = $1.stoken; }
620 | TYPENAME { $$ = $1.stoken; }
621 | NAME_OR_INT { $$ = $1.stoken; }
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.
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. */
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 */
648 parse_number (struct parser_state *par_state,
649 const char *p, int len, int parsed_float, YYSTYPE *putithere)
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. */
659 int base = input_radix;
662 /* Number of "L" suffixes encountered. */
665 /* We have found a "L" or "U" suffix. */
666 int found_suffix = 0;
669 struct type *signed_type;
670 struct type *unsigned_type;
674 const struct builtin_go_type *builtin_go_types
675 = builtin_go_type (par_state->gdbarch ());
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')
681 putithere->typed_val_float.type
682 = builtin_go_types->builtin_float32;
685 else if (len >= 1 && tolower (p[len - 1]) == 'l')
687 putithere->typed_val_float.type
688 = parse_type (par_state)->builtin_long_double;
691 /* Default type for floating-point literals is float64. */
694 putithere->typed_val_float.type
695 = builtin_go_types->builtin_float64;
698 if (!parse_float (p, len,
699 putithere->typed_val_float.type,
700 putithere->typed_val_float.val))
705 /* Handle base-switching prefixes 0x, 0t, 0d, 0. */
749 if (c >= 'A' && c <= 'Z')
751 if (c != 'l' && c != 'u')
753 if (c >= '0' && c <= '9')
761 if (base > 10 && c >= 'a' && c <= 'f')
765 n += i = c - 'a' + 10;
778 return ERROR; /* Char not a digit */
781 return ERROR; /* Invalid digit in this base. */
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. */
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)
794 if ((unsigned_p && (ULONGEST) prevn >= (ULONGEST) n))
795 error (_("Numeric constant too large."));
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. */
812 un = (ULONGEST)n >> 2;
814 && (un >> (gdbarch_int_bit (par_state->gdbarch ()) - 2)) == 0)
817 = ((ULONGEST)1) << (gdbarch_int_bit (par_state->gdbarch ()) - 1);
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
825 unsigned_type = parse_type (par_state)->builtin_unsigned_int;
826 signed_type = parse_type (par_state)->builtin_int;
829 && (un >> (gdbarch_long_bit (par_state->gdbarch ()) - 2)) == 0)
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;
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);
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;
850 putithere->typed_val_int.val = n;
852 /* If the high bit of the worked out type is set then this number
853 has to be unsigned. */
855 if (unsigned_p || (n & high_bit))
857 putithere->typed_val_int.type = unsigned_type;
861 putithere->typed_val_int.type = signed_type;
867 /* Temporary obstack used for holding strings. */
868 static struct obstack tempbuf;
869 static int tempbuf_init;
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. */
879 parse_string_or_char (const char *tokptr, const char **outptr,
880 struct typed_stoken *value, int *host_chars)
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
896 obstack_free (&tempbuf, NULL);
897 obstack_init (&tempbuf);
899 /* Skip the quote. */
911 *host_chars += c_parse_escape (&tokptr, &tempbuf);
917 obstack_1grow (&tempbuf, c);
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. */
926 if (*tokptr != quote)
929 error (_("Unterminated string in expression."));
931 error (_("Unmatched single quote."));
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);
941 return quote == '\'' ? CHAR : STRING;
948 enum exp_opcode opcode;
951 static const struct token tokentab3[] =
953 {">>=", ASSIGN_MODIFY, BINOP_RSH},
954 {"<<=", ASSIGN_MODIFY, BINOP_LSH},
955 /*{"&^=", ASSIGN_MODIFY, BINOP_BITWISE_ANDNOT}, TODO */
956 {"...", DOTDOTDOT, OP_NULL},
959 static const struct token tokentab2[] =
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 */
984 /* Identifier-like tokens. */
985 static const struct token ident_tokens[] =
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},
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;
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;
1012 /* Depth of parentheses. */
1013 static int paren_depth;
1015 /* Read one token, getting characters through lexptr. */
1018 lex_one_token (struct parser_state *par_state)
1023 const char *tokstart;
1024 int saw_structop = last_was_structop;
1026 last_was_structop = 0;
1030 par_state->prev_lexptr = par_state->lexptr;
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)
1037 par_state->lexptr += 3;
1038 yylval.opcode = tokentab3[i].opcode;
1039 return tokentab3[i].token;
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)
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;
1053 switch (c = *tokstart)
1056 if (saw_name_at_eof)
1058 saw_name_at_eof = 0;
1061 else if (saw_structop)
1069 par_state->lexptr++;
1075 par_state->lexptr++;
1080 if (paren_depth == 0)
1083 par_state->lexptr++;
1087 if (pstate->comma_terminates
1088 && paren_depth == 0)
1090 par_state->lexptr++;
1094 /* Might be a floating point number. */
1095 if (par_state->lexptr[1] < '0' || par_state->lexptr[1] > '9')
1097 if (pstate->parse_completion)
1098 last_was_structop = 1;
1099 goto symbol; /* Nope, must be a symbol. */
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;
1119 if (c == '0' && (p[1] == 'x' || p[1] == 'X'))
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 == '.')
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
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')))
1148 toktype = parse_number (par_state, tokstart, p - tokstart,
1149 got_dot|got_e, &yylval);
1150 if (toktype == ERROR)
1152 char *err_copy = (char *) alloca (p - tokstart + 1);
1154 memcpy (err_copy, tokstart, p - tokstart);
1155 err_copy[p - tokstart] = 0;
1156 error (_("Invalid number \"%s\"."), err_copy);
1158 par_state->lexptr = p;
1164 const char *p = &tokstart[1];
1165 size_t len = strlen ("entry");
1167 while (isspace (*p))
1169 if (strncmp (p, "entry", len) == 0 && !isalnum (p[len])
1172 par_state->lexptr = &p[len];
1195 par_state->lexptr++;
1203 int result = parse_string_or_char (tokstart, &par_state->lexptr,
1204 &yylval.tsval, &host_len);
1208 error (_("Empty character constant."));
1209 else if (host_len > 2 && c == '\'')
1212 namelen = par_state->lexptr - tokstart - 1;
1215 else if (host_len > 1)
1216 error (_("Invalid character constant."));
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);
1227 /* It's a name. See how long it is. */
1229 for (c = tokstart[namelen];
1230 (c == '_' || c == '$' || (c >= '0' && c <= '9')
1231 || (c >= 'a' && c <= 'z') || (c >= 'A' && c <= 'Z'));)
1233 c = tokstart[++namelen];
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. */
1240 && tokstart[0] == 'i'
1241 && tokstart[1] == 'f')
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
1250 Handle abbreviations of these, similarly to
1251 breakpoint.c:find_condition_and_thread.
1252 TODO: Watch for "goroutine" here? */
1254 && strncmp (tokstart, "thread", namelen) == 0
1255 && (tokstart[namelen] == ' ' || tokstart[namelen] == '\t'))
1257 const char *p = tokstart + namelen + 1;
1259 while (*p == ' ' || *p == '\t')
1261 if (*p >= '0' && *p <= '9')
1265 par_state->lexptr += namelen;
1269 yylval.sval.ptr = tokstart;
1270 yylval.sval.length = namelen;
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)
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;
1283 if (*tokstart == '$')
1284 return DOLLAR_VARIABLE;
1286 if (pstate->parse_completion && *par_state->lexptr == '\0')
1287 saw_name_at_eof = 1;
1291 /* An object of this type is pushed on a FIFO by the "outer" lexer. */
1292 struct token_and_value
1298 /* A FIFO of tokens that have been read but not yet returned to the
1300 static std::vector<token_and_value> token_fifo;
1302 /* Non-zero if the lexer should return tokens from the FIFO. */
1305 /* Temporary storage for yylex; this holds symbol names as they are
1307 static auto_obstack name_obstack;
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. */
1313 static struct stoken
1314 build_packaged_name (const char *package, int package_len,
1315 const char *name, int name_len)
1317 struct stoken result;
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;
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. */
1335 package_name_p (const char *name, const struct block *block)
1338 struct field_of_this_result is_a_field_of_this;
1340 sym = lookup_symbol (name, block, STRUCT_DOMAIN, &is_a_field_of_this).symbol;
1343 && SYMBOL_CLASS (sym) == LOC_TYPEDEF
1344 && SYMBOL_TYPE (sym)->code () == TYPE_CODE_MODULE)
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. */
1355 classify_unsafe_function (struct stoken function_name)
1357 std::string copy = copy_name (function_name);
1359 if (copy == "Sizeof")
1361 yylval.sval = function_name;
1362 return SIZEOF_KEYWORD;
1365 error (_("Unknown function in `unsafe' package: %s"), copy.c_str ());
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.
1372 The result is one of NAME, NAME_OR_INT, or TYPENAME. */
1375 classify_packaged_name (const struct block *block)
1377 struct block_symbol sym;
1378 struct field_of_this_result is_a_field_of_this;
1380 std::string copy = copy_name (yylval.sval);
1382 sym = lookup_symbol (copy.c_str (), block, VAR_DOMAIN, &is_a_field_of_this);
1386 yylval.ssym.sym = sym;
1387 yylval.ssym.is_a_field_of_this = is_a_field_of_this.type != NULL;
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.
1399 The result is one of NAME, NAME_OR_INT, or TYPENAME. */
1402 classify_name (struct parser_state *par_state, const struct block *block)
1405 struct block_symbol sym;
1406 struct field_of_this_result is_a_field_of_this;
1408 std::string copy = copy_name (yylval.sval);
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 (),
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;
1423 /* TODO: What about other types? */
1425 sym = lookup_symbol (copy.c_str (), block, VAR_DOMAIN, &is_a_field_of_this);
1429 yylval.ssym.sym = sym;
1430 yylval.ssym.is_a_field_of_this = is_a_field_of_this.type != NULL;
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
1440 char *current_package_name = go_block_package_name (block);
1442 if (current_package_name != NULL)
1444 struct stoken sval =
1445 build_packaged_name (current_package_name,
1446 strlen (current_package_name),
1447 copy.c_str (), copy.size ());
1449 xfree (current_package_name);
1450 sym = lookup_symbol (sval.ptr, block, VAR_DOMAIN,
1451 &is_a_field_of_this);
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;
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))
1468 YYSTYPE newlval; /* Its value is ignored. */
1469 int hextype = parse_number (par_state, copy.c_str (),
1470 yylval.sval.length, 0, &newlval);
1473 yylval.ssym.sym.symbol = NULL;
1474 yylval.ssym.sym.block = NULL;
1475 yylval.ssym.is_a_field_of_this = 0;
1480 yylval.ssym.sym.symbol = NULL;
1481 yylval.ssym.sym.block = NULL;
1482 yylval.ssym.is_a_field_of_this = 0;
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. */
1492 token_and_value current, next;
1494 if (popping && !token_fifo.empty ())
1496 token_and_value tv = token_fifo[0];
1497 token_fifo.erase (token_fifo.begin ());
1499 /* There's no need to fall through to handle package.name
1500 as that can never happen here. In theory. */
1505 current.token = lex_one_token (pstate);
1507 /* TODO: Need a way to force specifying name1 as a package.
1510 if (current.token != NAME)
1511 return current.token;
1513 /* See if we have "name1 . name2". */
1515 current.value = yylval;
1516 next.token = lex_one_token (pstate);
1517 next.value = yylval;
1519 if (next.token == '.')
1521 token_and_value name2;
1523 name2.token = lex_one_token (pstate);
1524 name2.value = yylval;
1526 if (name2.token == NAME)
1528 /* Ok, we have "name1 . name2". */
1529 std::string copy = copy_name (current.value.sval);
1531 if (copy == "unsafe")
1534 return classify_unsafe_function (name2.value.sval);
1537 if (package_name_p (copy.c_str (), pstate->expression_context_block))
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);
1548 token_fifo.push_back (next);
1549 token_fifo.push_back (name2);
1552 token_fifo.push_back (next);
1554 /* If we arrive here we don't have a package-qualified name. */
1557 yylval = current.value;
1558 return classify_name (pstate, pstate->expression_context_block);
1561 /* See language.h. */
1564 go_language::parser (struct parser_state *par_state) const
1566 /* Setting up the parser state. */
1567 scoped_restore pstate_restore = make_scoped_restore (&pstate);
1568 gdb_assert (par_state != NULL);
1571 scoped_restore restore_yydebug = make_scoped_restore (&yydebug,
1574 /* Initialize some state used by the lexer. */
1575 last_was_structop = 0;
1576 saw_name_at_eof = 0;
1579 token_fifo.clear ();
1581 name_obstack.clear ();
1583 int result = yyparse ();
1585 pstate->set_operation (pstate->pop ());
1590 yyerror (const char *msg)
1592 if (pstate->prev_lexptr)
1593 pstate->lexptr = pstate->prev_lexptr;
1595 error (_("A %s in expression, near `%s'."), msg, pstate->lexptr);