1 /* YACC parser for Java expressions, for GDB.
2 Copyright (C) 1997-2014 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. */
41 #include "expression.h"
43 #include "parser-defs.h"
46 #include "bfd.h" /* Required by objfiles.h. */
47 #include "symfile.h" /* Required by objfiles.h. */
48 #include "objfiles.h" /* For have_full_symbols and have_partial_symbols */
50 #include "completer.h"
52 #define parse_type(ps) builtin_type (parse_gdbarch (ps))
53 #define parse_java_type(ps) builtin_java_type (parse_gdbarch (ps))
55 /* Remap normal yacc parser interface names (yyparse, yylex, yyerror, etc),
56 as well as gratuitiously global symbol names, so we can have multiple
57 yacc generated parsers in gdb. Note that these are only the variables
58 produced by yacc. If other parser generators (bison, byacc, etc) produce
59 additional global names that conflict at link time, then those parser
60 generators need to be fixed instead of adding those names to this list. */
62 #define yymaxdepth java_maxdepth
63 #define yyparse java_parse_internal
64 #define yylex java_lex
65 #define yyerror java_error
66 #define yylval java_lval
67 #define yychar java_char
68 #define yydebug java_debug
69 #define yypact java_pact
72 #define yydef java_def
73 #define yychk java_chk
74 #define yypgo java_pgo
75 #define yyact java_act
76 #define yyexca java_exca
77 #define yyerrflag java_errflag
78 #define yynerrs java_nerrs
82 #define yy_yys java_yys
83 #define yystate java_state
84 #define yytmp java_tmp
86 #define yy_yyv java_yyv
87 #define yyval java_val
88 #define yylloc java_lloc
89 #define yyreds java_reds /* With YYDEBUG defined */
90 #define yytoks java_toks /* With YYDEBUG defined */
91 #define yyname java_name /* With YYDEBUG defined */
92 #define yyrule java_rule /* With YYDEBUG defined */
93 #define yylhs java_yylhs
94 #define yylen java_yylen
95 #define yydefred java_yydefred
96 #define yydgoto java_yydgoto
97 #define yysindex java_yysindex
98 #define yyrindex java_yyrindex
99 #define yygindex java_yygindex
100 #define yytable java_yytable
101 #define yycheck java_yycheck
102 #define yyss java_yyss
103 #define yysslim java_yysslim
104 #define yyssp java_yyssp
105 #define yystacksize java_yystacksize
106 #define yyvs java_yyvs
107 #define yyvsp java_yyvsp
110 #define YYDEBUG 1 /* Default to yydebug support */
113 #define YYFPRINTF parser_fprintf
115 /* The state of the parser, used internally when we are parsing the
118 static struct parser_state *pstate = NULL;
122 static int yylex (void);
124 void yyerror (char *);
126 static struct type *java_type_from_name (struct stoken);
127 static void push_expression_name (struct parser_state *, struct stoken);
128 static void push_fieldnames (struct parser_state *, struct stoken);
130 static struct expression *copy_exp (struct expression *, int);
131 static void insert_exp (struct parser_state *, int, struct expression *);
135 /* Although the yacc "value" of an expression is not used,
136 since the result is stored in the structure being created,
137 other node types do have values. */
154 struct symtoken ssym;
156 enum exp_opcode opcode;
157 struct internalvar *ivar;
162 /* YYSTYPE gets defined by %union */
163 static int parse_number (struct parser_state *, const char *, int,
167 %type <lval> rcurly Dims Dims_opt
168 %type <tval> ClassOrInterfaceType ClassType /* ReferenceType Type ArrayType */
169 %type <tval> IntegralType FloatingPointType NumericType PrimitiveType ArrayType PrimitiveOrArrayType
171 %token <typed_val_int> INTEGER_LITERAL
172 %token <typed_val_float> FLOATING_POINT_LITERAL
174 %token <sval> IDENTIFIER
175 %token <sval> STRING_LITERAL
176 %token <lval> BOOLEAN_LITERAL
177 %token <tsym> TYPENAME
178 %type <sval> Name SimpleName QualifiedName ForcedName
180 /* A NAME_OR_INT is a symbol which is not known in the symbol table,
181 but which would parse as a valid number in the current input radix.
182 E.g. "c" when input_radix==16. Depending on the parse, it will be
183 turned into a name or into a number. */
185 %token <sval> NAME_OR_INT
189 /* Special type cases, put in to allow the parser to distinguish different
191 %token LONG SHORT BYTE INT CHAR BOOLEAN DOUBLE FLOAT
195 %token <opcode> ASSIGN_MODIFY
200 %right '=' ASSIGN_MODIFY
208 %left '<' '>' LEQ GEQ
212 %right INCREMENT DECREMENT
222 type_exp: PrimitiveOrArrayType
224 write_exp_elt_opcode (pstate, OP_TYPE);
225 write_exp_elt_type (pstate, $1);
226 write_exp_elt_opcode (pstate, OP_TYPE);
230 PrimitiveOrArrayType:
238 write_exp_elt_opcode (pstate, OP_STRING);
239 write_exp_string (pstate, $1);
240 write_exp_elt_opcode (pstate, OP_STRING);
246 { write_exp_elt_opcode (pstate, OP_LONG);
247 write_exp_elt_type (pstate, $1.type);
248 write_exp_elt_longcst (pstate, (LONGEST)($1.val));
249 write_exp_elt_opcode (pstate, OP_LONG); }
252 parse_number (pstate, $1.ptr, $1.length, 0, &val);
253 write_exp_elt_opcode (pstate, OP_LONG);
254 write_exp_elt_type (pstate, val.typed_val_int.type);
255 write_exp_elt_longcst (pstate,
256 (LONGEST) val.typed_val_int.val);
257 write_exp_elt_opcode (pstate, OP_LONG);
259 | FLOATING_POINT_LITERAL
260 { write_exp_elt_opcode (pstate, OP_DOUBLE);
261 write_exp_elt_type (pstate, $1.type);
262 write_exp_elt_dblcst (pstate, $1.dval);
263 write_exp_elt_opcode (pstate, OP_DOUBLE); }
265 { write_exp_elt_opcode (pstate, OP_LONG);
266 write_exp_elt_type (pstate,
267 parse_java_type (pstate)->builtin_boolean);
268 write_exp_elt_longcst (pstate, (LONGEST)$1);
269 write_exp_elt_opcode (pstate, OP_LONG); }
283 { $$ = parse_java_type (pstate)->builtin_boolean; }
293 { $$ = parse_java_type (pstate)->builtin_byte; }
295 { $$ = parse_java_type (pstate)->builtin_short; }
297 { $$ = parse_java_type (pstate)->builtin_int; }
299 { $$ = parse_java_type (pstate)->builtin_long; }
301 { $$ = parse_java_type (pstate)->builtin_char; }
306 { $$ = parse_java_type (pstate)->builtin_float; }
308 { $$ = parse_java_type (pstate)->builtin_double; }
318 ClassOrInterfaceType:
320 { $$ = java_type_from_name ($1); }
329 { $$ = java_array_type ($1, $2); }
331 { $$ = java_array_type (java_type_from_name ($1), $2); }
351 { $$.length = $1.length + $3.length + 1;
352 if ($1.ptr + $1.length + 1 == $3.ptr
353 && $1.ptr[$1.length] == '.')
354 $$.ptr = $1.ptr; /* Optimization. */
359 buf = malloc ($$.length + 1);
360 make_cleanup (free, buf);
361 sprintf (buf, "%.*s.%.*s",
362 $1.length, $1.ptr, $3.length, $3.ptr);
369 { write_exp_elt_opcode(OP_TYPE);
370 write_exp_elt_type($1);
371 write_exp_elt_opcode(OP_TYPE);}
375 /* Expressions, including the comma operator. */
377 | exp1 ',' Expression
378 { write_exp_elt_opcode (pstate, BINOP_COMMA); }
383 | ArrayCreationExpression
389 | ClassInstanceCreationExpression
393 | lcurly ArgumentList rcurly
394 { write_exp_elt_opcode (pstate, OP_ARRAY);
395 write_exp_elt_longcst (pstate, (LONGEST) 0);
396 write_exp_elt_longcst (pstate, (LONGEST) $3);
397 write_exp_elt_opcode (pstate, OP_ARRAY); }
402 { start_arglist (); }
407 { $$ = end_arglist () - 1; }
410 ClassInstanceCreationExpression:
411 NEW ClassType '(' ArgumentList_opt ')'
412 { internal_error (__FILE__, __LINE__,
413 _("FIXME - ClassInstanceCreationExpression")); }
419 | ArgumentList ',' Expression
429 ArrayCreationExpression:
430 NEW PrimitiveType DimExprs Dims_opt
431 { internal_error (__FILE__, __LINE__,
432 _("FIXME - ArrayCreationExpression")); }
433 | NEW ClassOrInterfaceType DimExprs Dims_opt
434 { internal_error (__FILE__, __LINE__,
435 _("FIXME - ArrayCreationExpression")); }
461 Primary '.' SimpleName
462 { push_fieldnames (pstate, $3); }
463 | VARIABLE '.' SimpleName
464 { push_fieldnames (pstate, $3); }
465 /*| SUPER '.' SimpleName { FIXME } */
470 { push_expression_name (pstate, $1); }
477 { write_exp_elt_opcode (pstate, OP_FUNCALL);
478 write_exp_elt_longcst (pstate, (LONGEST) end_arglist ());
479 write_exp_elt_opcode (pstate, OP_FUNCALL); }
480 | Primary '.' SimpleName '(' ArgumentList_opt ')'
481 { error (_("Form of method invocation not implemented")); }
482 | SUPER '.' SimpleName '(' ArgumentList_opt ')'
483 { error (_("Form of method invocation not implemented")); }
487 Name '[' Expression ']'
489 /* Emit code for the Name now, then exchange it in the
490 expout array with the Expression's code. We could
491 introduce a OP_SWAP code or a reversed version of
492 BINOP_SUBSCRIPT, but that makes the rest of GDB pay
493 for our parsing kludges. */
494 struct expression *name_expr;
496 push_expression_name (pstate, $1);
497 name_expr = copy_exp (pstate->expout, pstate->expout_ptr);
498 pstate->expout_ptr -= name_expr->nelts;
501 - length_of_subexp (pstate->expout,
505 write_exp_elt_opcode (pstate, BINOP_SUBSCRIPT);
507 | VARIABLE '[' Expression ']'
508 { write_exp_elt_opcode (pstate, BINOP_SUBSCRIPT); }
509 | PrimaryNoNewArray '[' Expression ']'
510 { write_exp_elt_opcode (pstate, BINOP_SUBSCRIPT); }
516 { push_expression_name (pstate, $1); }
518 /* Already written by write_dollar_variable. */
519 | PostIncrementExpression
520 | PostDecrementExpression
523 PostIncrementExpression:
524 PostfixExpression INCREMENT
525 { write_exp_elt_opcode (pstate, UNOP_POSTINCREMENT); }
528 PostDecrementExpression:
529 PostfixExpression DECREMENT
530 { write_exp_elt_opcode (pstate, UNOP_POSTDECREMENT); }
534 PreIncrementExpression
535 | PreDecrementExpression
536 | '+' UnaryExpression
537 | '-' UnaryExpression
538 { write_exp_elt_opcode (pstate, UNOP_NEG); }
539 | '*' UnaryExpression
540 { write_exp_elt_opcode (pstate,
541 UNOP_IND); } /*FIXME not in Java */
542 | UnaryExpressionNotPlusMinus
545 PreIncrementExpression:
546 INCREMENT UnaryExpression
547 { write_exp_elt_opcode (pstate, UNOP_PREINCREMENT); }
550 PreDecrementExpression:
551 DECREMENT UnaryExpression
552 { write_exp_elt_opcode (pstate, UNOP_PREDECREMENT); }
555 UnaryExpressionNotPlusMinus:
557 | '~' UnaryExpression
558 { write_exp_elt_opcode (pstate, UNOP_COMPLEMENT); }
559 | '!' UnaryExpression
560 { write_exp_elt_opcode (pstate, UNOP_LOGICAL_NOT); }
565 '(' PrimitiveType Dims_opt ')' UnaryExpression
566 { write_exp_elt_opcode (pstate, UNOP_CAST);
567 write_exp_elt_type (pstate, java_array_type ($2, $3));
568 write_exp_elt_opcode (pstate, UNOP_CAST); }
569 | '(' Expression ')' UnaryExpressionNotPlusMinus
571 int last_exp_size = length_of_subexp (pstate->expout,
575 int base = pstate->expout_ptr - last_exp_size - 3;
578 || pstate->expout->elts[base+2].opcode != OP_TYPE)
579 error (_("Invalid cast expression"));
580 type = pstate->expout->elts[base+1].type;
581 /* Remove the 'Expression' and slide the
582 UnaryExpressionNotPlusMinus down to replace it. */
583 for (i = 0; i < last_exp_size; i++)
584 pstate->expout->elts[base + i]
585 = pstate->expout->elts[base + i + 3];
586 pstate->expout_ptr -= 3;
587 if (TYPE_CODE (type) == TYPE_CODE_STRUCT)
588 type = lookup_pointer_type (type);
589 write_exp_elt_opcode (pstate, UNOP_CAST);
590 write_exp_elt_type (pstate, type);
591 write_exp_elt_opcode (pstate, UNOP_CAST);
593 | '(' Name Dims ')' UnaryExpressionNotPlusMinus
594 { write_exp_elt_opcode (pstate, UNOP_CAST);
595 write_exp_elt_type (pstate,
596 java_array_type (java_type_from_name
598 write_exp_elt_opcode (pstate, UNOP_CAST); }
602 MultiplicativeExpression:
604 | MultiplicativeExpression '*' UnaryExpression
605 { write_exp_elt_opcode (pstate, BINOP_MUL); }
606 | MultiplicativeExpression '/' UnaryExpression
607 { write_exp_elt_opcode (pstate, BINOP_DIV); }
608 | MultiplicativeExpression '%' UnaryExpression
609 { write_exp_elt_opcode (pstate, BINOP_REM); }
613 MultiplicativeExpression
614 | AdditiveExpression '+' MultiplicativeExpression
615 { write_exp_elt_opcode (pstate, BINOP_ADD); }
616 | AdditiveExpression '-' MultiplicativeExpression
617 { write_exp_elt_opcode (pstate, BINOP_SUB); }
622 | ShiftExpression LSH AdditiveExpression
623 { write_exp_elt_opcode (pstate, BINOP_LSH); }
624 | ShiftExpression RSH AdditiveExpression
625 { write_exp_elt_opcode (pstate, BINOP_RSH); }
626 /* | ShiftExpression >>> AdditiveExpression { FIXME } */
629 RelationalExpression:
631 | RelationalExpression '<' ShiftExpression
632 { write_exp_elt_opcode (pstate, BINOP_LESS); }
633 | RelationalExpression '>' ShiftExpression
634 { write_exp_elt_opcode (pstate, BINOP_GTR); }
635 | RelationalExpression LEQ ShiftExpression
636 { write_exp_elt_opcode (pstate, BINOP_LEQ); }
637 | RelationalExpression GEQ ShiftExpression
638 { write_exp_elt_opcode (pstate, BINOP_GEQ); }
639 /* | RelationalExpresion INSTANCEOF ReferenceType { FIXME } */
644 | EqualityExpression EQUAL RelationalExpression
645 { write_exp_elt_opcode (pstate, BINOP_EQUAL); }
646 | EqualityExpression NOTEQUAL RelationalExpression
647 { write_exp_elt_opcode (pstate, BINOP_NOTEQUAL); }
652 | AndExpression '&' EqualityExpression
653 { write_exp_elt_opcode (pstate, BINOP_BITWISE_AND); }
656 ExclusiveOrExpression:
658 | ExclusiveOrExpression '^' AndExpression
659 { write_exp_elt_opcode (pstate, BINOP_BITWISE_XOR); }
661 InclusiveOrExpression:
662 ExclusiveOrExpression
663 | InclusiveOrExpression '|' ExclusiveOrExpression
664 { write_exp_elt_opcode (pstate, BINOP_BITWISE_IOR); }
667 ConditionalAndExpression:
668 InclusiveOrExpression
669 | ConditionalAndExpression ANDAND InclusiveOrExpression
670 { write_exp_elt_opcode (pstate, BINOP_LOGICAL_AND); }
673 ConditionalOrExpression:
674 ConditionalAndExpression
675 | ConditionalOrExpression OROR ConditionalAndExpression
676 { write_exp_elt_opcode (pstate, BINOP_LOGICAL_OR); }
679 ConditionalExpression:
680 ConditionalOrExpression
681 | ConditionalOrExpression '?' Expression ':' ConditionalExpression
682 { write_exp_elt_opcode (pstate, TERNOP_COND); }
685 AssignmentExpression:
686 ConditionalExpression
691 LeftHandSide '=' ConditionalExpression
692 { write_exp_elt_opcode (pstate, BINOP_ASSIGN); }
693 | LeftHandSide ASSIGN_MODIFY ConditionalExpression
694 { write_exp_elt_opcode (pstate, BINOP_ASSIGN_MODIFY);
695 write_exp_elt_opcode (pstate, $2);
696 write_exp_elt_opcode (pstate, BINOP_ASSIGN_MODIFY); }
701 { push_expression_name (pstate, $1); }
703 /* Already written by write_dollar_variable. */
714 /* Take care of parsing a number (anything that starts with a digit).
715 Set yylval and return the token type; update lexptr.
716 LEN is the number of characters in it. */
718 /*** Needs some error checking for the float case ***/
721 parse_number (struct parser_state *par_state,
722 const char *p, int len, int parsed_float, YYSTYPE *putithere)
725 ULONGEST limit, limit_div_base;
728 int base = input_radix;
737 if (! parse_float (p, len, &putithere->typed_val_float.dval, &suffix))
740 suffix_len = p + len - suffix;
743 putithere->typed_val_float.type
744 = parse_type (par_state)->builtin_double;
745 else if (suffix_len == 1)
747 /* See if it has `f' or `d' suffix (float or double). */
748 if (tolower (*suffix) == 'f')
749 putithere->typed_val_float.type =
750 parse_type (par_state)->builtin_float;
751 else if (tolower (*suffix) == 'd')
752 putithere->typed_val_float.type =
753 parse_type (par_state)->builtin_double;
760 return FLOATING_POINT_LITERAL;
763 /* Handle base-switching prefixes 0x, 0t, 0d, 0 */
795 /* A paranoid calculation of (1<<64)-1. */
796 limit = (ULONGEST)0xffffffff;
797 limit = ((limit << 16) << 16) | limit;
798 if (c == 'l' || c == 'L')
800 type = parse_java_type (par_state)->builtin_long;
805 type = parse_java_type (par_state)->builtin_int;
807 limit_div_base = limit / (ULONGEST) base;
812 if (c >= '0' && c <= '9')
814 else if (c >= 'A' && c <= 'Z')
816 else if (c >= 'a' && c <= 'z')
819 return ERROR; /* Char not a digit */
822 if (n > limit_div_base
823 || (n *= base) > limit - c)
824 error (_("Numeric constant too large"));
828 /* If the type is bigger than a 32-bit signed integer can be, implicitly
829 promote to long. Java does not do this, so mark it as
830 parse_type (par_state)->builtin_uint64 rather than
831 parse_java_type (par_state)->builtin_long.
832 0x80000000 will become -0x80000000 instead of 0x80000000L, because we
833 don't know the sign at this point. */
834 if (type == parse_java_type (par_state)->builtin_int
835 && n > (ULONGEST)0x80000000)
836 type = parse_type (par_state)->builtin_uint64;
838 putithere->typed_val_int.val = n;
839 putithere->typed_val_int.type = type;
841 return INTEGER_LITERAL;
848 enum exp_opcode opcode;
851 static const struct token tokentab3[] =
853 {">>=", ASSIGN_MODIFY, BINOP_RSH},
854 {"<<=", ASSIGN_MODIFY, BINOP_LSH}
857 static const struct token tokentab2[] =
859 {"+=", ASSIGN_MODIFY, BINOP_ADD},
860 {"-=", ASSIGN_MODIFY, BINOP_SUB},
861 {"*=", ASSIGN_MODIFY, BINOP_MUL},
862 {"/=", ASSIGN_MODIFY, BINOP_DIV},
863 {"%=", ASSIGN_MODIFY, BINOP_REM},
864 {"|=", ASSIGN_MODIFY, BINOP_BITWISE_IOR},
865 {"&=", ASSIGN_MODIFY, BINOP_BITWISE_AND},
866 {"^=", ASSIGN_MODIFY, BINOP_BITWISE_XOR},
867 {"++", INCREMENT, BINOP_END},
868 {"--", DECREMENT, BINOP_END},
869 {"&&", ANDAND, BINOP_END},
870 {"||", OROR, BINOP_END},
871 {"<<", LSH, BINOP_END},
872 {">>", RSH, BINOP_END},
873 {"==", EQUAL, BINOP_END},
874 {"!=", NOTEQUAL, BINOP_END},
875 {"<=", LEQ, BINOP_END},
876 {">=", GEQ, BINOP_END}
879 /* Read one token, getting characters through lexptr. */
887 const char *tokstart;
890 static char *tempbuf;
891 static int tempbufsize;
895 prev_lexptr = lexptr;
898 /* See if it is a special token of length 3. */
899 for (i = 0; i < sizeof tokentab3 / sizeof tokentab3[0]; i++)
900 if (strncmp (tokstart, tokentab3[i].operator, 3) == 0)
903 yylval.opcode = tokentab3[i].opcode;
904 return tokentab3[i].token;
907 /* See if it is a special token of length 2. */
908 for (i = 0; i < sizeof tokentab2 / sizeof tokentab2[0]; i++)
909 if (strncmp (tokstart, tokentab2[i].operator, 2) == 0)
912 yylval.opcode = tokentab2[i].opcode;
913 return tokentab2[i].token;
916 switch (c = *tokstart)
928 /* We either have a character constant ('0' or '\177' for example)
929 or we have a quoted symbol reference ('foo(int,int)' in C++
934 c = parse_escape (parse_gdbarch (pstate), &lexptr);
936 error (_("Empty character constant"));
938 yylval.typed_val_int.val = c;
939 yylval.typed_val_int.type = parse_java_type (pstate)->builtin_char;
944 namelen = skip_quoted (tokstart) - tokstart;
947 lexptr = tokstart + namelen;
948 if (lexptr[-1] != '\'')
949 error (_("Unmatched single quote"));
954 error (_("Invalid character constant"));
956 return INTEGER_LITERAL;
964 if (paren_depth == 0)
971 if (comma_terminates && paren_depth == 0)
977 /* Might be a floating point number. */
978 if (lexptr[1] < '0' || lexptr[1] > '9')
979 goto symbol; /* Nope, must be a symbol. */
980 /* FALL THRU into number case. */
994 int got_dot = 0, got_e = 0, toktype;
995 const char *p = tokstart;
996 int hex = input_radix > 10;
998 if (c == '0' && (p[1] == 'x' || p[1] == 'X'))
1003 else if (c == '0' && (p[1]=='t' || p[1]=='T' || p[1]=='d' || p[1]=='D'))
1011 /* This test includes !hex because 'e' is a valid hex digit
1012 and thus does not indicate a floating point number when
1013 the radix is hex. */
1014 if (!hex && !got_e && (*p == 'e' || *p == 'E'))
1015 got_dot = got_e = 1;
1016 /* This test does not include !hex, because a '.' always indicates
1017 a decimal floating point number regardless of the radix. */
1018 else if (!got_dot && *p == '.')
1020 else if (got_e && (p[-1] == 'e' || p[-1] == 'E')
1021 && (*p == '-' || *p == '+'))
1022 /* This is the sign of the exponent, not the end of the
1025 /* We will take any letters or digits. parse_number will
1026 complain if past the radix, or if L or U are not final. */
1027 else if ((*p < '0' || *p > '9')
1028 && ((*p < 'a' || *p > 'z')
1029 && (*p < 'A' || *p > 'Z')))
1032 toktype = parse_number (pstate, tokstart, p - tokstart,
1033 got_dot|got_e, &yylval);
1034 if (toktype == ERROR)
1036 char *err_copy = (char *) alloca (p - tokstart + 1);
1038 memcpy (err_copy, tokstart, p - tokstart);
1039 err_copy[p - tokstart] = 0;
1040 error (_("Invalid number \"%s\""), err_copy);
1071 /* Build the gdb internal form of the input string in tempbuf,
1072 translating any standard C escape forms seen. Note that the
1073 buffer is null byte terminated *only* for the convenience of
1074 debugging gdb itself and printing the buffer contents when
1075 the buffer contains no embedded nulls. Gdb does not depend
1076 upon the buffer being null byte terminated, it uses the length
1077 string instead. This allows gdb to handle C strings (as well
1078 as strings in other languages) with embedded null bytes */
1080 tokptr = ++tokstart;
1084 /* Grow the static temp buffer if necessary, including allocating
1085 the first one on demand. */
1086 if (tempbufindex + 1 >= tempbufsize)
1088 tempbuf = (char *) realloc (tempbuf, tempbufsize += 64);
1094 /* Do nothing, loop will terminate. */
1098 c = parse_escape (parse_gdbarch (pstate), &tokptr);
1103 tempbuf[tempbufindex++] = c;
1106 tempbuf[tempbufindex++] = *tokptr++;
1109 } while ((*tokptr != '"') && (*tokptr != '\0'));
1110 if (*tokptr++ != '"')
1112 error (_("Unterminated string in expression"));
1114 tempbuf[tempbufindex] = '\0'; /* See note above */
1115 yylval.sval.ptr = tempbuf;
1116 yylval.sval.length = tempbufindex;
1118 return (STRING_LITERAL);
1121 if (!(c == '_' || c == '$'
1122 || (c >= 'a' && c <= 'z') || (c >= 'A' && c <= 'Z')))
1123 /* We must have come across a bad character (e.g. ';'). */
1124 error (_("Invalid character '%c' in expression"), c);
1126 /* It's a name. See how long it is. */
1128 for (c = tokstart[namelen];
1131 || (c >= '0' && c <= '9')
1132 || (c >= 'a' && c <= 'z')
1133 || (c >= 'A' && c <= 'Z')
1140 while (tokstart[++i] && tokstart[i] != '>');
1141 if (tokstart[i] == '>')
1144 c = tokstart[++namelen];
1147 /* The token "if" terminates the expression and is NOT
1148 removed from the input stream. */
1149 if (namelen == 2 && tokstart[0] == 'i' && tokstart[1] == 'f')
1158 /* Catch specific keywords. Should be done with a data structure. */
1162 if (strncmp (tokstart, "boolean", 7) == 0)
1166 if (strncmp (tokstart, "double", 6) == 0)
1170 if (strncmp (tokstart, "short", 5) == 0)
1172 if (strncmp (tokstart, "false", 5) == 0)
1175 return BOOLEAN_LITERAL;
1177 if (strncmp (tokstart, "super", 5) == 0)
1179 if (strncmp (tokstart, "float", 5) == 0)
1183 if (strncmp (tokstart, "long", 4) == 0)
1185 if (strncmp (tokstart, "byte", 4) == 0)
1187 if (strncmp (tokstart, "char", 4) == 0)
1189 if (strncmp (tokstart, "true", 4) == 0)
1192 return BOOLEAN_LITERAL;
1196 if (strncmp (tokstart, "int", 3) == 0)
1198 if (strncmp (tokstart, "new", 3) == 0)
1205 yylval.sval.ptr = tokstart;
1206 yylval.sval.length = namelen;
1208 if (*tokstart == '$')
1210 write_dollar_variable (pstate, yylval.sval);
1214 /* Input names that aren't symbols but ARE valid hex numbers,
1215 when the input radix permits them, can be names or numbers
1216 depending on the parse. Note we support radixes > 16 here. */
1217 if (((tokstart[0] >= 'a' && tokstart[0] < 'a' + input_radix - 10) ||
1218 (tokstart[0] >= 'A' && tokstart[0] < 'A' + input_radix - 10)))
1220 YYSTYPE newlval; /* Its value is ignored. */
1221 int hextype = parse_number (pstate, tokstart, namelen, 0, &newlval);
1222 if (hextype == INTEGER_LITERAL)
1229 java_parse (struct parser_state *par_state)
1232 struct cleanup *c = make_cleanup_clear_parser_state (&pstate);
1234 /* Setting up the parser state. */
1235 gdb_assert (par_state != NULL);
1238 result = yyparse ();
1248 lexptr = prev_lexptr;
1251 error (_("%s: near `%s'"), msg, lexptr);
1253 error (_("error in expression, near `%s'"), lexptr);
1256 static struct type *
1257 java_type_from_name (struct stoken name)
1259 char *tmp = copy_name (name);
1260 struct type *typ = java_lookup_class (tmp);
1261 if (typ == NULL || TYPE_CODE (typ) != TYPE_CODE_STRUCT)
1262 error (_("No class named `%s'"), tmp);
1266 /* If NAME is a valid variable name in this scope, push it and return 1.
1267 Otherwise, return 0. */
1270 push_variable (struct parser_state *par_state, struct stoken name)
1272 char *tmp = copy_name (name);
1273 struct field_of_this_result is_a_field_of_this;
1276 sym = lookup_symbol (tmp, expression_context_block, VAR_DOMAIN,
1277 &is_a_field_of_this);
1278 if (sym && SYMBOL_CLASS (sym) != LOC_TYPEDEF)
1280 if (symbol_read_needs_frame (sym))
1282 if (innermost_block == 0 ||
1283 contained_in (block_found, innermost_block))
1284 innermost_block = block_found;
1287 write_exp_elt_opcode (par_state, OP_VAR_VALUE);
1288 /* We want to use the selected frame, not another more inner frame
1289 which happens to be in the same block. */
1290 write_exp_elt_block (par_state, NULL);
1291 write_exp_elt_sym (par_state, sym);
1292 write_exp_elt_opcode (par_state, OP_VAR_VALUE);
1295 if (is_a_field_of_this.type != NULL)
1297 /* it hangs off of `this'. Must not inadvertently convert from a
1298 method call to data ref. */
1299 if (innermost_block == 0 ||
1300 contained_in (block_found, innermost_block))
1301 innermost_block = block_found;
1302 write_exp_elt_opcode (par_state, OP_THIS);
1303 write_exp_elt_opcode (par_state, OP_THIS);
1304 write_exp_elt_opcode (par_state, STRUCTOP_PTR);
1305 write_exp_string (par_state, name);
1306 write_exp_elt_opcode (par_state, STRUCTOP_PTR);
1312 /* Assuming a reference expression has been pushed, emit the
1313 STRUCTOP_PTR ops to access the field named NAME. If NAME is a
1314 qualified name (has '.'), generate a field access for each part. */
1317 push_fieldnames (struct parser_state *par_state, struct stoken name)
1320 struct stoken token;
1321 token.ptr = name.ptr;
1324 if (i == name.length || name.ptr[i] == '.')
1326 /* token.ptr is start of current field name. */
1327 token.length = &name.ptr[i] - token.ptr;
1328 write_exp_elt_opcode (par_state, STRUCTOP_PTR);
1329 write_exp_string (par_state, token);
1330 write_exp_elt_opcode (par_state, STRUCTOP_PTR);
1331 token.ptr += token.length + 1;
1333 if (i >= name.length)
1338 /* Helper routine for push_expression_name.
1339 Handle a qualified name, where DOT_INDEX is the index of the first '.' */
1342 push_qualified_expression_name (struct parser_state *par_state,
1343 struct stoken name, int dot_index)
1345 struct stoken token;
1349 token.ptr = name.ptr;
1350 token.length = dot_index;
1352 if (push_variable (par_state, token))
1354 token.ptr = name.ptr + dot_index + 1;
1355 token.length = name.length - dot_index - 1;
1356 push_fieldnames (par_state, token);
1360 token.ptr = name.ptr;
1363 token.length = dot_index;
1364 tmp = copy_name (token);
1365 typ = java_lookup_class (tmp);
1368 if (dot_index == name.length)
1370 write_exp_elt_opcode (par_state, OP_TYPE);
1371 write_exp_elt_type (par_state, typ);
1372 write_exp_elt_opcode (par_state, OP_TYPE);
1375 dot_index++; /* Skip '.' */
1376 name.ptr += dot_index;
1377 name.length -= dot_index;
1379 while (dot_index < name.length && name.ptr[dot_index] != '.')
1381 token.ptr = name.ptr;
1382 token.length = dot_index;
1383 write_exp_elt_opcode (par_state, OP_SCOPE);
1384 write_exp_elt_type (par_state, typ);
1385 write_exp_string (par_state, token);
1386 write_exp_elt_opcode (par_state, OP_SCOPE);
1387 if (dot_index < name.length)
1390 name.ptr += dot_index;
1391 name.length -= dot_index;
1392 push_fieldnames (par_state, name);
1396 else if (dot_index >= name.length)
1398 dot_index++; /* Skip '.' */
1399 while (dot_index < name.length && name.ptr[dot_index] != '.')
1402 error (_("unknown type `%.*s'"), name.length, name.ptr);
1405 /* Handle Name in an expression (or LHS).
1406 Handle VAR, TYPE, TYPE.FIELD1....FIELDN and VAR.FIELD1....FIELDN. */
1409 push_expression_name (struct parser_state *par_state, struct stoken name)
1415 for (i = 0; i < name.length; i++)
1417 if (name.ptr[i] == '.')
1419 /* It's a Qualified Expression Name. */
1420 push_qualified_expression_name (par_state, name, i);
1425 /* It's a Simple Expression Name. */
1427 if (push_variable (par_state, name))
1429 tmp = copy_name (name);
1430 typ = java_lookup_class (tmp);
1433 write_exp_elt_opcode (par_state, OP_TYPE);
1434 write_exp_elt_type (par_state, typ);
1435 write_exp_elt_opcode (par_state, OP_TYPE);
1439 struct bound_minimal_symbol msymbol;
1441 msymbol = lookup_bound_minimal_symbol (tmp);
1442 if (msymbol.minsym != NULL)
1443 write_exp_msymbol (par_state, msymbol);
1444 else if (!have_full_symbols () && !have_partial_symbols ())
1445 error (_("No symbol table is loaded. Use the \"file\" command"));
1447 error (_("No symbol \"%s\" in current context."), tmp);
1453 /* The following two routines, copy_exp and insert_exp, aren't specific to
1454 Java, so they could go in parse.c, but their only purpose is to support
1455 the parsing kludges we use in this file, so maybe it's best to isolate
1458 /* Copy the expression whose last element is at index ENDPOS - 1 in EXPR
1459 into a freshly malloc'ed struct expression. Its language_defn is set
1461 static struct expression *
1462 copy_exp (struct expression *expr, int endpos)
1464 int len = length_of_subexp (expr, endpos);
1465 struct expression *new
1466 = (struct expression *) malloc (sizeof (*new) + EXP_ELEM_TO_BYTES (len));
1469 memcpy (new->elts, expr->elts + endpos - len, EXP_ELEM_TO_BYTES (len));
1470 new->language_defn = 0;
1475 /* Insert the expression NEW into the current expression (expout) at POS. */
1477 insert_exp (struct parser_state *par_state, int pos, struct expression *new)
1479 int newlen = new->nelts;
1482 /* Grow expout if necessary. In this function's only use at present,
1483 this should never be necessary. */
1484 increase_expout_size (par_state, newlen);
1486 for (i = par_state->expout_ptr - 1; i >= pos; i--)
1487 par_state->expout->elts[i + newlen] = par_state->expout->elts[i];
1489 memcpy (par_state->expout->elts + pos, new->elts,
1490 EXP_ELEM_TO_BYTES (newlen));
1491 par_state->expout_ptr += newlen;