1130803Smarcel/* YACC parser for C expressions, for GDB.
2130803Smarcel
3130803Smarcel   Copyright 1986, 1989, 1990, 1991, 1993, 1994, 2002 Free Software
4130803Smarcel   Foundation, Inc.
5130803Smarcel
6130803Smarcel   This program is free software; you can redistribute it and/or modify
7130803Smarcel   it under the terms of the GNU General Public License as published by
8130803Smarcel   the Free Software Foundation; either version 2 of the License, or
9130803Smarcel   (at your option) any later version.
10130803Smarcel
11130803Smarcel   This program is distributed in the hope that it will be useful,
12130803Smarcel   but WITHOUT ANY WARRANTY; without even the implied warranty of
13130803Smarcel   MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE.  See the
14130803Smarcel   GNU General Public License for more details.
15130803Smarcel
16130803Smarcel   You should have received a copy of the GNU General Public License
17130803Smarcel   along with this program; if not, write to the Free Software
18130803Smarcel   Foundation, Inc., 59 Temple Place - Suite 330,
19130803Smarcel   Boston, MA 02111-1307, USA.  */
20130803Smarcel
21130803Smarcel/* Parse a C expression from text in a string, and return the result
22130803Smarcel   as a struct expression pointer.  That structure contains arithmetic
23130803Smarcel   operations in reverse polish, with constants represented by
24130803Smarcel   operations that are followed by special data.  See expression.h for
25130803Smarcel   the details of the format.  What is important here is that it can
26130803Smarcel   be built up sequentially during the process of parsing; the lower
27130803Smarcel   levels of the tree always come first in the result.
28130803Smarcel
29130803Smarcel   Note that malloc's and realloc's in this file are transformed to
30130803Smarcel   xmalloc and xrealloc respectively by the same sed command in the
31130803Smarcel   makefile that remaps any other malloc/realloc inserted by the
32130803Smarcel   parser generator.  Doing this with #defines and trying to control
33130803Smarcel   the interaction with include files (<malloc.h> and <stdlib.h> for
34130803Smarcel   example) just became too messy, particularly when such includes can
35130803Smarcel   be inserted at random times by the parser generator.  */
36130803Smarcel
37130803Smarcel%{
38130803Smarcel
39130803Smarcel#include "defs.h"
40130803Smarcel#include "gdb_string.h"
41130803Smarcel#include <ctype.h>
42130803Smarcel#include "expression.h"
43130803Smarcel
44130803Smarcel#include "objc-lang.h"	/* For objc language constructs.  */
45130803Smarcel
46130803Smarcel#include "value.h"
47130803Smarcel#include "parser-defs.h"
48130803Smarcel#include "language.h"
49130803Smarcel#include "c-lang.h"
50130803Smarcel#include "bfd.h" /* Required by objfiles.h.  */
51130803Smarcel#include "symfile.h" /* Required by objfiles.h.  */
52130803Smarcel#include "objfiles.h" /* For have_full_symbols and have_partial_symbols.  */
53130803Smarcel#include "top.h"
54130803Smarcel#include "completer.h" /* For skip_quoted().  */
55130803Smarcel#include "block.h"
56130803Smarcel
57130803Smarcel/* Remap normal yacc parser interface names (yyparse, yylex, yyerror,
58130803Smarcel   etc), as well as gratuitiously global symbol names, so we can have
59130803Smarcel   multiple yacc generated parsers in gdb.  Note that these are only
60130803Smarcel   the variables produced by yacc.  If other parser generators (bison,
61130803Smarcel   byacc, etc) produce additional global names that conflict at link
62130803Smarcel   time, then those parser generators need to be fixed instead of
63130803Smarcel   adding those names to this list.  */
64130803Smarcel
65130803Smarcel#define	yymaxdepth	objc_maxdepth
66130803Smarcel#define	yyparse		objc_parse
67130803Smarcel#define	yylex		objc_lex
68130803Smarcel#define	yyerror		objc_error
69130803Smarcel#define	yylval		objc_lval
70130803Smarcel#define	yychar		objc_char
71130803Smarcel#define	yydebug		objc_debug
72130803Smarcel#define	yypact		objc_pact
73130803Smarcel#define	yyr1		objc_r1
74130803Smarcel#define	yyr2		objc_r2
75130803Smarcel#define	yydef		objc_def
76130803Smarcel#define	yychk		objc_chk
77130803Smarcel#define	yypgo		objc_pgo
78130803Smarcel#define	yyact		objc_act
79130803Smarcel#define	yyexca		objc_exca
80130803Smarcel#define yyerrflag	objc_errflag
81130803Smarcel#define yynerrs		objc_nerrs
82130803Smarcel#define	yyps		objc_ps
83130803Smarcel#define	yypv		objc_pv
84130803Smarcel#define	yys		objc_s
85130803Smarcel#define	yy_yys		objc_yys
86130803Smarcel#define	yystate		objc_state
87130803Smarcel#define	yytmp		objc_tmp
88130803Smarcel#define	yyv		objc_v
89130803Smarcel#define	yy_yyv		objc_yyv
90130803Smarcel#define	yyval		objc_val
91130803Smarcel#define	yylloc		objc_lloc
92130803Smarcel#define yyreds		objc_reds		/* With YYDEBUG defined */
93130803Smarcel#define yytoks		objc_toks		/* With YYDEBUG defined */
94130803Smarcel#define yyname  	objc_name          	/* With YYDEBUG defined */
95130803Smarcel#define yyrule  	objc_rule          	/* With YYDEBUG defined */
96130803Smarcel#define yylhs		objc_yylhs
97130803Smarcel#define yylen		objc_yylen
98130803Smarcel#define yydefred	objc_yydefred
99130803Smarcel#define yydgoto		objc_yydgoto
100130803Smarcel#define yysindex	objc_yysindex
101130803Smarcel#define yyrindex	objc_yyrindex
102130803Smarcel#define yygindex	objc_yygindex
103130803Smarcel#define yytable		objc_yytable
104130803Smarcel#define yycheck		objc_yycheck
105130803Smarcel
106130803Smarcel#ifndef YYDEBUG
107130803Smarcel#define	YYDEBUG	0		/* Default to no yydebug support.  */
108130803Smarcel#endif
109130803Smarcel
110130803Smarcelint
111130803Smarcelyyparse PARAMS ((void));
112130803Smarcel
113130803Smarcelstatic int
114130803Smarcelyylex PARAMS ((void));
115130803Smarcel
116130803Smarcelvoid
117130803Smarcelyyerror PARAMS ((char *));
118130803Smarcel
119130803Smarcel%}
120130803Smarcel
121130803Smarcel/* Although the yacc "value" of an expression is not used,
122130803Smarcel   since the result is stored in the structure being created,
123130803Smarcel   other node types do have values.  */
124130803Smarcel
125130803Smarcel%union
126130803Smarcel  {
127130803Smarcel    LONGEST lval;
128130803Smarcel    struct {
129130803Smarcel      LONGEST val;
130130803Smarcel      struct type *type;
131130803Smarcel    } typed_val_int;
132130803Smarcel    struct {
133130803Smarcel      DOUBLEST dval;
134130803Smarcel      struct type *type;
135130803Smarcel    } typed_val_float;
136130803Smarcel    struct symbol *sym;
137130803Smarcel    struct type *tval;
138130803Smarcel    struct stoken sval;
139130803Smarcel    struct ttype tsym;
140130803Smarcel    struct symtoken ssym;
141130803Smarcel    int voidval;
142130803Smarcel    struct block *bval;
143130803Smarcel    enum exp_opcode opcode;
144130803Smarcel    struct internalvar *ivar;
145130803Smarcel    struct objc_class_str class;
146130803Smarcel
147130803Smarcel    struct type **tvec;
148130803Smarcel    int *ivec;
149130803Smarcel  }
150130803Smarcel
151130803Smarcel%{
152130803Smarcel/* YYSTYPE gets defined by %union.  */
153130803Smarcelstatic int
154130803Smarcelparse_number PARAMS ((char *, int, int, YYSTYPE *));
155130803Smarcel%}
156130803Smarcel
157130803Smarcel%type <voidval> exp exp1 type_exp start variable qualified_name lcurly
158130803Smarcel%type <lval> rcurly
159130803Smarcel%type <tval> type typebase
160130803Smarcel%type <tvec> nonempty_typelist
161130803Smarcel/* %type <bval> block */
162130803Smarcel
163130803Smarcel/* Fancy type parsing.  */
164130803Smarcel%type <voidval> func_mod direct_abs_decl abs_decl
165130803Smarcel%type <tval> ptype
166130803Smarcel%type <lval> array_mod
167130803Smarcel
168130803Smarcel%token <typed_val_int> INT
169130803Smarcel%token <typed_val_float> FLOAT
170130803Smarcel
171130803Smarcel/* Both NAME and TYPENAME tokens represent symbols in the input, and
172130803Smarcel   both convey their data as strings.  But a TYPENAME is a string that
173130803Smarcel   happens to be defined as a typedef or builtin type name (such as
174130803Smarcel   int or char) and a NAME is any other symbol.  Contexts where this
175130803Smarcel   distinction is not important can use the nonterminal "name", which
176130803Smarcel   matches either NAME or TYPENAME.  */
177130803Smarcel
178130803Smarcel%token <sval> STRING
179130803Smarcel%token <sval> NSSTRING		/* ObjC Foundation "NSString" literal */
180130803Smarcel%token <sval> SELECTOR		/* ObjC "@selector" pseudo-operator   */
181130803Smarcel%token <ssym> NAME /* BLOCKNAME defined below to give it higher precedence. */
182130803Smarcel%token <tsym> TYPENAME
183130803Smarcel%token <class> CLASSNAME	/* ObjC Class name */
184130803Smarcel%type <sval> name
185130803Smarcel%type <ssym> name_not_typename
186130803Smarcel%type <tsym> typename
187130803Smarcel
188130803Smarcel/* A NAME_OR_INT is a symbol which is not known in the symbol table,
189130803Smarcel   but which would parse as a valid number in the current input radix.
190130803Smarcel   E.g. "c" when input_radix==16.  Depending on the parse, it will be
191130803Smarcel   turned into a name or into a number.  */
192130803Smarcel
193130803Smarcel%token <ssym> NAME_OR_INT
194130803Smarcel
195130803Smarcel%token STRUCT CLASS UNION ENUM SIZEOF UNSIGNED COLONCOLON
196130803Smarcel%token TEMPLATE
197130803Smarcel%token ERROR
198130803Smarcel
199130803Smarcel/* Special type cases, put in to allow the parser to distinguish
200130803Smarcel   different legal basetypes.  */
201130803Smarcel%token SIGNED_KEYWORD LONG SHORT INT_KEYWORD CONST_KEYWORD VOLATILE_KEYWORD DOUBLE_KEYWORD
202130803Smarcel
203130803Smarcel%token <voidval> VARIABLE
204130803Smarcel
205130803Smarcel%token <opcode> ASSIGN_MODIFY
206130803Smarcel
207130803Smarcel%left ','
208130803Smarcel%left ABOVE_COMMA
209130803Smarcel%right '=' ASSIGN_MODIFY
210130803Smarcel%right '?'
211130803Smarcel%left OROR
212130803Smarcel%left ANDAND
213130803Smarcel%left '|'
214130803Smarcel%left '^'
215130803Smarcel%left '&'
216130803Smarcel%left EQUAL NOTEQUAL
217130803Smarcel%left '<' '>' LEQ GEQ
218130803Smarcel%left LSH RSH
219130803Smarcel%left '@'
220130803Smarcel%left '+' '-'
221130803Smarcel%left '*' '/' '%'
222130803Smarcel%right UNARY INCREMENT DECREMENT
223130803Smarcel%right ARROW '.' '[' '('
224130803Smarcel%token <ssym> BLOCKNAME
225130803Smarcel%type <bval> block
226130803Smarcel%left COLONCOLON
227130803Smarcel
228130803Smarcel
229130803Smarcel%%
230130803Smarcel
231130803Smarcelstart   :	exp1
232130803Smarcel	|	type_exp
233130803Smarcel	;
234130803Smarcel
235130803Smarceltype_exp:	type
236130803Smarcel			{ write_exp_elt_opcode(OP_TYPE);
237130803Smarcel			  write_exp_elt_type($1);
238130803Smarcel			  write_exp_elt_opcode(OP_TYPE);}
239130803Smarcel	;
240130803Smarcel
241130803Smarcel/* Expressions, including the comma operator.  */
242130803Smarcelexp1	:	exp
243130803Smarcel	|	exp1 ',' exp
244130803Smarcel			{ write_exp_elt_opcode (BINOP_COMMA); }
245130803Smarcel	;
246130803Smarcel
247130803Smarcel/* Expressions, not including the comma operator.  */
248130803Smarcelexp	:	'*' exp    %prec UNARY
249130803Smarcel			{ write_exp_elt_opcode (UNOP_IND); }
250130803Smarcel	;
251130803Smarcel
252130803Smarcelexp	:	'&' exp    %prec UNARY
253130803Smarcel			{ write_exp_elt_opcode (UNOP_ADDR); }
254130803Smarcel	;
255130803Smarcel
256130803Smarcelexp	:	'-' exp    %prec UNARY
257130803Smarcel			{ write_exp_elt_opcode (UNOP_NEG); }
258130803Smarcel	;
259130803Smarcel
260130803Smarcelexp	:	'!' exp    %prec UNARY
261130803Smarcel			{ write_exp_elt_opcode (UNOP_LOGICAL_NOT); }
262130803Smarcel	;
263130803Smarcel
264130803Smarcelexp	:	'~' exp    %prec UNARY
265130803Smarcel			{ write_exp_elt_opcode (UNOP_COMPLEMENT); }
266130803Smarcel	;
267130803Smarcel
268130803Smarcelexp	:	INCREMENT exp    %prec UNARY
269130803Smarcel			{ write_exp_elt_opcode (UNOP_PREINCREMENT); }
270130803Smarcel	;
271130803Smarcel
272130803Smarcelexp	:	DECREMENT exp    %prec UNARY
273130803Smarcel			{ write_exp_elt_opcode (UNOP_PREDECREMENT); }
274130803Smarcel	;
275130803Smarcel
276130803Smarcelexp	:	exp INCREMENT    %prec UNARY
277130803Smarcel			{ write_exp_elt_opcode (UNOP_POSTINCREMENT); }
278130803Smarcel	;
279130803Smarcel
280130803Smarcelexp	:	exp DECREMENT    %prec UNARY
281130803Smarcel			{ write_exp_elt_opcode (UNOP_POSTDECREMENT); }
282130803Smarcel	;
283130803Smarcel
284130803Smarcelexp	:	SIZEOF exp       %prec UNARY
285130803Smarcel			{ write_exp_elt_opcode (UNOP_SIZEOF); }
286130803Smarcel	;
287130803Smarcel
288130803Smarcelexp	:	exp ARROW name
289130803Smarcel			{ write_exp_elt_opcode (STRUCTOP_PTR);
290130803Smarcel			  write_exp_string ($3);
291130803Smarcel			  write_exp_elt_opcode (STRUCTOP_PTR); }
292130803Smarcel	;
293130803Smarcel
294130803Smarcelexp	:	exp ARROW qualified_name
295130803Smarcel			{ /* exp->type::name becomes exp->*(&type::name) */
296130803Smarcel			  /* Note: this doesn't work if name is a
297130803Smarcel			     static member!  FIXME */
298130803Smarcel			  write_exp_elt_opcode (UNOP_ADDR);
299130803Smarcel			  write_exp_elt_opcode (STRUCTOP_MPTR); }
300130803Smarcel	;
301130803Smarcelexp	:	exp ARROW '*' exp
302130803Smarcel			{ write_exp_elt_opcode (STRUCTOP_MPTR); }
303130803Smarcel	;
304130803Smarcel
305130803Smarcelexp	:	exp '.' name
306130803Smarcel			{ write_exp_elt_opcode (STRUCTOP_STRUCT);
307130803Smarcel			  write_exp_string ($3);
308130803Smarcel			  write_exp_elt_opcode (STRUCTOP_STRUCT); }
309130803Smarcel	;
310130803Smarcel
311130803Smarcel
312130803Smarcelexp	:	exp '.' qualified_name
313130803Smarcel			{ /* exp.type::name becomes exp.*(&type::name) */
314130803Smarcel			  /* Note: this doesn't work if name is a
315130803Smarcel			     static member!  FIXME */
316130803Smarcel			  write_exp_elt_opcode (UNOP_ADDR);
317130803Smarcel			  write_exp_elt_opcode (STRUCTOP_MEMBER); }
318130803Smarcel	;
319130803Smarcel
320130803Smarcelexp	:	exp '.' '*' exp
321130803Smarcel			{ write_exp_elt_opcode (STRUCTOP_MEMBER); }
322130803Smarcel	;
323130803Smarcel
324130803Smarcelexp	:	exp '[' exp1 ']'
325130803Smarcel			{ write_exp_elt_opcode (BINOP_SUBSCRIPT); }
326130803Smarcel	;
327130803Smarcel/*
328130803Smarcel * The rules below parse ObjC message calls of the form:
329130803Smarcel *	'[' target selector {':' argument}* ']'
330130803Smarcel */
331130803Smarcel
332130803Smarcelexp	: 	'[' TYPENAME
333130803Smarcel			{
334130803Smarcel			  CORE_ADDR class;
335130803Smarcel
336130803Smarcel			  class = lookup_objc_class (copy_name ($2.stoken));
337130803Smarcel			  if (class == 0)
338130803Smarcel			    error ("%s is not an ObjC Class",
339130803Smarcel				   copy_name ($2.stoken));
340130803Smarcel			  write_exp_elt_opcode (OP_LONG);
341130803Smarcel			  write_exp_elt_type (builtin_type_int);
342130803Smarcel			  write_exp_elt_longcst ((LONGEST) class);
343130803Smarcel			  write_exp_elt_opcode (OP_LONG);
344130803Smarcel			  start_msglist();
345130803Smarcel			}
346130803Smarcel		msglist ']'
347130803Smarcel			{ write_exp_elt_opcode (OP_OBJC_MSGCALL);
348130803Smarcel			  end_msglist();
349130803Smarcel			  write_exp_elt_opcode (OP_OBJC_MSGCALL);
350130803Smarcel			}
351130803Smarcel	;
352130803Smarcel
353130803Smarcelexp	:	'[' CLASSNAME
354130803Smarcel			{
355130803Smarcel			  write_exp_elt_opcode (OP_LONG);
356130803Smarcel			  write_exp_elt_type (builtin_type_int);
357130803Smarcel			  write_exp_elt_longcst ((LONGEST) $2.class);
358130803Smarcel			  write_exp_elt_opcode (OP_LONG);
359130803Smarcel			  start_msglist();
360130803Smarcel			}
361130803Smarcel		msglist ']'
362130803Smarcel			{ write_exp_elt_opcode (OP_OBJC_MSGCALL);
363130803Smarcel			  end_msglist();
364130803Smarcel			  write_exp_elt_opcode (OP_OBJC_MSGCALL);
365130803Smarcel			}
366130803Smarcel	;
367130803Smarcel
368130803Smarcelexp	:	'[' exp
369130803Smarcel			{ start_msglist(); }
370130803Smarcel		msglist ']'
371130803Smarcel			{ write_exp_elt_opcode (OP_OBJC_MSGCALL);
372130803Smarcel			  end_msglist();
373130803Smarcel			  write_exp_elt_opcode (OP_OBJC_MSGCALL);
374130803Smarcel			}
375130803Smarcel	;
376130803Smarcel
377130803Smarcelmsglist :	name
378130803Smarcel			{ add_msglist(&$1, 0); }
379130803Smarcel	|	msgarglist
380130803Smarcel	;
381130803Smarcel
382130803Smarcelmsgarglist :	msgarg
383130803Smarcel	|	msgarglist msgarg
384130803Smarcel	;
385130803Smarcel
386130803Smarcelmsgarg	:	name ':' exp
387130803Smarcel			{ add_msglist(&$1, 1); }
388130803Smarcel	|	':' exp	/* Unnamed arg.  */
389130803Smarcel			{ add_msglist(0, 1);   }
390130803Smarcel	|	',' exp	/* Variable number of args.  */
391130803Smarcel			{ add_msglist(0, 0);   }
392130803Smarcel	;
393130803Smarcel
394130803Smarcelexp	:	exp '('
395130803Smarcel			/* This is to save the value of arglist_len
396130803Smarcel			   being accumulated by an outer function call.  */
397130803Smarcel			{ start_arglist (); }
398130803Smarcel		arglist ')'	%prec ARROW
399130803Smarcel			{ write_exp_elt_opcode (OP_FUNCALL);
400130803Smarcel			  write_exp_elt_longcst ((LONGEST) end_arglist ());
401130803Smarcel			  write_exp_elt_opcode (OP_FUNCALL); }
402130803Smarcel	;
403130803Smarcel
404130803Smarcellcurly	:	'{'
405130803Smarcel			{ start_arglist (); }
406130803Smarcel	;
407130803Smarcel
408130803Smarcelarglist	:
409130803Smarcel	;
410130803Smarcel
411130803Smarcelarglist	:	exp
412130803Smarcel			{ arglist_len = 1; }
413130803Smarcel	;
414130803Smarcel
415130803Smarcelarglist	:	arglist ',' exp   %prec ABOVE_COMMA
416130803Smarcel			{ arglist_len++; }
417130803Smarcel	;
418130803Smarcel
419130803Smarcelrcurly	:	'}'
420130803Smarcel			{ $$ = end_arglist () - 1; }
421130803Smarcel	;
422130803Smarcelexp	:	lcurly arglist rcurly	%prec ARROW
423130803Smarcel			{ write_exp_elt_opcode (OP_ARRAY);
424130803Smarcel			  write_exp_elt_longcst ((LONGEST) 0);
425130803Smarcel			  write_exp_elt_longcst ((LONGEST) $3);
426130803Smarcel			  write_exp_elt_opcode (OP_ARRAY); }
427130803Smarcel	;
428130803Smarcel
429130803Smarcelexp	:	lcurly type rcurly exp  %prec UNARY
430130803Smarcel			{ write_exp_elt_opcode (UNOP_MEMVAL);
431130803Smarcel			  write_exp_elt_type ($2);
432130803Smarcel			  write_exp_elt_opcode (UNOP_MEMVAL); }
433130803Smarcel	;
434130803Smarcel
435130803Smarcelexp	:	'(' type ')' exp  %prec UNARY
436130803Smarcel			{ write_exp_elt_opcode (UNOP_CAST);
437130803Smarcel			  write_exp_elt_type ($2);
438130803Smarcel			  write_exp_elt_opcode (UNOP_CAST); }
439130803Smarcel	;
440130803Smarcel
441130803Smarcelexp	:	'(' exp1 ')'
442130803Smarcel			{ }
443130803Smarcel	;
444130803Smarcel
445130803Smarcel/* Binary operators in order of decreasing precedence.  */
446130803Smarcel
447130803Smarcelexp	:	exp '@' exp
448130803Smarcel			{ write_exp_elt_opcode (BINOP_REPEAT); }
449130803Smarcel	;
450130803Smarcel
451130803Smarcelexp	:	exp '*' exp
452130803Smarcel			{ write_exp_elt_opcode (BINOP_MUL); }
453130803Smarcel	;
454130803Smarcel
455130803Smarcelexp	:	exp '/' exp
456130803Smarcel			{ write_exp_elt_opcode (BINOP_DIV); }
457130803Smarcel	;
458130803Smarcel
459130803Smarcelexp	:	exp '%' exp
460130803Smarcel			{ write_exp_elt_opcode (BINOP_REM); }
461130803Smarcel	;
462130803Smarcel
463130803Smarcelexp	:	exp '+' exp
464130803Smarcel			{ write_exp_elt_opcode (BINOP_ADD); }
465130803Smarcel	;
466130803Smarcel
467130803Smarcelexp	:	exp '-' exp
468130803Smarcel			{ write_exp_elt_opcode (BINOP_SUB); }
469130803Smarcel	;
470130803Smarcel
471130803Smarcelexp	:	exp LSH exp
472130803Smarcel			{ write_exp_elt_opcode (BINOP_LSH); }
473130803Smarcel	;
474130803Smarcel
475130803Smarcelexp	:	exp RSH exp
476130803Smarcel			{ write_exp_elt_opcode (BINOP_RSH); }
477130803Smarcel	;
478130803Smarcel
479130803Smarcelexp	:	exp EQUAL exp
480130803Smarcel			{ write_exp_elt_opcode (BINOP_EQUAL); }
481130803Smarcel	;
482130803Smarcel
483130803Smarcelexp	:	exp NOTEQUAL exp
484130803Smarcel			{ write_exp_elt_opcode (BINOP_NOTEQUAL); }
485130803Smarcel	;
486130803Smarcel
487130803Smarcelexp	:	exp LEQ exp
488130803Smarcel			{ write_exp_elt_opcode (BINOP_LEQ); }
489130803Smarcel	;
490130803Smarcel
491130803Smarcelexp	:	exp GEQ exp
492130803Smarcel			{ write_exp_elt_opcode (BINOP_GEQ); }
493130803Smarcel	;
494130803Smarcel
495130803Smarcelexp	:	exp '<' exp
496130803Smarcel			{ write_exp_elt_opcode (BINOP_LESS); }
497130803Smarcel	;
498130803Smarcel
499130803Smarcelexp	:	exp '>' exp
500130803Smarcel			{ write_exp_elt_opcode (BINOP_GTR); }
501130803Smarcel	;
502130803Smarcel
503130803Smarcelexp	:	exp '&' exp
504130803Smarcel			{ write_exp_elt_opcode (BINOP_BITWISE_AND); }
505130803Smarcel	;
506130803Smarcel
507130803Smarcelexp	:	exp '^' exp
508130803Smarcel			{ write_exp_elt_opcode (BINOP_BITWISE_XOR); }
509130803Smarcel	;
510130803Smarcel
511130803Smarcelexp	:	exp '|' exp
512130803Smarcel			{ write_exp_elt_opcode (BINOP_BITWISE_IOR); }
513130803Smarcel	;
514130803Smarcel
515130803Smarcelexp	:	exp ANDAND exp
516130803Smarcel			{ write_exp_elt_opcode (BINOP_LOGICAL_AND); }
517130803Smarcel	;
518130803Smarcel
519130803Smarcelexp	:	exp OROR exp
520130803Smarcel			{ write_exp_elt_opcode (BINOP_LOGICAL_OR); }
521130803Smarcel	;
522130803Smarcel
523130803Smarcelexp	:	exp '?' exp ':' exp	%prec '?'
524130803Smarcel			{ write_exp_elt_opcode (TERNOP_COND); }
525130803Smarcel	;
526130803Smarcel
527130803Smarcelexp	:	exp '=' exp
528130803Smarcel			{ write_exp_elt_opcode (BINOP_ASSIGN); }
529130803Smarcel	;
530130803Smarcel
531130803Smarcelexp	:	exp ASSIGN_MODIFY exp
532130803Smarcel			{ write_exp_elt_opcode (BINOP_ASSIGN_MODIFY);
533130803Smarcel			  write_exp_elt_opcode ($2);
534130803Smarcel			  write_exp_elt_opcode (BINOP_ASSIGN_MODIFY); }
535130803Smarcel	;
536130803Smarcel
537130803Smarcelexp	:	INT
538130803Smarcel			{ write_exp_elt_opcode (OP_LONG);
539130803Smarcel			  write_exp_elt_type ($1.type);
540130803Smarcel			  write_exp_elt_longcst ((LONGEST)($1.val));
541130803Smarcel			  write_exp_elt_opcode (OP_LONG); }
542130803Smarcel	;
543130803Smarcel
544130803Smarcelexp	:	NAME_OR_INT
545130803Smarcel			{ YYSTYPE val;
546130803Smarcel			  parse_number ($1.stoken.ptr, $1.stoken.length, 0, &val);
547130803Smarcel			  write_exp_elt_opcode (OP_LONG);
548130803Smarcel			  write_exp_elt_type (val.typed_val_int.type);
549130803Smarcel			  write_exp_elt_longcst ((LONGEST)val.typed_val_int.val);
550130803Smarcel			  write_exp_elt_opcode (OP_LONG);
551130803Smarcel			}
552130803Smarcel	;
553130803Smarcel
554130803Smarcel
555130803Smarcelexp	:	FLOAT
556130803Smarcel			{ write_exp_elt_opcode (OP_DOUBLE);
557130803Smarcel			  write_exp_elt_type ($1.type);
558130803Smarcel			  write_exp_elt_dblcst ($1.dval);
559130803Smarcel			  write_exp_elt_opcode (OP_DOUBLE); }
560130803Smarcel	;
561130803Smarcel
562130803Smarcelexp	:	variable
563130803Smarcel	;
564130803Smarcel
565130803Smarcelexp	:	VARIABLE
566130803Smarcel			/* Already written by write_dollar_variable.  */
567130803Smarcel	;
568130803Smarcel
569130803Smarcelexp	:	SELECTOR
570130803Smarcel			{
571130803Smarcel			  write_exp_elt_opcode (OP_OBJC_SELECTOR);
572130803Smarcel			  write_exp_string ($1);
573130803Smarcel			  write_exp_elt_opcode (OP_OBJC_SELECTOR); }
574130803Smarcel	;
575130803Smarcel
576130803Smarcelexp	:	SIZEOF '(' type ')'	%prec UNARY
577130803Smarcel			{ write_exp_elt_opcode (OP_LONG);
578130803Smarcel			  write_exp_elt_type (builtin_type_int);
579130803Smarcel			  CHECK_TYPEDEF ($3);
580130803Smarcel			  write_exp_elt_longcst ((LONGEST) TYPE_LENGTH ($3));
581130803Smarcel			  write_exp_elt_opcode (OP_LONG); }
582130803Smarcel	;
583130803Smarcel
584130803Smarcelexp	:	STRING
585130803Smarcel			{ /* C strings are converted into array
586130803Smarcel			     constants with an explicit null byte
587130803Smarcel			     added at the end.  Thus the array upper
588130803Smarcel			     bound is the string length.  There is no
589130803Smarcel			     such thing in C as a completely empty
590130803Smarcel			     string.  */
591130803Smarcel			  char *sp = $1.ptr; int count = $1.length;
592130803Smarcel			  while (count-- > 0)
593130803Smarcel			    {
594130803Smarcel			      write_exp_elt_opcode (OP_LONG);
595130803Smarcel			      write_exp_elt_type (builtin_type_char);
596130803Smarcel			      write_exp_elt_longcst ((LONGEST)(*sp++));
597130803Smarcel			      write_exp_elt_opcode (OP_LONG);
598130803Smarcel			    }
599130803Smarcel			  write_exp_elt_opcode (OP_LONG);
600130803Smarcel			  write_exp_elt_type (builtin_type_char);
601130803Smarcel			  write_exp_elt_longcst ((LONGEST)'\0');
602130803Smarcel			  write_exp_elt_opcode (OP_LONG);
603130803Smarcel			  write_exp_elt_opcode (OP_ARRAY);
604130803Smarcel			  write_exp_elt_longcst ((LONGEST) 0);
605130803Smarcel			  write_exp_elt_longcst ((LONGEST) ($1.length));
606130803Smarcel			  write_exp_elt_opcode (OP_ARRAY); }
607130803Smarcel	;
608130803Smarcel
609130803Smarcelexp     :	NSSTRING	/* ObjC NextStep NSString constant
610130803Smarcel				 * of the form '@' '"' string '"'.
611130803Smarcel				 */
612130803Smarcel			{ write_exp_elt_opcode (OP_OBJC_NSSTRING);
613130803Smarcel			  write_exp_string ($1);
614130803Smarcel			  write_exp_elt_opcode (OP_OBJC_NSSTRING); }
615130803Smarcel	;
616130803Smarcel
617130803Smarcelblock	:	BLOCKNAME
618130803Smarcel			{
619130803Smarcel			  if ($1.sym != 0)
620130803Smarcel			      $$ = SYMBOL_BLOCK_VALUE ($1.sym);
621130803Smarcel			  else
622130803Smarcel			    {
623130803Smarcel			      struct symtab *tem =
624130803Smarcel				  lookup_symtab (copy_name ($1.stoken));
625130803Smarcel			      if (tem)
626130803Smarcel				$$ = BLOCKVECTOR_BLOCK (BLOCKVECTOR (tem), STATIC_BLOCK);
627130803Smarcel			      else
628130803Smarcel				error ("No file or function \"%s\".",
629130803Smarcel				       copy_name ($1.stoken));
630130803Smarcel			    }
631130803Smarcel			}
632130803Smarcel	;
633130803Smarcel
634130803Smarcelblock	:	block COLONCOLON name
635130803Smarcel			{ struct symbol *tem
636130803Smarcel			    = lookup_symbol (copy_name ($3), $1,
637130803Smarcel					     VAR_DOMAIN, (int *) NULL,
638130803Smarcel					     (struct symtab **) NULL);
639130803Smarcel			  if (!tem || SYMBOL_CLASS (tem) != LOC_BLOCK)
640130803Smarcel			    error ("No function \"%s\" in specified context.",
641130803Smarcel				   copy_name ($3));
642130803Smarcel			  $$ = SYMBOL_BLOCK_VALUE (tem); }
643130803Smarcel	;
644130803Smarcel
645130803Smarcelvariable:	block COLONCOLON name
646130803Smarcel			{ struct symbol *sym;
647130803Smarcel			  sym = lookup_symbol (copy_name ($3), $1,
648130803Smarcel					       VAR_DOMAIN, (int *) NULL,
649130803Smarcel					       (struct symtab **) NULL);
650130803Smarcel			  if (sym == 0)
651130803Smarcel			    error ("No symbol \"%s\" in specified context.",
652130803Smarcel				   copy_name ($3));
653130803Smarcel
654130803Smarcel			  write_exp_elt_opcode (OP_VAR_VALUE);
655130803Smarcel			  /* block_found is set by lookup_symbol.  */
656130803Smarcel			  write_exp_elt_block (block_found);
657130803Smarcel			  write_exp_elt_sym (sym);
658130803Smarcel			  write_exp_elt_opcode (OP_VAR_VALUE); }
659130803Smarcel	;
660130803Smarcel
661130803Smarcelqualified_name:	typebase COLONCOLON name
662130803Smarcel			{
663130803Smarcel			  struct type *type = $1;
664130803Smarcel			  if (TYPE_CODE (type) != TYPE_CODE_STRUCT
665130803Smarcel			      && TYPE_CODE (type) != TYPE_CODE_UNION)
666130803Smarcel			    error ("`%s' is not defined as an aggregate type.",
667130803Smarcel				   TYPE_NAME (type));
668130803Smarcel
669130803Smarcel			  write_exp_elt_opcode (OP_SCOPE);
670130803Smarcel			  write_exp_elt_type (type);
671130803Smarcel			  write_exp_string ($3);
672130803Smarcel			  write_exp_elt_opcode (OP_SCOPE);
673130803Smarcel			}
674130803Smarcel	|	typebase COLONCOLON '~' name
675130803Smarcel			{
676130803Smarcel			  struct type *type = $1;
677130803Smarcel			  struct stoken tmp_token;
678130803Smarcel			  if (TYPE_CODE (type) != TYPE_CODE_STRUCT
679130803Smarcel			      && TYPE_CODE (type) != TYPE_CODE_UNION)
680130803Smarcel			    error ("`%s' is not defined as an aggregate type.",
681130803Smarcel				   TYPE_NAME (type));
682130803Smarcel
683130803Smarcel			  if (!DEPRECATED_STREQ (type_name_no_tag (type), $4.ptr))
684130803Smarcel			    error ("invalid destructor `%s::~%s'",
685130803Smarcel				   type_name_no_tag (type), $4.ptr);
686130803Smarcel
687130803Smarcel			  tmp_token.ptr = (char*) alloca ($4.length + 2);
688130803Smarcel			  tmp_token.length = $4.length + 1;
689130803Smarcel			  tmp_token.ptr[0] = '~';
690130803Smarcel			  memcpy (tmp_token.ptr+1, $4.ptr, $4.length);
691130803Smarcel			  tmp_token.ptr[tmp_token.length] = 0;
692130803Smarcel			  write_exp_elt_opcode (OP_SCOPE);
693130803Smarcel			  write_exp_elt_type (type);
694130803Smarcel			  write_exp_string (tmp_token);
695130803Smarcel			  write_exp_elt_opcode (OP_SCOPE);
696130803Smarcel			}
697130803Smarcel	;
698130803Smarcel
699130803Smarcelvariable:	qualified_name
700130803Smarcel	|	COLONCOLON name
701130803Smarcel			{
702130803Smarcel			  char *name = copy_name ($2);
703130803Smarcel			  struct symbol *sym;
704130803Smarcel			  struct minimal_symbol *msymbol;
705130803Smarcel
706130803Smarcel			  sym =
707130803Smarcel			    lookup_symbol (name, (const struct block *) NULL,
708130803Smarcel					   VAR_DOMAIN, (int *) NULL,
709130803Smarcel					   (struct symtab **) NULL);
710130803Smarcel			  if (sym)
711130803Smarcel			    {
712130803Smarcel			      write_exp_elt_opcode (OP_VAR_VALUE);
713130803Smarcel			      write_exp_elt_block (NULL);
714130803Smarcel			      write_exp_elt_sym (sym);
715130803Smarcel			      write_exp_elt_opcode (OP_VAR_VALUE);
716130803Smarcel			      break;
717130803Smarcel			    }
718130803Smarcel
719130803Smarcel			  msymbol = lookup_minimal_symbol (name, NULL, NULL);
720130803Smarcel			  if (msymbol != NULL)
721130803Smarcel			    {
722130803Smarcel			      write_exp_msymbol (msymbol,
723130803Smarcel						 lookup_function_type (builtin_type_int),
724130803Smarcel						 builtin_type_int);
725130803Smarcel			    }
726130803Smarcel			  else
727130803Smarcel			    if (!have_full_symbols () && !have_partial_symbols ())
728130803Smarcel			      error ("No symbol table is loaded.  Use the \"file\" command.");
729130803Smarcel			    else
730130803Smarcel			      error ("No symbol \"%s\" in current context.", name);
731130803Smarcel			}
732130803Smarcel	;
733130803Smarcel
734130803Smarcelvariable:	name_not_typename
735130803Smarcel			{ struct symbol *sym = $1.sym;
736130803Smarcel
737130803Smarcel			  if (sym)
738130803Smarcel			    {
739130803Smarcel			      if (symbol_read_needs_frame (sym))
740130803Smarcel				{
741130803Smarcel				  if (innermost_block == 0 ||
742130803Smarcel				      contained_in (block_found,
743130803Smarcel						    innermost_block))
744130803Smarcel				    innermost_block = block_found;
745130803Smarcel				}
746130803Smarcel
747130803Smarcel			      write_exp_elt_opcode (OP_VAR_VALUE);
748130803Smarcel			      /* We want to use the selected frame, not
749130803Smarcel				 another more inner frame which happens to
750130803Smarcel				 be in the same block.  */
751130803Smarcel			      write_exp_elt_block (NULL);
752130803Smarcel			      write_exp_elt_sym (sym);
753130803Smarcel			      write_exp_elt_opcode (OP_VAR_VALUE);
754130803Smarcel			    }
755130803Smarcel			  else if ($1.is_a_field_of_this)
756130803Smarcel			    {
757130803Smarcel			      /* C++/ObjC: it hangs off of `this'/'self'.
758130803Smarcel				 Must not inadvertently convert from a
759130803Smarcel				 method call to data ref.  */
760130803Smarcel			      if (innermost_block == 0 ||
761130803Smarcel				  contained_in (block_found, innermost_block))
762130803Smarcel				innermost_block = block_found;
763130803Smarcel			      write_exp_elt_opcode (OP_OBJC_SELF);
764130803Smarcel			      write_exp_elt_opcode (OP_OBJC_SELF);
765130803Smarcel			      write_exp_elt_opcode (STRUCTOP_PTR);
766130803Smarcel			      write_exp_string ($1.stoken);
767130803Smarcel			      write_exp_elt_opcode (STRUCTOP_PTR);
768130803Smarcel			    }
769130803Smarcel			  else
770130803Smarcel			    {
771130803Smarcel			      struct minimal_symbol *msymbol;
772130803Smarcel			      char *arg = copy_name ($1.stoken);
773130803Smarcel
774130803Smarcel			      msymbol =
775130803Smarcel				lookup_minimal_symbol (arg, NULL, NULL);
776130803Smarcel			      if (msymbol != NULL)
777130803Smarcel				{
778130803Smarcel				  write_exp_msymbol (msymbol,
779130803Smarcel						     lookup_function_type (builtin_type_int),
780130803Smarcel						     builtin_type_int);
781130803Smarcel				}
782130803Smarcel			      else if (!have_full_symbols () &&
783130803Smarcel				       !have_partial_symbols ())
784130803Smarcel				error ("No symbol table is loaded.  Use the \"file\" command.");
785130803Smarcel			      else
786130803Smarcel				error ("No symbol \"%s\" in current context.",
787130803Smarcel				       copy_name ($1.stoken));
788130803Smarcel			    }
789130803Smarcel			}
790130803Smarcel	;
791130803Smarcel
792130803Smarcel
793130803Smarcelptype	:	typebase
794130803Smarcel	/* "const" and "volatile" are curently ignored.  A type
795130803Smarcel	   qualifier before the type is currently handled in the
796130803Smarcel	   typebase rule.  The reason for recognizing these here
797130803Smarcel	   (shift/reduce conflicts) might be obsolete now that some
798130803Smarcel	   pointer to member rules have been deleted.  */
799130803Smarcel	|	typebase CONST_KEYWORD
800130803Smarcel	|	typebase VOLATILE_KEYWORD
801130803Smarcel	|	typebase abs_decl
802130803Smarcel		{ $$ = follow_types ($1); }
803130803Smarcel	|	typebase CONST_KEYWORD abs_decl
804130803Smarcel		{ $$ = follow_types ($1); }
805130803Smarcel	|	typebase VOLATILE_KEYWORD abs_decl
806130803Smarcel		{ $$ = follow_types ($1); }
807130803Smarcel	;
808130803Smarcel
809130803Smarcelabs_decl:	'*'
810130803Smarcel			{ push_type (tp_pointer); $$ = 0; }
811130803Smarcel	|	'*' abs_decl
812130803Smarcel			{ push_type (tp_pointer); $$ = $2; }
813130803Smarcel	|	'&'
814130803Smarcel			{ push_type (tp_reference); $$ = 0; }
815130803Smarcel	|	'&' abs_decl
816130803Smarcel			{ push_type (tp_reference); $$ = $2; }
817130803Smarcel	|	direct_abs_decl
818130803Smarcel	;
819130803Smarcel
820130803Smarceldirect_abs_decl: '(' abs_decl ')'
821130803Smarcel			{ $$ = $2; }
822130803Smarcel	|	direct_abs_decl array_mod
823130803Smarcel			{
824130803Smarcel			  push_type_int ($2);
825130803Smarcel			  push_type (tp_array);
826130803Smarcel			}
827130803Smarcel	|	array_mod
828130803Smarcel			{
829130803Smarcel			  push_type_int ($1);
830130803Smarcel			  push_type (tp_array);
831130803Smarcel			  $$ = 0;
832130803Smarcel			}
833130803Smarcel
834130803Smarcel	| 	direct_abs_decl func_mod
835130803Smarcel			{ push_type (tp_function); }
836130803Smarcel	|	func_mod
837130803Smarcel			{ push_type (tp_function); }
838130803Smarcel	;
839130803Smarcel
840130803Smarcelarray_mod:	'[' ']'
841130803Smarcel			{ $$ = -1; }
842130803Smarcel	|	'[' INT ']'
843130803Smarcel			{ $$ = $2.val; }
844130803Smarcel	;
845130803Smarcel
846130803Smarcelfunc_mod:	'(' ')'
847130803Smarcel			{ $$ = 0; }
848130803Smarcel	|	'(' nonempty_typelist ')'
849130803Smarcel			{ free ($2); $$ = 0; }
850130803Smarcel	;
851130803Smarcel
852130803Smarcel/* We used to try to recognize more pointer to member types here, but
853130803Smarcel   that didn't work (shift/reduce conflicts meant that these rules
854130803Smarcel   never got executed).  The problem is that
855130803Smarcel     int (foo::bar::baz::bizzle)
856130803Smarcel   is a function type but
857130803Smarcel     int (foo::bar::baz::bizzle::*)
858130803Smarcel   is a pointer to member type.  Stroustrup loses again!  */
859130803Smarcel
860130803Smarceltype	:	ptype
861130803Smarcel	|	typebase COLONCOLON '*'
862130803Smarcel			{ $$ = lookup_member_type (builtin_type_int, $1); }
863130803Smarcel	;
864130803Smarcel
865130803Smarceltypebase  /* Implements (approximately): (type-qualifier)* type-specifier.  */
866130803Smarcel	:	TYPENAME
867130803Smarcel			{ $$ = $1.type; }
868130803Smarcel	|	CLASSNAME
869130803Smarcel			{
870130803Smarcel			  if ($1.type == NULL)
871130803Smarcel			    error ("No symbol \"%s\" in current context.",
872130803Smarcel				   copy_name($1.stoken));
873130803Smarcel			  else
874130803Smarcel			    $$ = $1.type;
875130803Smarcel			}
876130803Smarcel	|	INT_KEYWORD
877130803Smarcel			{ $$ = builtin_type_int; }
878130803Smarcel	|	LONG
879130803Smarcel			{ $$ = builtin_type_long; }
880130803Smarcel	|	SHORT
881130803Smarcel			{ $$ = builtin_type_short; }
882130803Smarcel	|	LONG INT_KEYWORD
883130803Smarcel			{ $$ = builtin_type_long; }
884130803Smarcel	|	UNSIGNED LONG INT_KEYWORD
885130803Smarcel			{ $$ = builtin_type_unsigned_long; }
886130803Smarcel	|	LONG LONG
887130803Smarcel			{ $$ = builtin_type_long_long; }
888130803Smarcel	|	LONG LONG INT_KEYWORD
889130803Smarcel			{ $$ = builtin_type_long_long; }
890130803Smarcel	|	UNSIGNED LONG LONG
891130803Smarcel			{ $$ = builtin_type_unsigned_long_long; }
892130803Smarcel	|	UNSIGNED LONG LONG INT_KEYWORD
893130803Smarcel			{ $$ = builtin_type_unsigned_long_long; }
894130803Smarcel	|	SHORT INT_KEYWORD
895130803Smarcel			{ $$ = builtin_type_short; }
896130803Smarcel	|	UNSIGNED SHORT INT_KEYWORD
897130803Smarcel			{ $$ = builtin_type_unsigned_short; }
898130803Smarcel	|	DOUBLE_KEYWORD
899130803Smarcel			{ $$ = builtin_type_double; }
900130803Smarcel	|	LONG DOUBLE_KEYWORD
901130803Smarcel			{ $$ = builtin_type_long_double; }
902130803Smarcel	|	STRUCT name
903130803Smarcel			{ $$ = lookup_struct (copy_name ($2),
904130803Smarcel					      expression_context_block); }
905130803Smarcel	|	CLASS name
906130803Smarcel			{ $$ = lookup_struct (copy_name ($2),
907130803Smarcel					      expression_context_block); }
908130803Smarcel	|	UNION name
909130803Smarcel			{ $$ = lookup_union (copy_name ($2),
910130803Smarcel					     expression_context_block); }
911130803Smarcel	|	ENUM name
912130803Smarcel			{ $$ = lookup_enum (copy_name ($2),
913130803Smarcel					    expression_context_block); }
914130803Smarcel	|	UNSIGNED typename
915130803Smarcel			{ $$ = lookup_unsigned_typename (TYPE_NAME($2.type)); }
916130803Smarcel	|	UNSIGNED
917130803Smarcel			{ $$ = builtin_type_unsigned_int; }
918130803Smarcel	|	SIGNED_KEYWORD typename
919130803Smarcel			{ $$ = lookup_signed_typename (TYPE_NAME($2.type)); }
920130803Smarcel	|	SIGNED_KEYWORD
921130803Smarcel			{ $$ = builtin_type_int; }
922130803Smarcel	|	TEMPLATE name '<' type '>'
923130803Smarcel			{ $$ = lookup_template_type(copy_name($2), $4,
924130803Smarcel						    expression_context_block);
925130803Smarcel			}
926130803Smarcel	/* "const" and "volatile" are curently ignored.  A type
927130803Smarcel	   qualifier after the type is handled in the ptype rule.  I
928130803Smarcel	   think these could be too.  */
929130803Smarcel	|	CONST_KEYWORD typebase { $$ = $2; }
930130803Smarcel	|	VOLATILE_KEYWORD typebase { $$ = $2; }
931130803Smarcel	;
932130803Smarcel
933130803Smarceltypename:	TYPENAME
934130803Smarcel	|	INT_KEYWORD
935130803Smarcel		{
936130803Smarcel		  $$.stoken.ptr = "int";
937130803Smarcel		  $$.stoken.length = 3;
938130803Smarcel		  $$.type = builtin_type_int;
939130803Smarcel		}
940130803Smarcel	|	LONG
941130803Smarcel		{
942130803Smarcel		  $$.stoken.ptr = "long";
943130803Smarcel		  $$.stoken.length = 4;
944130803Smarcel		  $$.type = builtin_type_long;
945130803Smarcel		}
946130803Smarcel	|	SHORT
947130803Smarcel		{
948130803Smarcel		  $$.stoken.ptr = "short";
949130803Smarcel		  $$.stoken.length = 5;
950130803Smarcel		  $$.type = builtin_type_short;
951130803Smarcel		}
952130803Smarcel	;
953130803Smarcel
954130803Smarcelnonempty_typelist
955130803Smarcel	:	type
956130803Smarcel		{ $$ = (struct type **) malloc (sizeof (struct type *) * 2);
957130803Smarcel		  $<ivec>$[0] = 1;	/* Number of types in vector.  */
958130803Smarcel		  $$[1] = $1;
959130803Smarcel		}
960130803Smarcel	|	nonempty_typelist ',' type
961130803Smarcel		{ int len = sizeof (struct type *) * (++($<ivec>1[0]) + 1);
962130803Smarcel		  $$ = (struct type **) realloc ((char *) $1, len);
963130803Smarcel		  $$[$<ivec>$[0]] = $3;
964130803Smarcel		}
965130803Smarcel	;
966130803Smarcel
967130803Smarcelname	:	NAME        { $$ = $1.stoken; }
968130803Smarcel	|	BLOCKNAME   { $$ = $1.stoken; }
969130803Smarcel	|	TYPENAME    { $$ = $1.stoken; }
970130803Smarcel	|	CLASSNAME   { $$ = $1.stoken; }
971130803Smarcel	|	NAME_OR_INT { $$ = $1.stoken; }
972130803Smarcel	;
973130803Smarcel
974130803Smarcelname_not_typename :	NAME
975130803Smarcel	|	BLOCKNAME
976130803Smarcel/* These would be useful if name_not_typename was useful, but it is
977130803Smarcel   just a fake for "variable", so these cause reduce/reduce conflicts
978130803Smarcel   because the parser can't tell whether NAME_OR_INT is a
979130803Smarcel   name_not_typename (=variable, =exp) or just an exp.  If
980130803Smarcel   name_not_typename was ever used in an lvalue context where only a
981130803Smarcel   name could occur, this might be useful.  */
982130803Smarcel/*  	| NAME_OR_INT */
983130803Smarcel	;
984130803Smarcel
985130803Smarcel%%
986130803Smarcel
987130803Smarcel/* Take care of parsing a number (anything that starts with a digit).
988130803Smarcel   Set yylval and return the token type; update lexptr.  LEN is the
989130803Smarcel   number of characters in it.  */
990130803Smarcel
991130803Smarcel/*** Needs some error checking for the float case.  ***/
992130803Smarcel
993130803Smarcelstatic int
994130803Smarcelparse_number (p, len, parsed_float, putithere)
995130803Smarcel     char *p;
996130803Smarcel     int len;
997130803Smarcel     int parsed_float;
998130803Smarcel     YYSTYPE *putithere;
999130803Smarcel{
1000130803Smarcel  /* FIXME: Shouldn't these be unsigned?  We don't deal with negative
1001130803Smarcel     values here, and we do kind of silly things like cast to
1002130803Smarcel     unsigned.  */
1003130803Smarcel  LONGEST n = 0;
1004130803Smarcel  LONGEST prevn = 0;
1005130803Smarcel  unsigned LONGEST un;
1006130803Smarcel
1007130803Smarcel  int i = 0;
1008130803Smarcel  int c;
1009130803Smarcel  int base = input_radix;
1010130803Smarcel  int unsigned_p = 0;
1011130803Smarcel
1012130803Smarcel  /* Number of "L" suffixes encountered.  */
1013130803Smarcel  int long_p = 0;
1014130803Smarcel
1015130803Smarcel  /* We have found a "L" or "U" suffix.  */
1016130803Smarcel  int found_suffix = 0;
1017130803Smarcel
1018130803Smarcel  unsigned LONGEST high_bit;
1019130803Smarcel  struct type *signed_type;
1020130803Smarcel  struct type *unsigned_type;
1021130803Smarcel
1022130803Smarcel  if (parsed_float)
1023130803Smarcel    {
1024130803Smarcel      char c;
1025130803Smarcel
1026130803Smarcel      /* It's a float since it contains a point or an exponent.  */
1027130803Smarcel
1028130803Smarcel      if (sizeof (putithere->typed_val_float.dval) <= sizeof (float))
1029130803Smarcel	sscanf (p, "%g", (float *)&putithere->typed_val_float.dval);
1030130803Smarcel      else if (sizeof (putithere->typed_val_float.dval) <= sizeof (double))
1031130803Smarcel	sscanf (p, "%lg", (double *)&putithere->typed_val_float.dval);
1032130803Smarcel      else
1033130803Smarcel	{
1034130803Smarcel#ifdef PRINTF_HAS_LONG_DOUBLE
1035130803Smarcel	  sscanf (p, "%Lg", &putithere->typed_val_float.dval);
1036130803Smarcel#else
1037130803Smarcel	  /* Scan it into a double, then assign it to the long double.
1038130803Smarcel	     This at least wins with values representable in the range
1039130803Smarcel	     of doubles.  */
1040130803Smarcel	  double temp;
1041130803Smarcel	  sscanf (p, "%lg", &temp);
1042130803Smarcel	  putithere->typed_val_float.dval = temp;
1043130803Smarcel#endif
1044130803Smarcel	}
1045130803Smarcel
1046130803Smarcel      /* See if it has `f' or `l' suffix (float or long double).  */
1047130803Smarcel
1048130803Smarcel      c = tolower (p[len - 1]);
1049130803Smarcel
1050130803Smarcel      if (c == 'f')
1051130803Smarcel	putithere->typed_val_float.type = builtin_type_float;
1052130803Smarcel      else if (c == 'l')
1053130803Smarcel	putithere->typed_val_float.type = builtin_type_long_double;
1054130803Smarcel      else if (isdigit (c) || c == '.')
1055130803Smarcel	putithere->typed_val_float.type = builtin_type_double;
1056130803Smarcel      else
1057130803Smarcel	return ERROR;
1058130803Smarcel
1059130803Smarcel      return FLOAT;
1060130803Smarcel    }
1061130803Smarcel
1062130803Smarcel  /* Handle base-switching prefixes 0x, 0t, 0d, and 0.  */
1063130803Smarcel  if (p[0] == '0')
1064130803Smarcel    switch (p[1])
1065130803Smarcel      {
1066130803Smarcel      case 'x':
1067130803Smarcel      case 'X':
1068130803Smarcel	if (len >= 3)
1069130803Smarcel	  {
1070130803Smarcel	    p += 2;
1071130803Smarcel	    base = 16;
1072130803Smarcel	    len -= 2;
1073130803Smarcel	  }
1074130803Smarcel	break;
1075130803Smarcel
1076130803Smarcel      case 't':
1077130803Smarcel      case 'T':
1078130803Smarcel      case 'd':
1079130803Smarcel      case 'D':
1080130803Smarcel	if (len >= 3)
1081130803Smarcel	  {
1082130803Smarcel	    p += 2;
1083130803Smarcel	    base = 10;
1084130803Smarcel	    len -= 2;
1085130803Smarcel	  }
1086130803Smarcel	break;
1087130803Smarcel
1088130803Smarcel      default:
1089130803Smarcel	base = 8;
1090130803Smarcel	break;
1091130803Smarcel      }
1092130803Smarcel
1093130803Smarcel  while (len-- > 0)
1094130803Smarcel    {
1095130803Smarcel      c = *p++;
1096130803Smarcel      if (c >= 'A' && c <= 'Z')
1097130803Smarcel	c += 'a' - 'A';
1098130803Smarcel      if (c != 'l' && c != 'u')
1099130803Smarcel	n *= base;
1100130803Smarcel      if (c >= '0' && c <= '9')
1101130803Smarcel	{
1102130803Smarcel	  if (found_suffix)
1103130803Smarcel	    return ERROR;
1104130803Smarcel	  n += i = c - '0';
1105130803Smarcel	}
1106130803Smarcel      else
1107130803Smarcel	{
1108130803Smarcel	  if (base > 10 && c >= 'a' && c <= 'f')
1109130803Smarcel	    {
1110130803Smarcel	      if (found_suffix)
1111130803Smarcel		return ERROR;
1112130803Smarcel	      n += i = c - 'a' + 10;
1113130803Smarcel	    }
1114130803Smarcel	  else if (c == 'l')
1115130803Smarcel	    {
1116130803Smarcel	      ++long_p;
1117130803Smarcel	      found_suffix = 1;
1118130803Smarcel	    }
1119130803Smarcel	  else if (c == 'u')
1120130803Smarcel	    {
1121130803Smarcel	      unsigned_p = 1;
1122130803Smarcel	      found_suffix = 1;
1123130803Smarcel	    }
1124130803Smarcel	  else
1125130803Smarcel	    return ERROR;	/* Char not a digit.  */
1126130803Smarcel	}
1127130803Smarcel      if (i >= base)
1128130803Smarcel	return ERROR;		/* Invalid digit in this base.  */
1129130803Smarcel
1130130803Smarcel      /* Portably test for overflow (only works for nonzero values, so
1131130803Smarcel	 make a second check for zero).  FIXME: Can't we just make n
1132130803Smarcel	 and prevn unsigned and avoid this?  */
1133130803Smarcel      if (c != 'l' && c != 'u' && (prevn >= n) && n != 0)
1134130803Smarcel	unsigned_p = 1;		/* Try something unsigned.  */
1135130803Smarcel
1136130803Smarcel      /* Portably test for unsigned overflow.
1137130803Smarcel	 FIXME: This check is wrong; for example it doesn't find
1138130803Smarcel	 overflow on 0x123456789 when LONGEST is 32 bits.  */
1139130803Smarcel      if (c != 'l' && c != 'u' && n != 0)
1140130803Smarcel	{
1141130803Smarcel	  if ((unsigned_p && (unsigned LONGEST) prevn >= (unsigned LONGEST) n))
1142130803Smarcel	    error ("Numeric constant too large.");
1143130803Smarcel	}
1144130803Smarcel      prevn = n;
1145130803Smarcel    }
1146130803Smarcel
1147130803Smarcel  /* An integer constant is an int, a long, or a long long.  An L
1148130803Smarcel     suffix forces it to be long; an LL suffix forces it to be long
1149130803Smarcel     long.  If not forced to a larger size, it gets the first type of
1150130803Smarcel     the above that it fits in.  To figure out whether it fits, we
1151130803Smarcel     shift it right and see whether anything remains.  Note that we
1152130803Smarcel     can't shift sizeof (LONGEST) * HOST_CHAR_BIT bits or more in one
1153130803Smarcel     operation, because many compilers will warn about such a shift
1154130803Smarcel     (which always produces a zero result).  Sometimes TARGET_INT_BIT
1155130803Smarcel     or TARGET_LONG_BIT will be that big, sometimes not.  To deal with
1156130803Smarcel     the case where it is we just always shift the value more than
1157130803Smarcel     once, with fewer bits each time.  */
1158130803Smarcel
1159130803Smarcel  un = (unsigned LONGEST)n >> 2;
1160130803Smarcel  if (long_p == 0
1161130803Smarcel      && (un >> (TARGET_INT_BIT - 2)) == 0)
1162130803Smarcel    {
1163130803Smarcel      high_bit = ((unsigned LONGEST)1) << (TARGET_INT_BIT-1);
1164130803Smarcel
1165130803Smarcel      /* A large decimal (not hex or octal) constant (between INT_MAX
1166130803Smarcel	 and UINT_MAX) is a long or unsigned long, according to ANSI,
1167130803Smarcel	 never an unsigned int, but this code treats it as unsigned
1168130803Smarcel	 int.  This probably should be fixed.  GCC gives a warning on
1169130803Smarcel	 such constants.  */
1170130803Smarcel
1171130803Smarcel      unsigned_type = builtin_type_unsigned_int;
1172130803Smarcel      signed_type = builtin_type_int;
1173130803Smarcel    }
1174130803Smarcel  else if (long_p <= 1
1175130803Smarcel	   && (un >> (TARGET_LONG_BIT - 2)) == 0)
1176130803Smarcel    {
1177130803Smarcel      high_bit = ((unsigned LONGEST)1) << (TARGET_LONG_BIT-1);
1178130803Smarcel      unsigned_type = builtin_type_unsigned_long;
1179130803Smarcel      signed_type = builtin_type_long;
1180130803Smarcel    }
1181130803Smarcel  else
1182130803Smarcel    {
1183130803Smarcel      high_bit = (((unsigned LONGEST)1)
1184130803Smarcel		  << (TARGET_LONG_LONG_BIT - 32 - 1)
1185130803Smarcel		  << 16
1186130803Smarcel		  << 16);
1187130803Smarcel      if (high_bit == 0)
1188130803Smarcel	/* A long long does not fit in a LONGEST.  */
1189130803Smarcel	high_bit =
1190130803Smarcel	  (unsigned LONGEST)1 << (sizeof (LONGEST) * HOST_CHAR_BIT - 1);
1191130803Smarcel      unsigned_type = builtin_type_unsigned_long_long;
1192130803Smarcel      signed_type = builtin_type_long_long;
1193130803Smarcel    }
1194130803Smarcel
1195130803Smarcel   putithere->typed_val_int.val = n;
1196130803Smarcel
1197130803Smarcel   /* If the high bit of the worked out type is set then this number
1198130803Smarcel      has to be unsigned.  */
1199130803Smarcel
1200130803Smarcel   if (unsigned_p || (n & high_bit))
1201130803Smarcel     {
1202130803Smarcel       putithere->typed_val_int.type = unsigned_type;
1203130803Smarcel     }
1204130803Smarcel   else
1205130803Smarcel     {
1206130803Smarcel       putithere->typed_val_int.type = signed_type;
1207130803Smarcel     }
1208130803Smarcel
1209130803Smarcel   return INT;
1210130803Smarcel}
1211130803Smarcel
1212130803Smarcelstruct token
1213130803Smarcel{
1214130803Smarcel  char *operator;
1215130803Smarcel  int token;
1216130803Smarcel  enum exp_opcode opcode;
1217130803Smarcel};
1218130803Smarcel
1219130803Smarcelstatic const struct token tokentab3[] =
1220130803Smarcel  {
1221130803Smarcel    {">>=", ASSIGN_MODIFY, BINOP_RSH},
1222130803Smarcel    {"<<=", ASSIGN_MODIFY, BINOP_LSH}
1223130803Smarcel  };
1224130803Smarcel
1225130803Smarcelstatic const struct token tokentab2[] =
1226130803Smarcel  {
1227130803Smarcel    {"+=", ASSIGN_MODIFY, BINOP_ADD},
1228130803Smarcel    {"-=", ASSIGN_MODIFY, BINOP_SUB},
1229130803Smarcel    {"*=", ASSIGN_MODIFY, BINOP_MUL},
1230130803Smarcel    {"/=", ASSIGN_MODIFY, BINOP_DIV},
1231130803Smarcel    {"%=", ASSIGN_MODIFY, BINOP_REM},
1232130803Smarcel    {"|=", ASSIGN_MODIFY, BINOP_BITWISE_IOR},
1233130803Smarcel    {"&=", ASSIGN_MODIFY, BINOP_BITWISE_AND},
1234130803Smarcel    {"^=", ASSIGN_MODIFY, BINOP_BITWISE_XOR},
1235130803Smarcel    {"++", INCREMENT, BINOP_END},
1236130803Smarcel    {"--", DECREMENT, BINOP_END},
1237130803Smarcel    {"->", ARROW, BINOP_END},
1238130803Smarcel    {"&&", ANDAND, BINOP_END},
1239130803Smarcel    {"||", OROR, BINOP_END},
1240130803Smarcel    {"::", COLONCOLON, BINOP_END},
1241130803Smarcel    {"<<", LSH, BINOP_END},
1242130803Smarcel    {">>", RSH, BINOP_END},
1243130803Smarcel    {"==", EQUAL, BINOP_END},
1244130803Smarcel    {"!=", NOTEQUAL, BINOP_END},
1245130803Smarcel    {"<=", LEQ, BINOP_END},
1246130803Smarcel    {">=", GEQ, BINOP_END}
1247130803Smarcel  };
1248130803Smarcel
1249130803Smarcel/* Read one token, getting characters through lexptr.  */
1250130803Smarcel
1251130803Smarcelstatic int
1252130803Smarcelyylex ()
1253130803Smarcel{
1254130803Smarcel  int c, tokchr;
1255130803Smarcel  int namelen;
1256130803Smarcel  unsigned int i;
1257130803Smarcel  char *tokstart;
1258130803Smarcel  char *tokptr;
1259130803Smarcel  int tempbufindex;
1260130803Smarcel  static char *tempbuf;
1261130803Smarcel  static int tempbufsize;
1262130803Smarcel
1263130803Smarcel retry:
1264130803Smarcel
1265130803Smarcel  tokstart = lexptr;
1266130803Smarcel  /* See if it is a special token of length 3.  */
1267130803Smarcel  for (i = 0; i < sizeof tokentab3 / sizeof tokentab3[0]; i++)
1268130803Smarcel    if (DEPRECATED_STREQN (tokstart, tokentab3[i].operator, 3))
1269130803Smarcel      {
1270130803Smarcel	lexptr += 3;
1271130803Smarcel	yylval.opcode = tokentab3[i].opcode;
1272130803Smarcel	return tokentab3[i].token;
1273130803Smarcel      }
1274130803Smarcel
1275130803Smarcel  /* See if it is a special token of length 2.  */
1276130803Smarcel  for (i = 0; i < sizeof tokentab2 / sizeof tokentab2[0]; i++)
1277130803Smarcel    if (DEPRECATED_STREQN (tokstart, tokentab2[i].operator, 2))
1278130803Smarcel      {
1279130803Smarcel	lexptr += 2;
1280130803Smarcel	yylval.opcode = tokentab2[i].opcode;
1281130803Smarcel	return tokentab2[i].token;
1282130803Smarcel      }
1283130803Smarcel
1284130803Smarcel  c = 0;
1285130803Smarcel  switch (tokchr = *tokstart)
1286130803Smarcel    {
1287130803Smarcel    case 0:
1288130803Smarcel      return 0;
1289130803Smarcel
1290130803Smarcel    case ' ':
1291130803Smarcel    case '\t':
1292130803Smarcel    case '\n':
1293130803Smarcel      lexptr++;
1294130803Smarcel      goto retry;
1295130803Smarcel
1296130803Smarcel    case '\'':
1297130803Smarcel      /* We either have a character constant ('0' or '\177' for
1298130803Smarcel	 example) or we have a quoted symbol reference ('foo(int,int)'
1299130803Smarcel	 in C++ for example).  */
1300130803Smarcel      lexptr++;
1301130803Smarcel      c = *lexptr++;
1302130803Smarcel      if (c == '\\')
1303130803Smarcel	c = parse_escape (&lexptr);
1304130803Smarcel      else if (c == '\'')
1305130803Smarcel	error ("Empty character constant.");
1306130803Smarcel
1307130803Smarcel      yylval.typed_val_int.val = c;
1308130803Smarcel      yylval.typed_val_int.type = builtin_type_char;
1309130803Smarcel
1310130803Smarcel      c = *lexptr++;
1311130803Smarcel      if (c != '\'')
1312130803Smarcel	{
1313130803Smarcel	  namelen = skip_quoted (tokstart) - tokstart;
1314130803Smarcel	  if (namelen > 2)
1315130803Smarcel	    {
1316130803Smarcel	      lexptr = tokstart + namelen;
1317130803Smarcel	      if (lexptr[-1] != '\'')
1318130803Smarcel		error ("Unmatched single quote.");
1319130803Smarcel	      namelen -= 2;
1320130803Smarcel	      tokstart++;
1321130803Smarcel	      goto tryname;
1322130803Smarcel	    }
1323130803Smarcel	  error ("Invalid character constant.");
1324130803Smarcel	}
1325130803Smarcel      return INT;
1326130803Smarcel
1327130803Smarcel    case '(':
1328130803Smarcel      paren_depth++;
1329130803Smarcel      lexptr++;
1330130803Smarcel      return '(';
1331130803Smarcel
1332130803Smarcel    case ')':
1333130803Smarcel      if (paren_depth == 0)
1334130803Smarcel	return 0;
1335130803Smarcel      paren_depth--;
1336130803Smarcel      lexptr++;
1337130803Smarcel      return ')';
1338130803Smarcel
1339130803Smarcel    case ',':
1340130803Smarcel      if (comma_terminates && paren_depth == 0)
1341130803Smarcel	return 0;
1342130803Smarcel      lexptr++;
1343130803Smarcel      return ',';
1344130803Smarcel
1345130803Smarcel    case '.':
1346130803Smarcel      /* Might be a floating point number.  */
1347130803Smarcel      if (lexptr[1] < '0' || lexptr[1] > '9')
1348130803Smarcel	goto symbol;		/* Nope, must be a symbol.  */
1349130803Smarcel      /* FALL THRU into number case.  */
1350130803Smarcel
1351130803Smarcel    case '0':
1352130803Smarcel    case '1':
1353130803Smarcel    case '2':
1354130803Smarcel    case '3':
1355130803Smarcel    case '4':
1356130803Smarcel    case '5':
1357130803Smarcel    case '6':
1358130803Smarcel    case '7':
1359130803Smarcel    case '8':
1360130803Smarcel    case '9':
1361130803Smarcel      {
1362130803Smarcel	/* It's a number.  */
1363130803Smarcel	int got_dot = 0, got_e = 0, toktype = FLOAT;
1364130803Smarcel	/* Initialize toktype to anything other than ERROR.  */
1365130803Smarcel	char *p = tokstart;
1366130803Smarcel	int hex = input_radix > 10;
1367130803Smarcel	int local_radix = input_radix;
1368130803Smarcel	if (tokchr == '0' && (p[1] == 'x' || p[1] == 'X'))
1369130803Smarcel	  {
1370130803Smarcel	    p += 2;
1371130803Smarcel	    hex = 1;
1372130803Smarcel	    local_radix = 16;
1373130803Smarcel	  }
1374130803Smarcel	else if (tokchr == '0' && (p[1]=='t' || p[1]=='T' || p[1]=='d' || p[1]=='D'))
1375130803Smarcel	  {
1376130803Smarcel	    p += 2;
1377130803Smarcel	    hex = 0;
1378130803Smarcel	    local_radix = 10;
1379130803Smarcel	  }
1380130803Smarcel
1381130803Smarcel	for (;; ++p)
1382130803Smarcel	  {
1383130803Smarcel	    /* This test includes !hex because 'e' is a valid hex digit
1384130803Smarcel	       and thus does not indicate a floating point number when
1385130803Smarcel	       the radix is hex.  */
1386130803Smarcel
1387130803Smarcel	    if (!hex && (*p == 'e' || *p == 'E'))
1388130803Smarcel	      if (got_e)
1389130803Smarcel		toktype = ERROR;	/* Only one 'e' in a float.  */
1390130803Smarcel	      else
1391130803Smarcel		got_e = 1;
1392130803Smarcel	    /* This test does not include !hex, because a '.' always
1393130803Smarcel	       indicates a decimal floating point number regardless of
1394130803Smarcel	       the radix.  */
1395130803Smarcel	    else if (*p == '.')
1396130803Smarcel	      if (got_dot)
1397130803Smarcel		toktype = ERROR;	/* Only one '.' in a float.  */
1398130803Smarcel	      else
1399130803Smarcel		got_dot = 1;
1400130803Smarcel	    else if (got_e && (p[-1] == 'e' || p[-1] == 'E') &&
1401130803Smarcel		    (*p == '-' || *p == '+'))
1402130803Smarcel	      /* This is the sign of the exponent, not the end of the
1403130803Smarcel		 number.  */
1404130803Smarcel	      continue;
1405130803Smarcel	    /* Always take decimal digits; parse_number handles radix
1406130803Smarcel               error.  */
1407130803Smarcel	    else if (*p >= '0' && *p <= '9')
1408130803Smarcel	      continue;
1409130803Smarcel	    /* We will take letters only if hex is true, and only up
1410130803Smarcel	       to what the input radix would permit.  FSF was content
1411130803Smarcel	       to rely on parse_number to validate; but it leaks.  */
1412130803Smarcel	    else if (*p >= 'a' && *p <= 'z')
1413130803Smarcel	      {
1414130803Smarcel		if (!hex || *p >= ('a' + local_radix - 10))
1415130803Smarcel		  toktype = ERROR;
1416130803Smarcel	      }
1417130803Smarcel	    else if (*p >= 'A' && *p <= 'Z')
1418130803Smarcel	      {
1419130803Smarcel		if (!hex || *p >= ('A' + local_radix - 10))
1420130803Smarcel		  toktype = ERROR;
1421130803Smarcel	      }
1422130803Smarcel	    else break;
1423130803Smarcel	  }
1424130803Smarcel	if (toktype != ERROR)
1425130803Smarcel	  toktype = parse_number (tokstart, p - tokstart,
1426130803Smarcel				  got_dot | got_e, &yylval);
1427130803Smarcel        if (toktype == ERROR)
1428130803Smarcel	  {
1429130803Smarcel	    char *err_copy = (char *) alloca (p - tokstart + 1);
1430130803Smarcel
1431130803Smarcel	    memcpy (err_copy, tokstart, p - tokstart);
1432130803Smarcel	    err_copy[p - tokstart] = 0;
1433130803Smarcel	    error ("Invalid number \"%s\".", err_copy);
1434130803Smarcel	  }
1435130803Smarcel	lexptr = p;
1436130803Smarcel	return toktype;
1437130803Smarcel      }
1438130803Smarcel
1439130803Smarcel    case '+':
1440130803Smarcel    case '-':
1441130803Smarcel    case '*':
1442130803Smarcel    case '/':
1443130803Smarcel    case '%':
1444130803Smarcel    case '|':
1445130803Smarcel    case '&':
1446130803Smarcel    case '^':
1447130803Smarcel    case '~':
1448130803Smarcel    case '!':
1449130803Smarcel#if 0
1450130803Smarcel    case '@':		/* Moved out below.  */
1451130803Smarcel#endif
1452130803Smarcel    case '<':
1453130803Smarcel    case '>':
1454130803Smarcel    case '[':
1455130803Smarcel    case ']':
1456130803Smarcel    case '?':
1457130803Smarcel    case ':':
1458130803Smarcel    case '=':
1459130803Smarcel    case '{':
1460130803Smarcel    case '}':
1461130803Smarcel    symbol:
1462130803Smarcel      lexptr++;
1463130803Smarcel      return tokchr;
1464130803Smarcel
1465130803Smarcel    case '@':
1466130803Smarcel      if (strncmp(tokstart, "@selector", 9) == 0)
1467130803Smarcel	{
1468130803Smarcel	  tokptr = strchr(tokstart, '(');
1469130803Smarcel	  if (tokptr == NULL)
1470130803Smarcel	    {
1471130803Smarcel	      error ("Missing '(' in @selector(...)");
1472130803Smarcel	    }
1473130803Smarcel	  tempbufindex = 0;
1474130803Smarcel	  tokptr++;	/* Skip the '('.  */
1475130803Smarcel	  do {
1476130803Smarcel	    /* Grow the static temp buffer if necessary, including
1477130803Smarcel	       allocating the first one on demand.  */
1478130803Smarcel	    if (tempbufindex + 1 >= tempbufsize)
1479130803Smarcel	      {
1480130803Smarcel		tempbuf = (char *) realloc (tempbuf, tempbufsize += 64);
1481130803Smarcel	      }
1482130803Smarcel	    tempbuf[tempbufindex++] = *tokptr++;
1483130803Smarcel	  } while ((*tokptr != ')') && (*tokptr != '\0'));
1484130803Smarcel	  if (*tokptr++ != ')')
1485130803Smarcel	    {
1486130803Smarcel	      error ("Missing ')' in @selector(...)");
1487130803Smarcel	    }
1488130803Smarcel	  tempbuf[tempbufindex] = '\0';
1489130803Smarcel	  yylval.sval.ptr = tempbuf;
1490130803Smarcel	  yylval.sval.length = tempbufindex;
1491130803Smarcel	  lexptr = tokptr;
1492130803Smarcel	  return SELECTOR;
1493130803Smarcel	}
1494130803Smarcel      if (tokstart[1] != '"')
1495130803Smarcel        {
1496130803Smarcel          lexptr++;
1497130803Smarcel          return tokchr;
1498130803Smarcel        }
1499130803Smarcel      /* ObjC NextStep NSString constant: fall thru and parse like
1500130803Smarcel         STRING.  */
1501130803Smarcel      tokstart++;
1502130803Smarcel
1503130803Smarcel    case '"':
1504130803Smarcel
1505130803Smarcel      /* Build the gdb internal form of the input string in tempbuf,
1506130803Smarcel	 translating any standard C escape forms seen.  Note that the
1507130803Smarcel	 buffer is null byte terminated *only* for the convenience of
1508130803Smarcel	 debugging gdb itself and printing the buffer contents when
1509130803Smarcel	 the buffer contains no embedded nulls.  Gdb does not depend
1510130803Smarcel	 upon the buffer being null byte terminated, it uses the
1511130803Smarcel	 length string instead.  This allows gdb to handle C strings
1512130803Smarcel	 (as well as strings in other languages) with embedded null
1513130803Smarcel	 bytes.  */
1514130803Smarcel
1515130803Smarcel      tokptr = ++tokstart;
1516130803Smarcel      tempbufindex = 0;
1517130803Smarcel
1518130803Smarcel      do {
1519130803Smarcel	/* Grow the static temp buffer if necessary, including
1520130803Smarcel	   allocating the first one on demand.  */
1521130803Smarcel	if (tempbufindex + 1 >= tempbufsize)
1522130803Smarcel	  {
1523130803Smarcel	    tempbuf = (char *) realloc (tempbuf, tempbufsize += 64);
1524130803Smarcel	  }
1525130803Smarcel	switch (*tokptr)
1526130803Smarcel	  {
1527130803Smarcel	  case '\0':
1528130803Smarcel	  case '"':
1529130803Smarcel	    /* Do nothing, loop will terminate.  */
1530130803Smarcel	    break;
1531130803Smarcel	  case '\\':
1532130803Smarcel	    tokptr++;
1533130803Smarcel	    c = parse_escape (&tokptr);
1534130803Smarcel	    if (c == -1)
1535130803Smarcel	      {
1536130803Smarcel		continue;
1537130803Smarcel	      }
1538130803Smarcel	    tempbuf[tempbufindex++] = c;
1539130803Smarcel	    break;
1540130803Smarcel	  default:
1541130803Smarcel	    tempbuf[tempbufindex++] = *tokptr++;
1542130803Smarcel	    break;
1543130803Smarcel	  }
1544130803Smarcel      } while ((*tokptr != '"') && (*tokptr != '\0'));
1545130803Smarcel      if (*tokptr++ != '"')
1546130803Smarcel	{
1547130803Smarcel	  error ("Unterminated string in expression.");
1548130803Smarcel	}
1549130803Smarcel      tempbuf[tempbufindex] = '\0';	/* See note above.  */
1550130803Smarcel      yylval.sval.ptr = tempbuf;
1551130803Smarcel      yylval.sval.length = tempbufindex;
1552130803Smarcel      lexptr = tokptr;
1553130803Smarcel      return (tokchr == '@' ? NSSTRING : STRING);
1554130803Smarcel    }
1555130803Smarcel
1556130803Smarcel  if (!(tokchr == '_' || tokchr == '$' ||
1557130803Smarcel       (tokchr >= 'a' && tokchr <= 'z') || (tokchr >= 'A' && tokchr <= 'Z')))
1558130803Smarcel    /* We must have come across a bad character (e.g. ';').  */
1559130803Smarcel    error ("Invalid character '%c' in expression.", c);
1560130803Smarcel
1561130803Smarcel  /* It's a name.  See how long it is.  */
1562130803Smarcel  namelen = 0;
1563130803Smarcel  for (c = tokstart[namelen];
1564130803Smarcel       (c == '_' || c == '$' || (c >= '0' && c <= '9')
1565130803Smarcel	|| (c >= 'a' && c <= 'z') || (c >= 'A' && c <= 'Z') || c == '<');)
1566130803Smarcel    {
1567130803Smarcel       if (c == '<')
1568130803Smarcel	 {
1569130803Smarcel	   int i = namelen;
1570130803Smarcel	   while (tokstart[++i] && tokstart[i] != '>');
1571130803Smarcel	   if (tokstart[i] == '>')
1572130803Smarcel	     namelen = i;
1573130803Smarcel	  }
1574130803Smarcel       c = tokstart[++namelen];
1575130803Smarcel     }
1576130803Smarcel
1577130803Smarcel  /* The token "if" terminates the expression and is NOT
1578130803Smarcel     removed from the input stream.  */
1579130803Smarcel  if (namelen == 2 && tokstart[0] == 'i' && tokstart[1] == 'f')
1580130803Smarcel    {
1581130803Smarcel      return 0;
1582130803Smarcel    }
1583130803Smarcel
1584130803Smarcel  lexptr += namelen;
1585130803Smarcel
1586130803Smarcel  tryname:
1587130803Smarcel
1588130803Smarcel  /* Catch specific keywords.  Should be done with a data structure.  */
1589130803Smarcel  switch (namelen)
1590130803Smarcel    {
1591130803Smarcel    case 8:
1592130803Smarcel      if (DEPRECATED_STREQN (tokstart, "unsigned", 8))
1593130803Smarcel	return UNSIGNED;
1594130803Smarcel      if (current_language->la_language == language_cplus
1595130803Smarcel	  && strncmp (tokstart, "template", 8) == 0)
1596130803Smarcel	return TEMPLATE;
1597130803Smarcel      if (DEPRECATED_STREQN (tokstart, "volatile", 8))
1598130803Smarcel	return VOLATILE_KEYWORD;
1599130803Smarcel      break;
1600130803Smarcel    case 6:
1601130803Smarcel      if (DEPRECATED_STREQN (tokstart, "struct", 6))
1602130803Smarcel	return STRUCT;
1603130803Smarcel      if (DEPRECATED_STREQN (tokstart, "signed", 6))
1604130803Smarcel	return SIGNED_KEYWORD;
1605130803Smarcel      if (DEPRECATED_STREQN (tokstart, "sizeof", 6))
1606130803Smarcel	return SIZEOF;
1607130803Smarcel      if (DEPRECATED_STREQN (tokstart, "double", 6))
1608130803Smarcel	return DOUBLE_KEYWORD;
1609130803Smarcel      break;
1610130803Smarcel    case 5:
1611130803Smarcel      if ((current_language->la_language == language_cplus)
1612130803Smarcel	  && strncmp (tokstart, "class", 5) == 0)
1613130803Smarcel	return CLASS;
1614130803Smarcel      if (DEPRECATED_STREQN (tokstart, "union", 5))
1615130803Smarcel	return UNION;
1616130803Smarcel      if (DEPRECATED_STREQN (tokstart, "short", 5))
1617130803Smarcel	return SHORT;
1618130803Smarcel      if (DEPRECATED_STREQN (tokstart, "const", 5))
1619130803Smarcel	return CONST_KEYWORD;
1620130803Smarcel      break;
1621130803Smarcel    case 4:
1622130803Smarcel      if (DEPRECATED_STREQN (tokstart, "enum", 4))
1623130803Smarcel	return ENUM;
1624130803Smarcel      if (DEPRECATED_STREQN (tokstart, "long", 4))
1625130803Smarcel	return LONG;
1626130803Smarcel      break;
1627130803Smarcel    case 3:
1628130803Smarcel      if (DEPRECATED_STREQN (tokstart, "int", 3))
1629130803Smarcel	return INT_KEYWORD;
1630130803Smarcel      break;
1631130803Smarcel    default:
1632130803Smarcel      break;
1633130803Smarcel    }
1634130803Smarcel
1635130803Smarcel  yylval.sval.ptr = tokstart;
1636130803Smarcel  yylval.sval.length = namelen;
1637130803Smarcel
1638130803Smarcel  if (*tokstart == '$')
1639130803Smarcel    {
1640130803Smarcel      write_dollar_variable (yylval.sval);
1641130803Smarcel      return VARIABLE;
1642130803Smarcel    }
1643130803Smarcel
1644130803Smarcel  /* Use token-type BLOCKNAME for symbols that happen to be defined as
1645130803Smarcel     functions or symtabs.  If this is not so, then ...
1646130803Smarcel     Use token-type TYPENAME for symbols that happen to be defined
1647130803Smarcel     currently as names of types; NAME for other symbols.
1648130803Smarcel     The caller is not constrained to care about the distinction.  */
1649130803Smarcel  {
1650130803Smarcel    char *tmp = copy_name (yylval.sval);
1651130803Smarcel    struct symbol *sym;
1652130803Smarcel    int is_a_field_of_this = 0, *need_this;
1653130803Smarcel    int hextype;
1654130803Smarcel
1655130803Smarcel    if (current_language->la_language == language_cplus ||
1656130803Smarcel	current_language->la_language == language_objc)
1657130803Smarcel      need_this = &is_a_field_of_this;
1658130803Smarcel    else
1659130803Smarcel      need_this = (int *) NULL;
1660130803Smarcel
1661130803Smarcel    sym = lookup_symbol (tmp, expression_context_block,
1662130803Smarcel			 VAR_DOMAIN,
1663130803Smarcel			 need_this,
1664130803Smarcel			 (struct symtab **) NULL);
1665130803Smarcel    /* Call lookup_symtab, not lookup_partial_symtab, in case there
1666130803Smarcel       are no psymtabs (coff, xcoff, or some future change to blow
1667130803Smarcel       away the psymtabs once symbols are read).  */
1668130803Smarcel    if ((sym && SYMBOL_CLASS (sym) == LOC_BLOCK) ||
1669130803Smarcel        lookup_symtab (tmp))
1670130803Smarcel      {
1671130803Smarcel	yylval.ssym.sym = sym;
1672130803Smarcel	yylval.ssym.is_a_field_of_this = is_a_field_of_this;
1673130803Smarcel	return BLOCKNAME;
1674130803Smarcel      }
1675130803Smarcel    if (sym && SYMBOL_CLASS (sym) == LOC_TYPEDEF)
1676130803Smarcel        {
1677130803Smarcel#if 1
1678130803Smarcel	  /* Despite the following flaw, we need to keep this code
1679130803Smarcel	     enabled.  Because we can get called from
1680130803Smarcel	     check_stub_method, if we don't handle nested types then
1681130803Smarcel	     it screws many operations in any program which uses
1682130803Smarcel	     nested types.  */
1683130803Smarcel	  /* In "A::x", if x is a member function of A and there
1684130803Smarcel	     happens to be a type (nested or not, since the stabs
1685130803Smarcel	     don't make that distinction) named x, then this code
1686130803Smarcel	     incorrectly thinks we are dealing with nested types
1687130803Smarcel	     rather than a member function.  */
1688130803Smarcel
1689130803Smarcel	  char *p;
1690130803Smarcel	  char *namestart;
1691130803Smarcel	  struct symbol *best_sym;
1692130803Smarcel
1693130803Smarcel	  /* Look ahead to detect nested types.  This probably should
1694130803Smarcel	     be done in the grammar, but trying seemed to introduce a
1695130803Smarcel	     lot of shift/reduce and reduce/reduce conflicts.  It's
1696130803Smarcel	     possible that it could be done, though.  Or perhaps a
1697130803Smarcel	     non-grammar, but less ad hoc, approach would work well.  */
1698130803Smarcel
1699130803Smarcel	  /* Since we do not currently have any way of distinguishing
1700130803Smarcel	     a nested type from a non-nested one (the stabs don't tell
1701130803Smarcel	     us whether a type is nested), we just ignore the
1702130803Smarcel	     containing type.  */
1703130803Smarcel
1704130803Smarcel	  p = lexptr;
1705130803Smarcel	  best_sym = sym;
1706130803Smarcel	  while (1)
1707130803Smarcel	    {
1708130803Smarcel	      /* Skip whitespace.  */
1709130803Smarcel	      while (*p == ' ' || *p == '\t' || *p == '\n')
1710130803Smarcel		++p;
1711130803Smarcel	      if (*p == ':' && p[1] == ':')
1712130803Smarcel		{
1713130803Smarcel		  /* Skip the `::'.  */
1714130803Smarcel		  p += 2;
1715130803Smarcel		  /* Skip whitespace.  */
1716130803Smarcel		  while (*p == ' ' || *p == '\t' || *p == '\n')
1717130803Smarcel		    ++p;
1718130803Smarcel		  namestart = p;
1719130803Smarcel		  while (*p == '_' || *p == '$' || (*p >= '0' && *p <= '9')
1720130803Smarcel			 || (*p >= 'a' && *p <= 'z')
1721130803Smarcel			 || (*p >= 'A' && *p <= 'Z'))
1722130803Smarcel		    ++p;
1723130803Smarcel		  if (p != namestart)
1724130803Smarcel		    {
1725130803Smarcel		      struct symbol *cur_sym;
1726130803Smarcel		      /* As big as the whole rest of the expression,
1727130803Smarcel			 which is at least big enough.  */
1728130803Smarcel		      char *ncopy = alloca (strlen (tmp) +
1729130803Smarcel					    strlen (namestart) + 3);
1730130803Smarcel		      char *tmp1;
1731130803Smarcel
1732130803Smarcel		      tmp1 = ncopy;
1733130803Smarcel		      memcpy (tmp1, tmp, strlen (tmp));
1734130803Smarcel		      tmp1 += strlen (tmp);
1735130803Smarcel		      memcpy (tmp1, "::", 2);
1736130803Smarcel		      tmp1 += 2;
1737130803Smarcel		      memcpy (tmp1, namestart, p - namestart);
1738130803Smarcel		      tmp1[p - namestart] = '\0';
1739130803Smarcel		      cur_sym = lookup_symbol (ncopy,
1740130803Smarcel					       expression_context_block,
1741130803Smarcel					       VAR_DOMAIN, (int *) NULL,
1742130803Smarcel					       (struct symtab **) NULL);
1743130803Smarcel		      if (cur_sym)
1744130803Smarcel			{
1745130803Smarcel			  if (SYMBOL_CLASS (cur_sym) == LOC_TYPEDEF)
1746130803Smarcel			    {
1747130803Smarcel			      best_sym = cur_sym;
1748130803Smarcel			      lexptr = p;
1749130803Smarcel			    }
1750130803Smarcel			  else
1751130803Smarcel			    break;
1752130803Smarcel			}
1753130803Smarcel		      else
1754130803Smarcel			break;
1755130803Smarcel		    }
1756130803Smarcel		  else
1757130803Smarcel		    break;
1758130803Smarcel		}
1759130803Smarcel	      else
1760130803Smarcel		break;
1761130803Smarcel	    }
1762130803Smarcel
1763130803Smarcel	  yylval.tsym.type = SYMBOL_TYPE (best_sym);
1764130803Smarcel#else /* not 0 */
1765130803Smarcel	  yylval.tsym.type = SYMBOL_TYPE (sym);
1766130803Smarcel#endif /* not 0 */
1767130803Smarcel	  return TYPENAME;
1768130803Smarcel        }
1769130803Smarcel    if ((yylval.tsym.type = lookup_primitive_typename (tmp)) != 0)
1770130803Smarcel	return TYPENAME;
1771130803Smarcel
1772130803Smarcel    /* See if it's an ObjC classname.  */
1773130803Smarcel    if (!sym)
1774130803Smarcel      {
1775130803Smarcel	CORE_ADDR Class = lookup_objc_class(tmp);
1776130803Smarcel	if (Class)
1777130803Smarcel	  {
1778130803Smarcel	    yylval.class.class = Class;
1779130803Smarcel	    if ((sym = lookup_struct_typedef (tmp,
1780130803Smarcel					      expression_context_block,
1781130803Smarcel					      1)))
1782130803Smarcel	      yylval.class.type = SYMBOL_TYPE (sym);
1783130803Smarcel	    return CLASSNAME;
1784130803Smarcel	  }
1785130803Smarcel      }
1786130803Smarcel
1787130803Smarcel    /* Input names that aren't symbols but ARE valid hex numbers,
1788130803Smarcel       when the input radix permits them, can be names or numbers
1789130803Smarcel       depending on the parse.  Note we support radixes > 16 here.  */
1790130803Smarcel    if (!sym &&
1791130803Smarcel        ((tokstart[0] >= 'a' && tokstart[0] < 'a' + input_radix - 10) ||
1792130803Smarcel         (tokstart[0] >= 'A' && tokstart[0] < 'A' + input_radix - 10)))
1793130803Smarcel      {
1794130803Smarcel 	YYSTYPE newlval;	/* Its value is ignored.  */
1795130803Smarcel	hextype = parse_number (tokstart, namelen, 0, &newlval);
1796130803Smarcel	if (hextype == INT)
1797130803Smarcel	  {
1798130803Smarcel	    yylval.ssym.sym = sym;
1799130803Smarcel	    yylval.ssym.is_a_field_of_this = is_a_field_of_this;
1800130803Smarcel	    return NAME_OR_INT;
1801130803Smarcel	  }
1802130803Smarcel      }
1803130803Smarcel
1804130803Smarcel    /* Any other kind of symbol.  */
1805130803Smarcel    yylval.ssym.sym = sym;
1806130803Smarcel    yylval.ssym.is_a_field_of_this = is_a_field_of_this;
1807130803Smarcel    return NAME;
1808130803Smarcel  }
1809130803Smarcel}
1810130803Smarcel
1811130803Smarcelvoid
1812130803Smarcelyyerror (msg)
1813130803Smarcel     char *msg;
1814130803Smarcel{
1815130803Smarcel  if (*lexptr == '\0')
1816130803Smarcel    error("A %s near end of expression.",  (msg ? msg : "error"));
1817130803Smarcel  else
1818130803Smarcel    error ("A %s in expression, near `%s'.", (msg ? msg : "error"),
1819130803Smarcel	   lexptr);
1820130803Smarcel}
1821