Replace copyreloc-main.c with copyreloc-main.S
[platform/upstream/binutils.git] / gdb / jv-exp.y
1 /* YACC parser for Java expressions, for GDB.
2    Copyright (C) 1997-2014 Free Software Foundation, Inc.
3
4    This file is part of GDB.
5
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.
10
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.
15
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/>.  */
18
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.
27
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.  */
35   
36 %{
37
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"
50
51 #define parse_type(ps) builtin_type (parse_gdbarch (ps))
52 #define parse_java_type(ps) builtin_java_type (parse_gdbarch (ps))
53
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.  */
60
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       
69 #define yyr1    java_r1                 
70 #define yyr2    java_r2                 
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
78 #define yyps    java_ps
79 #define yypv    java_pv
80 #define yys     java_s
81 #define yy_yys  java_yys
82 #define yystate java_state
83 #define yytmp   java_tmp
84 #define yyv     java_v
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
107
108 #ifndef YYDEBUG
109 #define YYDEBUG 1               /* Default to yydebug support */
110 #endif
111
112 #define YYFPRINTF parser_fprintf
113
114 /* The state of the parser, used internally when we are parsing the
115    expression.  */
116
117 static struct parser_state *pstate = NULL;
118
119 int yyparse (void);
120
121 static int yylex (void);
122
123 void yyerror (char *);
124
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);
128
129 static struct expression *copy_exp (struct expression *, int);
130 static void insert_exp (struct parser_state *, int, struct expression *);
131
132 %}
133
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.  */
137
138 %union
139   {
140     LONGEST lval;
141     struct {
142       LONGEST val;
143       struct type *type;
144     } typed_val_int;
145     struct {
146       DOUBLEST dval;
147       struct type *type;
148     } typed_val_float;
149     struct symbol *sym;
150     struct type *tval;
151     struct stoken sval;
152     struct ttype tsym;
153     struct symtoken ssym;
154     struct block *bval;
155     enum exp_opcode opcode;
156     struct internalvar *ivar;
157     int *ivec;
158   }
159
160 %{
161 /* YYSTYPE gets defined by %union */
162 static int parse_number (struct parser_state *, const char *, int,
163                          int, YYSTYPE *);
164 %}
165
166 %type <lval> rcurly Dims Dims_opt
167 %type <tval> ClassOrInterfaceType ClassType /* ReferenceType Type ArrayType */
168 %type <tval> IntegralType FloatingPointType NumericType PrimitiveType ArrayType PrimitiveOrArrayType
169
170 %token <typed_val_int> INTEGER_LITERAL
171 %token <typed_val_float> FLOATING_POINT_LITERAL
172
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
178
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.  */
183
184 %token <sval> NAME_OR_INT 
185
186 %token ERROR
187
188 /* Special type cases, put in to allow the parser to distinguish different
189    legal basetypes.  */
190 %token LONG SHORT BYTE INT CHAR BOOLEAN DOUBLE FLOAT
191
192 %token VARIABLE
193
194 %token <opcode> ASSIGN_MODIFY
195
196 %token SUPER NEW
197
198 %left ','
199 %right '=' ASSIGN_MODIFY
200 %right '?'
201 %left OROR
202 %left ANDAND
203 %left '|'
204 %left '^'
205 %left '&'
206 %left EQUAL NOTEQUAL
207 %left '<' '>' LEQ GEQ
208 %left LSH RSH
209 %left '+' '-'
210 %left '*' '/' '%'
211 %right INCREMENT DECREMENT
212 %right '.' '[' '('
213
214 \f
215 %%
216
217 start   :       exp1
218         |       type_exp
219         ;
220
221 type_exp:       PrimitiveOrArrayType
222                 {
223                   write_exp_elt_opcode (pstate, OP_TYPE);
224                   write_exp_elt_type (pstate, $1);
225                   write_exp_elt_opcode (pstate, OP_TYPE);
226                 }
227         ;
228
229 PrimitiveOrArrayType:
230                 PrimitiveType
231         |       ArrayType
232         ;
233
234 StringLiteral:
235         STRING_LITERAL
236                 {
237                   write_exp_elt_opcode (pstate, OP_STRING);
238                   write_exp_string (pstate, $1);
239                   write_exp_elt_opcode (pstate, OP_STRING);
240                 }
241 ;
242
243 Literal:
244         INTEGER_LITERAL
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); }
249 |       NAME_OR_INT
250                 { YYSTYPE val;
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);
257                 }
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); }
263 |       BOOLEAN_LITERAL
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); }
269 |       StringLiteral
270         ;
271
272 /* UNUSED:
273 Type:
274         PrimitiveType
275 |       ReferenceType
276 ;
277 */
278
279 PrimitiveType:
280         NumericType
281 |       BOOLEAN
282                 { $$ = parse_java_type (pstate)->builtin_boolean; }
283 ;
284
285 NumericType:
286         IntegralType
287 |       FloatingPointType
288 ;
289
290 IntegralType:
291         BYTE
292                 { $$ = parse_java_type (pstate)->builtin_byte; }
293 |       SHORT
294                 { $$ = parse_java_type (pstate)->builtin_short; }
295 |       INT
296                 { $$ = parse_java_type (pstate)->builtin_int; }
297 |       LONG
298                 { $$ = parse_java_type (pstate)->builtin_long; }
299 |       CHAR
300                 { $$ = parse_java_type (pstate)->builtin_char; }
301 ;
302
303 FloatingPointType:
304         FLOAT
305                 { $$ = parse_java_type (pstate)->builtin_float; }
306 |       DOUBLE
307                 { $$ = parse_java_type (pstate)->builtin_double; }
308 ;
309
310 /* UNUSED:
311 ReferenceType:
312         ClassOrInterfaceType
313 |       ArrayType
314 ;
315 */
316
317 ClassOrInterfaceType:
318         Name
319                 { $$ = java_type_from_name ($1); }
320 ;
321
322 ClassType:
323         ClassOrInterfaceType
324 ;
325
326 ArrayType:
327         PrimitiveType Dims
328                 { $$ = java_array_type ($1, $2); }
329 |       Name Dims
330                 { $$ = java_array_type (java_type_from_name ($1), $2); }
331 ;
332
333 Name:
334         IDENTIFIER
335 |       QualifiedName
336 ;
337
338 ForcedName:
339         SimpleName
340 |       QualifiedName
341 ;
342
343 SimpleName:
344         IDENTIFIER
345 |       NAME_OR_INT
346 ;
347
348 QualifiedName:
349         Name '.' SimpleName
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.  */
354                   else
355                     {
356                       char *buf;
357
358                       buf = malloc ($$.length + 1);
359                       make_cleanup (free, buf);
360                       sprintf (buf, "%.*s.%.*s",
361                                $1.length, $1.ptr, $3.length, $3.ptr);
362                       $$.ptr = buf;
363                 } }
364 ;
365
366 /*
367 type_exp:       type
368                         { write_exp_elt_opcode(OP_TYPE);
369                           write_exp_elt_type($1);
370                           write_exp_elt_opcode(OP_TYPE);}
371         ;
372         */
373
374 /* Expressions, including the comma operator.  */
375 exp1    :       Expression
376         |       exp1 ',' Expression
377                         { write_exp_elt_opcode (pstate, BINOP_COMMA); }
378         ;
379
380 Primary:
381         PrimaryNoNewArray
382 |       ArrayCreationExpression
383 ;
384
385 PrimaryNoNewArray:
386         Literal
387 |       '(' Expression ')'
388 |       ClassInstanceCreationExpression
389 |       FieldAccess
390 |       MethodInvocation
391 |       ArrayAccess
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); }
397 ;
398
399 lcurly:
400         '{'
401                 { start_arglist (); }
402 ;
403
404 rcurly:
405         '}'
406                 { $$ = end_arglist () - 1; }
407 ;
408
409 ClassInstanceCreationExpression:
410         NEW ClassType '(' ArgumentList_opt ')'
411                 { internal_error (__FILE__, __LINE__,
412                                   _("FIXME - ClassInstanceCreationExpression")); }
413 ;
414
415 ArgumentList:
416         Expression
417                 { arglist_len = 1; }
418 |       ArgumentList ',' Expression
419                 { arglist_len++; }
420 ;
421
422 ArgumentList_opt:
423         /* EMPTY */
424                 { arglist_len = 0; }
425 | ArgumentList
426 ;
427
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")); }
435 ;
436
437 DimExprs:
438         DimExpr
439 |       DimExprs DimExpr
440 ;
441
442 DimExpr:
443         '[' Expression ']'
444 ;
445
446 Dims:
447         '[' ']'
448                 { $$ = 1; }
449 |       Dims '[' ']'
450         { $$ = $1 + 1; }
451 ;
452
453 Dims_opt:
454         Dims
455 |       /* EMPTY */
456                 { $$ = 0; }
457 ;
458
459 FieldAccess:
460         Primary '.' SimpleName
461                 { push_fieldnames (pstate, $3); }
462 |       VARIABLE '.' SimpleName
463                 { push_fieldnames (pstate, $3); }
464 /*|     SUPER '.' SimpleName { FIXME } */
465 ;
466
467 FuncStart:
468         Name '('
469                 { push_expression_name (pstate, $1); }
470 ;
471
472 MethodInvocation:
473         FuncStart
474                 { start_arglist(); }
475         ArgumentList_opt ')'
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")); }
483 ;
484
485 ArrayAccess:
486         Name '[' Expression ']'
487                 {
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;
494
495                   push_expression_name (pstate, $1);
496                   name_expr = copy_exp (pstate->expout, pstate->expout_ptr);
497                   pstate->expout_ptr -= name_expr->nelts;
498                   insert_exp (pstate,
499                               pstate->expout_ptr
500                               - length_of_subexp (pstate->expout,
501                                                   pstate->expout_ptr),
502                               name_expr);
503                   free (name_expr);
504                   write_exp_elt_opcode (pstate, BINOP_SUBSCRIPT);
505                 }
506 |       VARIABLE '[' Expression ']'
507                 { write_exp_elt_opcode (pstate, BINOP_SUBSCRIPT); }
508 |       PrimaryNoNewArray '[' Expression ']'
509                 { write_exp_elt_opcode (pstate, BINOP_SUBSCRIPT); }
510 ;
511
512 PostfixExpression:
513         Primary
514 |       Name
515                 { push_expression_name (pstate, $1); }
516 |       VARIABLE
517                 /* Already written by write_dollar_variable.  */
518 |       PostIncrementExpression
519 |       PostDecrementExpression
520 ;
521
522 PostIncrementExpression:
523         PostfixExpression INCREMENT
524                 { write_exp_elt_opcode (pstate, UNOP_POSTINCREMENT); }
525 ;
526
527 PostDecrementExpression:
528         PostfixExpression DECREMENT
529                 { write_exp_elt_opcode (pstate, UNOP_POSTDECREMENT); }
530 ;
531
532 UnaryExpression:
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
542 ;
543
544 PreIncrementExpression:
545         INCREMENT UnaryExpression
546                 { write_exp_elt_opcode (pstate, UNOP_PREINCREMENT); }
547 ;
548
549 PreDecrementExpression:
550         DECREMENT UnaryExpression
551                 { write_exp_elt_opcode (pstate, UNOP_PREDECREMENT); }
552 ;
553
554 UnaryExpressionNotPlusMinus:
555         PostfixExpression
556 |       '~' UnaryExpression
557                 { write_exp_elt_opcode (pstate, UNOP_COMPLEMENT); }
558 |       '!' UnaryExpression
559                 { write_exp_elt_opcode (pstate, UNOP_LOGICAL_NOT); }
560 |       CastExpression
561         ;
562
563 CastExpression:
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
569                 {
570                   int last_exp_size = length_of_subexp (pstate->expout,
571                                                         pstate->expout_ptr);
572                   struct type *type;
573                   int i;
574                   int base = pstate->expout_ptr - last_exp_size - 3;
575
576                   if (base < 0
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);
591                 }
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
596                                                        ($2), $3));
597                   write_exp_elt_opcode (pstate, UNOP_CAST); }
598 ;
599
600
601 MultiplicativeExpression:
602         UnaryExpression
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); }
609 ;
610
611 AdditiveExpression:
612         MultiplicativeExpression
613 |       AdditiveExpression '+' MultiplicativeExpression
614                 { write_exp_elt_opcode (pstate, BINOP_ADD); }
615 |       AdditiveExpression '-' MultiplicativeExpression
616                 { write_exp_elt_opcode (pstate, BINOP_SUB); }
617 ;
618
619 ShiftExpression:
620         AdditiveExpression
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 } */
626 ;
627
628 RelationalExpression:
629         ShiftExpression
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 } */
639 ;
640
641 EqualityExpression:
642         RelationalExpression
643 |       EqualityExpression EQUAL RelationalExpression
644                 { write_exp_elt_opcode (pstate, BINOP_EQUAL); }
645 |       EqualityExpression NOTEQUAL RelationalExpression
646                 { write_exp_elt_opcode (pstate, BINOP_NOTEQUAL); }
647 ;
648
649 AndExpression:
650         EqualityExpression
651 |       AndExpression '&' EqualityExpression
652                 { write_exp_elt_opcode (pstate, BINOP_BITWISE_AND); }
653 ;
654
655 ExclusiveOrExpression:
656         AndExpression
657 |       ExclusiveOrExpression '^' AndExpression
658                 { write_exp_elt_opcode (pstate, BINOP_BITWISE_XOR); }
659 ;
660 InclusiveOrExpression:
661         ExclusiveOrExpression
662 |       InclusiveOrExpression '|' ExclusiveOrExpression
663                 { write_exp_elt_opcode (pstate, BINOP_BITWISE_IOR); }
664 ;
665
666 ConditionalAndExpression:
667         InclusiveOrExpression
668 |       ConditionalAndExpression ANDAND InclusiveOrExpression
669                 { write_exp_elt_opcode (pstate, BINOP_LOGICAL_AND); }
670 ;
671
672 ConditionalOrExpression:
673         ConditionalAndExpression
674 |       ConditionalOrExpression OROR ConditionalAndExpression
675                 { write_exp_elt_opcode (pstate, BINOP_LOGICAL_OR); }
676 ;
677
678 ConditionalExpression:
679         ConditionalOrExpression
680 |       ConditionalOrExpression '?' Expression ':' ConditionalExpression
681                 { write_exp_elt_opcode (pstate, TERNOP_COND); }
682 ;
683
684 AssignmentExpression:
685         ConditionalExpression
686 |       Assignment
687 ;
688                           
689 Assignment:
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); }
696 ;
697
698 LeftHandSide:
699         ForcedName
700                 { push_expression_name (pstate, $1); }
701 |       VARIABLE
702                 /* Already written by write_dollar_variable.  */
703 |       FieldAccess
704 |       ArrayAccess
705 ;
706
707
708 Expression:
709         AssignmentExpression
710 ;
711
712 %%
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.  */
716
717 /*** Needs some error checking for the float case ***/
718
719 static int
720 parse_number (struct parser_state *par_state,
721               const char *p, int len, int parsed_float, YYSTYPE *putithere)
722 {
723   ULONGEST n = 0;
724   ULONGEST limit, limit_div_base;
725
726   int c;
727   int base = input_radix;
728
729   struct type *type;
730
731   if (parsed_float)
732     {
733       const char *suffix;
734       int suffix_len;
735
736       if (! parse_float (p, len, &putithere->typed_val_float.dval, &suffix))
737         return ERROR;
738
739       suffix_len = p + len - suffix;
740
741       if (suffix_len == 0)
742         putithere->typed_val_float.type
743           = parse_type (par_state)->builtin_double;
744       else if (suffix_len == 1)
745         {
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;
753           else
754             return ERROR;
755         }
756       else
757         return ERROR;
758
759       return FLOATING_POINT_LITERAL;
760     }
761
762   /* Handle base-switching prefixes 0x, 0t, 0d, 0 */
763   if (p[0] == '0')
764     switch (p[1])
765       {
766       case 'x':
767       case 'X':
768         if (len >= 3)
769           {
770             p += 2;
771             base = 16;
772             len -= 2;
773           }
774         break;
775
776       case 't':
777       case 'T':
778       case 'd':
779       case 'D':
780         if (len >= 3)
781           {
782             p += 2;
783             base = 10;
784             len -= 2;
785           }
786         break;
787
788       default:
789         base = 8;
790         break;
791       }
792
793   c = p[len-1];
794   /* A paranoid calculation of (1<<64)-1.  */
795   limit = (ULONGEST)0xffffffff;
796   limit = ((limit << 16) << 16) | limit;
797   if (c == 'l' || c == 'L')
798     {
799       type = parse_java_type (par_state)->builtin_long;
800       len--;
801     }
802   else
803     {
804       type = parse_java_type (par_state)->builtin_int;
805     }
806   limit_div_base = limit / (ULONGEST) base;
807
808   while (--len >= 0)
809     {
810       c = *p++;
811       if (c >= '0' && c <= '9')
812         c -= '0';
813       else if (c >= 'A' && c <= 'Z')
814         c -= 'A' - 10;
815       else if (c >= 'a' && c <= 'z')
816         c -= 'a' - 10;
817       else
818         return ERROR;   /* Char not a digit */
819       if (c >= base)
820         return ERROR;
821       if (n > limit_div_base
822           || (n *= base) > limit - c)
823         error (_("Numeric constant too large"));
824       n += c;
825         }
826
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;
836
837   putithere->typed_val_int.val = n;
838   putithere->typed_val_int.type = type;
839
840   return INTEGER_LITERAL;
841 }
842
843 struct token
844 {
845   char *operator;
846   int token;
847   enum exp_opcode opcode;
848 };
849
850 static const struct token tokentab3[] =
851   {
852     {">>=", ASSIGN_MODIFY, BINOP_RSH},
853     {"<<=", ASSIGN_MODIFY, BINOP_LSH}
854   };
855
856 static const struct token tokentab2[] =
857   {
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}
876   };
877
878 /* Read one token, getting characters through lexptr.  */
879
880 static int
881 yylex (void)
882 {
883   int c;
884   int namelen;
885   unsigned int i;
886   const char *tokstart;
887   const char *tokptr;
888   int tempbufindex;
889   static char *tempbuf;
890   static int tempbufsize;
891   
892  retry:
893
894   prev_lexptr = lexptr;
895
896   tokstart = 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)
900       {
901         lexptr += 3;
902         yylval.opcode = tokentab3[i].opcode;
903         return tokentab3[i].token;
904       }
905
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)
909       {
910         lexptr += 2;
911         yylval.opcode = tokentab2[i].opcode;
912         return tokentab2[i].token;
913       }
914
915   switch (c = *tokstart)
916     {
917     case 0:
918       return 0;
919
920     case ' ':
921     case '\t':
922     case '\n':
923       lexptr++;
924       goto retry;
925
926     case '\'':
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++
929          for example).  */
930       lexptr++;
931       c = *lexptr++;
932       if (c == '\\')
933         c = parse_escape (parse_gdbarch (pstate), &lexptr);
934       else if (c == '\'')
935         error (_("Empty character constant"));
936
937       yylval.typed_val_int.val = c;
938       yylval.typed_val_int.type = parse_java_type (pstate)->builtin_char;
939
940       c = *lexptr++;
941       if (c != '\'')
942         {
943           namelen = skip_quoted (tokstart) - tokstart;
944           if (namelen > 2)
945             {
946               lexptr = tokstart + namelen;
947               if (lexptr[-1] != '\'')
948                 error (_("Unmatched single quote"));
949               namelen -= 2;
950               tokstart++;
951               goto tryname;
952             }
953           error (_("Invalid character constant"));
954         }
955       return INTEGER_LITERAL;
956
957     case '(':
958       paren_depth++;
959       lexptr++;
960       return c;
961
962     case ')':
963       if (paren_depth == 0)
964         return 0;
965       paren_depth--;
966       lexptr++;
967       return c;
968
969     case ',':
970       if (comma_terminates && paren_depth == 0)
971         return 0;
972       lexptr++;
973       return c;
974
975     case '.':
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.  */
980
981     case '0':
982     case '1':
983     case '2':
984     case '3':
985     case '4':
986     case '5':
987     case '6':
988     case '7':
989     case '8':
990     case '9':
991       {
992         /* It's a number.  */
993         int got_dot = 0, got_e = 0, toktype;
994         const char *p = tokstart;
995         int hex = input_radix > 10;
996
997         if (c == '0' && (p[1] == 'x' || p[1] == 'X'))
998           {
999             p += 2;
1000             hex = 1;
1001           }
1002         else if (c == '0' && (p[1]=='t' || p[1]=='T' || p[1]=='d' || p[1]=='D'))
1003           {
1004             p += 2;
1005             hex = 0;
1006           }
1007
1008         for (;; ++p)
1009           {
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 == '.')
1018               got_dot = 1;
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
1022                  number.  */
1023               continue;
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')))
1029               break;
1030           }
1031         toktype = parse_number (pstate, tokstart, p - tokstart,
1032                                 got_dot|got_e, &yylval);
1033         if (toktype == ERROR)
1034           {
1035             char *err_copy = (char *) alloca (p - tokstart + 1);
1036
1037             memcpy (err_copy, tokstart, p - tokstart);
1038             err_copy[p - tokstart] = 0;
1039             error (_("Invalid number \"%s\""), err_copy);
1040           }
1041         lexptr = p;
1042         return toktype;
1043       }
1044
1045     case '+':
1046     case '-':
1047     case '*':
1048     case '/':
1049     case '%':
1050     case '|':
1051     case '&':
1052     case '^':
1053     case '~':
1054     case '!':
1055     case '<':
1056     case '>':
1057     case '[':
1058     case ']':
1059     case '?':
1060     case ':':
1061     case '=':
1062     case '{':
1063     case '}':
1064     symbol:
1065       lexptr++;
1066       return c;
1067
1068     case '"':
1069
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 */
1078
1079       tokptr = ++tokstart;
1080       tempbufindex = 0;
1081
1082       do {
1083         /* Grow the static temp buffer if necessary, including allocating
1084            the first one on demand.  */
1085         if (tempbufindex + 1 >= tempbufsize)
1086           {
1087             tempbuf = (char *) realloc (tempbuf, tempbufsize += 64);
1088           }
1089         switch (*tokptr)
1090           {
1091           case '\0':
1092           case '"':
1093             /* Do nothing, loop will terminate.  */
1094             break;
1095           case '\\':
1096             tokptr++;
1097             c = parse_escape (parse_gdbarch (pstate), &tokptr);
1098             if (c == -1)
1099               {
1100                 continue;
1101               }
1102             tempbuf[tempbufindex++] = c;
1103             break;
1104           default:
1105             tempbuf[tempbufindex++] = *tokptr++;
1106             break;
1107           }
1108       } while ((*tokptr != '"') && (*tokptr != '\0'));
1109       if (*tokptr++ != '"')
1110         {
1111           error (_("Unterminated string in expression"));
1112         }
1113       tempbuf[tempbufindex] = '\0';     /* See note above */
1114       yylval.sval.ptr = tempbuf;
1115       yylval.sval.length = tempbufindex;
1116       lexptr = tokptr;
1117       return (STRING_LITERAL);
1118     }
1119
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);
1124
1125   /* It's a name.  See how long it is.  */
1126   namelen = 0;
1127   for (c = tokstart[namelen];
1128        (c == '_'
1129         || c == '$'
1130         || (c >= '0' && c <= '9')
1131         || (c >= 'a' && c <= 'z')
1132         || (c >= 'A' && c <= 'Z')
1133         || c == '<');
1134        )
1135     {
1136       if (c == '<')
1137         {
1138           int i = namelen;
1139           while (tokstart[++i] && tokstart[i] != '>');
1140           if (tokstart[i] == '>')
1141             namelen = i;
1142         }
1143        c = tokstart[++namelen];
1144      }
1145
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')
1149     {
1150       return 0;
1151     }
1152
1153   lexptr += namelen;
1154
1155   tryname:
1156
1157   /* Catch specific keywords.  Should be done with a data structure.  */
1158   switch (namelen)
1159     {
1160     case 7:
1161       if (strncmp (tokstart, "boolean", 7) == 0)
1162         return BOOLEAN;
1163       break;
1164     case 6:
1165       if (strncmp (tokstart, "double", 6) == 0)      
1166         return DOUBLE;
1167       break;
1168     case 5:
1169       if (strncmp (tokstart, "short", 5) == 0)
1170         return SHORT;
1171       if (strncmp (tokstart, "false", 5) == 0)
1172         {
1173           yylval.lval = 0;
1174           return BOOLEAN_LITERAL;
1175         }
1176       if (strncmp (tokstart, "super", 5) == 0)
1177         return SUPER;
1178       if (strncmp (tokstart, "float", 5) == 0)
1179         return FLOAT;
1180       break;
1181     case 4:
1182       if (strncmp (tokstart, "long", 4) == 0)
1183         return LONG;
1184       if (strncmp (tokstart, "byte", 4) == 0)
1185         return BYTE;
1186       if (strncmp (tokstart, "char", 4) == 0)
1187         return CHAR;
1188       if (strncmp (tokstart, "true", 4) == 0)
1189         {
1190           yylval.lval = 1;
1191           return BOOLEAN_LITERAL;
1192         }
1193       break;
1194     case 3:
1195       if (strncmp (tokstart, "int", 3) == 0)
1196         return INT;
1197       if (strncmp (tokstart, "new", 3) == 0)
1198         return NEW;
1199       break;
1200     default:
1201       break;
1202     }
1203
1204   yylval.sval.ptr = tokstart;
1205   yylval.sval.length = namelen;
1206
1207   if (*tokstart == '$')
1208     {
1209       write_dollar_variable (pstate, yylval.sval);
1210       return VARIABLE;
1211     }
1212
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)))
1218     {
1219       YYSTYPE newlval;  /* Its value is ignored.  */
1220       int hextype = parse_number (pstate, tokstart, namelen, 0, &newlval);
1221       if (hextype == INTEGER_LITERAL)
1222         return NAME_OR_INT;
1223     }
1224   return IDENTIFIER;
1225 }
1226
1227 int
1228 java_parse (struct parser_state *par_state)
1229 {
1230   int result;
1231   struct cleanup *c = make_cleanup_clear_parser_state (&pstate);
1232
1233   /* Setting up the parser state.  */
1234   gdb_assert (par_state != NULL);
1235   pstate = par_state;
1236
1237   result = yyparse ();
1238   do_cleanups (c);
1239
1240   return result;
1241 }
1242
1243 void
1244 yyerror (char *msg)
1245 {
1246   if (prev_lexptr)
1247     lexptr = prev_lexptr;
1248
1249   if (msg)
1250     error (_("%s: near `%s'"), msg, lexptr);
1251   else
1252     error (_("error in expression, near `%s'"), lexptr);
1253 }
1254
1255 static struct type *
1256 java_type_from_name (struct stoken name)
1257 {
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);
1262   return typ;
1263 }
1264
1265 /* If NAME is a valid variable name in this scope, push it and return 1.
1266    Otherwise, return 0.  */
1267
1268 static int
1269 push_variable (struct parser_state *par_state, struct stoken name)
1270 {
1271   char *tmp = copy_name (name);
1272   struct field_of_this_result is_a_field_of_this;
1273   struct symbol *sym;
1274
1275   sym = lookup_symbol (tmp, expression_context_block, VAR_DOMAIN,
1276                        &is_a_field_of_this);
1277   if (sym && SYMBOL_CLASS (sym) != LOC_TYPEDEF)
1278     {
1279       if (symbol_read_needs_frame (sym))
1280         {
1281           if (innermost_block == 0 ||
1282               contained_in (block_found, innermost_block))
1283             innermost_block = block_found;
1284         }
1285
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);
1292       return 1;
1293     }
1294   if (is_a_field_of_this.type != NULL)
1295     {
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);
1306       return 1;
1307     }
1308   return 0;
1309 }
1310
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.  */
1314
1315 static void
1316 push_fieldnames (struct parser_state *par_state, struct stoken name)
1317 {
1318   int i;
1319   struct stoken token;
1320   token.ptr = name.ptr;
1321   for (i = 0;  ;  i++)
1322     {
1323       if (i == name.length || name.ptr[i] == '.')
1324         {
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;
1331         }
1332       if (i >= name.length)
1333         break;
1334     }
1335 }
1336
1337 /* Helper routine for push_expression_name.
1338    Handle a qualified name, where DOT_INDEX is the index of the first '.' */
1339
1340 static void
1341 push_qualified_expression_name (struct parser_state *par_state,
1342                                 struct stoken name, int dot_index)
1343 {
1344   struct stoken token;
1345   char *tmp;
1346   struct type *typ;
1347
1348   token.ptr = name.ptr;
1349   token.length = dot_index;
1350
1351   if (push_variable (par_state, token))
1352     {
1353       token.ptr = name.ptr + dot_index + 1;
1354       token.length = name.length - dot_index - 1;
1355       push_fieldnames (par_state, token);
1356       return;
1357     }
1358
1359   token.ptr = name.ptr;
1360   for (;;)
1361     {
1362       token.length = dot_index;
1363       tmp = copy_name (token);
1364       typ = java_lookup_class (tmp);
1365       if (typ != NULL)
1366         {
1367           if (dot_index == name.length)
1368             {
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);
1372               return;
1373             }
1374           dot_index++;  /* Skip '.' */
1375           name.ptr += dot_index;
1376           name.length -= dot_index;
1377           dot_index = 0;
1378           while (dot_index < name.length && name.ptr[dot_index] != '.') 
1379             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)
1387             {
1388               dot_index++;
1389               name.ptr += dot_index;
1390               name.length -= dot_index;
1391               push_fieldnames (par_state, name);
1392             }
1393           return;
1394         }
1395       else if (dot_index >= name.length)
1396         break;
1397       dot_index++;  /* Skip '.' */
1398       while (dot_index < name.length && name.ptr[dot_index] != '.')
1399         dot_index++;
1400     }
1401   error (_("unknown type `%.*s'"), name.length, name.ptr);
1402 }
1403
1404 /* Handle Name in an expression (or LHS).
1405    Handle VAR, TYPE, TYPE.FIELD1....FIELDN and VAR.FIELD1....FIELDN.  */
1406
1407 static void
1408 push_expression_name (struct parser_state *par_state, struct stoken name)
1409 {
1410   char *tmp;
1411   struct type *typ;
1412   int i;
1413
1414   for (i = 0;  i < name.length;  i++)
1415     {
1416       if (name.ptr[i] == '.')
1417         {
1418           /* It's a Qualified Expression Name.  */
1419           push_qualified_expression_name (par_state, name, i);
1420           return;
1421         }
1422     }
1423
1424   /* It's a Simple Expression Name.  */
1425   
1426   if (push_variable (par_state, name))
1427     return;
1428   tmp = copy_name (name);
1429   typ = java_lookup_class (tmp);
1430   if (typ != NULL)
1431     {
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);
1435     }
1436   else
1437     {
1438       struct bound_minimal_symbol msymbol;
1439
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"));
1445       else
1446         error (_("No symbol \"%s\" in current context."), tmp);
1447     }
1448
1449 }
1450
1451
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
1455    them here.  */
1456
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
1459    to null.  */
1460 static struct expression *
1461 copy_exp (struct expression *expr, int endpos)
1462 {
1463   int len = length_of_subexp (expr, endpos);
1464   struct expression *new
1465     = (struct expression *) malloc (sizeof (*new) + EXP_ELEM_TO_BYTES (len));
1466
1467   new->nelts = len;
1468   memcpy (new->elts, expr->elts + endpos - len, EXP_ELEM_TO_BYTES (len));
1469   new->language_defn = 0;
1470
1471   return new;
1472 }
1473
1474 /* Insert the expression NEW into the current expression (expout) at POS.  */
1475 static void
1476 insert_exp (struct parser_state *par_state, int pos, struct expression *new)
1477 {
1478   int newlen = new->nelts;
1479   int i;
1480
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);
1484
1485   for (i = par_state->expout_ptr - 1; i >= pos; i--)
1486     par_state->expout->elts[i + newlen] = par_state->expout->elts[i];
1487   
1488   memcpy (par_state->expout->elts + pos, new->elts,
1489           EXP_ELEM_TO_BYTES (newlen));
1490   par_state->expout_ptr += newlen;
1491 }