1 /* YACC parser for Java expressions, for GDB.
2 Copyright (C) 1997-2015 Free Software Foundation, Inc.
4 This file is part of GDB.
6 This program is free software; you can redistribute it and/or modify
7 it under the terms of the GNU General Public License as published by
8 the Free Software Foundation; either version 3 of the License, or
9 (at your option) any later version.
11 This program is distributed in the hope that it will be useful,
12 but WITHOUT ANY WARRANTY; without even the implied warranty of
13 MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the
14 GNU General Public License for more details.
16 You should have received a copy of the GNU General Public License
17 along with this program. If not, see <http://www.gnu.org/licenses/>. */
19 /* Parse a Java expression from text in a string,
20 and return the result as a struct expression pointer.
21 That structure contains arithmetic operations in reverse polish,
22 with constants represented by operations that are followed by special data.
23 See expression.h for the details of the format.
24 What is important here is that it can be built up sequentially
25 during the process of parsing; the lower levels of the tree always
26 come first in the result. Well, almost always; see ArrayAccess.
28 Note that malloc's and realloc's in this file are transformed to
29 xmalloc and xrealloc respectively by the same sed command in the
30 makefile that remaps any other malloc/realloc inserted by the parser
31 generator. Doing this with #defines and trying to control the interaction
32 with include files (<malloc.h> and <stdlib.h> for example) just became
33 too messy, particularly when such includes can be inserted at random
34 times by the parser generator. */
40 #include "expression.h"
42 #include "parser-defs.h"
45 #include "bfd.h" /* Required by objfiles.h. */
46 #include "symfile.h" /* Required by objfiles.h. */
47 #include "objfiles.h" /* For have_full_symbols and have_partial_symbols */
49 #include "completer.h"
51 #define parse_type(ps) builtin_type (parse_gdbarch (ps))
52 #define parse_java_type(ps) builtin_java_type (parse_gdbarch (ps))
54 /* Remap normal yacc parser interface names (yyparse, yylex, yyerror, etc),
55 as well as gratuitiously global symbol names, so we can have multiple
56 yacc generated parsers in gdb. Note that these are only the variables
57 produced by yacc. If other parser generators (bison, byacc, etc) produce
58 additional global names that conflict at link time, then those parser
59 generators need to be fixed instead of adding those names to this list. */
61 #define yymaxdepth java_maxdepth
62 #define yyparse java_parse_internal
63 #define yylex java_lex
64 #define yyerror java_error
65 #define yylval java_lval
66 #define yychar java_char
67 #define yydebug java_debug
68 #define yypact java_pact
71 #define yydef java_def
72 #define yychk java_chk
73 #define yypgo java_pgo
74 #define yyact java_act
75 #define yyexca java_exca
76 #define yyerrflag java_errflag
77 #define yynerrs java_nerrs
81 #define yy_yys java_yys
82 #define yystate java_state
83 #define yytmp java_tmp
85 #define yy_yyv java_yyv
86 #define yyval java_val
87 #define yylloc java_lloc
88 #define yyreds java_reds /* With YYDEBUG defined */
89 #define yytoks java_toks /* With YYDEBUG defined */
90 #define yyname java_name /* With YYDEBUG defined */
91 #define yyrule java_rule /* With YYDEBUG defined */
92 #define yylhs java_yylhs
93 #define yylen java_yylen
94 #define yydefred java_yydefred
95 #define yydgoto java_yydgoto
96 #define yysindex java_yysindex
97 #define yyrindex java_yyrindex
98 #define yygindex java_yygindex
99 #define yytable java_yytable
100 #define yycheck java_yycheck
101 #define yyss java_yyss
102 #define yysslim java_yysslim
103 #define yyssp java_yyssp
104 #define yystacksize java_yystacksize
105 #define yyvs java_yyvs
106 #define yyvsp java_yyvsp
109 #define YYDEBUG 1 /* Default to yydebug support */
112 #define YYFPRINTF parser_fprintf
114 /* The state of the parser, used internally when we are parsing the
117 static struct parser_state *pstate = NULL;
121 static int yylex (void);
123 void yyerror (char *);
125 static struct type *java_type_from_name (struct stoken);
126 static void push_expression_name (struct parser_state *, struct stoken);
127 static void push_fieldnames (struct parser_state *, struct stoken);
129 static struct expression *copy_exp (struct expression *, int);
130 static void insert_exp (struct parser_state *, int, struct expression *);
134 /* Although the yacc "value" of an expression is not used,
135 since the result is stored in the structure being created,
136 other node types do have values. */
153 struct symtoken ssym;
155 enum exp_opcode opcode;
156 struct internalvar *ivar;
161 /* YYSTYPE gets defined by %union */
162 static int parse_number (struct parser_state *, const char *, int,
166 %type <lval> rcurly Dims Dims_opt
167 %type <tval> ClassOrInterfaceType ClassType /* ReferenceType Type ArrayType */
168 %type <tval> IntegralType FloatingPointType NumericType PrimitiveType ArrayType PrimitiveOrArrayType
170 %token <typed_val_int> INTEGER_LITERAL
171 %token <typed_val_float> FLOATING_POINT_LITERAL
173 %token <sval> IDENTIFIER
174 %token <sval> STRING_LITERAL
175 %token <lval> BOOLEAN_LITERAL
176 %token <tsym> TYPENAME
177 %type <sval> Name SimpleName QualifiedName ForcedName
179 /* A NAME_OR_INT is a symbol which is not known in the symbol table,
180 but which would parse as a valid number in the current input radix.
181 E.g. "c" when input_radix==16. Depending on the parse, it will be
182 turned into a name or into a number. */
184 %token <sval> NAME_OR_INT
188 /* Special type cases, put in to allow the parser to distinguish different
190 %token LONG SHORT BYTE INT CHAR BOOLEAN DOUBLE FLOAT
194 %token <opcode> ASSIGN_MODIFY
199 %right '=' ASSIGN_MODIFY
207 %left '<' '>' LEQ GEQ
211 %right INCREMENT DECREMENT
221 type_exp: PrimitiveOrArrayType
223 write_exp_elt_opcode (pstate, OP_TYPE);
224 write_exp_elt_type (pstate, $1);
225 write_exp_elt_opcode (pstate, OP_TYPE);
229 PrimitiveOrArrayType:
237 write_exp_elt_opcode (pstate, OP_STRING);
238 write_exp_string (pstate, $1);
239 write_exp_elt_opcode (pstate, OP_STRING);
245 { write_exp_elt_opcode (pstate, OP_LONG);
246 write_exp_elt_type (pstate, $1.type);
247 write_exp_elt_longcst (pstate, (LONGEST)($1.val));
248 write_exp_elt_opcode (pstate, OP_LONG); }
251 parse_number (pstate, $1.ptr, $1.length, 0, &val);
252 write_exp_elt_opcode (pstate, OP_LONG);
253 write_exp_elt_type (pstate, val.typed_val_int.type);
254 write_exp_elt_longcst (pstate,
255 (LONGEST) val.typed_val_int.val);
256 write_exp_elt_opcode (pstate, OP_LONG);
258 | FLOATING_POINT_LITERAL
259 { write_exp_elt_opcode (pstate, OP_DOUBLE);
260 write_exp_elt_type (pstate, $1.type);
261 write_exp_elt_dblcst (pstate, $1.dval);
262 write_exp_elt_opcode (pstate, OP_DOUBLE); }
264 { write_exp_elt_opcode (pstate, OP_LONG);
265 write_exp_elt_type (pstate,
266 parse_java_type (pstate)->builtin_boolean);
267 write_exp_elt_longcst (pstate, (LONGEST)$1);
268 write_exp_elt_opcode (pstate, OP_LONG); }
282 { $$ = parse_java_type (pstate)->builtin_boolean; }
292 { $$ = parse_java_type (pstate)->builtin_byte; }
294 { $$ = parse_java_type (pstate)->builtin_short; }
296 { $$ = parse_java_type (pstate)->builtin_int; }
298 { $$ = parse_java_type (pstate)->builtin_long; }
300 { $$ = parse_java_type (pstate)->builtin_char; }
305 { $$ = parse_java_type (pstate)->builtin_float; }
307 { $$ = parse_java_type (pstate)->builtin_double; }
317 ClassOrInterfaceType:
319 { $$ = java_type_from_name ($1); }
328 { $$ = java_array_type ($1, $2); }
330 { $$ = java_array_type (java_type_from_name ($1), $2); }
350 { $$.length = $1.length + $3.length + 1;
351 if ($1.ptr + $1.length + 1 == $3.ptr
352 && $1.ptr[$1.length] == '.')
353 $$.ptr = $1.ptr; /* Optimization. */
358 buf = malloc ($$.length + 1);
359 make_cleanup (free, buf);
360 sprintf (buf, "%.*s.%.*s",
361 $1.length, $1.ptr, $3.length, $3.ptr);
368 { write_exp_elt_opcode(OP_TYPE);
369 write_exp_elt_type($1);
370 write_exp_elt_opcode(OP_TYPE);}
374 /* Expressions, including the comma operator. */
376 | exp1 ',' Expression
377 { write_exp_elt_opcode (pstate, BINOP_COMMA); }
382 | ArrayCreationExpression
388 | ClassInstanceCreationExpression
392 | lcurly ArgumentList rcurly
393 { write_exp_elt_opcode (pstate, OP_ARRAY);
394 write_exp_elt_longcst (pstate, (LONGEST) 0);
395 write_exp_elt_longcst (pstate, (LONGEST) $3);
396 write_exp_elt_opcode (pstate, OP_ARRAY); }
401 { start_arglist (); }
406 { $$ = end_arglist () - 1; }
409 ClassInstanceCreationExpression:
410 NEW ClassType '(' ArgumentList_opt ')'
411 { internal_error (__FILE__, __LINE__,
412 _("FIXME - ClassInstanceCreationExpression")); }
418 | ArgumentList ',' Expression
428 ArrayCreationExpression:
429 NEW PrimitiveType DimExprs Dims_opt
430 { internal_error (__FILE__, __LINE__,
431 _("FIXME - ArrayCreationExpression")); }
432 | NEW ClassOrInterfaceType DimExprs Dims_opt
433 { internal_error (__FILE__, __LINE__,
434 _("FIXME - ArrayCreationExpression")); }
460 Primary '.' SimpleName
461 { push_fieldnames (pstate, $3); }
462 | VARIABLE '.' SimpleName
463 { push_fieldnames (pstate, $3); }
464 /*| SUPER '.' SimpleName { FIXME } */
469 { push_expression_name (pstate, $1); }
476 { write_exp_elt_opcode (pstate, OP_FUNCALL);
477 write_exp_elt_longcst (pstate, (LONGEST) end_arglist ());
478 write_exp_elt_opcode (pstate, OP_FUNCALL); }
479 | Primary '.' SimpleName '(' ArgumentList_opt ')'
480 { error (_("Form of method invocation not implemented")); }
481 | SUPER '.' SimpleName '(' ArgumentList_opt ')'
482 { error (_("Form of method invocation not implemented")); }
486 Name '[' Expression ']'
488 /* Emit code for the Name now, then exchange it in the
489 expout array with the Expression's code. We could
490 introduce a OP_SWAP code or a reversed version of
491 BINOP_SUBSCRIPT, but that makes the rest of GDB pay
492 for our parsing kludges. */
493 struct expression *name_expr;
495 push_expression_name (pstate, $1);
496 name_expr = copy_exp (pstate->expout, pstate->expout_ptr);
497 pstate->expout_ptr -= name_expr->nelts;
500 - length_of_subexp (pstate->expout,
504 write_exp_elt_opcode (pstate, BINOP_SUBSCRIPT);
506 | VARIABLE '[' Expression ']'
507 { write_exp_elt_opcode (pstate, BINOP_SUBSCRIPT); }
508 | PrimaryNoNewArray '[' Expression ']'
509 { write_exp_elt_opcode (pstate, BINOP_SUBSCRIPT); }
515 { push_expression_name (pstate, $1); }
517 /* Already written by write_dollar_variable. */
518 | PostIncrementExpression
519 | PostDecrementExpression
522 PostIncrementExpression:
523 PostfixExpression INCREMENT
524 { write_exp_elt_opcode (pstate, UNOP_POSTINCREMENT); }
527 PostDecrementExpression:
528 PostfixExpression DECREMENT
529 { write_exp_elt_opcode (pstate, UNOP_POSTDECREMENT); }
533 PreIncrementExpression
534 | PreDecrementExpression
535 | '+' UnaryExpression
536 | '-' UnaryExpression
537 { write_exp_elt_opcode (pstate, UNOP_NEG); }
538 | '*' UnaryExpression
539 { write_exp_elt_opcode (pstate,
540 UNOP_IND); } /*FIXME not in Java */
541 | UnaryExpressionNotPlusMinus
544 PreIncrementExpression:
545 INCREMENT UnaryExpression
546 { write_exp_elt_opcode (pstate, UNOP_PREINCREMENT); }
549 PreDecrementExpression:
550 DECREMENT UnaryExpression
551 { write_exp_elt_opcode (pstate, UNOP_PREDECREMENT); }
554 UnaryExpressionNotPlusMinus:
556 | '~' UnaryExpression
557 { write_exp_elt_opcode (pstate, UNOP_COMPLEMENT); }
558 | '!' UnaryExpression
559 { write_exp_elt_opcode (pstate, UNOP_LOGICAL_NOT); }
564 '(' PrimitiveType Dims_opt ')' UnaryExpression
565 { write_exp_elt_opcode (pstate, UNOP_CAST);
566 write_exp_elt_type (pstate, java_array_type ($2, $3));
567 write_exp_elt_opcode (pstate, UNOP_CAST); }
568 | '(' Expression ')' UnaryExpressionNotPlusMinus
570 int last_exp_size = length_of_subexp (pstate->expout,
574 int base = pstate->expout_ptr - last_exp_size - 3;
577 || pstate->expout->elts[base+2].opcode != OP_TYPE)
578 error (_("Invalid cast expression"));
579 type = pstate->expout->elts[base+1].type;
580 /* Remove the 'Expression' and slide the
581 UnaryExpressionNotPlusMinus down to replace it. */
582 for (i = 0; i < last_exp_size; i++)
583 pstate->expout->elts[base + i]
584 = pstate->expout->elts[base + i + 3];
585 pstate->expout_ptr -= 3;
586 if (TYPE_CODE (type) == TYPE_CODE_STRUCT)
587 type = lookup_pointer_type (type);
588 write_exp_elt_opcode (pstate, UNOP_CAST);
589 write_exp_elt_type (pstate, type);
590 write_exp_elt_opcode (pstate, UNOP_CAST);
592 | '(' Name Dims ')' UnaryExpressionNotPlusMinus
593 { write_exp_elt_opcode (pstate, UNOP_CAST);
594 write_exp_elt_type (pstate,
595 java_array_type (java_type_from_name
597 write_exp_elt_opcode (pstate, UNOP_CAST); }
601 MultiplicativeExpression:
603 | MultiplicativeExpression '*' UnaryExpression
604 { write_exp_elt_opcode (pstate, BINOP_MUL); }
605 | MultiplicativeExpression '/' UnaryExpression
606 { write_exp_elt_opcode (pstate, BINOP_DIV); }
607 | MultiplicativeExpression '%' UnaryExpression
608 { write_exp_elt_opcode (pstate, BINOP_REM); }
612 MultiplicativeExpression
613 | AdditiveExpression '+' MultiplicativeExpression
614 { write_exp_elt_opcode (pstate, BINOP_ADD); }
615 | AdditiveExpression '-' MultiplicativeExpression
616 { write_exp_elt_opcode (pstate, BINOP_SUB); }
621 | ShiftExpression LSH AdditiveExpression
622 { write_exp_elt_opcode (pstate, BINOP_LSH); }
623 | ShiftExpression RSH AdditiveExpression
624 { write_exp_elt_opcode (pstate, BINOP_RSH); }
625 /* | ShiftExpression >>> AdditiveExpression { FIXME } */
628 RelationalExpression:
630 | RelationalExpression '<' ShiftExpression
631 { write_exp_elt_opcode (pstate, BINOP_LESS); }
632 | RelationalExpression '>' ShiftExpression
633 { write_exp_elt_opcode (pstate, BINOP_GTR); }
634 | RelationalExpression LEQ ShiftExpression
635 { write_exp_elt_opcode (pstate, BINOP_LEQ); }
636 | RelationalExpression GEQ ShiftExpression
637 { write_exp_elt_opcode (pstate, BINOP_GEQ); }
638 /* | RelationalExpresion INSTANCEOF ReferenceType { FIXME } */
643 | EqualityExpression EQUAL RelationalExpression
644 { write_exp_elt_opcode (pstate, BINOP_EQUAL); }
645 | EqualityExpression NOTEQUAL RelationalExpression
646 { write_exp_elt_opcode (pstate, BINOP_NOTEQUAL); }
651 | AndExpression '&' EqualityExpression
652 { write_exp_elt_opcode (pstate, BINOP_BITWISE_AND); }
655 ExclusiveOrExpression:
657 | ExclusiveOrExpression '^' AndExpression
658 { write_exp_elt_opcode (pstate, BINOP_BITWISE_XOR); }
660 InclusiveOrExpression:
661 ExclusiveOrExpression
662 | InclusiveOrExpression '|' ExclusiveOrExpression
663 { write_exp_elt_opcode (pstate, BINOP_BITWISE_IOR); }
666 ConditionalAndExpression:
667 InclusiveOrExpression
668 | ConditionalAndExpression ANDAND InclusiveOrExpression
669 { write_exp_elt_opcode (pstate, BINOP_LOGICAL_AND); }
672 ConditionalOrExpression:
673 ConditionalAndExpression
674 | ConditionalOrExpression OROR ConditionalAndExpression
675 { write_exp_elt_opcode (pstate, BINOP_LOGICAL_OR); }
678 ConditionalExpression:
679 ConditionalOrExpression
680 | ConditionalOrExpression '?' Expression ':' ConditionalExpression
681 { write_exp_elt_opcode (pstate, TERNOP_COND); }
684 AssignmentExpression:
685 ConditionalExpression
690 LeftHandSide '=' ConditionalExpression
691 { write_exp_elt_opcode (pstate, BINOP_ASSIGN); }
692 | LeftHandSide ASSIGN_MODIFY ConditionalExpression
693 { write_exp_elt_opcode (pstate, BINOP_ASSIGN_MODIFY);
694 write_exp_elt_opcode (pstate, $2);
695 write_exp_elt_opcode (pstate, BINOP_ASSIGN_MODIFY); }
700 { push_expression_name (pstate, $1); }
702 /* Already written by write_dollar_variable. */
713 /* Take care of parsing a number (anything that starts with a digit).
714 Set yylval and return the token type; update lexptr.
715 LEN is the number of characters in it. */
717 /*** Needs some error checking for the float case ***/
720 parse_number (struct parser_state *par_state,
721 const char *p, int len, int parsed_float, YYSTYPE *putithere)
724 ULONGEST limit, limit_div_base;
727 int base = input_radix;
736 if (! parse_float (p, len, &putithere->typed_val_float.dval, &suffix))
739 suffix_len = p + len - suffix;
742 putithere->typed_val_float.type
743 = parse_type (par_state)->builtin_double;
744 else if (suffix_len == 1)
746 /* See if it has `f' or `d' suffix (float or double). */
747 if (tolower (*suffix) == 'f')
748 putithere->typed_val_float.type =
749 parse_type (par_state)->builtin_float;
750 else if (tolower (*suffix) == 'd')
751 putithere->typed_val_float.type =
752 parse_type (par_state)->builtin_double;
759 return FLOATING_POINT_LITERAL;
762 /* Handle base-switching prefixes 0x, 0t, 0d, 0 */
794 /* A paranoid calculation of (1<<64)-1. */
795 limit = (ULONGEST)0xffffffff;
796 limit = ((limit << 16) << 16) | limit;
797 if (c == 'l' || c == 'L')
799 type = parse_java_type (par_state)->builtin_long;
804 type = parse_java_type (par_state)->builtin_int;
806 limit_div_base = limit / (ULONGEST) base;
811 if (c >= '0' && c <= '9')
813 else if (c >= 'A' && c <= 'Z')
815 else if (c >= 'a' && c <= 'z')
818 return ERROR; /* Char not a digit */
821 if (n > limit_div_base
822 || (n *= base) > limit - c)
823 error (_("Numeric constant too large"));
827 /* If the type is bigger than a 32-bit signed integer can be, implicitly
828 promote to long. Java does not do this, so mark it as
829 parse_type (par_state)->builtin_uint64 rather than
830 parse_java_type (par_state)->builtin_long.
831 0x80000000 will become -0x80000000 instead of 0x80000000L, because we
832 don't know the sign at this point. */
833 if (type == parse_java_type (par_state)->builtin_int
834 && n > (ULONGEST)0x80000000)
835 type = parse_type (par_state)->builtin_uint64;
837 putithere->typed_val_int.val = n;
838 putithere->typed_val_int.type = type;
840 return INTEGER_LITERAL;
847 enum exp_opcode opcode;
850 static const struct token tokentab3[] =
852 {">>=", ASSIGN_MODIFY, BINOP_RSH},
853 {"<<=", ASSIGN_MODIFY, BINOP_LSH}
856 static const struct token tokentab2[] =
858 {"+=", ASSIGN_MODIFY, BINOP_ADD},
859 {"-=", ASSIGN_MODIFY, BINOP_SUB},
860 {"*=", ASSIGN_MODIFY, BINOP_MUL},
861 {"/=", ASSIGN_MODIFY, BINOP_DIV},
862 {"%=", ASSIGN_MODIFY, BINOP_REM},
863 {"|=", ASSIGN_MODIFY, BINOP_BITWISE_IOR},
864 {"&=", ASSIGN_MODIFY, BINOP_BITWISE_AND},
865 {"^=", ASSIGN_MODIFY, BINOP_BITWISE_XOR},
866 {"++", INCREMENT, BINOP_END},
867 {"--", DECREMENT, BINOP_END},
868 {"&&", ANDAND, BINOP_END},
869 {"||", OROR, BINOP_END},
870 {"<<", LSH, BINOP_END},
871 {">>", RSH, BINOP_END},
872 {"==", EQUAL, BINOP_END},
873 {"!=", NOTEQUAL, BINOP_END},
874 {"<=", LEQ, BINOP_END},
875 {">=", GEQ, BINOP_END}
878 /* Read one token, getting characters through lexptr. */
886 const char *tokstart;
889 static char *tempbuf;
890 static int tempbufsize;
894 prev_lexptr = lexptr;
897 /* See if it is a special token of length 3. */
898 for (i = 0; i < sizeof tokentab3 / sizeof tokentab3[0]; i++)
899 if (strncmp (tokstart, tokentab3[i].operator, 3) == 0)
902 yylval.opcode = tokentab3[i].opcode;
903 return tokentab3[i].token;
906 /* See if it is a special token of length 2. */
907 for (i = 0; i < sizeof tokentab2 / sizeof tokentab2[0]; i++)
908 if (strncmp (tokstart, tokentab2[i].operator, 2) == 0)
911 yylval.opcode = tokentab2[i].opcode;
912 return tokentab2[i].token;
915 switch (c = *tokstart)
927 /* We either have a character constant ('0' or '\177' for example)
928 or we have a quoted symbol reference ('foo(int,int)' in C++
933 c = parse_escape (parse_gdbarch (pstate), &lexptr);
935 error (_("Empty character constant"));
937 yylval.typed_val_int.val = c;
938 yylval.typed_val_int.type = parse_java_type (pstate)->builtin_char;
943 namelen = skip_quoted (tokstart) - tokstart;
946 lexptr = tokstart + namelen;
947 if (lexptr[-1] != '\'')
948 error (_("Unmatched single quote"));
953 error (_("Invalid character constant"));
955 return INTEGER_LITERAL;
963 if (paren_depth == 0)
970 if (comma_terminates && paren_depth == 0)
976 /* Might be a floating point number. */
977 if (lexptr[1] < '0' || lexptr[1] > '9')
978 goto symbol; /* Nope, must be a symbol. */
979 /* FALL THRU into number case. */
993 int got_dot = 0, got_e = 0, toktype;
994 const char *p = tokstart;
995 int hex = input_radix > 10;
997 if (c == '0' && (p[1] == 'x' || p[1] == 'X'))
1002 else if (c == '0' && (p[1]=='t' || p[1]=='T' || p[1]=='d' || p[1]=='D'))
1010 /* This test includes !hex because 'e' is a valid hex digit
1011 and thus does not indicate a floating point number when
1012 the radix is hex. */
1013 if (!hex && !got_e && (*p == 'e' || *p == 'E'))
1014 got_dot = got_e = 1;
1015 /* This test does not include !hex, because a '.' always indicates
1016 a decimal floating point number regardless of the radix. */
1017 else if (!got_dot && *p == '.')
1019 else if (got_e && (p[-1] == 'e' || p[-1] == 'E')
1020 && (*p == '-' || *p == '+'))
1021 /* This is the sign of the exponent, not the end of the
1024 /* We will take any letters or digits. parse_number will
1025 complain if past the radix, or if L or U are not final. */
1026 else if ((*p < '0' || *p > '9')
1027 && ((*p < 'a' || *p > 'z')
1028 && (*p < 'A' || *p > 'Z')))
1031 toktype = parse_number (pstate, tokstart, p - tokstart,
1032 got_dot|got_e, &yylval);
1033 if (toktype == ERROR)
1035 char *err_copy = (char *) alloca (p - tokstart + 1);
1037 memcpy (err_copy, tokstart, p - tokstart);
1038 err_copy[p - tokstart] = 0;
1039 error (_("Invalid number \"%s\""), err_copy);
1070 /* Build the gdb internal form of the input string in tempbuf,
1071 translating any standard C escape forms seen. Note that the
1072 buffer is null byte terminated *only* for the convenience of
1073 debugging gdb itself and printing the buffer contents when
1074 the buffer contains no embedded nulls. Gdb does not depend
1075 upon the buffer being null byte terminated, it uses the length
1076 string instead. This allows gdb to handle C strings (as well
1077 as strings in other languages) with embedded null bytes */
1079 tokptr = ++tokstart;
1083 /* Grow the static temp buffer if necessary, including allocating
1084 the first one on demand. */
1085 if (tempbufindex + 1 >= tempbufsize)
1087 tempbuf = (char *) realloc (tempbuf, tempbufsize += 64);
1093 /* Do nothing, loop will terminate. */
1097 c = parse_escape (parse_gdbarch (pstate), &tokptr);
1102 tempbuf[tempbufindex++] = c;
1105 tempbuf[tempbufindex++] = *tokptr++;
1108 } while ((*tokptr != '"') && (*tokptr != '\0'));
1109 if (*tokptr++ != '"')
1111 error (_("Unterminated string in expression"));
1113 tempbuf[tempbufindex] = '\0'; /* See note above */
1114 yylval.sval.ptr = tempbuf;
1115 yylval.sval.length = tempbufindex;
1117 return (STRING_LITERAL);
1120 if (!(c == '_' || c == '$'
1121 || (c >= 'a' && c <= 'z') || (c >= 'A' && c <= 'Z')))
1122 /* We must have come across a bad character (e.g. ';'). */
1123 error (_("Invalid character '%c' in expression"), c);
1125 /* It's a name. See how long it is. */
1127 for (c = tokstart[namelen];
1130 || (c >= '0' && c <= '9')
1131 || (c >= 'a' && c <= 'z')
1132 || (c >= 'A' && c <= 'Z')
1139 while (tokstart[++i] && tokstart[i] != '>');
1140 if (tokstart[i] == '>')
1143 c = tokstart[++namelen];
1146 /* The token "if" terminates the expression and is NOT
1147 removed from the input stream. */
1148 if (namelen == 2 && tokstart[0] == 'i' && tokstart[1] == 'f')
1157 /* Catch specific keywords. Should be done with a data structure. */
1161 if (strncmp (tokstart, "boolean", 7) == 0)
1165 if (strncmp (tokstart, "double", 6) == 0)
1169 if (strncmp (tokstart, "short", 5) == 0)
1171 if (strncmp (tokstart, "false", 5) == 0)
1174 return BOOLEAN_LITERAL;
1176 if (strncmp (tokstart, "super", 5) == 0)
1178 if (strncmp (tokstart, "float", 5) == 0)
1182 if (strncmp (tokstart, "long", 4) == 0)
1184 if (strncmp (tokstart, "byte", 4) == 0)
1186 if (strncmp (tokstart, "char", 4) == 0)
1188 if (strncmp (tokstart, "true", 4) == 0)
1191 return BOOLEAN_LITERAL;
1195 if (strncmp (tokstart, "int", 3) == 0)
1197 if (strncmp (tokstart, "new", 3) == 0)
1204 yylval.sval.ptr = tokstart;
1205 yylval.sval.length = namelen;
1207 if (*tokstart == '$')
1209 write_dollar_variable (pstate, yylval.sval);
1213 /* Input names that aren't symbols but ARE valid hex numbers,
1214 when the input radix permits them, can be names or numbers
1215 depending on the parse. Note we support radixes > 16 here. */
1216 if (((tokstart[0] >= 'a' && tokstart[0] < 'a' + input_radix - 10) ||
1217 (tokstart[0] >= 'A' && tokstart[0] < 'A' + input_radix - 10)))
1219 YYSTYPE newlval; /* Its value is ignored. */
1220 int hextype = parse_number (pstate, tokstart, namelen, 0, &newlval);
1221 if (hextype == INTEGER_LITERAL)
1228 java_parse (struct parser_state *par_state)
1231 struct cleanup *c = make_cleanup_clear_parser_state (&pstate);
1233 /* Setting up the parser state. */
1234 gdb_assert (par_state != NULL);
1237 result = yyparse ();
1247 lexptr = prev_lexptr;
1250 error (_("%s: near `%s'"), msg, lexptr);
1252 error (_("error in expression, near `%s'"), lexptr);
1255 static struct type *
1256 java_type_from_name (struct stoken name)
1258 char *tmp = copy_name (name);
1259 struct type *typ = java_lookup_class (tmp);
1260 if (typ == NULL || TYPE_CODE (typ) != TYPE_CODE_STRUCT)
1261 error (_("No class named `%s'"), tmp);
1265 /* If NAME is a valid variable name in this scope, push it and return 1.
1266 Otherwise, return 0. */
1269 push_variable (struct parser_state *par_state, struct stoken name)
1271 char *tmp = copy_name (name);
1272 struct field_of_this_result is_a_field_of_this;
1275 sym = lookup_symbol (tmp, expression_context_block, VAR_DOMAIN,
1276 &is_a_field_of_this);
1277 if (sym && SYMBOL_CLASS (sym) != LOC_TYPEDEF)
1279 if (symbol_read_needs_frame (sym))
1281 if (innermost_block == 0 ||
1282 contained_in (block_found, innermost_block))
1283 innermost_block = block_found;
1286 write_exp_elt_opcode (par_state, OP_VAR_VALUE);
1287 /* We want to use the selected frame, not another more inner frame
1288 which happens to be in the same block. */
1289 write_exp_elt_block (par_state, NULL);
1290 write_exp_elt_sym (par_state, sym);
1291 write_exp_elt_opcode (par_state, OP_VAR_VALUE);
1294 if (is_a_field_of_this.type != NULL)
1296 /* it hangs off of `this'. Must not inadvertently convert from a
1297 method call to data ref. */
1298 if (innermost_block == 0 ||
1299 contained_in (block_found, innermost_block))
1300 innermost_block = block_found;
1301 write_exp_elt_opcode (par_state, OP_THIS);
1302 write_exp_elt_opcode (par_state, OP_THIS);
1303 write_exp_elt_opcode (par_state, STRUCTOP_PTR);
1304 write_exp_string (par_state, name);
1305 write_exp_elt_opcode (par_state, STRUCTOP_PTR);
1311 /* Assuming a reference expression has been pushed, emit the
1312 STRUCTOP_PTR ops to access the field named NAME. If NAME is a
1313 qualified name (has '.'), generate a field access for each part. */
1316 push_fieldnames (struct parser_state *par_state, struct stoken name)
1319 struct stoken token;
1320 token.ptr = name.ptr;
1323 if (i == name.length || name.ptr[i] == '.')
1325 /* token.ptr is start of current field name. */
1326 token.length = &name.ptr[i] - token.ptr;
1327 write_exp_elt_opcode (par_state, STRUCTOP_PTR);
1328 write_exp_string (par_state, token);
1329 write_exp_elt_opcode (par_state, STRUCTOP_PTR);
1330 token.ptr += token.length + 1;
1332 if (i >= name.length)
1337 /* Helper routine for push_expression_name.
1338 Handle a qualified name, where DOT_INDEX is the index of the first '.' */
1341 push_qualified_expression_name (struct parser_state *par_state,
1342 struct stoken name, int dot_index)
1344 struct stoken token;
1348 token.ptr = name.ptr;
1349 token.length = dot_index;
1351 if (push_variable (par_state, token))
1353 token.ptr = name.ptr + dot_index + 1;
1354 token.length = name.length - dot_index - 1;
1355 push_fieldnames (par_state, token);
1359 token.ptr = name.ptr;
1362 token.length = dot_index;
1363 tmp = copy_name (token);
1364 typ = java_lookup_class (tmp);
1367 if (dot_index == name.length)
1369 write_exp_elt_opcode (par_state, OP_TYPE);
1370 write_exp_elt_type (par_state, typ);
1371 write_exp_elt_opcode (par_state, OP_TYPE);
1374 dot_index++; /* Skip '.' */
1375 name.ptr += dot_index;
1376 name.length -= dot_index;
1378 while (dot_index < name.length && name.ptr[dot_index] != '.')
1380 token.ptr = name.ptr;
1381 token.length = dot_index;
1382 write_exp_elt_opcode (par_state, OP_SCOPE);
1383 write_exp_elt_type (par_state, typ);
1384 write_exp_string (par_state, token);
1385 write_exp_elt_opcode (par_state, OP_SCOPE);
1386 if (dot_index < name.length)
1389 name.ptr += dot_index;
1390 name.length -= dot_index;
1391 push_fieldnames (par_state, name);
1395 else if (dot_index >= name.length)
1397 dot_index++; /* Skip '.' */
1398 while (dot_index < name.length && name.ptr[dot_index] != '.')
1401 error (_("unknown type `%.*s'"), name.length, name.ptr);
1404 /* Handle Name in an expression (or LHS).
1405 Handle VAR, TYPE, TYPE.FIELD1....FIELDN and VAR.FIELD1....FIELDN. */
1408 push_expression_name (struct parser_state *par_state, struct stoken name)
1414 for (i = 0; i < name.length; i++)
1416 if (name.ptr[i] == '.')
1418 /* It's a Qualified Expression Name. */
1419 push_qualified_expression_name (par_state, name, i);
1424 /* It's a Simple Expression Name. */
1426 if (push_variable (par_state, name))
1428 tmp = copy_name (name);
1429 typ = java_lookup_class (tmp);
1432 write_exp_elt_opcode (par_state, OP_TYPE);
1433 write_exp_elt_type (par_state, typ);
1434 write_exp_elt_opcode (par_state, OP_TYPE);
1438 struct bound_minimal_symbol msymbol;
1440 msymbol = lookup_bound_minimal_symbol (tmp);
1441 if (msymbol.minsym != NULL)
1442 write_exp_msymbol (par_state, msymbol);
1443 else if (!have_full_symbols () && !have_partial_symbols ())
1444 error (_("No symbol table is loaded. Use the \"file\" command"));
1446 error (_("No symbol \"%s\" in current context."), tmp);
1452 /* The following two routines, copy_exp and insert_exp, aren't specific to
1453 Java, so they could go in parse.c, but their only purpose is to support
1454 the parsing kludges we use in this file, so maybe it's best to isolate
1457 /* Copy the expression whose last element is at index ENDPOS - 1 in EXPR
1458 into a freshly malloc'ed struct expression. Its language_defn is set
1460 static struct expression *
1461 copy_exp (struct expression *expr, int endpos)
1463 int len = length_of_subexp (expr, endpos);
1464 struct expression *new
1465 = (struct expression *) malloc (sizeof (*new) + EXP_ELEM_TO_BYTES (len));
1468 memcpy (new->elts, expr->elts + endpos - len, EXP_ELEM_TO_BYTES (len));
1469 new->language_defn = 0;
1474 /* Insert the expression NEW into the current expression (expout) at POS. */
1476 insert_exp (struct parser_state *par_state, int pos, struct expression *new)
1478 int newlen = new->nelts;
1481 /* Grow expout if necessary. In this function's only use at present,
1482 this should never be necessary. */
1483 increase_expout_size (par_state, newlen);
1485 for (i = par_state->expout_ptr - 1; i >= pos; i--)
1486 par_state->expout->elts[i + newlen] = par_state->expout->elts[i];
1488 memcpy (par_state->expout->elts + pos, new->elts,
1489 EXP_ELEM_TO_BYTES (newlen));
1490 par_state->expout_ptr += newlen;