1130803Smarcel/* YACC parser for Ada expressions, for GDB.
2130803Smarcel   Copyright (C) 1986, 1989, 1990, 1991, 1993, 1994, 1997, 2000, 2003
3130803Smarcel   Free Software Foundation, Inc.
4130803Smarcel
5130803SmarcelThis file is part of GDB.
6130803Smarcel
7130803SmarcelThis program is free software; you can redistribute it and/or modify
8130803Smarcelit under the terms of the GNU General Public License as published by
9130803Smarcelthe Free Software Foundation; either version 2 of the License, or
10130803Smarcel(at your option) any later version.
11130803Smarcel
12130803SmarcelThis program is distributed in the hope that it will be useful,
13130803Smarcelbut WITHOUT ANY WARRANTY; without even the implied warranty of
14130803SmarcelMERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE.  See the
15130803SmarcelGNU General Public License for more details.
16130803Smarcel
17130803SmarcelYou should have received a copy of the GNU General Public License
18130803Smarcelalong with this program; if not, write to the Free Software
19130803SmarcelFoundation, Inc., 675 Mass Ave, Cambridge, MA 02139, USA.  */
20130803Smarcel
21130803Smarcel/* Parse an Ada expression from text in a string,
22130803Smarcel   and return the result as a  struct expression  pointer.
23130803Smarcel   That structure contains arithmetic operations in reverse polish,
24130803Smarcel   with constants represented by operations that are followed by special data.
25130803Smarcel   See expression.h for the details of the format.
26130803Smarcel   What is important here is that it can be built up sequentially
27130803Smarcel   during the process of parsing; the lower levels of the tree always
28130803Smarcel   come first in the result.
29130803Smarcel
30130803Smarcel   malloc's and realloc's in this file are transformed to
31130803Smarcel   xmalloc and xrealloc respectively by the same sed command in the
32130803Smarcel   makefile that remaps any other malloc/realloc inserted by the parser
33130803Smarcel   generator.  Doing this with #defines and trying to control the interaction
34130803Smarcel   with include files (<malloc.h> and <stdlib.h> for example) just became
35130803Smarcel   too messy, particularly when such includes can be inserted at random
36130803Smarcel   times by the parser generator.  */
37130803Smarcel
38130803Smarcel%{
39130803Smarcel
40130803Smarcel#include "defs.h"
41130803Smarcel#include <string.h>
42130803Smarcel#include <ctype.h>
43130803Smarcel#include "expression.h"
44130803Smarcel#include "value.h"
45130803Smarcel#include "parser-defs.h"
46130803Smarcel#include "language.h"
47130803Smarcel#include "ada-lang.h"
48130803Smarcel#include "bfd.h" /* Required by objfiles.h.  */
49130803Smarcel#include "symfile.h" /* Required by objfiles.h.  */
50130803Smarcel#include "objfiles.h" /* For have_full_symbols and have_partial_symbols */
51130803Smarcel#include "frame.h"
52130803Smarcel#include "block.h"
53130803Smarcel
54130803Smarcel/* Remap normal yacc parser interface names (yyparse, yylex, yyerror, etc),
55130803Smarcel   as well as gratuitiously global symbol names, so we can have multiple
56130803Smarcel   yacc generated parsers in gdb.  These are only the variables
57130803Smarcel   produced by yacc.  If other parser generators (bison, byacc, etc) produce
58130803Smarcel   additional global names that conflict at link time, then those parser
59130803Smarcel   generators need to be fixed instead of adding those names to this list. */
60130803Smarcel
61130803Smarcel/* NOTE: This is clumsy, especially since BISON and FLEX provide --prefix
62130803Smarcel   options.  I presume we are maintaining it to accommodate systems
63130803Smarcel   without BISON?  (PNH) */
64130803Smarcel
65130803Smarcel#define	yymaxdepth ada_maxdepth
66130803Smarcel#define	yyparse	_ada_parse	/* ada_parse calls this after  initialization */
67130803Smarcel#define	yylex	ada_lex
68130803Smarcel#define	yyerror	ada_error
69130803Smarcel#define	yylval	ada_lval
70130803Smarcel#define	yychar	ada_char
71130803Smarcel#define	yydebug	ada_debug
72130803Smarcel#define	yypact	ada_pact
73130803Smarcel#define	yyr1	ada_r1
74130803Smarcel#define	yyr2	ada_r2
75130803Smarcel#define	yydef	ada_def
76130803Smarcel#define	yychk	ada_chk
77130803Smarcel#define	yypgo	ada_pgo
78130803Smarcel#define	yyact	ada_act
79130803Smarcel#define	yyexca	ada_exca
80130803Smarcel#define yyerrflag ada_errflag
81130803Smarcel#define yynerrs	ada_nerrs
82130803Smarcel#define	yyps	ada_ps
83130803Smarcel#define	yypv	ada_pv
84130803Smarcel#define	yys	ada_s
85130803Smarcel#define	yy_yys	ada_yys
86130803Smarcel#define	yystate	ada_state
87130803Smarcel#define	yytmp	ada_tmp
88130803Smarcel#define	yyv	ada_v
89130803Smarcel#define	yy_yyv	ada_yyv
90130803Smarcel#define	yyval	ada_val
91130803Smarcel#define	yylloc	ada_lloc
92130803Smarcel#define yyreds	ada_reds		/* With YYDEBUG defined */
93130803Smarcel#define yytoks	ada_toks		/* With YYDEBUG defined */
94130803Smarcel#define yyname	ada_name		/* With YYDEBUG defined */
95130803Smarcel#define yyrule	ada_rule		/* With YYDEBUG defined */
96130803Smarcel
97130803Smarcel#ifndef YYDEBUG
98130803Smarcel#define	YYDEBUG	1		/* Default to yydebug support */
99130803Smarcel#endif
100130803Smarcel
101130803Smarcel#define YYFPRINTF parser_fprintf
102130803Smarcel
103130803Smarcelstruct name_info {
104130803Smarcel  struct symbol* sym;
105130803Smarcel  struct minimal_symbol* msym;
106130803Smarcel  struct block* block;
107130803Smarcel  struct stoken stoken;
108130803Smarcel};
109130803Smarcel
110130803Smarcel/* If expression is in the context of TYPE'(...), then TYPE, else
111130803Smarcel * NULL. */
112130803Smarcelstatic struct type* type_qualifier;
113130803Smarcel
114130803Smarcelint yyparse (void);
115130803Smarcel
116130803Smarcelstatic int yylex (void);
117130803Smarcel
118130803Smarcelvoid yyerror (char *);
119130803Smarcel
120130803Smarcelstatic struct stoken string_to_operator (struct stoken);
121130803Smarcel
122130803Smarcelstatic void write_attribute_call0 (enum ada_attribute);
123130803Smarcel
124130803Smarcelstatic void write_attribute_call1 (enum ada_attribute, LONGEST);
125130803Smarcel
126130803Smarcelstatic void write_attribute_calln (enum ada_attribute, int);
127130803Smarcel
128130803Smarcelstatic void write_object_renaming (struct block*, struct symbol*);
129130803Smarcel
130130803Smarcelstatic void write_var_from_name (struct block*, struct name_info);
131130803Smarcel
132130803Smarcelstatic LONGEST
133130803Smarcelconvert_char_literal (struct type*, LONGEST);
134130803Smarcel%}
135130803Smarcel
136130803Smarcel%union
137130803Smarcel  {
138130803Smarcel    LONGEST lval;
139130803Smarcel    struct {
140130803Smarcel      LONGEST val;
141130803Smarcel      struct type *type;
142130803Smarcel    } typed_val;
143130803Smarcel    struct {
144130803Smarcel      DOUBLEST dval;
145130803Smarcel      struct type *type;
146130803Smarcel    } typed_val_float;
147130803Smarcel    struct type *tval;
148130803Smarcel    struct stoken sval;
149130803Smarcel    struct name_info ssym;
150130803Smarcel    int voidval;
151130803Smarcel    struct block *bval;
152130803Smarcel    struct internalvar *ivar;
153130803Smarcel
154130803Smarcel  }
155130803Smarcel
156130803Smarcel%type <voidval> exp exp1 simple_exp start variable
157130803Smarcel%type <tval> type
158130803Smarcel
159130803Smarcel%token <typed_val> INT NULL_PTR CHARLIT
160130803Smarcel%token <typed_val_float> FLOAT
161130803Smarcel%token <tval> TYPENAME
162130803Smarcel%token <bval> BLOCKNAME
163130803Smarcel
164130803Smarcel/* Both NAME and TYPENAME tokens represent symbols in the input,
165130803Smarcel   and both convey their data as strings.
166130803Smarcel   But a TYPENAME is a string that happens to be defined as a typedef
167130803Smarcel   or builtin type name (such as int or char)
168130803Smarcel   and a NAME is any other symbol.
169130803Smarcel   Contexts where this distinction is not important can use the
170130803Smarcel   nonterminal "name", which matches either NAME or TYPENAME.  */
171130803Smarcel
172130803Smarcel%token <sval> STRING
173130803Smarcel%token <ssym> NAME DOT_ID OBJECT_RENAMING
174130803Smarcel%type <bval> block
175130803Smarcel%type <lval> arglist tick_arglist
176130803Smarcel
177130803Smarcel%type <tval> save_qualifier
178130803Smarcel
179130803Smarcel%token DOT_ALL
180130803Smarcel
181130803Smarcel/* Special type cases, put in to allow the parser to distinguish different
182130803Smarcel   legal basetypes.  */
183130803Smarcel%token <lval> LAST REGNAME
184130803Smarcel
185130803Smarcel%token <ivar> INTERNAL_VARIABLE
186130803Smarcel
187130803Smarcel%nonassoc ASSIGN
188130803Smarcel%left _AND_ OR XOR THEN ELSE
189130803Smarcel%left '=' NOTEQUAL '<' '>' LEQ GEQ IN DOTDOT
190130803Smarcel%left '@'
191130803Smarcel%left '+' '-' '&'
192130803Smarcel%left UNARY
193130803Smarcel%left '*' '/' MOD REM
194130803Smarcel%right STARSTAR ABS NOT
195130803Smarcel /* The following are right-associative only so that reductions at this
196130803Smarcel    precedence have lower precedence than '.' and '('. The syntax still
197130803Smarcel    forces a.b.c, e.g., to be LEFT-associated. */
198130803Smarcel%right TICK_ACCESS TICK_ADDRESS TICK_FIRST TICK_LAST TICK_LENGTH
199130803Smarcel%right TICK_MAX TICK_MIN TICK_MODULUS
200130803Smarcel%right TICK_POS TICK_RANGE TICK_SIZE TICK_TAG TICK_VAL
201130803Smarcel%right '.' '(' '[' DOT_ID DOT_ALL
202130803Smarcel
203130803Smarcel%token ARROW NEW
204130803Smarcel
205130803Smarcel
206130803Smarcel%%
207130803Smarcel
208130803Smarcelstart   :	exp1
209130803Smarcel	|	type	{ write_exp_elt_opcode (OP_TYPE);
210130803Smarcel			  write_exp_elt_type ($1);
211130803Smarcel 			  write_exp_elt_opcode (OP_TYPE); }
212130803Smarcel	;
213130803Smarcel
214130803Smarcel/* Expressions, including the sequencing operator.  */
215130803Smarcelexp1	:	exp
216130803Smarcel	|	exp1 ';' exp
217130803Smarcel			{ write_exp_elt_opcode (BINOP_COMMA); }
218130803Smarcel	;
219130803Smarcel
220130803Smarcel/* Expressions, not including the sequencing operator.  */
221130803Smarcelsimple_exp :	simple_exp DOT_ALL
222130803Smarcel			{ write_exp_elt_opcode (UNOP_IND); }
223130803Smarcel	;
224130803Smarcel
225130803Smarcelsimple_exp :	simple_exp DOT_ID
226130803Smarcel			{ write_exp_elt_opcode (STRUCTOP_STRUCT);
227130803Smarcel			  write_exp_string ($2.stoken);
228130803Smarcel			  write_exp_elt_opcode (STRUCTOP_STRUCT);
229130803Smarcel			  }
230130803Smarcel	;
231130803Smarcel
232130803Smarcelsimple_exp :	simple_exp '(' arglist ')'
233130803Smarcel			{
234130803Smarcel			  write_exp_elt_opcode (OP_FUNCALL);
235130803Smarcel			  write_exp_elt_longcst ($3);
236130803Smarcel			  write_exp_elt_opcode (OP_FUNCALL);
237130803Smarcel		        }
238130803Smarcel	;
239130803Smarcel
240130803Smarcelsimple_exp :	type '(' exp ')'
241130803Smarcel			{
242130803Smarcel			  write_exp_elt_opcode (UNOP_CAST);
243130803Smarcel			  write_exp_elt_type ($1);
244130803Smarcel			  write_exp_elt_opcode (UNOP_CAST);
245130803Smarcel			}
246130803Smarcel	;
247130803Smarcel
248130803Smarcelsimple_exp :	type '\'' save_qualifier { type_qualifier = $1; } '(' exp ')'
249130803Smarcel			{
250130803Smarcel			  /*			  write_exp_elt_opcode (UNOP_QUAL); */
251130803Smarcel			  /* FIXME: UNOP_QUAL should be defined in expression.h */
252130803Smarcel			  write_exp_elt_type ($1);
253130803Smarcel			  /* write_exp_elt_opcode (UNOP_QUAL); */
254130803Smarcel			  /* FIXME: UNOP_QUAL should be defined in expression.h */
255130803Smarcel			  type_qualifier = $3;
256130803Smarcel			}
257130803Smarcel	;
258130803Smarcel
259130803Smarcelsave_qualifier : 	{ $$ = type_qualifier; }
260130803Smarcel	;
261130803Smarcel
262130803Smarcelsimple_exp :
263130803Smarcel		simple_exp '(' exp DOTDOT exp ')'
264130803Smarcel			{ write_exp_elt_opcode (TERNOP_SLICE); }
265130803Smarcel	;
266130803Smarcel
267130803Smarcelsimple_exp :	'(' exp1 ')'	{ }
268130803Smarcel	;
269130803Smarcel
270130803Smarcelsimple_exp :	variable
271130803Smarcel	;
272130803Smarcel
273130803Smarcelsimple_exp:	REGNAME /* GDB extension */
274130803Smarcel			{ write_exp_elt_opcode (OP_REGISTER);
275130803Smarcel			  write_exp_elt_longcst ((LONGEST) $1);
276130803Smarcel			  write_exp_elt_opcode (OP_REGISTER);
277130803Smarcel			}
278130803Smarcel	;
279130803Smarcel
280130803Smarcelsimple_exp:	INTERNAL_VARIABLE /* GDB extension */
281130803Smarcel			{ write_exp_elt_opcode (OP_INTERNALVAR);
282130803Smarcel			  write_exp_elt_intern ($1);
283130803Smarcel			  write_exp_elt_opcode (OP_INTERNALVAR);
284130803Smarcel			}
285130803Smarcel	;
286130803Smarcel
287130803Smarcel
288130803Smarcelexp	: 	simple_exp
289130803Smarcel	;
290130803Smarcel
291130803Smarcelsimple_exp:	LAST
292130803Smarcel			{ write_exp_elt_opcode (OP_LAST);
293130803Smarcel			  write_exp_elt_longcst ((LONGEST) $1);
294130803Smarcel			  write_exp_elt_opcode (OP_LAST);
295130803Smarcel			 }
296130803Smarcel	;
297130803Smarcel
298130803Smarcelexp	: 	exp ASSIGN exp   /* Extension for convenience */
299130803Smarcel			{ write_exp_elt_opcode (BINOP_ASSIGN); }
300130803Smarcel	;
301130803Smarcel
302130803Smarcelexp	:	'-' exp    %prec UNARY
303130803Smarcel			{ write_exp_elt_opcode (UNOP_NEG); }
304130803Smarcel	;
305130803Smarcel
306130803Smarcelexp	:	'+' exp    %prec UNARY
307130803Smarcel			{ write_exp_elt_opcode (UNOP_PLUS); }
308130803Smarcel	;
309130803Smarcel
310130803Smarcelexp     :	NOT exp    %prec UNARY
311130803Smarcel			{ write_exp_elt_opcode (UNOP_LOGICAL_NOT); }
312130803Smarcel	;
313130803Smarcel
314130803Smarcelexp	:       ABS exp	   %prec UNARY
315130803Smarcel			{ write_exp_elt_opcode (UNOP_ABS); }
316130803Smarcel	;
317130803Smarcel
318130803Smarcelarglist	:		{ $$ = 0; }
319130803Smarcel	;
320130803Smarcel
321130803Smarcelarglist	:	exp
322130803Smarcel			{ $$ = 1; }
323130803Smarcel	|	any_name ARROW exp
324130803Smarcel			{ $$ = 1; }
325130803Smarcel	|	arglist ',' exp
326130803Smarcel			{ $$ = $1 + 1; }
327130803Smarcel	|	arglist ',' any_name ARROW exp
328130803Smarcel			{ $$ = $1 + 1; }
329130803Smarcel	;
330130803Smarcel
331130803Smarcelexp	:	'{' type '}' exp  %prec '.'
332130803Smarcel		/* GDB extension */
333130803Smarcel			{ write_exp_elt_opcode (UNOP_MEMVAL);
334130803Smarcel			  write_exp_elt_type ($2);
335130803Smarcel			  write_exp_elt_opcode (UNOP_MEMVAL);
336130803Smarcel			}
337130803Smarcel	;
338130803Smarcel
339130803Smarcel/* Binary operators in order of decreasing precedence.  */
340130803Smarcel
341130803Smarcelexp 	: 	exp STARSTAR exp
342130803Smarcel			{ write_exp_elt_opcode (BINOP_EXP); }
343130803Smarcel	;
344130803Smarcel
345130803Smarcelexp	:	exp '*' exp
346130803Smarcel			{ write_exp_elt_opcode (BINOP_MUL); }
347130803Smarcel	;
348130803Smarcel
349130803Smarcelexp	:	exp '/' exp
350130803Smarcel			{ write_exp_elt_opcode (BINOP_DIV); }
351130803Smarcel	;
352130803Smarcel
353130803Smarcelexp	:	exp REM exp /* May need to be fixed to give correct Ada REM */
354130803Smarcel			{ write_exp_elt_opcode (BINOP_REM); }
355130803Smarcel	;
356130803Smarcel
357130803Smarcelexp	:	exp MOD exp
358130803Smarcel			{ write_exp_elt_opcode (BINOP_MOD); }
359130803Smarcel	;
360130803Smarcel
361130803Smarcelexp	:	exp '@' exp	/* GDB extension */
362130803Smarcel			{ write_exp_elt_opcode (BINOP_REPEAT); }
363130803Smarcel	;
364130803Smarcel
365130803Smarcelexp	:	exp '+' exp
366130803Smarcel			{ write_exp_elt_opcode (BINOP_ADD); }
367130803Smarcel	;
368130803Smarcel
369130803Smarcelexp	:	exp '&' exp
370130803Smarcel			{ write_exp_elt_opcode (BINOP_CONCAT); }
371130803Smarcel	;
372130803Smarcel
373130803Smarcelexp	:	exp '-' exp
374130803Smarcel			{ write_exp_elt_opcode (BINOP_SUB); }
375130803Smarcel	;
376130803Smarcel
377130803Smarcelexp	:	exp '=' exp
378130803Smarcel			{ write_exp_elt_opcode (BINOP_EQUAL); }
379130803Smarcel	;
380130803Smarcel
381130803Smarcelexp	:	exp NOTEQUAL exp
382130803Smarcel			{ write_exp_elt_opcode (BINOP_NOTEQUAL); }
383130803Smarcel	;
384130803Smarcel
385130803Smarcelexp	:	exp LEQ exp
386130803Smarcel			{ write_exp_elt_opcode (BINOP_LEQ); }
387130803Smarcel	;
388130803Smarcel
389130803Smarcelexp	:	exp IN exp DOTDOT exp
390130803Smarcel                        { /*write_exp_elt_opcode (TERNOP_MBR); */ }
391130803Smarcel                          /* FIXME: TERNOP_MBR should be defined in
392130803Smarcel			     expression.h */
393130803Smarcel        |       exp IN exp TICK_RANGE tick_arglist
394130803Smarcel                        { /*write_exp_elt_opcode (BINOP_MBR); */
395130803Smarcel			  /* FIXME: BINOP_MBR should be defined in expression.h */
396130803Smarcel			  write_exp_elt_longcst ((LONGEST) $5);
397130803Smarcel			  /*write_exp_elt_opcode (BINOP_MBR); */
398130803Smarcel			}
399130803Smarcel 	|	exp IN TYPENAME		%prec TICK_ACCESS
400130803Smarcel                        { /*write_exp_elt_opcode (UNOP_MBR); */
401130803Smarcel			  /* FIXME: UNOP_QUAL should be defined in expression.h */
402130803Smarcel		          write_exp_elt_type ($3);
403130803Smarcel			  /*		          write_exp_elt_opcode (UNOP_MBR); */
404130803Smarcel			  /* FIXME: UNOP_MBR should be defined in expression.h */
405130803Smarcel			}
406130803Smarcel	|	exp NOT IN exp DOTDOT exp
407130803Smarcel                        { /*write_exp_elt_opcode (TERNOP_MBR); */
408130803Smarcel			  /* FIXME: TERNOP_MBR should be defined in expression.h */
409130803Smarcel		          write_exp_elt_opcode (UNOP_LOGICAL_NOT);
410130803Smarcel			}
411130803Smarcel        |       exp NOT IN exp TICK_RANGE tick_arglist
412130803Smarcel                        { /* write_exp_elt_opcode (BINOP_MBR); */
413130803Smarcel			  /* FIXME: BINOP_MBR should be defined in expression.h */
414130803Smarcel			  write_exp_elt_longcst ((LONGEST) $6);
415130803Smarcel			  /*write_exp_elt_opcode (BINOP_MBR);*/
416130803Smarcel			  /* FIXME: BINOP_MBR should be defined in expression.h */
417130803Smarcel		          write_exp_elt_opcode (UNOP_LOGICAL_NOT);
418130803Smarcel			}
419130803Smarcel 	|	exp NOT IN TYPENAME	%prec TICK_ACCESS
420130803Smarcel                        { /*write_exp_elt_opcode (UNOP_MBR);*/
421130803Smarcel			  /* FIXME: UNOP_MBR should be defined in expression.h */
422130803Smarcel		          write_exp_elt_type ($4);
423130803Smarcel			  /*		          write_exp_elt_opcode (UNOP_MBR);*/
424130803Smarcel			  /* FIXME: UNOP_MBR should be defined in expression.h */
425130803Smarcel		          write_exp_elt_opcode (UNOP_LOGICAL_NOT);
426130803Smarcel			}
427130803Smarcel	;
428130803Smarcel
429130803Smarcelexp	:	exp GEQ exp
430130803Smarcel			{ write_exp_elt_opcode (BINOP_GEQ); }
431130803Smarcel	;
432130803Smarcel
433130803Smarcelexp	:	exp '<' exp
434130803Smarcel			{ write_exp_elt_opcode (BINOP_LESS); }
435130803Smarcel	;
436130803Smarcel
437130803Smarcelexp	:	exp '>' exp
438130803Smarcel			{ write_exp_elt_opcode (BINOP_GTR); }
439130803Smarcel	;
440130803Smarcel
441130803Smarcelexp     :	exp _AND_ exp  /* Fix for Ada elementwise AND. */
442130803Smarcel			{ write_exp_elt_opcode (BINOP_BITWISE_AND); }
443130803Smarcel        ;
444130803Smarcel
445130803Smarcelexp     :       exp _AND_ THEN exp	%prec _AND_
446130803Smarcel			{ write_exp_elt_opcode (BINOP_LOGICAL_AND); }
447130803Smarcel        ;
448130803Smarcel
449130803Smarcelexp     :	exp OR exp     /* Fix for Ada elementwise OR */
450130803Smarcel			{ write_exp_elt_opcode (BINOP_BITWISE_IOR); }
451130803Smarcel        ;
452130803Smarcel
453130803Smarcelexp     :       exp OR ELSE exp
454130803Smarcel			{ write_exp_elt_opcode (BINOP_LOGICAL_OR); }
455130803Smarcel        ;
456130803Smarcel
457130803Smarcelexp     :       exp XOR exp    /* Fix for Ada elementwise XOR */
458130803Smarcel			{ write_exp_elt_opcode (BINOP_BITWISE_XOR); }
459130803Smarcel        ;
460130803Smarcel
461130803Smarcelsimple_exp :	simple_exp TICK_ACCESS
462130803Smarcel			{ write_exp_elt_opcode (UNOP_ADDR); }
463130803Smarcel	|	simple_exp TICK_ADDRESS
464130803Smarcel			{ write_exp_elt_opcode (UNOP_ADDR);
465130803Smarcel			  write_exp_elt_opcode (UNOP_CAST);
466130803Smarcel			  write_exp_elt_type (builtin_type_ada_system_address);
467130803Smarcel			  write_exp_elt_opcode (UNOP_CAST);
468130803Smarcel			}
469130803Smarcel	|	simple_exp TICK_FIRST tick_arglist
470130803Smarcel			{ write_attribute_call1 (ATR_FIRST, $3); }
471130803Smarcel	|	simple_exp TICK_LAST tick_arglist
472130803Smarcel			{ write_attribute_call1 (ATR_LAST, $3); }
473130803Smarcel	| 	simple_exp TICK_LENGTH tick_arglist
474130803Smarcel			{ write_attribute_call1 (ATR_LENGTH, $3); }
475130803Smarcel        |       simple_exp TICK_SIZE
476130803Smarcel			{ write_attribute_call0 (ATR_SIZE); }
477130803Smarcel	|	simple_exp TICK_TAG
478130803Smarcel			{ write_attribute_call0 (ATR_TAG); }
479130803Smarcel        |       opt_type_prefix TICK_MIN '(' exp ',' exp ')'
480130803Smarcel			{ write_attribute_calln (ATR_MIN, 2); }
481130803Smarcel        |       opt_type_prefix TICK_MAX '(' exp ',' exp ')'
482130803Smarcel			{ write_attribute_calln (ATR_MAX, 2); }
483130803Smarcel	| 	opt_type_prefix TICK_POS '(' exp ')'
484130803Smarcel			{ write_attribute_calln (ATR_POS, 1); }
485130803Smarcel	|	type_prefix TICK_FIRST tick_arglist
486130803Smarcel			{ write_attribute_call1 (ATR_FIRST, $3); }
487130803Smarcel	|	type_prefix TICK_LAST tick_arglist
488130803Smarcel			{ write_attribute_call1 (ATR_LAST, $3); }
489130803Smarcel	| 	type_prefix TICK_LENGTH tick_arglist
490130803Smarcel			{ write_attribute_call1 (ATR_LENGTH, $3); }
491130803Smarcel	|	type_prefix TICK_VAL '(' exp ')'
492130803Smarcel			{ write_attribute_calln (ATR_VAL, 1); }
493130803Smarcel	|	type_prefix TICK_MODULUS
494130803Smarcel			{ write_attribute_call0 (ATR_MODULUS); }
495130803Smarcel	;
496130803Smarcel
497130803Smarceltick_arglist :			%prec '('
498130803Smarcel			{ $$ = 1; }
499130803Smarcel	| 	'(' INT ')'
500130803Smarcel			{ $$ = $2.val; }
501130803Smarcel	;
502130803Smarcel
503130803Smarceltype_prefix :
504130803Smarcel		TYPENAME
505130803Smarcel			{ write_exp_elt_opcode (OP_TYPE);
506130803Smarcel			  write_exp_elt_type ($1);
507130803Smarcel			  write_exp_elt_opcode (OP_TYPE); }
508130803Smarcel	;
509130803Smarcel
510130803Smarcelopt_type_prefix :
511130803Smarcel		type_prefix
512130803Smarcel	| 	/* EMPTY */
513130803Smarcel			{ write_exp_elt_opcode (OP_TYPE);
514130803Smarcel			  write_exp_elt_type (builtin_type_void);
515130803Smarcel			  write_exp_elt_opcode (OP_TYPE); }
516130803Smarcel	;
517130803Smarcel
518130803Smarcel
519130803Smarcelexp	:	INT
520130803Smarcel			{ write_exp_elt_opcode (OP_LONG);
521130803Smarcel			  write_exp_elt_type ($1.type);
522130803Smarcel			  write_exp_elt_longcst ((LONGEST)($1.val));
523130803Smarcel			  write_exp_elt_opcode (OP_LONG);
524130803Smarcel			}
525130803Smarcel	;
526130803Smarcel
527130803Smarcelexp	:	CHARLIT
528130803Smarcel			{ write_exp_elt_opcode (OP_LONG);
529130803Smarcel			  if (type_qualifier == NULL)
530130803Smarcel			    write_exp_elt_type ($1.type);
531130803Smarcel			  else
532130803Smarcel			    write_exp_elt_type (type_qualifier);
533130803Smarcel			  write_exp_elt_longcst
534130803Smarcel			    (convert_char_literal (type_qualifier, $1.val));
535130803Smarcel			  write_exp_elt_opcode (OP_LONG);
536130803Smarcel			}
537130803Smarcel	;
538130803Smarcel
539130803Smarcelexp	:	FLOAT
540130803Smarcel			{ write_exp_elt_opcode (OP_DOUBLE);
541130803Smarcel			  write_exp_elt_type ($1.type);
542130803Smarcel			  write_exp_elt_dblcst ($1.dval);
543130803Smarcel			  write_exp_elt_opcode (OP_DOUBLE);
544130803Smarcel			}
545130803Smarcel	;
546130803Smarcel
547130803Smarcelexp	:	NULL_PTR
548130803Smarcel			{ write_exp_elt_opcode (OP_LONG);
549130803Smarcel			  write_exp_elt_type (builtin_type_int);
550130803Smarcel			  write_exp_elt_longcst ((LONGEST)(0));
551130803Smarcel			  write_exp_elt_opcode (OP_LONG);
552130803Smarcel			 }
553130803Smarcel	;
554130803Smarcel
555130803Smarcelexp	:	STRING
556130803Smarcel			{ /* Ada strings are converted into array constants
557130803Smarcel			     a lower bound of 1.  Thus, the array upper bound
558130803Smarcel			     is the string length. */
559130803Smarcel			  char *sp = $1.ptr; int count;
560130803Smarcel			  if ($1.length == 0)
561130803Smarcel			    { /* One dummy character for the type */
562130803Smarcel			      write_exp_elt_opcode (OP_LONG);
563130803Smarcel			      write_exp_elt_type (builtin_type_ada_char);
564130803Smarcel			      write_exp_elt_longcst ((LONGEST)(0));
565130803Smarcel			      write_exp_elt_opcode (OP_LONG);
566130803Smarcel			    }
567130803Smarcel			  for (count = $1.length; count > 0; count -= 1)
568130803Smarcel			    {
569130803Smarcel			      write_exp_elt_opcode (OP_LONG);
570130803Smarcel			      write_exp_elt_type (builtin_type_ada_char);
571130803Smarcel			      write_exp_elt_longcst ((LONGEST)(*sp));
572130803Smarcel			      sp += 1;
573130803Smarcel			      write_exp_elt_opcode (OP_LONG);
574130803Smarcel			    }
575130803Smarcel			  write_exp_elt_opcode (OP_ARRAY);
576130803Smarcel			  write_exp_elt_longcst ((LONGEST) 1);
577130803Smarcel			  write_exp_elt_longcst ((LONGEST) ($1.length));
578130803Smarcel			  write_exp_elt_opcode (OP_ARRAY);
579130803Smarcel			 }
580130803Smarcel	;
581130803Smarcel
582130803Smarcelexp	: 	NEW TYPENAME
583130803Smarcel			{ error ("NEW not implemented."); }
584130803Smarcel	;
585130803Smarcel
586130803Smarcelvariable:	NAME   		{ write_var_from_name (NULL, $1); }
587130803Smarcel	|	block NAME  	/* GDB extension */
588130803Smarcel                                { write_var_from_name ($1, $2); }
589130803Smarcel	|	OBJECT_RENAMING { write_object_renaming (NULL, $1.sym); }
590130803Smarcel	|	block OBJECT_RENAMING
591130803Smarcel				{ write_object_renaming ($1, $2.sym); }
592130803Smarcel	;
593130803Smarcel
594130803Smarcelany_name :	NAME 		{ }
595130803Smarcel        |       TYPENAME	{ }
596130803Smarcel        |       OBJECT_RENAMING	{ }
597130803Smarcel        ;
598130803Smarcel
599130803Smarcelblock	:	BLOCKNAME  /* GDB extension */
600130803Smarcel			{ $$ = $1; }
601130803Smarcel	|	block BLOCKNAME /* GDB extension */
602130803Smarcel			{ $$ = $2; }
603130803Smarcel	;
604130803Smarcel
605130803Smarcel
606130803Smarceltype	:	TYPENAME	{ $$ = $1; }
607130803Smarcel	|	block TYPENAME  { $$ = $2; }
608130803Smarcel	| 	TYPENAME TICK_ACCESS
609130803Smarcel				{ $$ = lookup_pointer_type ($1); }
610130803Smarcel	|	block TYPENAME TICK_ACCESS
611130803Smarcel				{ $$ = lookup_pointer_type ($2); }
612130803Smarcel        ;
613130803Smarcel
614130803Smarcel/* Some extensions borrowed from C, for the benefit of those who find they
615130803Smarcel   can't get used to Ada notation in GDB. */
616130803Smarcel
617130803Smarcelexp	:	'*' exp		%prec '.'
618130803Smarcel			{ write_exp_elt_opcode (UNOP_IND); }
619130803Smarcel	|	'&' exp		%prec '.'
620130803Smarcel			{ write_exp_elt_opcode (UNOP_ADDR); }
621130803Smarcel	|	exp '[' exp ']'
622130803Smarcel			{ write_exp_elt_opcode (BINOP_SUBSCRIPT); }
623130803Smarcel	;
624130803Smarcel
625130803Smarcel%%
626130803Smarcel
627130803Smarcel/* yylex defined in ada-lex.c: Reads one token, getting characters */
628130803Smarcel/* through lexptr.  */
629130803Smarcel
630130803Smarcel/* Remap normal flex interface names (yylex) as well as gratuitiously */
631130803Smarcel/* global symbol names, so we can have multiple flex-generated parsers */
632130803Smarcel/* in gdb.  */
633130803Smarcel
634130803Smarcel/* (See note above on previous definitions for YACC.) */
635130803Smarcel
636130803Smarcel#define yy_create_buffer ada_yy_create_buffer
637130803Smarcel#define yy_delete_buffer ada_yy_delete_buffer
638130803Smarcel#define yy_init_buffer ada_yy_init_buffer
639130803Smarcel#define yy_load_buffer_state ada_yy_load_buffer_state
640130803Smarcel#define yy_switch_to_buffer ada_yy_switch_to_buffer
641130803Smarcel#define yyrestart ada_yyrestart
642130803Smarcel#define yytext ada_yytext
643130803Smarcel#define yywrap ada_yywrap
644130803Smarcel
645130803Smarcel/* The following kludge was found necessary to prevent conflicts between */
646130803Smarcel/* defs.h and non-standard stdlib.h files.  */
647130803Smarcel#define qsort __qsort__dummy
648130803Smarcel#include "ada-lex.c"
649130803Smarcel
650130803Smarcelint
651130803Smarcelada_parse ()
652130803Smarcel{
653130803Smarcel  lexer_init (yyin);		/* (Re-)initialize lexer. */
654130803Smarcel  left_block_context = NULL;
655130803Smarcel  type_qualifier = NULL;
656130803Smarcel
657130803Smarcel  return _ada_parse ();
658130803Smarcel}
659130803Smarcel
660130803Smarcelvoid
661130803Smarcelyyerror (msg)
662130803Smarcel     char *msg;
663130803Smarcel{
664130803Smarcel  error ("A %s in expression, near `%s'.", (msg ? msg : "error"), lexptr);
665130803Smarcel}
666130803Smarcel
667130803Smarcel/* The operator name corresponding to operator symbol STRING (adds
668130803Smarcel   quotes and maps to lower-case).  Destroys the previous contents of
669130803Smarcel   the array pointed to by STRING.ptr.  Error if STRING does not match
670130803Smarcel   a valid Ada operator.  Assumes that STRING.ptr points to a
671130803Smarcel   null-terminated string and that, if STRING is a valid operator
672130803Smarcel   symbol, the array pointed to by STRING.ptr contains at least
673130803Smarcel   STRING.length+3 characters. */
674130803Smarcel
675130803Smarcelstatic struct stoken
676130803Smarcelstring_to_operator (string)
677130803Smarcel     struct stoken string;
678130803Smarcel{
679130803Smarcel  int i;
680130803Smarcel
681130803Smarcel  for (i = 0; ada_opname_table[i].mangled != NULL; i += 1)
682130803Smarcel    {
683130803Smarcel      if (string.length == strlen (ada_opname_table[i].demangled)-2
684130803Smarcel	  && strncasecmp (string.ptr, ada_opname_table[i].demangled+1,
685130803Smarcel			  string.length) == 0)
686130803Smarcel	{
687130803Smarcel	  strncpy (string.ptr, ada_opname_table[i].demangled,
688130803Smarcel		   string.length+2);
689130803Smarcel	  string.length += 2;
690130803Smarcel	  return string;
691130803Smarcel	}
692130803Smarcel    }
693130803Smarcel  error ("Invalid operator symbol `%s'", string.ptr);
694130803Smarcel}
695130803Smarcel
696130803Smarcel/* Emit expression to access an instance of SYM, in block BLOCK (if
697130803Smarcel * non-NULL), and with :: qualification ORIG_LEFT_CONTEXT. */
698130803Smarcelstatic void
699130803Smarcelwrite_var_from_sym (orig_left_context, block, sym)
700130803Smarcel     struct block* orig_left_context;
701130803Smarcel     struct block* block;
702130803Smarcel     struct symbol* sym;
703130803Smarcel{
704130803Smarcel  if (orig_left_context == NULL && symbol_read_needs_frame (sym))
705130803Smarcel    {
706130803Smarcel      if (innermost_block == 0 ||
707130803Smarcel	  contained_in (block, innermost_block))
708130803Smarcel	innermost_block = block;
709130803Smarcel    }
710130803Smarcel
711130803Smarcel  write_exp_elt_opcode (OP_VAR_VALUE);
712130803Smarcel  /* We want to use the selected frame, not another more inner frame
713130803Smarcel     which happens to be in the same block */
714130803Smarcel  write_exp_elt_block (NULL);
715130803Smarcel  write_exp_elt_sym (sym);
716130803Smarcel  write_exp_elt_opcode (OP_VAR_VALUE);
717130803Smarcel}
718130803Smarcel
719130803Smarcel/* Emit expression to access an instance of NAME. */
720130803Smarcelstatic void
721130803Smarcelwrite_var_from_name (orig_left_context, name)
722130803Smarcel     struct block* orig_left_context;
723130803Smarcel     struct name_info name;
724130803Smarcel{
725130803Smarcel  if (name.msym != NULL)
726130803Smarcel    {
727130803Smarcel      write_exp_msymbol (name.msym,
728130803Smarcel			 lookup_function_type (builtin_type_int),
729130803Smarcel			 builtin_type_int);
730130803Smarcel    }
731130803Smarcel  else if (name.sym == NULL)
732130803Smarcel    {
733130803Smarcel      /* Multiple matches: record name and starting block for later
734130803Smarcel         resolution by ada_resolve. */
735130803Smarcel      /*      write_exp_elt_opcode (OP_UNRESOLVED_VALUE); */
736130803Smarcel      /* FIXME: OP_UNRESOLVED_VALUE should be defined in expression.h */
737130803Smarcel      write_exp_elt_block (name.block);
738130803Smarcel      /*      write_exp_elt_name (name.stoken.ptr); */
739130803Smarcel      /* FIXME: write_exp_elt_name should be defined in defs.h, located in parse.c */
740130803Smarcel      /*      write_exp_elt_opcode (OP_UNRESOLVED_VALUE); */
741130803Smarcel      /* FIXME: OP_UNRESOLVED_VALUE should be defined in expression.h */
742130803Smarcel    }
743130803Smarcel  else
744130803Smarcel    write_var_from_sym (orig_left_context, name.block, name.sym);
745130803Smarcel}
746130803Smarcel
747130803Smarcel/* Write a call on parameterless attribute ATR.  */
748130803Smarcel
749130803Smarcelstatic void
750130803Smarcelwrite_attribute_call0 (atr)
751130803Smarcel     enum ada_attribute atr;
752130803Smarcel{
753130803Smarcel  /*  write_exp_elt_opcode (OP_ATTRIBUTE); */
754130803Smarcel  /* FIXME: OP_ATTRIBUTE should be defined in expression.h */
755130803Smarcel  write_exp_elt_longcst ((LONGEST) 0);
756130803Smarcel  write_exp_elt_longcst ((LONGEST) atr);
757130803Smarcel  /*  write_exp_elt_opcode (OP_ATTRIBUTE); */
758130803Smarcel  /* FIXME: OP_ATTRIBUTE should be defined in expression.h */
759130803Smarcel}
760130803Smarcel
761130803Smarcel/* Write a call on an attribute ATR with one constant integer
762130803Smarcel * parameter. */
763130803Smarcel
764130803Smarcelstatic void
765130803Smarcelwrite_attribute_call1 (atr, arg)
766130803Smarcel     enum ada_attribute atr;
767130803Smarcel     LONGEST arg;
768130803Smarcel{
769130803Smarcel  write_exp_elt_opcode (OP_LONG);
770130803Smarcel  write_exp_elt_type (builtin_type_int);
771130803Smarcel  write_exp_elt_longcst (arg);
772130803Smarcel  write_exp_elt_opcode (OP_LONG);
773130803Smarcel  /*write_exp_elt_opcode (OP_ATTRIBUTE);*/
774130803Smarcel  /* FIXME: OP_ATTRIBUTE should be defined in expression.h */
775130803Smarcel  write_exp_elt_longcst ((LONGEST) 1);
776130803Smarcel  write_exp_elt_longcst ((LONGEST) atr);
777130803Smarcel  /*write_exp_elt_opcode (OP_ATTRIBUTE);*/
778130803Smarcel  /* FIXME: OP_ATTRIBUTE should be defined in expression.h */
779130803Smarcel}
780130803Smarcel
781130803Smarcel/* Write a call on an attribute ATR with N parameters, whose code must have
782130803Smarcel * been generated previously. */
783130803Smarcel
784130803Smarcelstatic void
785130803Smarcelwrite_attribute_calln (atr, n)
786130803Smarcel     enum ada_attribute atr;
787130803Smarcel     int n;
788130803Smarcel{
789130803Smarcel  /*write_exp_elt_opcode (OP_ATTRIBUTE);*/
790130803Smarcel  /* FIXME: OP_ATTRIBUTE should be defined in expression.h */
791130803Smarcel  write_exp_elt_longcst ((LONGEST) n);
792130803Smarcel  write_exp_elt_longcst ((LONGEST) atr);
793130803Smarcel  /*  write_exp_elt_opcode (OP_ATTRIBUTE);*/
794130803Smarcel  /* FIXME: OP_ATTRIBUTE should be defined in expression.h */
795130803Smarcel}
796130803Smarcel
797130803Smarcel/* Emit expression corresponding to the renamed object designated by
798130803Smarcel * the type RENAMING, which must be the referent of an object renaming
799130803Smarcel * type, in the context of ORIG_LEFT_CONTEXT (?). */
800130803Smarcelstatic void
801130803Smarcelwrite_object_renaming (orig_left_context, renaming)
802130803Smarcel     struct block* orig_left_context;
803130803Smarcel     struct symbol* renaming;
804130803Smarcel{
805130803Smarcel  const char* qualification = DEPRECATED_SYMBOL_NAME (renaming);
806130803Smarcel  const char* simple_tail;
807130803Smarcel  const char* expr = TYPE_FIELD_NAME (SYMBOL_TYPE (renaming), 0);
808130803Smarcel  const char* suffix;
809130803Smarcel  char* name;
810130803Smarcel  struct symbol* sym;
811130803Smarcel  enum { SIMPLE_INDEX, LOWER_BOUND, UPPER_BOUND } slice_state;
812130803Smarcel
813130803Smarcel  /* if orig_left_context is null, then use the currently selected
814130803Smarcel     block, otherwise we might fail our symbol lookup below */
815130803Smarcel  if (orig_left_context == NULL)
816130803Smarcel    orig_left_context = get_selected_block (NULL);
817130803Smarcel
818130803Smarcel  for (simple_tail = qualification + strlen (qualification);
819130803Smarcel       simple_tail != qualification; simple_tail -= 1)
820130803Smarcel    {
821130803Smarcel      if (*simple_tail == '.')
822130803Smarcel	{
823130803Smarcel	  simple_tail += 1;
824130803Smarcel	  break;
825130803Smarcel	}
826130803Smarcel      else if (DEPRECATED_STREQN (simple_tail, "__", 2))
827130803Smarcel	{
828130803Smarcel	  simple_tail += 2;
829130803Smarcel	  break;
830130803Smarcel	}
831130803Smarcel    }
832130803Smarcel
833130803Smarcel  suffix = strstr (expr, "___XE");
834130803Smarcel  if (suffix == NULL)
835130803Smarcel    goto BadEncoding;
836130803Smarcel
837130803Smarcel  name = (char*) malloc (suffix - expr + 1);
838130803Smarcel  /*  add_name_string_cleanup (name); */
839130803Smarcel  /* FIXME: add_name_string_cleanup should be defined in
840130803Smarcel     parser-defs.h, implemented in parse.c */
841130803Smarcel  strncpy (name, expr, suffix-expr);
842130803Smarcel  name[suffix-expr] = '\000';
843130803Smarcel  sym = lookup_symbol (name, orig_left_context, VAR_DOMAIN, 0, NULL);
844130803Smarcel  /*  if (sym == NULL)
845130803Smarcel    error ("Could not find renamed variable: %s", ada_demangle (name));
846130803Smarcel  */
847130803Smarcel  /* FIXME: ada_demangle should be defined in defs.h, implemented in ada-lang.c */
848130803Smarcel  write_var_from_sym (orig_left_context, block_found, sym);
849130803Smarcel
850130803Smarcel  suffix += 5;
851130803Smarcel  slice_state = SIMPLE_INDEX;
852130803Smarcel  while (*suffix == 'X')
853130803Smarcel    {
854130803Smarcel      suffix += 1;
855130803Smarcel
856130803Smarcel      switch (*suffix) {
857130803Smarcel      case 'L':
858130803Smarcel	slice_state = LOWER_BOUND;
859130803Smarcel      case 'S':
860130803Smarcel	suffix += 1;
861130803Smarcel	if (isdigit (*suffix))
862130803Smarcel	  {
863130803Smarcel	    char* next;
864130803Smarcel	    long val = strtol (suffix, &next, 10);
865130803Smarcel	    if (next == suffix)
866130803Smarcel	      goto BadEncoding;
867130803Smarcel	    suffix = next;
868130803Smarcel	    write_exp_elt_opcode (OP_LONG);
869130803Smarcel	    write_exp_elt_type (builtin_type_ada_int);
870130803Smarcel	    write_exp_elt_longcst ((LONGEST) val);
871130803Smarcel	    write_exp_elt_opcode (OP_LONG);
872130803Smarcel	  }
873130803Smarcel	else
874130803Smarcel	  {
875130803Smarcel	    const char* end;
876130803Smarcel	    char* index_name;
877130803Smarcel	    int index_len;
878130803Smarcel	    struct symbol* index_sym;
879130803Smarcel
880130803Smarcel	    end = strchr (suffix, 'X');
881130803Smarcel	    if (end == NULL)
882130803Smarcel	      end = suffix + strlen (suffix);
883130803Smarcel
884130803Smarcel	    index_len = simple_tail - qualification + 2 + (suffix - end) + 1;
885130803Smarcel	    index_name = (char*) malloc (index_len);
886130803Smarcel	    memset (index_name, '\000', index_len);
887130803Smarcel	    /*	    add_name_string_cleanup (index_name);*/
888130803Smarcel	    /* FIXME: add_name_string_cleanup should be defined in
889130803Smarcel	       parser-defs.h, implemented in parse.c */
890130803Smarcel	    strncpy (index_name, qualification, simple_tail - qualification);
891130803Smarcel	    index_name[simple_tail - qualification] = '\000';
892130803Smarcel	    strncat (index_name, suffix, suffix-end);
893130803Smarcel	    suffix = end;
894130803Smarcel
895130803Smarcel	    index_sym =
896130803Smarcel	      lookup_symbol (index_name, NULL, VAR_DOMAIN, 0, NULL);
897130803Smarcel	    if (index_sym == NULL)
898130803Smarcel	      error ("Could not find %s", index_name);
899130803Smarcel	    write_var_from_sym (NULL, block_found, sym);
900130803Smarcel	  }
901130803Smarcel	if (slice_state == SIMPLE_INDEX)
902130803Smarcel	  {
903130803Smarcel	    write_exp_elt_opcode (OP_FUNCALL);
904130803Smarcel	    write_exp_elt_longcst ((LONGEST) 1);
905130803Smarcel	    write_exp_elt_opcode (OP_FUNCALL);
906130803Smarcel	  }
907130803Smarcel	else if (slice_state == LOWER_BOUND)
908130803Smarcel	  slice_state = UPPER_BOUND;
909130803Smarcel	else if (slice_state == UPPER_BOUND)
910130803Smarcel	  {
911130803Smarcel	    write_exp_elt_opcode (TERNOP_SLICE);
912130803Smarcel	    slice_state = SIMPLE_INDEX;
913130803Smarcel	  }
914130803Smarcel	break;
915130803Smarcel
916130803Smarcel      case 'R':
917130803Smarcel	{
918130803Smarcel	  struct stoken field_name;
919130803Smarcel	  const char* end;
920130803Smarcel	  suffix += 1;
921130803Smarcel
922130803Smarcel	  if (slice_state != SIMPLE_INDEX)
923130803Smarcel	    goto BadEncoding;
924130803Smarcel	  end = strchr (suffix, 'X');
925130803Smarcel	  if (end == NULL)
926130803Smarcel	    end = suffix + strlen (suffix);
927130803Smarcel	  field_name.length = end - suffix;
928130803Smarcel	  field_name.ptr = (char*) malloc (end - suffix + 1);
929130803Smarcel	  strncpy (field_name.ptr, suffix, end - suffix);
930130803Smarcel	  field_name.ptr[end - suffix] = '\000';
931130803Smarcel	  suffix = end;
932130803Smarcel	  write_exp_elt_opcode (STRUCTOP_STRUCT);
933130803Smarcel	  write_exp_string (field_name);
934130803Smarcel	  write_exp_elt_opcode (STRUCTOP_STRUCT);
935130803Smarcel	  break;
936130803Smarcel	}
937130803Smarcel
938130803Smarcel      default:
939130803Smarcel	goto BadEncoding;
940130803Smarcel      }
941130803Smarcel    }
942130803Smarcel  if (slice_state == SIMPLE_INDEX)
943130803Smarcel    return;
944130803Smarcel
945130803Smarcel BadEncoding:
946130803Smarcel  error ("Internal error in encoding of renaming declaration: %s",
947130803Smarcel	 DEPRECATED_SYMBOL_NAME (renaming));
948130803Smarcel}
949130803Smarcel
950130803Smarcel/* Convert the character literal whose ASCII value would be VAL to the
951130803Smarcel   appropriate value of type TYPE, if there is a translation.
952130803Smarcel   Otherwise return VAL.  Hence, in an enumeration type ('A', 'B'),
953130803Smarcel   the literal 'A' (VAL == 65), returns 0. */
954130803Smarcelstatic LONGEST
955130803Smarcelconvert_char_literal (struct type* type, LONGEST val)
956130803Smarcel{
957130803Smarcel  char name[7];
958130803Smarcel  int f;
959130803Smarcel
960130803Smarcel  if (type == NULL || TYPE_CODE (type) != TYPE_CODE_ENUM)
961130803Smarcel    return val;
962130803Smarcel  sprintf (name, "QU%02x", (int) val);
963130803Smarcel  for (f = 0; f < TYPE_NFIELDS (type); f += 1)
964130803Smarcel    {
965130803Smarcel      if (DEPRECATED_STREQ (name, TYPE_FIELD_NAME (type, f)))
966130803Smarcel	return TYPE_FIELD_BITPOS (type, f);
967130803Smarcel    }
968130803Smarcel  return val;
969130803Smarcel}
970