S/390: Move start of 64 bit binaries from 2GB to 256MB.
[binutils-gdb.git] / gdb / jv-exp.y
blob79b8127b595f48024ed3c15818a893691818d041
1 /* YACC parser for Java expressions, for GDB.
2 Copyright (C) 1997-2016 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. */
38 #include "defs.h"
39 #include <ctype.h>
40 #include "expression.h"
41 #include "value.h"
42 #include "parser-defs.h"
43 #include "language.h"
44 #include "jv-lang.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 */
48 #include "block.h"
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,
55 etc). */
56 #define GDB_YY_REMAP_PREFIX java_
57 #include "yy-remap.h"
59 /* The state of the parser, used internally when we are parsing the
60 expression. */
62 static struct parser_state *pstate = NULL;
64 int yyparse (void);
66 static int yylex (void);
68 void yyerror (char *);
70 static struct type *java_type_from_name (struct stoken);
71 static void push_expression_name (struct parser_state *, struct stoken);
72 static void push_fieldnames (struct parser_state *, struct stoken);
74 static struct expression *copy_exp (struct expression *, int);
75 static void insert_exp (struct parser_state *, int, struct expression *);
79 /* Although the yacc "value" of an expression is not used,
80 since the result is stored in the structure being created,
81 other node types do have values. */
83 %union
85 LONGEST lval;
86 struct {
87 LONGEST val;
88 struct type *type;
89 } typed_val_int;
90 struct {
91 DOUBLEST dval;
92 struct type *type;
93 } typed_val_float;
94 struct symbol *sym;
95 struct type *tval;
96 struct stoken sval;
97 struct ttype tsym;
98 struct symtoken ssym;
99 struct block *bval;
100 enum exp_opcode opcode;
101 struct internalvar *ivar;
102 int *ivec;
106 /* YYSTYPE gets defined by %union */
107 static int parse_number (struct parser_state *, const char *, int,
108 int, YYSTYPE *);
111 %type <lval> rcurly Dims Dims_opt
112 %type <tval> ClassOrInterfaceType ClassType /* ReferenceType Type ArrayType */
113 %type <tval> IntegralType FloatingPointType NumericType PrimitiveType ArrayType PrimitiveOrArrayType
115 %token <typed_val_int> INTEGER_LITERAL
116 %token <typed_val_float> FLOATING_POINT_LITERAL
118 %token <sval> IDENTIFIER
119 %token <sval> STRING_LITERAL
120 %token <lval> BOOLEAN_LITERAL
121 %token <tsym> TYPENAME
122 %type <sval> Name SimpleName QualifiedName ForcedName
124 /* A NAME_OR_INT is a symbol which is not known in the symbol table,
125 but which would parse as a valid number in the current input radix.
126 E.g. "c" when input_radix==16. Depending on the parse, it will be
127 turned into a name or into a number. */
129 %token <sval> NAME_OR_INT
131 %token ERROR
133 /* Special type cases, put in to allow the parser to distinguish different
134 legal basetypes. */
135 %token LONG SHORT BYTE INT CHAR BOOLEAN DOUBLE FLOAT
137 %token VARIABLE
139 %token <opcode> ASSIGN_MODIFY
141 %token SUPER NEW
143 %left ','
144 %right '=' ASSIGN_MODIFY
145 %right '?'
146 %left OROR
147 %left ANDAND
148 %left '|'
149 %left '^'
150 %left '&'
151 %left EQUAL NOTEQUAL
152 %left '<' '>' LEQ GEQ
153 %left LSH RSH
154 %left '+' '-'
155 %left '*' '/' '%'
156 %right INCREMENT DECREMENT
157 %right '.' '[' '('
162 start : exp1
163 | type_exp
166 type_exp: PrimitiveOrArrayType
168 write_exp_elt_opcode (pstate, OP_TYPE);
169 write_exp_elt_type (pstate, $1);
170 write_exp_elt_opcode (pstate, OP_TYPE);
174 PrimitiveOrArrayType:
175 PrimitiveType
176 | ArrayType
179 StringLiteral:
180 STRING_LITERAL
182 write_exp_elt_opcode (pstate, OP_STRING);
183 write_exp_string (pstate, $1);
184 write_exp_elt_opcode (pstate, OP_STRING);
188 Literal:
189 INTEGER_LITERAL
190 { write_exp_elt_opcode (pstate, OP_LONG);
191 write_exp_elt_type (pstate, $1.type);
192 write_exp_elt_longcst (pstate, (LONGEST)($1.val));
193 write_exp_elt_opcode (pstate, OP_LONG); }
194 | NAME_OR_INT
195 { YYSTYPE val;
196 parse_number (pstate, $1.ptr, $1.length, 0, &val);
197 write_exp_elt_opcode (pstate, OP_LONG);
198 write_exp_elt_type (pstate, val.typed_val_int.type);
199 write_exp_elt_longcst (pstate,
200 (LONGEST) val.typed_val_int.val);
201 write_exp_elt_opcode (pstate, OP_LONG);
203 | FLOATING_POINT_LITERAL
204 { write_exp_elt_opcode (pstate, OP_DOUBLE);
205 write_exp_elt_type (pstate, $1.type);
206 write_exp_elt_dblcst (pstate, $1.dval);
207 write_exp_elt_opcode (pstate, OP_DOUBLE); }
208 | BOOLEAN_LITERAL
209 { write_exp_elt_opcode (pstate, OP_LONG);
210 write_exp_elt_type (pstate,
211 parse_java_type (pstate)->builtin_boolean);
212 write_exp_elt_longcst (pstate, (LONGEST)$1);
213 write_exp_elt_opcode (pstate, OP_LONG); }
214 | StringLiteral
217 /* UNUSED:
218 Type:
219 PrimitiveType
220 | ReferenceType
224 PrimitiveType:
225 NumericType
226 | BOOLEAN
227 { $$ = parse_java_type (pstate)->builtin_boolean; }
230 NumericType:
231 IntegralType
232 | FloatingPointType
235 IntegralType:
236 BYTE
237 { $$ = parse_java_type (pstate)->builtin_byte; }
238 | SHORT
239 { $$ = parse_java_type (pstate)->builtin_short; }
240 | INT
241 { $$ = parse_java_type (pstate)->builtin_int; }
242 | LONG
243 { $$ = parse_java_type (pstate)->builtin_long; }
244 | CHAR
245 { $$ = parse_java_type (pstate)->builtin_char; }
248 FloatingPointType:
249 FLOAT
250 { $$ = parse_java_type (pstate)->builtin_float; }
251 | DOUBLE
252 { $$ = parse_java_type (pstate)->builtin_double; }
255 /* UNUSED:
256 ReferenceType:
257 ClassOrInterfaceType
258 | ArrayType
262 ClassOrInterfaceType:
263 Name
264 { $$ = java_type_from_name ($1); }
267 ClassType:
268 ClassOrInterfaceType
271 ArrayType:
272 PrimitiveType Dims
273 { $$ = java_array_type ($1, $2); }
274 | Name Dims
275 { $$ = java_array_type (java_type_from_name ($1), $2); }
278 Name:
279 IDENTIFIER
280 | QualifiedName
283 ForcedName:
284 SimpleName
285 | QualifiedName
288 SimpleName:
289 IDENTIFIER
290 | NAME_OR_INT
293 QualifiedName:
294 Name '.' SimpleName
295 { $$.length = $1.length + $3.length + 1;
296 if ($1.ptr + $1.length + 1 == $3.ptr
297 && $1.ptr[$1.length] == '.')
298 $$.ptr = $1.ptr; /* Optimization. */
299 else
301 char *buf;
303 buf = (char *) malloc ($$.length + 1);
304 make_cleanup (free, buf);
305 sprintf (buf, "%.*s.%.*s",
306 $1.length, $1.ptr, $3.length, $3.ptr);
307 $$.ptr = buf;
312 type_exp: type
313 { write_exp_elt_opcode(OP_TYPE);
314 write_exp_elt_type($1);
315 write_exp_elt_opcode(OP_TYPE);}
319 /* Expressions, including the comma operator. */
320 exp1 : Expression
321 | exp1 ',' Expression
322 { write_exp_elt_opcode (pstate, BINOP_COMMA); }
325 Primary:
326 PrimaryNoNewArray
327 | ArrayCreationExpression
330 PrimaryNoNewArray:
331 Literal
332 | '(' Expression ')'
333 | ClassInstanceCreationExpression
334 | FieldAccess
335 | MethodInvocation
336 | ArrayAccess
337 | lcurly ArgumentList rcurly
338 { write_exp_elt_opcode (pstate, OP_ARRAY);
339 write_exp_elt_longcst (pstate, (LONGEST) 0);
340 write_exp_elt_longcst (pstate, (LONGEST) $3);
341 write_exp_elt_opcode (pstate, OP_ARRAY); }
344 lcurly:
346 { start_arglist (); }
349 rcurly:
351 { $$ = end_arglist () - 1; }
354 ClassInstanceCreationExpression:
355 NEW ClassType '(' ArgumentList_opt ')'
356 { internal_error (__FILE__, __LINE__,
357 _("FIXME - ClassInstanceCreationExpression")); }
360 ArgumentList:
361 Expression
362 { arglist_len = 1; }
363 | ArgumentList ',' Expression
364 { arglist_len++; }
367 ArgumentList_opt:
368 /* EMPTY */
369 { arglist_len = 0; }
370 | ArgumentList
373 ArrayCreationExpression:
374 NEW PrimitiveType DimExprs Dims_opt
375 { internal_error (__FILE__, __LINE__,
376 _("FIXME - ArrayCreationExpression")); }
377 | NEW ClassOrInterfaceType DimExprs Dims_opt
378 { internal_error (__FILE__, __LINE__,
379 _("FIXME - ArrayCreationExpression")); }
382 DimExprs:
383 DimExpr
384 | DimExprs DimExpr
387 DimExpr:
388 '[' Expression ']'
391 Dims:
392 '[' ']'
393 { $$ = 1; }
394 | Dims '[' ']'
395 { $$ = $1 + 1; }
398 Dims_opt:
399 Dims
400 | /* EMPTY */
401 { $$ = 0; }
404 FieldAccess:
405 Primary '.' SimpleName
406 { push_fieldnames (pstate, $3); }
407 | VARIABLE '.' SimpleName
408 { push_fieldnames (pstate, $3); }
409 /*| SUPER '.' SimpleName { FIXME } */
412 FuncStart:
413 Name '('
414 { push_expression_name (pstate, $1); }
417 MethodInvocation:
418 FuncStart
419 { start_arglist(); }
420 ArgumentList_opt ')'
421 { write_exp_elt_opcode (pstate, OP_FUNCALL);
422 write_exp_elt_longcst (pstate, (LONGEST) end_arglist ());
423 write_exp_elt_opcode (pstate, OP_FUNCALL); }
424 | Primary '.' SimpleName '(' ArgumentList_opt ')'
425 { error (_("Form of method invocation not implemented")); }
426 | SUPER '.' SimpleName '(' ArgumentList_opt ')'
427 { error (_("Form of method invocation not implemented")); }
430 ArrayAccess:
431 Name '[' Expression ']'
433 /* Emit code for the Name now, then exchange it in the
434 expout array with the Expression's code. We could
435 introduce a OP_SWAP code or a reversed version of
436 BINOP_SUBSCRIPT, but that makes the rest of GDB pay
437 for our parsing kludges. */
438 struct expression *name_expr;
440 push_expression_name (pstate, $1);
441 name_expr = copy_exp (pstate->expout, pstate->expout_ptr);
442 pstate->expout_ptr -= name_expr->nelts;
443 insert_exp (pstate,
444 pstate->expout_ptr
445 - length_of_subexp (pstate->expout,
446 pstate->expout_ptr),
447 name_expr);
448 free (name_expr);
449 write_exp_elt_opcode (pstate, BINOP_SUBSCRIPT);
451 | VARIABLE '[' Expression ']'
452 { write_exp_elt_opcode (pstate, BINOP_SUBSCRIPT); }
453 | PrimaryNoNewArray '[' Expression ']'
454 { write_exp_elt_opcode (pstate, BINOP_SUBSCRIPT); }
457 PostfixExpression:
458 Primary
459 | Name
460 { push_expression_name (pstate, $1); }
461 | VARIABLE
462 /* Already written by write_dollar_variable. */
463 | PostIncrementExpression
464 | PostDecrementExpression
467 PostIncrementExpression:
468 PostfixExpression INCREMENT
469 { write_exp_elt_opcode (pstate, UNOP_POSTINCREMENT); }
472 PostDecrementExpression:
473 PostfixExpression DECREMENT
474 { write_exp_elt_opcode (pstate, UNOP_POSTDECREMENT); }
477 UnaryExpression:
478 PreIncrementExpression
479 | PreDecrementExpression
480 | '+' UnaryExpression
481 | '-' UnaryExpression
482 { write_exp_elt_opcode (pstate, UNOP_NEG); }
483 | '*' UnaryExpression
484 { write_exp_elt_opcode (pstate,
485 UNOP_IND); } /*FIXME not in Java */
486 | UnaryExpressionNotPlusMinus
489 PreIncrementExpression:
490 INCREMENT UnaryExpression
491 { write_exp_elt_opcode (pstate, UNOP_PREINCREMENT); }
494 PreDecrementExpression:
495 DECREMENT UnaryExpression
496 { write_exp_elt_opcode (pstate, UNOP_PREDECREMENT); }
499 UnaryExpressionNotPlusMinus:
500 PostfixExpression
501 | '~' UnaryExpression
502 { write_exp_elt_opcode (pstate, UNOP_COMPLEMENT); }
503 | '!' UnaryExpression
504 { write_exp_elt_opcode (pstate, UNOP_LOGICAL_NOT); }
505 | CastExpression
508 CastExpression:
509 '(' PrimitiveType Dims_opt ')' UnaryExpression
510 { write_exp_elt_opcode (pstate, UNOP_CAST);
511 write_exp_elt_type (pstate, java_array_type ($2, $3));
512 write_exp_elt_opcode (pstate, UNOP_CAST); }
513 | '(' Expression ')' UnaryExpressionNotPlusMinus
515 int last_exp_size = length_of_subexp (pstate->expout,
516 pstate->expout_ptr);
517 struct type *type;
518 int i;
519 int base = pstate->expout_ptr - last_exp_size - 3;
521 if (base < 0
522 || pstate->expout->elts[base+2].opcode != OP_TYPE)
523 error (_("Invalid cast expression"));
524 type = pstate->expout->elts[base+1].type;
525 /* Remove the 'Expression' and slide the
526 UnaryExpressionNotPlusMinus down to replace it. */
527 for (i = 0; i < last_exp_size; i++)
528 pstate->expout->elts[base + i]
529 = pstate->expout->elts[base + i + 3];
530 pstate->expout_ptr -= 3;
531 if (TYPE_CODE (type) == TYPE_CODE_STRUCT)
532 type = lookup_pointer_type (type);
533 write_exp_elt_opcode (pstate, UNOP_CAST);
534 write_exp_elt_type (pstate, type);
535 write_exp_elt_opcode (pstate, UNOP_CAST);
537 | '(' Name Dims ')' UnaryExpressionNotPlusMinus
538 { write_exp_elt_opcode (pstate, UNOP_CAST);
539 write_exp_elt_type (pstate,
540 java_array_type (java_type_from_name
541 ($2), $3));
542 write_exp_elt_opcode (pstate, UNOP_CAST); }
546 MultiplicativeExpression:
547 UnaryExpression
548 | MultiplicativeExpression '*' UnaryExpression
549 { write_exp_elt_opcode (pstate, BINOP_MUL); }
550 | MultiplicativeExpression '/' UnaryExpression
551 { write_exp_elt_opcode (pstate, BINOP_DIV); }
552 | MultiplicativeExpression '%' UnaryExpression
553 { write_exp_elt_opcode (pstate, BINOP_REM); }
556 AdditiveExpression:
557 MultiplicativeExpression
558 | AdditiveExpression '+' MultiplicativeExpression
559 { write_exp_elt_opcode (pstate, BINOP_ADD); }
560 | AdditiveExpression '-' MultiplicativeExpression
561 { write_exp_elt_opcode (pstate, BINOP_SUB); }
564 ShiftExpression:
565 AdditiveExpression
566 | ShiftExpression LSH AdditiveExpression
567 { write_exp_elt_opcode (pstate, BINOP_LSH); }
568 | ShiftExpression RSH AdditiveExpression
569 { write_exp_elt_opcode (pstate, BINOP_RSH); }
570 /* | ShiftExpression >>> AdditiveExpression { FIXME } */
573 RelationalExpression:
574 ShiftExpression
575 | RelationalExpression '<' ShiftExpression
576 { write_exp_elt_opcode (pstate, BINOP_LESS); }
577 | RelationalExpression '>' ShiftExpression
578 { write_exp_elt_opcode (pstate, BINOP_GTR); }
579 | RelationalExpression LEQ ShiftExpression
580 { write_exp_elt_opcode (pstate, BINOP_LEQ); }
581 | RelationalExpression GEQ ShiftExpression
582 { write_exp_elt_opcode (pstate, BINOP_GEQ); }
583 /* | RelationalExpresion INSTANCEOF ReferenceType { FIXME } */
586 EqualityExpression:
587 RelationalExpression
588 | EqualityExpression EQUAL RelationalExpression
589 { write_exp_elt_opcode (pstate, BINOP_EQUAL); }
590 | EqualityExpression NOTEQUAL RelationalExpression
591 { write_exp_elt_opcode (pstate, BINOP_NOTEQUAL); }
594 AndExpression:
595 EqualityExpression
596 | AndExpression '&' EqualityExpression
597 { write_exp_elt_opcode (pstate, BINOP_BITWISE_AND); }
600 ExclusiveOrExpression:
601 AndExpression
602 | ExclusiveOrExpression '^' AndExpression
603 { write_exp_elt_opcode (pstate, BINOP_BITWISE_XOR); }
605 InclusiveOrExpression:
606 ExclusiveOrExpression
607 | InclusiveOrExpression '|' ExclusiveOrExpression
608 { write_exp_elt_opcode (pstate, BINOP_BITWISE_IOR); }
611 ConditionalAndExpression:
612 InclusiveOrExpression
613 | ConditionalAndExpression ANDAND InclusiveOrExpression
614 { write_exp_elt_opcode (pstate, BINOP_LOGICAL_AND); }
617 ConditionalOrExpression:
618 ConditionalAndExpression
619 | ConditionalOrExpression OROR ConditionalAndExpression
620 { write_exp_elt_opcode (pstate, BINOP_LOGICAL_OR); }
623 ConditionalExpression:
624 ConditionalOrExpression
625 | ConditionalOrExpression '?' Expression ':' ConditionalExpression
626 { write_exp_elt_opcode (pstate, TERNOP_COND); }
629 AssignmentExpression:
630 ConditionalExpression
631 | Assignment
634 Assignment:
635 LeftHandSide '=' ConditionalExpression
636 { write_exp_elt_opcode (pstate, BINOP_ASSIGN); }
637 | LeftHandSide ASSIGN_MODIFY ConditionalExpression
638 { write_exp_elt_opcode (pstate, BINOP_ASSIGN_MODIFY);
639 write_exp_elt_opcode (pstate, $2);
640 write_exp_elt_opcode (pstate, BINOP_ASSIGN_MODIFY); }
643 LeftHandSide:
644 ForcedName
645 { push_expression_name (pstate, $1); }
646 | VARIABLE
647 /* Already written by write_dollar_variable. */
648 | FieldAccess
649 | ArrayAccess
653 Expression:
654 AssignmentExpression
658 /* Take care of parsing a number (anything that starts with a digit).
659 Set yylval and return the token type; update lexptr.
660 LEN is the number of characters in it. */
662 /*** Needs some error checking for the float case ***/
664 static int
665 parse_number (struct parser_state *par_state,
666 const char *p, int len, int parsed_float, YYSTYPE *putithere)
668 ULONGEST n = 0;
669 ULONGEST limit, limit_div_base;
671 int c;
672 int base = input_radix;
674 struct type *type;
676 if (parsed_float)
678 const char *suffix;
679 int suffix_len;
681 if (! parse_float (p, len, &putithere->typed_val_float.dval, &suffix))
682 return ERROR;
684 suffix_len = p + len - suffix;
686 if (suffix_len == 0)
687 putithere->typed_val_float.type
688 = parse_type (par_state)->builtin_double;
689 else if (suffix_len == 1)
691 /* See if it has `f' or `d' suffix (float or double). */
692 if (tolower (*suffix) == 'f')
693 putithere->typed_val_float.type =
694 parse_type (par_state)->builtin_float;
695 else if (tolower (*suffix) == 'd')
696 putithere->typed_val_float.type =
697 parse_type (par_state)->builtin_double;
698 else
699 return ERROR;
701 else
702 return ERROR;
704 return FLOATING_POINT_LITERAL;
707 /* Handle base-switching prefixes 0x, 0t, 0d, 0 */
708 if (p[0] == '0')
709 switch (p[1])
711 case 'x':
712 case 'X':
713 if (len >= 3)
715 p += 2;
716 base = 16;
717 len -= 2;
719 break;
721 case 't':
722 case 'T':
723 case 'd':
724 case 'D':
725 if (len >= 3)
727 p += 2;
728 base = 10;
729 len -= 2;
731 break;
733 default:
734 base = 8;
735 break;
738 c = p[len-1];
739 /* A paranoid calculation of (1<<64)-1. */
740 limit = (ULONGEST)0xffffffff;
741 limit = ((limit << 16) << 16) | limit;
742 if (c == 'l' || c == 'L')
744 type = parse_java_type (par_state)->builtin_long;
745 len--;
747 else
749 type = parse_java_type (par_state)->builtin_int;
751 limit_div_base = limit / (ULONGEST) base;
753 while (--len >= 0)
755 c = *p++;
756 if (c >= '0' && c <= '9')
757 c -= '0';
758 else if (c >= 'A' && c <= 'Z')
759 c -= 'A' - 10;
760 else if (c >= 'a' && c <= 'z')
761 c -= 'a' - 10;
762 else
763 return ERROR; /* Char not a digit */
764 if (c >= base)
765 return ERROR;
766 if (n > limit_div_base
767 || (n *= base) > limit - c)
768 error (_("Numeric constant too large"));
769 n += c;
772 /* If the type is bigger than a 32-bit signed integer can be, implicitly
773 promote to long. Java does not do this, so mark it as
774 parse_type (par_state)->builtin_uint64 rather than
775 parse_java_type (par_state)->builtin_long.
776 0x80000000 will become -0x80000000 instead of 0x80000000L, because we
777 don't know the sign at this point. */
778 if (type == parse_java_type (par_state)->builtin_int
779 && n > (ULONGEST)0x80000000)
780 type = parse_type (par_state)->builtin_uint64;
782 putithere->typed_val_int.val = n;
783 putithere->typed_val_int.type = type;
785 return INTEGER_LITERAL;
788 struct token
790 char *oper;
791 int token;
792 enum exp_opcode opcode;
795 static const struct token tokentab3[] =
797 {">>=", ASSIGN_MODIFY, BINOP_RSH},
798 {"<<=", ASSIGN_MODIFY, BINOP_LSH}
801 static const struct token tokentab2[] =
803 {"+=", ASSIGN_MODIFY, BINOP_ADD},
804 {"-=", ASSIGN_MODIFY, BINOP_SUB},
805 {"*=", ASSIGN_MODIFY, BINOP_MUL},
806 {"/=", ASSIGN_MODIFY, BINOP_DIV},
807 {"%=", ASSIGN_MODIFY, BINOP_REM},
808 {"|=", ASSIGN_MODIFY, BINOP_BITWISE_IOR},
809 {"&=", ASSIGN_MODIFY, BINOP_BITWISE_AND},
810 {"^=", ASSIGN_MODIFY, BINOP_BITWISE_XOR},
811 {"++", INCREMENT, BINOP_END},
812 {"--", DECREMENT, BINOP_END},
813 {"&&", ANDAND, BINOP_END},
814 {"||", OROR, BINOP_END},
815 {"<<", LSH, BINOP_END},
816 {">>", RSH, BINOP_END},
817 {"==", EQUAL, BINOP_END},
818 {"!=", NOTEQUAL, BINOP_END},
819 {"<=", LEQ, BINOP_END},
820 {">=", GEQ, BINOP_END}
823 /* Read one token, getting characters through lexptr. */
825 static int
826 yylex (void)
828 int c;
829 int namelen;
830 unsigned int i;
831 const char *tokstart;
832 const char *tokptr;
833 int tempbufindex;
834 static char *tempbuf;
835 static int tempbufsize;
837 retry:
839 prev_lexptr = lexptr;
841 tokstart = lexptr;
842 /* See if it is a special token of length 3. */
843 for (i = 0; i < sizeof tokentab3 / sizeof tokentab3[0]; i++)
844 if (strncmp (tokstart, tokentab3[i].oper, 3) == 0)
846 lexptr += 3;
847 yylval.opcode = tokentab3[i].opcode;
848 return tokentab3[i].token;
851 /* See if it is a special token of length 2. */
852 for (i = 0; i < sizeof tokentab2 / sizeof tokentab2[0]; i++)
853 if (strncmp (tokstart, tokentab2[i].oper, 2) == 0)
855 lexptr += 2;
856 yylval.opcode = tokentab2[i].opcode;
857 return tokentab2[i].token;
860 switch (c = *tokstart)
862 case 0:
863 return 0;
865 case ' ':
866 case '\t':
867 case '\n':
868 lexptr++;
869 goto retry;
871 case '\'':
872 /* We either have a character constant ('0' or '\177' for example)
873 or we have a quoted symbol reference ('foo(int,int)' in C++
874 for example). */
875 lexptr++;
876 c = *lexptr++;
877 if (c == '\\')
878 c = parse_escape (parse_gdbarch (pstate), &lexptr);
879 else if (c == '\'')
880 error (_("Empty character constant"));
882 yylval.typed_val_int.val = c;
883 yylval.typed_val_int.type = parse_java_type (pstate)->builtin_char;
885 c = *lexptr++;
886 if (c != '\'')
888 namelen = skip_quoted (tokstart) - tokstart;
889 if (namelen > 2)
891 lexptr = tokstart + namelen;
892 if (lexptr[-1] != '\'')
893 error (_("Unmatched single quote"));
894 namelen -= 2;
895 tokstart++;
896 goto tryname;
898 error (_("Invalid character constant"));
900 return INTEGER_LITERAL;
902 case '(':
903 paren_depth++;
904 lexptr++;
905 return c;
907 case ')':
908 if (paren_depth == 0)
909 return 0;
910 paren_depth--;
911 lexptr++;
912 return c;
914 case ',':
915 if (comma_terminates && paren_depth == 0)
916 return 0;
917 lexptr++;
918 return c;
920 case '.':
921 /* Might be a floating point number. */
922 if (lexptr[1] < '0' || lexptr[1] > '9')
923 goto symbol; /* Nope, must be a symbol. */
924 /* FALL THRU into number case. */
926 case '0':
927 case '1':
928 case '2':
929 case '3':
930 case '4':
931 case '5':
932 case '6':
933 case '7':
934 case '8':
935 case '9':
937 /* It's a number. */
938 int got_dot = 0, got_e = 0, toktype;
939 const char *p = tokstart;
940 int hex = input_radix > 10;
942 if (c == '0' && (p[1] == 'x' || p[1] == 'X'))
944 p += 2;
945 hex = 1;
947 else if (c == '0' && (p[1]=='t' || p[1]=='T' || p[1]=='d' || p[1]=='D'))
949 p += 2;
950 hex = 0;
953 for (;; ++p)
955 /* This test includes !hex because 'e' is a valid hex digit
956 and thus does not indicate a floating point number when
957 the radix is hex. */
958 if (!hex && !got_e && (*p == 'e' || *p == 'E'))
959 got_dot = got_e = 1;
960 /* This test does not include !hex, because a '.' always indicates
961 a decimal floating point number regardless of the radix. */
962 else if (!got_dot && *p == '.')
963 got_dot = 1;
964 else if (got_e && (p[-1] == 'e' || p[-1] == 'E')
965 && (*p == '-' || *p == '+'))
966 /* This is the sign of the exponent, not the end of the
967 number. */
968 continue;
969 /* We will take any letters or digits. parse_number will
970 complain if past the radix, or if L or U are not final. */
971 else if ((*p < '0' || *p > '9')
972 && ((*p < 'a' || *p > 'z')
973 && (*p < 'A' || *p > 'Z')))
974 break;
976 toktype = parse_number (pstate, tokstart, p - tokstart,
977 got_dot|got_e, &yylval);
978 if (toktype == ERROR)
980 char *err_copy = (char *) alloca (p - tokstart + 1);
982 memcpy (err_copy, tokstart, p - tokstart);
983 err_copy[p - tokstart] = 0;
984 error (_("Invalid number \"%s\""), err_copy);
986 lexptr = p;
987 return toktype;
990 case '+':
991 case '-':
992 case '*':
993 case '/':
994 case '%':
995 case '|':
996 case '&':
997 case '^':
998 case '~':
999 case '!':
1000 case '<':
1001 case '>':
1002 case '[':
1003 case ']':
1004 case '?':
1005 case ':':
1006 case '=':
1007 case '{':
1008 case '}':
1009 symbol:
1010 lexptr++;
1011 return c;
1013 case '"':
1015 /* Build the gdb internal form of the input string in tempbuf,
1016 translating any standard C escape forms seen. Note that the
1017 buffer is null byte terminated *only* for the convenience of
1018 debugging gdb itself and printing the buffer contents when
1019 the buffer contains no embedded nulls. Gdb does not depend
1020 upon the buffer being null byte terminated, it uses the length
1021 string instead. This allows gdb to handle C strings (as well
1022 as strings in other languages) with embedded null bytes */
1024 tokptr = ++tokstart;
1025 tempbufindex = 0;
1027 do {
1028 /* Grow the static temp buffer if necessary, including allocating
1029 the first one on demand. */
1030 if (tempbufindex + 1 >= tempbufsize)
1032 tempbuf = (char *) realloc (tempbuf, tempbufsize += 64);
1034 switch (*tokptr)
1036 case '\0':
1037 case '"':
1038 /* Do nothing, loop will terminate. */
1039 break;
1040 case '\\':
1041 tokptr++;
1042 c = parse_escape (parse_gdbarch (pstate), &tokptr);
1043 if (c == -1)
1045 continue;
1047 tempbuf[tempbufindex++] = c;
1048 break;
1049 default:
1050 tempbuf[tempbufindex++] = *tokptr++;
1051 break;
1053 } while ((*tokptr != '"') && (*tokptr != '\0'));
1054 if (*tokptr++ != '"')
1056 error (_("Unterminated string in expression"));
1058 tempbuf[tempbufindex] = '\0'; /* See note above */
1059 yylval.sval.ptr = tempbuf;
1060 yylval.sval.length = tempbufindex;
1061 lexptr = tokptr;
1062 return (STRING_LITERAL);
1065 if (!(c == '_' || c == '$'
1066 || (c >= 'a' && c <= 'z') || (c >= 'A' && c <= 'Z')))
1067 /* We must have come across a bad character (e.g. ';'). */
1068 error (_("Invalid character '%c' in expression"), c);
1070 /* It's a name. See how long it is. */
1071 namelen = 0;
1072 for (c = tokstart[namelen];
1073 (c == '_'
1074 || c == '$'
1075 || (c >= '0' && c <= '9')
1076 || (c >= 'a' && c <= 'z')
1077 || (c >= 'A' && c <= 'Z')
1078 || c == '<');
1081 if (c == '<')
1083 int i = namelen;
1084 while (tokstart[++i] && tokstart[i] != '>');
1085 if (tokstart[i] == '>')
1086 namelen = i;
1088 c = tokstart[++namelen];
1091 /* The token "if" terminates the expression and is NOT
1092 removed from the input stream. */
1093 if (namelen == 2 && tokstart[0] == 'i' && tokstart[1] == 'f')
1095 return 0;
1098 lexptr += namelen;
1100 tryname:
1102 /* Catch specific keywords. Should be done with a data structure. */
1103 switch (namelen)
1105 case 7:
1106 if (strncmp (tokstart, "boolean", 7) == 0)
1107 return BOOLEAN;
1108 break;
1109 case 6:
1110 if (strncmp (tokstart, "double", 6) == 0)
1111 return DOUBLE;
1112 break;
1113 case 5:
1114 if (strncmp (tokstart, "short", 5) == 0)
1115 return SHORT;
1116 if (strncmp (tokstart, "false", 5) == 0)
1118 yylval.lval = 0;
1119 return BOOLEAN_LITERAL;
1121 if (strncmp (tokstart, "super", 5) == 0)
1122 return SUPER;
1123 if (strncmp (tokstart, "float", 5) == 0)
1124 return FLOAT;
1125 break;
1126 case 4:
1127 if (strncmp (tokstart, "long", 4) == 0)
1128 return LONG;
1129 if (strncmp (tokstart, "byte", 4) == 0)
1130 return BYTE;
1131 if (strncmp (tokstart, "char", 4) == 0)
1132 return CHAR;
1133 if (strncmp (tokstart, "true", 4) == 0)
1135 yylval.lval = 1;
1136 return BOOLEAN_LITERAL;
1138 break;
1139 case 3:
1140 if (strncmp (tokstart, "int", 3) == 0)
1141 return INT;
1142 if (strncmp (tokstart, "new", 3) == 0)
1143 return NEW;
1144 break;
1145 default:
1146 break;
1149 yylval.sval.ptr = tokstart;
1150 yylval.sval.length = namelen;
1152 if (*tokstart == '$')
1154 write_dollar_variable (pstate, yylval.sval);
1155 return VARIABLE;
1158 /* Input names that aren't symbols but ARE valid hex numbers,
1159 when the input radix permits them, can be names or numbers
1160 depending on the parse. Note we support radixes > 16 here. */
1161 if (((tokstart[0] >= 'a' && tokstart[0] < 'a' + input_radix - 10) ||
1162 (tokstart[0] >= 'A' && tokstart[0] < 'A' + input_radix - 10)))
1164 YYSTYPE newlval; /* Its value is ignored. */
1165 int hextype = parse_number (pstate, tokstart, namelen, 0, &newlval);
1166 if (hextype == INTEGER_LITERAL)
1167 return NAME_OR_INT;
1169 return IDENTIFIER;
1173 java_parse (struct parser_state *par_state)
1175 int result;
1176 struct cleanup *c = make_cleanup_clear_parser_state (&pstate);
1178 /* Setting up the parser state. */
1179 gdb_assert (par_state != NULL);
1180 pstate = par_state;
1182 result = yyparse ();
1183 do_cleanups (c);
1185 return result;
1188 void
1189 yyerror (char *msg)
1191 if (prev_lexptr)
1192 lexptr = prev_lexptr;
1194 if (msg)
1195 error (_("%s: near `%s'"), msg, lexptr);
1196 else
1197 error (_("error in expression, near `%s'"), lexptr);
1200 static struct type *
1201 java_type_from_name (struct stoken name)
1203 char *tmp = copy_name (name);
1204 struct type *typ = java_lookup_class (tmp);
1205 if (typ == NULL || TYPE_CODE (typ) != TYPE_CODE_STRUCT)
1206 error (_("No class named `%s'"), tmp);
1207 return typ;
1210 /* If NAME is a valid variable name in this scope, push it and return 1.
1211 Otherwise, return 0. */
1213 static int
1214 push_variable (struct parser_state *par_state, struct stoken name)
1216 char *tmp = copy_name (name);
1217 struct field_of_this_result is_a_field_of_this;
1218 struct block_symbol sym;
1220 sym = lookup_symbol (tmp, expression_context_block, VAR_DOMAIN,
1221 &is_a_field_of_this);
1222 if (sym.symbol && SYMBOL_CLASS (sym.symbol) != LOC_TYPEDEF)
1224 if (symbol_read_needs_frame (sym.symbol))
1226 if (innermost_block == 0 ||
1227 contained_in (sym.block, innermost_block))
1228 innermost_block = sym.block;
1231 write_exp_elt_opcode (par_state, OP_VAR_VALUE);
1232 write_exp_elt_block (par_state, sym.block);
1233 write_exp_elt_sym (par_state, sym.symbol);
1234 write_exp_elt_opcode (par_state, OP_VAR_VALUE);
1235 return 1;
1237 if (is_a_field_of_this.type != NULL)
1239 /* it hangs off of `this'. Must not inadvertently convert from a
1240 method call to data ref. */
1241 if (innermost_block == 0 ||
1242 contained_in (sym.block, innermost_block))
1243 innermost_block = sym.block;
1244 write_exp_elt_opcode (par_state, OP_THIS);
1245 write_exp_elt_opcode (par_state, OP_THIS);
1246 write_exp_elt_opcode (par_state, STRUCTOP_PTR);
1247 write_exp_string (par_state, name);
1248 write_exp_elt_opcode (par_state, STRUCTOP_PTR);
1249 return 1;
1251 return 0;
1254 /* Assuming a reference expression has been pushed, emit the
1255 STRUCTOP_PTR ops to access the field named NAME. If NAME is a
1256 qualified name (has '.'), generate a field access for each part. */
1258 static void
1259 push_fieldnames (struct parser_state *par_state, struct stoken name)
1261 int i;
1262 struct stoken token;
1263 token.ptr = name.ptr;
1264 for (i = 0; ; i++)
1266 if (i == name.length || name.ptr[i] == '.')
1268 /* token.ptr is start of current field name. */
1269 token.length = &name.ptr[i] - token.ptr;
1270 write_exp_elt_opcode (par_state, STRUCTOP_PTR);
1271 write_exp_string (par_state, token);
1272 write_exp_elt_opcode (par_state, STRUCTOP_PTR);
1273 token.ptr += token.length + 1;
1275 if (i >= name.length)
1276 break;
1280 /* Helper routine for push_expression_name.
1281 Handle a qualified name, where DOT_INDEX is the index of the first '.' */
1283 static void
1284 push_qualified_expression_name (struct parser_state *par_state,
1285 struct stoken name, int dot_index)
1287 struct stoken token;
1288 char *tmp;
1289 struct type *typ;
1291 token.ptr = name.ptr;
1292 token.length = dot_index;
1294 if (push_variable (par_state, token))
1296 token.ptr = name.ptr + dot_index + 1;
1297 token.length = name.length - dot_index - 1;
1298 push_fieldnames (par_state, token);
1299 return;
1302 token.ptr = name.ptr;
1303 for (;;)
1305 token.length = dot_index;
1306 tmp = copy_name (token);
1307 typ = java_lookup_class (tmp);
1308 if (typ != NULL)
1310 if (dot_index == name.length)
1312 write_exp_elt_opcode (par_state, OP_TYPE);
1313 write_exp_elt_type (par_state, typ);
1314 write_exp_elt_opcode (par_state, OP_TYPE);
1315 return;
1317 dot_index++; /* Skip '.' */
1318 name.ptr += dot_index;
1319 name.length -= dot_index;
1320 dot_index = 0;
1321 while (dot_index < name.length && name.ptr[dot_index] != '.')
1322 dot_index++;
1323 token.ptr = name.ptr;
1324 token.length = dot_index;
1325 write_exp_elt_opcode (par_state, OP_SCOPE);
1326 write_exp_elt_type (par_state, typ);
1327 write_exp_string (par_state, token);
1328 write_exp_elt_opcode (par_state, OP_SCOPE);
1329 if (dot_index < name.length)
1331 dot_index++;
1332 name.ptr += dot_index;
1333 name.length -= dot_index;
1334 push_fieldnames (par_state, name);
1336 return;
1338 else if (dot_index >= name.length)
1339 break;
1340 dot_index++; /* Skip '.' */
1341 while (dot_index < name.length && name.ptr[dot_index] != '.')
1342 dot_index++;
1344 error (_("unknown type `%.*s'"), name.length, name.ptr);
1347 /* Handle Name in an expression (or LHS).
1348 Handle VAR, TYPE, TYPE.FIELD1....FIELDN and VAR.FIELD1....FIELDN. */
1350 static void
1351 push_expression_name (struct parser_state *par_state, struct stoken name)
1353 char *tmp;
1354 struct type *typ;
1355 int i;
1357 for (i = 0; i < name.length; i++)
1359 if (name.ptr[i] == '.')
1361 /* It's a Qualified Expression Name. */
1362 push_qualified_expression_name (par_state, name, i);
1363 return;
1367 /* It's a Simple Expression Name. */
1369 if (push_variable (par_state, name))
1370 return;
1371 tmp = copy_name (name);
1372 typ = java_lookup_class (tmp);
1373 if (typ != NULL)
1375 write_exp_elt_opcode (par_state, OP_TYPE);
1376 write_exp_elt_type (par_state, typ);
1377 write_exp_elt_opcode (par_state, OP_TYPE);
1379 else
1381 struct bound_minimal_symbol msymbol;
1383 msymbol = lookup_bound_minimal_symbol (tmp);
1384 if (msymbol.minsym != NULL)
1385 write_exp_msymbol (par_state, msymbol);
1386 else if (!have_full_symbols () && !have_partial_symbols ())
1387 error (_("No symbol table is loaded. Use the \"file\" command"));
1388 else
1389 error (_("No symbol \"%s\" in current context."), tmp);
1395 /* The following two routines, copy_exp and insert_exp, aren't specific to
1396 Java, so they could go in parse.c, but their only purpose is to support
1397 the parsing kludges we use in this file, so maybe it's best to isolate
1398 them here. */
1400 /* Copy the expression whose last element is at index ENDPOS - 1 in EXPR
1401 into a freshly malloc'ed struct expression. Its language_defn is set
1402 to null. */
1403 static struct expression *
1404 copy_exp (struct expression *expr, int endpos)
1406 int len = length_of_subexp (expr, endpos);
1407 struct expression *newobj
1408 = (struct expression *) malloc (sizeof (*newobj) + EXP_ELEM_TO_BYTES (len));
1410 newobj->nelts = len;
1411 memcpy (newobj->elts, expr->elts + endpos - len, EXP_ELEM_TO_BYTES (len));
1412 newobj->language_defn = 0;
1414 return newobj;
1417 /* Insert the expression NEW into the current expression (expout) at POS. */
1418 static void
1419 insert_exp (struct parser_state *par_state, int pos, struct expression *newobj)
1421 int newlen = newobj->nelts;
1422 int i;
1424 /* Grow expout if necessary. In this function's only use at present,
1425 this should never be necessary. */
1426 increase_expout_size (par_state, newlen);
1428 for (i = par_state->expout_ptr - 1; i >= pos; i--)
1429 par_state->expout->elts[i + newlen] = par_state->expout->elts[i];
1431 memcpy (par_state->expout->elts + pos, newobj->elts,
1432 EXP_ELEM_TO_BYTES (newlen));
1433 par_state->expout_ptr += newlen;