1215976Sjmallett/* YACC parser for C expressions, for GDB.
2232812Sjmallett   Copyright 1986, 1989, 1990, 1991, 1992, 1993, 1994, 1995, 1996, 1997,
3215976Sjmallett   1998, 1999, 2000, 2003, 2004
4215976Sjmallett   Free Software Foundation, Inc.
5215976Sjmallett
6215976SjmallettThis file is part of GDB.
7215976Sjmallett
8215976SjmallettThis program is free software; you can redistribute it and/or modify
9215976Sjmallettit under the terms of the GNU General Public License as published by
10215976Sjmallettthe Free Software Foundation; either version 2 of the License, or
11215976Sjmallett(at your option) any later version.
12215976Sjmallett
13215976SjmallettThis program is distributed in the hope that it will be useful,
14215976Sjmallettbut WITHOUT ANY WARRANTY; without even the implied warranty of
15215976SjmallettMERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE.  See the
16215976SjmallettGNU General Public License for more details.
17215976Sjmallett
18232812SjmallettYou should have received a copy of the GNU General Public License
19215976Sjmallettalong with this program; if not, write to the Free Software
20215976SjmallettFoundation, Inc., 59 Temple Place - Suite 330, Boston, MA 02111-1307, USA.  */
21215976Sjmallett
22215976Sjmallett/* Parse a C expression from text in a string,
23215976Sjmallett   and return the result as a  struct expression  pointer.
24215976Sjmallett   That structure contains arithmetic operations in reverse polish,
25215976Sjmallett   with constants represented by operations that are followed by special data.
26215976Sjmallett   See expression.h for the details of the format.
27215976Sjmallett   What is important here is that it can be built up sequentially
28215976Sjmallett   during the process of parsing; the lower levels of the tree always
29232812Sjmallett   come first in the result.
30215976Sjmallett
31215976Sjmallett   Note that malloc's and realloc's in this file are transformed to
32215976Sjmallett   xmalloc and xrealloc respectively by the same sed command in the
33215976Sjmallett   makefile that remaps any other malloc/realloc inserted by the parser
34215976Sjmallett   generator.  Doing this with #defines and trying to control the interaction
35215976Sjmallett   with include files (<malloc.h> and <stdlib.h> for example) just became
36215976Sjmallett   too messy, particularly when such includes can be inserted at random
37215976Sjmallett   times by the parser generator.  */
38215976Sjmallett
39215976Sjmallett%{
40215976Sjmallett
41215976Sjmallett#include "defs.h"
42215976Sjmallett#include "gdb_string.h"
43215976Sjmallett#include <ctype.h>
44215976Sjmallett#include "expression.h"
45215976Sjmallett#include "value.h"
46215976Sjmallett#include "parser-defs.h"
47215976Sjmallett#include "language.h"
48215976Sjmallett#include "c-lang.h"
49215976Sjmallett#include "bfd.h" /* Required by objfiles.h.  */
50215976Sjmallett#include "symfile.h" /* Required by objfiles.h.  */
51215976Sjmallett#include "objfiles.h" /* For have_full_symbols and have_partial_symbols */
52232812Sjmallett#include "charset.h"
53232812Sjmallett#include "block.h"
54215976Sjmallett#include "cp-support.h"
55215976Sjmallett
56215976Sjmallett/* Flag indicating we're dealing with HP-compiled objects */
57215976Sjmallettextern int hp_som_som_object_present;
58215976Sjmallett
59215976Sjmallett/* Remap normal yacc parser interface names (yyparse, yylex, yyerror, etc),
60215976Sjmallett   as well as gratuitiously global symbol names, so we can have multiple
61215976Sjmallett   yacc generated parsers in gdb.  Note that these are only the variables
62215976Sjmallett   produced by yacc.  If other parser generators (bison, byacc, etc) produce
63215976Sjmallett   additional global names that conflict at link time, then those parser
64215976Sjmallett   generators need to be fixed instead of adding those names to this list. */
65215976Sjmallett
66215976Sjmallett#define	yymaxdepth c_maxdepth
67215976Sjmallett#define	yyparse	c_parse
68215976Sjmallett#define	yylex	c_lex
69215976Sjmallett#define	yyerror	c_error
70215976Sjmallett#define	yylval	c_lval
71215976Sjmallett#define	yychar	c_char
72215976Sjmallett#define	yydebug	c_debug
73215976Sjmallett#define	yypact	c_pact
74215976Sjmallett#define	yyr1	c_r1
75215976Sjmallett#define	yyr2	c_r2
76215976Sjmallett#define	yydef	c_def
77215976Sjmallett#define	yychk	c_chk
78215976Sjmallett#define	yypgo	c_pgo
79215976Sjmallett#define	yyact	c_act
80215976Sjmallett#define	yyexca	c_exca
81215976Sjmallett#define yyerrflag c_errflag
82215976Sjmallett#define yynerrs	c_nerrs
83215976Sjmallett#define	yyps	c_ps
84215976Sjmallett#define	yypv	c_pv
85215976Sjmallett#define	yys	c_s
86215976Sjmallett#define	yy_yys	c_yys
87215976Sjmallett#define	yystate	c_state
88215976Sjmallett#define	yytmp	c_tmp
89215976Sjmallett#define	yyv	c_v
90215976Sjmallett#define	yy_yyv	c_yyv
91215976Sjmallett#define	yyval	c_val
92215976Sjmallett#define	yylloc	c_lloc
93215976Sjmallett#define yyreds	c_reds		/* With YYDEBUG defined */
94215976Sjmallett#define yytoks	c_toks		/* With YYDEBUG defined */
95215976Sjmallett#define yyname	c_name		/* With YYDEBUG defined */
96215976Sjmallett#define yyrule	c_rule		/* With YYDEBUG defined */
97215976Sjmallett#define yylhs	c_yylhs
98215976Sjmallett#define yylen	c_yylen
99215976Sjmallett#define yydefred c_yydefred
100215976Sjmallett#define yydgoto	c_yydgoto
101215976Sjmallett#define yysindex c_yysindex
102215976Sjmallett#define yyrindex c_yyrindex
103215976Sjmallett#define yygindex c_yygindex
104215976Sjmallett#define yytable	 c_yytable
105215976Sjmallett#define yycheck	 c_yycheck
106215976Sjmallett
107215976Sjmallett#ifndef YYDEBUG
108215976Sjmallett#define	YYDEBUG 1		/* Default to yydebug support */
109215976Sjmallett#endif
110215976Sjmallett
111215976Sjmallett#define YYFPRINTF parser_fprintf
112215976Sjmallett
113215976Sjmallettint yyparse (void);
114215976Sjmallett
115215976Sjmallettstatic int yylex (void);
116215976Sjmallett
117215976Sjmallettvoid yyerror (char *);
118215976Sjmallett
119215976Sjmallett%}
120215976Sjmallett
121215976Sjmallett/* Although the yacc "value" of an expression is not used,
122215976Sjmallett   since the result is stored in the structure being created,
123215976Sjmallett   other node types do have values.  */
124215976Sjmallett
125215976Sjmallett%union
126215976Sjmallett  {
127215976Sjmallett    LONGEST lval;
128215976Sjmallett    struct {
129215976Sjmallett      LONGEST val;
130215976Sjmallett      struct type *type;
131215976Sjmallett    } typed_val_int;
132215976Sjmallett    struct {
133215976Sjmallett      DOUBLEST dval;
134215976Sjmallett      struct type *type;
135215976Sjmallett    } typed_val_float;
136215976Sjmallett    struct symbol *sym;
137215976Sjmallett    struct type *tval;
138215976Sjmallett    struct stoken sval;
139215976Sjmallett    struct ttype tsym;
140215976Sjmallett    struct symtoken ssym;
141215976Sjmallett    int voidval;
142215976Sjmallett    struct block *bval;
143215976Sjmallett    enum exp_opcode opcode;
144215976Sjmallett    struct internalvar *ivar;
145215976Sjmallett
146215976Sjmallett    struct type **tvec;
147215976Sjmallett    int *ivec;
148215976Sjmallett  }
149215976Sjmallett
150215976Sjmallett%{
151215976Sjmallett/* YYSTYPE gets defined by %union */
152215976Sjmallettstatic int parse_number (char *, int, int, YYSTYPE *);
153215976Sjmallett%}
154215976Sjmallett
155215976Sjmallett%type <voidval> exp exp1 type_exp start variable qualified_name lcurly
156215976Sjmallett%type <lval> rcurly
157215976Sjmallett%type <tval> type typebase qualified_type
158215976Sjmallett%type <tvec> nonempty_typelist
159215976Sjmallett/* %type <bval> block */
160215976Sjmallett
161215976Sjmallett/* Fancy type parsing.  */
162215976Sjmallett%type <voidval> func_mod direct_abs_decl abs_decl
163215976Sjmallett%type <tval> ptype
164215976Sjmallett%type <lval> array_mod
165215976Sjmallett
166215976Sjmallett%token <typed_val_int> INT
167215976Sjmallett%token <typed_val_float> FLOAT
168215976Sjmallett
169215976Sjmallett/* Both NAME and TYPENAME tokens represent symbols in the input,
170215976Sjmallett   and both convey their data as strings.
171215976Sjmallett   But a TYPENAME is a string that happens to be defined as a typedef
172215976Sjmallett   or builtin type name (such as int or char)
173215976Sjmallett   and a NAME is any other symbol.
174215976Sjmallett   Contexts where this distinction is not important can use the
175215976Sjmallett   nonterminal "name", which matches either NAME or TYPENAME.  */
176215976Sjmallett
177215976Sjmallett%token <sval> STRING
178215976Sjmallett%token <ssym> NAME /* BLOCKNAME defined below to give it higher precedence. */
179215976Sjmallett%token <tsym> TYPENAME
180215976Sjmallett%type <sval> name
181215976Sjmallett%type <ssym> name_not_typename
182215976Sjmallett%type <tsym> typename
183215976Sjmallett
184215976Sjmallett/* A NAME_OR_INT is a symbol which is not known in the symbol table,
185215976Sjmallett   but which would parse as a valid number in the current input radix.
186215976Sjmallett   E.g. "c" when input_radix==16.  Depending on the parse, it will be
187215976Sjmallett   turned into a name or into a number.  */
188215976Sjmallett
189215976Sjmallett%token <ssym> NAME_OR_INT
190215976Sjmallett
191215976Sjmallett%token STRUCT CLASS UNION ENUM SIZEOF UNSIGNED COLONCOLON
192215976Sjmallett%token TEMPLATE
193215976Sjmallett%token ERROR
194215976Sjmallett
195215976Sjmallett/* Special type cases, put in to allow the parser to distinguish different
196215976Sjmallett   legal basetypes.  */
197215976Sjmallett%token SIGNED_KEYWORD LONG SHORT INT_KEYWORD CONST_KEYWORD VOLATILE_KEYWORD DOUBLE_KEYWORD
198215976Sjmallett
199215976Sjmallett%token <voidval> VARIABLE
200215976Sjmallett
201215976Sjmallett%token <opcode> ASSIGN_MODIFY
202215976Sjmallett
203215976Sjmallett/* C++ */
204215976Sjmallett%token TRUEKEYWORD
205215976Sjmallett%token FALSEKEYWORD
206215976Sjmallett
207215976Sjmallett
208215976Sjmallett%left ','
209215976Sjmallett%left ABOVE_COMMA
210215976Sjmallett%right '=' ASSIGN_MODIFY
211215976Sjmallett%right '?'
212215976Sjmallett%left OROR
213215976Sjmallett%left ANDAND
214215976Sjmallett%left '|'
215215976Sjmallett%left '^'
216215976Sjmallett%left '&'
217215976Sjmallett%left EQUAL NOTEQUAL
218215976Sjmallett%left '<' '>' LEQ GEQ
219215976Sjmallett%left LSH RSH
220215976Sjmallett%left '@'
221215976Sjmallett%left '+' '-'
222215976Sjmallett%left '*' '/' '%'
223215976Sjmallett%right UNARY INCREMENT DECREMENT
224215976Sjmallett%right ARROW '.' '[' '('
225215976Sjmallett%token <ssym> BLOCKNAME
226215976Sjmallett%token <bval> FILENAME
227215976Sjmallett%type <bval> block
228215976Sjmallett%left COLONCOLON
229215976Sjmallett
230215976Sjmallett
231215976Sjmallett%%
232215976Sjmallett
233215976Sjmallettstart   :	exp1
234215976Sjmallett	|	type_exp
235215976Sjmallett	;
236215976Sjmallett
237215976Sjmalletttype_exp:	type
238215976Sjmallett			{ write_exp_elt_opcode(OP_TYPE);
239215976Sjmallett			  write_exp_elt_type($1);
240215976Sjmallett			  write_exp_elt_opcode(OP_TYPE);}
241215976Sjmallett	;
242215976Sjmallett
243215976Sjmallett/* Expressions, including the comma operator.  */
244215976Sjmallettexp1	:	exp
245215976Sjmallett	|	exp1 ',' exp
246215976Sjmallett			{ write_exp_elt_opcode (BINOP_COMMA); }
247215976Sjmallett	;
248215976Sjmallett
249215976Sjmallett/* Expressions, not including the comma operator.  */
250215976Sjmallettexp	:	'*' exp    %prec UNARY
251215976Sjmallett			{ write_exp_elt_opcode (UNOP_IND); }
252215976Sjmallett	;
253215976Sjmallett
254215976Sjmallettexp	:	'&' exp    %prec UNARY
255215976Sjmallett			{ write_exp_elt_opcode (UNOP_ADDR); }
256215976Sjmallett	;
257215976Sjmallett
258215976Sjmallettexp	:	'-' exp    %prec UNARY
259215976Sjmallett			{ write_exp_elt_opcode (UNOP_NEG); }
260215976Sjmallett	;
261215976Sjmallett
262215976Sjmallettexp	:	'!' exp    %prec UNARY
263215976Sjmallett			{ write_exp_elt_opcode (UNOP_LOGICAL_NOT); }
264232812Sjmallett	;
265215976Sjmallett
266232812Sjmallettexp	:	'~' exp    %prec UNARY
267232812Sjmallett			{ write_exp_elt_opcode (UNOP_COMPLEMENT); }
268215976Sjmallett	;
269215976Sjmallett
270215976Sjmallettexp	:	INCREMENT exp    %prec UNARY
271215976Sjmallett			{ write_exp_elt_opcode (UNOP_PREINCREMENT); }
272215976Sjmallett	;
273215976Sjmallett
274215976Sjmallettexp	:	DECREMENT exp    %prec UNARY
275215976Sjmallett			{ write_exp_elt_opcode (UNOP_PREDECREMENT); }
276215976Sjmallett	;
277215976Sjmallett
278215976Sjmallettexp	:	exp INCREMENT    %prec UNARY
279215976Sjmallett			{ write_exp_elt_opcode (UNOP_POSTINCREMENT); }
280215976Sjmallett	;
281215976Sjmallett
282215976Sjmallettexp	:	exp DECREMENT    %prec UNARY
283215976Sjmallett			{ write_exp_elt_opcode (UNOP_POSTDECREMENT); }
284215976Sjmallett	;
285215976Sjmallett
286215976Sjmallettexp	:	SIZEOF exp       %prec UNARY
287215976Sjmallett			{ write_exp_elt_opcode (UNOP_SIZEOF); }
288215976Sjmallett	;
289215976Sjmallett
290215976Sjmallettexp	:	exp ARROW name
291215976Sjmallett			{ write_exp_elt_opcode (STRUCTOP_PTR);
292215976Sjmallett			  write_exp_string ($3);
293215976Sjmallett			  write_exp_elt_opcode (STRUCTOP_PTR); }
294215976Sjmallett	;
295215976Sjmallett
296215976Sjmallettexp	:	exp ARROW qualified_name
297215976Sjmallett			{ /* exp->type::name becomes exp->*(&type::name) */
298215976Sjmallett			  /* Note: this doesn't work if name is a
299215976Sjmallett			     static member!  FIXME */
300215976Sjmallett			  write_exp_elt_opcode (UNOP_ADDR);
301215976Sjmallett			  write_exp_elt_opcode (STRUCTOP_MPTR); }
302215976Sjmallett	;
303215976Sjmallett
304215976Sjmallettexp	:	exp ARROW '*' exp
305215976Sjmallett			{ write_exp_elt_opcode (STRUCTOP_MPTR); }
306215976Sjmallett	;
307215976Sjmallett
308215976Sjmallettexp	:	exp '.' name
309215976Sjmallett			{ write_exp_elt_opcode (STRUCTOP_STRUCT);
310232812Sjmallett			  write_exp_string ($3);
311215976Sjmallett			  write_exp_elt_opcode (STRUCTOP_STRUCT); }
312232812Sjmallett	;
313232812Sjmallett
314215976Sjmallettexp	:	exp '.' qualified_name
315215976Sjmallett			{ /* exp.type::name becomes exp.*(&type::name) */
316215976Sjmallett			  /* Note: this doesn't work if name is a
317215976Sjmallett			     static member!  FIXME */
318215976Sjmallett			  write_exp_elt_opcode (UNOP_ADDR);
319215976Sjmallett			  write_exp_elt_opcode (STRUCTOP_MEMBER); }
320215976Sjmallett	;
321215976Sjmallett
322215976Sjmallettexp	:	exp '.' '*' exp
323215976Sjmallett			{ write_exp_elt_opcode (STRUCTOP_MEMBER); }
324215976Sjmallett	;
325215976Sjmallett
326215976Sjmallettexp	:	exp '[' exp1 ']'
327215976Sjmallett			{ write_exp_elt_opcode (BINOP_SUBSCRIPT); }
328215976Sjmallett	;
329215976Sjmallett
330215976Sjmallettexp	:	exp '('
331215976Sjmallett			/* This is to save the value of arglist_len
332215976Sjmallett			   being accumulated by an outer function call.  */
333215976Sjmallett			{ start_arglist (); }
334215976Sjmallett		arglist ')'	%prec ARROW
335215976Sjmallett			{ write_exp_elt_opcode (OP_FUNCALL);
336215976Sjmallett			  write_exp_elt_longcst ((LONGEST) end_arglist ());
337215976Sjmallett			  write_exp_elt_opcode (OP_FUNCALL); }
338215976Sjmallett	;
339215976Sjmallett
340215976Sjmallettlcurly	:	'{'
341232812Sjmallett			{ start_arglist (); }
342215976Sjmallett	;
343232812Sjmallett
344232812Sjmallettarglist	:
345215976Sjmallett	;
346215976Sjmallett
347215976Sjmallettarglist	:	exp
348215976Sjmallett			{ arglist_len = 1; }
349215976Sjmallett	;
350215976Sjmallett
351215976Sjmallettarglist	:	arglist ',' exp   %prec ABOVE_COMMA
352215976Sjmallett			{ arglist_len++; }
353215976Sjmallett	;
354215976Sjmallett
355215976Sjmallettrcurly	:	'}'
356215976Sjmallett			{ $$ = end_arglist () - 1; }
357215976Sjmallett	;
358215976Sjmallettexp	:	lcurly arglist rcurly	%prec ARROW
359215976Sjmallett			{ write_exp_elt_opcode (OP_ARRAY);
360215976Sjmallett			  write_exp_elt_longcst ((LONGEST) 0);
361215976Sjmallett			  write_exp_elt_longcst ((LONGEST) $3);
362215976Sjmallett			  write_exp_elt_opcode (OP_ARRAY); }
363215976Sjmallett	;
364215976Sjmallett
365215976Sjmallettexp	:	lcurly type rcurly exp  %prec UNARY
366215976Sjmallett			{ write_exp_elt_opcode (UNOP_MEMVAL);
367215976Sjmallett			  write_exp_elt_type ($2);
368215976Sjmallett			  write_exp_elt_opcode (UNOP_MEMVAL); }
369215976Sjmallett	;
370215976Sjmallett
371215976Sjmallettexp	:	'(' type ')' exp  %prec UNARY
372215976Sjmallett			{ write_exp_elt_opcode (UNOP_CAST);
373215976Sjmallett			  write_exp_elt_type ($2);
374215976Sjmallett			  write_exp_elt_opcode (UNOP_CAST); }
375215976Sjmallett	;
376215976Sjmallett
377232812Sjmallettexp	:	'(' exp1 ')'
378215976Sjmallett			{ }
379232812Sjmallett	;
380232812Sjmallett
381215976Sjmallett/* Binary operators in order of decreasing precedence.  */
382215976Sjmallett
383215976Sjmallettexp	:	exp '@' exp
384215976Sjmallett			{ write_exp_elt_opcode (BINOP_REPEAT); }
385215976Sjmallett	;
386215976Sjmallett
387215976Sjmallettexp	:	exp '*' exp
388215976Sjmallett			{ write_exp_elt_opcode (BINOP_MUL); }
389215976Sjmallett	;
390215976Sjmallett
391215976Sjmallettexp	:	exp '/' exp
392215976Sjmallett			{ write_exp_elt_opcode (BINOP_DIV); }
393215976Sjmallett	;
394215976Sjmallett
395215976Sjmallettexp	:	exp '%' exp
396215976Sjmallett			{ write_exp_elt_opcode (BINOP_REM); }
397215976Sjmallett	;
398215976Sjmallett
399215976Sjmallettexp	:	exp '+' exp
400215976Sjmallett			{ write_exp_elt_opcode (BINOP_ADD); }
401215976Sjmallett	;
402215976Sjmallett
403215976Sjmallettexp	:	exp '-' exp
404215976Sjmallett			{ write_exp_elt_opcode (BINOP_SUB); }
405232812Sjmallett	;
406215976Sjmallett
407232812Sjmallettexp	:	exp LSH exp
408232812Sjmallett			{ write_exp_elt_opcode (BINOP_LSH); }
409215976Sjmallett	;
410215976Sjmallett
411215976Sjmallettexp	:	exp RSH exp
412215976Sjmallett			{ write_exp_elt_opcode (BINOP_RSH); }
413215976Sjmallett	;
414215976Sjmallett
415215976Sjmallettexp	:	exp EQUAL exp
416215976Sjmallett			{ write_exp_elt_opcode (BINOP_EQUAL); }
417215976Sjmallett	;
418215976Sjmallett
419215976Sjmallettexp	:	exp NOTEQUAL exp
420215976Sjmallett			{ write_exp_elt_opcode (BINOP_NOTEQUAL); }
421215976Sjmallett	;
422215976Sjmallett
423215976Sjmallettexp	:	exp LEQ exp
424215976Sjmallett			{ write_exp_elt_opcode (BINOP_LEQ); }
425215976Sjmallett	;
426215976Sjmallett
427215976Sjmallettexp	:	exp GEQ exp
428215976Sjmallett			{ write_exp_elt_opcode (BINOP_GEQ); }
429215976Sjmallett	;
430215976Sjmallett
431215976Sjmallettexp	:	exp '<' exp
432215976Sjmallett			{ write_exp_elt_opcode (BINOP_LESS); }
433232812Sjmallett	;
434215976Sjmallett
435232812Sjmallettexp	:	exp '>' exp
436232812Sjmallett			{ write_exp_elt_opcode (BINOP_GTR); }
437215976Sjmallett	;
438215976Sjmallett
439215976Sjmallettexp	:	exp '&' exp
440215976Sjmallett			{ write_exp_elt_opcode (BINOP_BITWISE_AND); }
441215976Sjmallett	;
442215976Sjmallett
443215976Sjmallettexp	:	exp '^' exp
444215976Sjmallett			{ write_exp_elt_opcode (BINOP_BITWISE_XOR); }
445215976Sjmallett	;
446215976Sjmallett
447215976Sjmallettexp	:	exp '|' exp
448215976Sjmallett			{ write_exp_elt_opcode (BINOP_BITWISE_IOR); }
449215976Sjmallett	;
450215976Sjmallett
451215976Sjmallettexp	:	exp ANDAND exp
452215976Sjmallett			{ write_exp_elt_opcode (BINOP_LOGICAL_AND); }
453215976Sjmallett	;
454215976Sjmallett
455215976Sjmallettexp	:	exp OROR exp
456215976Sjmallett			{ write_exp_elt_opcode (BINOP_LOGICAL_OR); }
457215976Sjmallett	;
458215976Sjmallett
459215976Sjmallettexp	:	exp '?' exp ':' exp	%prec '?'
460215976Sjmallett			{ write_exp_elt_opcode (TERNOP_COND); }
461215976Sjmallett	;
462215976Sjmallett
463215976Sjmallettexp	:	exp '=' exp
464215976Sjmallett			{ write_exp_elt_opcode (BINOP_ASSIGN); }
465215976Sjmallett	;
466215976Sjmallett
467215976Sjmallettexp	:	exp ASSIGN_MODIFY exp
468215976Sjmallett			{ write_exp_elt_opcode (BINOP_ASSIGN_MODIFY);
469215976Sjmallett			  write_exp_elt_opcode ($2);
470215976Sjmallett			  write_exp_elt_opcode (BINOP_ASSIGN_MODIFY); }
471215976Sjmallett	;
472215976Sjmallett
473215976Sjmallettexp	:	INT
474215976Sjmallett			{ write_exp_elt_opcode (OP_LONG);
475215976Sjmallett			  write_exp_elt_type ($1.type);
476215976Sjmallett			  write_exp_elt_longcst ((LONGEST)($1.val));
477215976Sjmallett			  write_exp_elt_opcode (OP_LONG); }
478215976Sjmallett	;
479215976Sjmallett
480215976Sjmallettexp	:	NAME_OR_INT
481215976Sjmallett			{ YYSTYPE val;
482215976Sjmallett			  parse_number ($1.stoken.ptr, $1.stoken.length, 0, &val);
483215976Sjmallett			  write_exp_elt_opcode (OP_LONG);
484215976Sjmallett			  write_exp_elt_type (val.typed_val_int.type);
485215976Sjmallett			  write_exp_elt_longcst ((LONGEST)val.typed_val_int.val);
486215976Sjmallett			  write_exp_elt_opcode (OP_LONG);
487215976Sjmallett			}
488215976Sjmallett	;
489215976Sjmallett
490215976Sjmallett
491215976Sjmallettexp	:	FLOAT
492215976Sjmallett			{ write_exp_elt_opcode (OP_DOUBLE);
493215976Sjmallett			  write_exp_elt_type ($1.type);
494215976Sjmallett			  write_exp_elt_dblcst ($1.dval);
495215976Sjmallett			  write_exp_elt_opcode (OP_DOUBLE); }
496215976Sjmallett	;
497215976Sjmallett
498215976Sjmallettexp	:	variable
499215976Sjmallett	;
500215976Sjmallett
501215976Sjmallettexp	:	VARIABLE
502215976Sjmallett			/* Already written by write_dollar_variable. */
503215976Sjmallett	;
504215976Sjmallett
505215976Sjmallettexp	:	SIZEOF '(' type ')'	%prec UNARY
506215976Sjmallett			{ write_exp_elt_opcode (OP_LONG);
507215976Sjmallett			  write_exp_elt_type (builtin_type_int);
508215976Sjmallett			  CHECK_TYPEDEF ($3);
509215976Sjmallett			  write_exp_elt_longcst ((LONGEST) TYPE_LENGTH ($3));
510215976Sjmallett			  write_exp_elt_opcode (OP_LONG); }
511215976Sjmallett	;
512215976Sjmallett
513215976Sjmallettexp	:	STRING
514215976Sjmallett			{ /* C strings are converted into array constants with
515215976Sjmallett			     an explicit null byte added at the end.  Thus
516215976Sjmallett			     the array upper bound is the string length.
517215976Sjmallett			     There is no such thing in C as a completely empty
518215976Sjmallett			     string. */
519215976Sjmallett			  char *sp = $1.ptr; int count = $1.length;
520215976Sjmallett			  while (count-- > 0)
521215976Sjmallett			    {
522215976Sjmallett			      write_exp_elt_opcode (OP_LONG);
523215976Sjmallett			      write_exp_elt_type (builtin_type_char);
524215976Sjmallett			      write_exp_elt_longcst ((LONGEST)(*sp++));
525215976Sjmallett			      write_exp_elt_opcode (OP_LONG);
526232812Sjmallett			    }
527215976Sjmallett			  write_exp_elt_opcode (OP_LONG);
528232812Sjmallett			  write_exp_elt_type (builtin_type_char);
529232812Sjmallett			  write_exp_elt_longcst ((LONGEST)'\0');
530215976Sjmallett			  write_exp_elt_opcode (OP_LONG);
531215976Sjmallett			  write_exp_elt_opcode (OP_ARRAY);
532215976Sjmallett			  write_exp_elt_longcst ((LONGEST) 0);
533215976Sjmallett			  write_exp_elt_longcst ((LONGEST) ($1.length));
534215976Sjmallett			  write_exp_elt_opcode (OP_ARRAY); }
535215976Sjmallett	;
536215976Sjmallett
537215976Sjmallett/* C++.  */
538215976Sjmallettexp     :       TRUEKEYWORD
539215976Sjmallett                        { write_exp_elt_opcode (OP_LONG);
540215976Sjmallett                          write_exp_elt_type (builtin_type_bool);
541215976Sjmallett                          write_exp_elt_longcst ((LONGEST) 1);
542215976Sjmallett                          write_exp_elt_opcode (OP_LONG); }
543215976Sjmallett	;
544215976Sjmallett
545215976Sjmallettexp     :       FALSEKEYWORD
546215976Sjmallett                        { write_exp_elt_opcode (OP_LONG);
547215976Sjmallett                          write_exp_elt_type (builtin_type_bool);
548215976Sjmallett                          write_exp_elt_longcst ((LONGEST) 0);
549215976Sjmallett                          write_exp_elt_opcode (OP_LONG); }
550215976Sjmallett	;
551215976Sjmallett
552215976Sjmallett/* end of C++.  */
553215976Sjmallett
554215976Sjmallettblock	:	BLOCKNAME
555215976Sjmallett			{
556215976Sjmallett			  if ($1.sym)
557215976Sjmallett			    $$ = SYMBOL_BLOCK_VALUE ($1.sym);
558215976Sjmallett			  else
559215976Sjmallett			    error ("No file or function \"%s\".",
560215976Sjmallett				   copy_name ($1.stoken));
561215976Sjmallett			}
562215976Sjmallett	|	FILENAME
563215976Sjmallett			{
564215976Sjmallett			  $$ = $1;
565215976Sjmallett			}
566215976Sjmallett	;
567215976Sjmallett
568215976Sjmallettblock	:	block COLONCOLON name
569215976Sjmallett			{ struct symbol *tem
570215976Sjmallett			    = lookup_symbol (copy_name ($3), $1,
571215976Sjmallett					     VAR_DOMAIN, (int *) NULL,
572215976Sjmallett					     (struct symtab **) NULL);
573215976Sjmallett			  if (!tem || SYMBOL_CLASS (tem) != LOC_BLOCK)
574232812Sjmallett			    error ("No function \"%s\" in specified context.",
575215976Sjmallett				   copy_name ($3));
576232812Sjmallett			  $$ = SYMBOL_BLOCK_VALUE (tem); }
577232812Sjmallett	;
578215976Sjmallett
579215976Sjmallettvariable:	block COLONCOLON name
580215976Sjmallett			{ struct symbol *sym;
581215976Sjmallett			  sym = lookup_symbol (copy_name ($3), $1,
582215976Sjmallett					       VAR_DOMAIN, (int *) NULL,
583215976Sjmallett					       (struct symtab **) NULL);
584215976Sjmallett			  if (sym == 0)
585215976Sjmallett			    error ("No symbol \"%s\" in specified context.",
586215976Sjmallett				   copy_name ($3));
587215976Sjmallett
588215976Sjmallett			  write_exp_elt_opcode (OP_VAR_VALUE);
589215976Sjmallett			  /* block_found is set by lookup_symbol.  */
590215976Sjmallett			  write_exp_elt_block (block_found);
591215976Sjmallett			  write_exp_elt_sym (sym);
592215976Sjmallett			  write_exp_elt_opcode (OP_VAR_VALUE); }
593215976Sjmallett	;
594215976Sjmallett
595215976Sjmallettqualified_name:	typebase COLONCOLON name
596215976Sjmallett			{
597215976Sjmallett			  struct type *type = $1;
598215976Sjmallett			  if (TYPE_CODE (type) != TYPE_CODE_STRUCT
599215976Sjmallett			      && TYPE_CODE (type) != TYPE_CODE_UNION
600215976Sjmallett			      && TYPE_CODE (type) != TYPE_CODE_NAMESPACE)
601215976Sjmallett			    error ("`%s' is not defined as an aggregate type.",
602215976Sjmallett				   TYPE_NAME (type));
603215976Sjmallett
604215976Sjmallett			  write_exp_elt_opcode (OP_SCOPE);
605215976Sjmallett			  write_exp_elt_type (type);
606215976Sjmallett			  write_exp_string ($3);
607215976Sjmallett			  write_exp_elt_opcode (OP_SCOPE);
608215976Sjmallett			}
609215976Sjmallett	|	typebase COLONCOLON '~' name
610215976Sjmallett			{
611215976Sjmallett			  struct type *type = $1;
612232812Sjmallett			  struct stoken tmp_token;
613215976Sjmallett			  if (TYPE_CODE (type) != TYPE_CODE_STRUCT
614232812Sjmallett			      && TYPE_CODE (type) != TYPE_CODE_UNION
615232812Sjmallett			      && TYPE_CODE (type) != TYPE_CODE_NAMESPACE)
616215976Sjmallett			    error ("`%s' is not defined as an aggregate type.",
617215976Sjmallett				   TYPE_NAME (type));
618215976Sjmallett
619215976Sjmallett			  tmp_token.ptr = (char*) alloca ($4.length + 2);
620215976Sjmallett			  tmp_token.length = $4.length + 1;
621215976Sjmallett			  tmp_token.ptr[0] = '~';
622215976Sjmallett			  memcpy (tmp_token.ptr+1, $4.ptr, $4.length);
623215976Sjmallett			  tmp_token.ptr[tmp_token.length] = 0;
624215976Sjmallett
625215976Sjmallett			  /* Check for valid destructor name.  */
626215976Sjmallett			  destructor_name_p (tmp_token.ptr, type);
627215976Sjmallett			  write_exp_elt_opcode (OP_SCOPE);
628215976Sjmallett			  write_exp_elt_type (type);
629215976Sjmallett			  write_exp_string (tmp_token);
630215976Sjmallett			  write_exp_elt_opcode (OP_SCOPE);
631215976Sjmallett			}
632215976Sjmallett	;
633215976Sjmallett
634215976Sjmallettvariable:	qualified_name
635215976Sjmallett	|	COLONCOLON name
636215976Sjmallett			{
637215976Sjmallett			  char *name = copy_name ($2);
638215976Sjmallett			  struct symbol *sym;
639215976Sjmallett			  struct minimal_symbol *msymbol;
640215976Sjmallett
641215976Sjmallett			  sym =
642215976Sjmallett			    lookup_symbol (name, (const struct block *) NULL,
643215976Sjmallett					   VAR_DOMAIN, (int *) NULL,
644215976Sjmallett					   (struct symtab **) NULL);
645215976Sjmallett			  if (sym)
646215976Sjmallett			    {
647215976Sjmallett			      write_exp_elt_opcode (OP_VAR_VALUE);
648215976Sjmallett			      write_exp_elt_block (NULL);
649215976Sjmallett			      write_exp_elt_sym (sym);
650215976Sjmallett			      write_exp_elt_opcode (OP_VAR_VALUE);
651215976Sjmallett			      break;
652215976Sjmallett			    }
653215976Sjmallett
654215976Sjmallett			  msymbol = lookup_minimal_symbol (name, NULL, NULL);
655215976Sjmallett			  if (msymbol != NULL)
656215976Sjmallett			    {
657215976Sjmallett			      write_exp_msymbol (msymbol,
658215976Sjmallett						 lookup_function_type (builtin_type_int),
659215976Sjmallett						 builtin_type_int);
660232812Sjmallett			    }
661215976Sjmallett			  else
662232812Sjmallett			    if (!have_full_symbols () && !have_partial_symbols ())
663232812Sjmallett			      error ("No symbol table is loaded.  Use the \"file\" command.");
664215976Sjmallett			    else
665215976Sjmallett			      error ("No symbol \"%s\" in current context.", name);
666215976Sjmallett			}
667215976Sjmallett	;
668215976Sjmallett
669215976Sjmallettvariable:	name_not_typename
670215976Sjmallett			{ struct symbol *sym = $1.sym;
671215976Sjmallett
672215976Sjmallett			  if (sym)
673215976Sjmallett			    {
674215976Sjmallett			      if (symbol_read_needs_frame (sym))
675215976Sjmallett				{
676215976Sjmallett				  if (innermost_block == 0 ||
677215976Sjmallett				      contained_in (block_found,
678215976Sjmallett						    innermost_block))
679215976Sjmallett				    innermost_block = block_found;
680215976Sjmallett				}
681215976Sjmallett
682215976Sjmallett			      write_exp_elt_opcode (OP_VAR_VALUE);
683215976Sjmallett			      /* We want to use the selected frame, not
684215976Sjmallett				 another more inner frame which happens to
685215976Sjmallett				 be in the same block.  */
686215976Sjmallett			      write_exp_elt_block (NULL);
687215976Sjmallett			      write_exp_elt_sym (sym);
688215976Sjmallett			      write_exp_elt_opcode (OP_VAR_VALUE);
689215976Sjmallett			    }
690215976Sjmallett			  else if ($1.is_a_field_of_this)
691215976Sjmallett			    {
692215976Sjmallett			      /* C++: it hangs off of `this'.  Must
693215976Sjmallett			         not inadvertently convert from a method call
694215976Sjmallett				 to data ref.  */
695215976Sjmallett			      if (innermost_block == 0 ||
696215976Sjmallett				  contained_in (block_found, innermost_block))
697215976Sjmallett				innermost_block = block_found;
698215976Sjmallett			      write_exp_elt_opcode (OP_THIS);
699215976Sjmallett			      write_exp_elt_opcode (OP_THIS);
700215976Sjmallett			      write_exp_elt_opcode (STRUCTOP_PTR);
701215976Sjmallett			      write_exp_string ($1.stoken);
702215976Sjmallett			      write_exp_elt_opcode (STRUCTOP_PTR);
703215976Sjmallett			    }
704215976Sjmallett			  else
705215976Sjmallett			    {
706215976Sjmallett			      struct minimal_symbol *msymbol;
707215976Sjmallett			      char *arg = copy_name ($1.stoken);
708215976Sjmallett
709215976Sjmallett			      msymbol =
710215976Sjmallett				lookup_minimal_symbol (arg, NULL, NULL);
711215976Sjmallett			      if (msymbol != NULL)
712215976Sjmallett				{
713215976Sjmallett				  write_exp_msymbol (msymbol,
714215976Sjmallett						     lookup_function_type (builtin_type_int),
715215976Sjmallett						     builtin_type_int);
716215976Sjmallett				}
717232812Sjmallett			      else if (!have_full_symbols () && !have_partial_symbols ())
718215976Sjmallett				error ("No symbol table is loaded.  Use the \"file\" command.");
719232812Sjmallett			      else
720232812Sjmallett				error ("No symbol \"%s\" in current context.",
721215976Sjmallett				       copy_name ($1.stoken));
722215976Sjmallett			    }
723215976Sjmallett			}
724215976Sjmallett	;
725215976Sjmallett
726215976Sjmallettspace_identifier : '@' NAME
727215976Sjmallett		{ push_type_address_space (copy_name ($2.stoken));
728215976Sjmallett		  push_type (tp_space_identifier);
729215976Sjmallett		}
730215976Sjmallett	;
731215976Sjmallett
732215976Sjmallettconst_or_volatile: const_or_volatile_noopt
733215976Sjmallett	|
734215976Sjmallett	;
735215976Sjmallett
736215976Sjmallettcv_with_space_id : const_or_volatile space_identifier const_or_volatile
737215976Sjmallett	;
738215976Sjmallett
739215976Sjmallettconst_or_volatile_or_space_identifier_noopt: cv_with_space_id
740215976Sjmallett	| const_or_volatile_noopt
741215976Sjmallett	;
742215976Sjmallett
743215976Sjmallettconst_or_volatile_or_space_identifier:
744215976Sjmallett		const_or_volatile_or_space_identifier_noopt
745215976Sjmallett	|
746215976Sjmallett	;
747215976Sjmallett
748215976Sjmallettabs_decl:	'*'
749215976Sjmallett			{ push_type (tp_pointer); $$ = 0; }
750215976Sjmallett	|	'*' abs_decl
751215976Sjmallett			{ push_type (tp_pointer); $$ = $2; }
752215976Sjmallett	|	'&'
753232812Sjmallett			{ push_type (tp_reference); $$ = 0; }
754215976Sjmallett	|	'&' abs_decl
755232812Sjmallett			{ push_type (tp_reference); $$ = $2; }
756232812Sjmallett	|	direct_abs_decl
757215976Sjmallett	;
758215976Sjmallett
759215976Sjmallettdirect_abs_decl: '(' abs_decl ')'
760215976Sjmallett			{ $$ = $2; }
761215976Sjmallett	|	direct_abs_decl array_mod
762215976Sjmallett			{
763215976Sjmallett			  push_type_int ($2);
764215976Sjmallett			  push_type (tp_array);
765215976Sjmallett			}
766215976Sjmallett	|	array_mod
767215976Sjmallett			{
768215976Sjmallett			  push_type_int ($1);
769215976Sjmallett			  push_type (tp_array);
770215976Sjmallett			  $$ = 0;
771215976Sjmallett			}
772215976Sjmallett
773215976Sjmallett	| 	direct_abs_decl func_mod
774215976Sjmallett			{ push_type (tp_function); }
775215976Sjmallett	|	func_mod
776215976Sjmallett			{ push_type (tp_function); }
777215976Sjmallett	;
778232812Sjmallett
779215976Sjmallettarray_mod:	'[' ']'
780232812Sjmallett			{ $$ = -1; }
781232812Sjmallett	|	'[' INT ']'
782215976Sjmallett			{ $$ = $2.val; }
783215976Sjmallett	;
784215976Sjmallett
785215976Sjmallettfunc_mod:	'(' ')'
786215976Sjmallett			{ $$ = 0; }
787215976Sjmallett	|	'(' nonempty_typelist ')'
788215976Sjmallett			{ free ($2); $$ = 0; }
789215976Sjmallett	;
790215976Sjmallett
791215976Sjmallett/* We used to try to recognize more pointer to member types here, but
792215976Sjmallett   that didn't work (shift/reduce conflicts meant that these rules never
793215976Sjmallett   got executed).  The problem is that
794215976Sjmallett     int (foo::bar::baz::bizzle)
795215976Sjmallett   is a function type but
796215976Sjmallett     int (foo::bar::baz::bizzle::*)
797215976Sjmallett   is a pointer to member type.  Stroustrup loses again!  */
798215976Sjmallett
799232812Sjmalletttype	:	ptype
800215976Sjmallett	|	typebase COLONCOLON '*'
801232812Sjmallett			{ $$ = lookup_member_type (builtin_type_int, $1); }
802232812Sjmallett	;
803215976Sjmallett
804215976Sjmalletttypebase  /* Implements (approximately): (type-qualifier)* type-specifier */
805215976Sjmallett	:	TYPENAME
806215976Sjmallett			{ $$ = $1.type; }
807215976Sjmallett	|	INT_KEYWORD
808215976Sjmallett			{ $$ = builtin_type_int; }
809215976Sjmallett	|	LONG
810215976Sjmallett			{ $$ = builtin_type_long; }
811215976Sjmallett	|	SHORT
812215976Sjmallett			{ $$ = builtin_type_short; }
813215976Sjmallett	|	LONG INT_KEYWORD
814215976Sjmallett			{ $$ = builtin_type_long; }
815215976Sjmallett	|	LONG SIGNED_KEYWORD INT_KEYWORD
816215976Sjmallett			{ $$ = builtin_type_long; }
817215976Sjmallett	|	LONG SIGNED_KEYWORD
818215976Sjmallett			{ $$ = builtin_type_long; }
819215976Sjmallett	|	SIGNED_KEYWORD LONG INT_KEYWORD
820232812Sjmallett			{ $$ = builtin_type_long; }
821215976Sjmallett	|	UNSIGNED LONG INT_KEYWORD
822232812Sjmallett			{ $$ = builtin_type_unsigned_long; }
823232812Sjmallett	|	LONG UNSIGNED INT_KEYWORD
824215976Sjmallett			{ $$ = builtin_type_unsigned_long; }
825215976Sjmallett	|	LONG UNSIGNED
826215976Sjmallett			{ $$ = builtin_type_unsigned_long; }
827215976Sjmallett	|	LONG LONG
828215976Sjmallett			{ $$ = builtin_type_long_long; }
829215976Sjmallett	|	LONG LONG INT_KEYWORD
830215976Sjmallett			{ $$ = builtin_type_long_long; }
831215976Sjmallett	|	LONG LONG SIGNED_KEYWORD INT_KEYWORD
832215976Sjmallett			{ $$ = builtin_type_long_long; }
833215976Sjmallett	|	LONG LONG SIGNED_KEYWORD
834215976Sjmallett			{ $$ = builtin_type_long_long; }
835215976Sjmallett	|	SIGNED_KEYWORD LONG LONG
836215976Sjmallett			{ $$ = builtin_type_long_long; }
837215976Sjmallett	|	SIGNED_KEYWORD LONG LONG INT_KEYWORD
838215976Sjmallett			{ $$ = builtin_type_long_long; }
839215976Sjmallett	|	UNSIGNED LONG LONG
840215976Sjmallett			{ $$ = builtin_type_unsigned_long_long; }
841215976Sjmallett	|	UNSIGNED LONG LONG INT_KEYWORD
842215976Sjmallett			{ $$ = builtin_type_unsigned_long_long; }
843215976Sjmallett	|	LONG LONG UNSIGNED
844215976Sjmallett			{ $$ = builtin_type_unsigned_long_long; }
845215976Sjmallett	|	LONG LONG UNSIGNED INT_KEYWORD
846232812Sjmallett			{ $$ = builtin_type_unsigned_long_long; }
847215976Sjmallett	|	SHORT INT_KEYWORD
848232812Sjmallett			{ $$ = builtin_type_short; }
849232812Sjmallett	|	SHORT SIGNED_KEYWORD INT_KEYWORD
850215976Sjmallett			{ $$ = builtin_type_short; }
851215976Sjmallett	|	SHORT SIGNED_KEYWORD
852215976Sjmallett			{ $$ = builtin_type_short; }
853215976Sjmallett	|	UNSIGNED SHORT INT_KEYWORD
854215976Sjmallett			{ $$ = builtin_type_unsigned_short; }
855215976Sjmallett	|	SHORT UNSIGNED
856215976Sjmallett			{ $$ = builtin_type_unsigned_short; }
857215976Sjmallett	|	SHORT UNSIGNED INT_KEYWORD
858215976Sjmallett			{ $$ = builtin_type_unsigned_short; }
859215976Sjmallett	|	DOUBLE_KEYWORD
860215976Sjmallett			{ $$ = builtin_type_double; }
861215976Sjmallett	|	LONG DOUBLE_KEYWORD
862215976Sjmallett			{ $$ = builtin_type_long_double; }
863215976Sjmallett	|	STRUCT name
864215976Sjmallett			{ $$ = lookup_struct (copy_name ($2),
865					      expression_context_block); }
866	|	CLASS name
867			{ $$ = lookup_struct (copy_name ($2),
868					      expression_context_block); }
869	|	UNION name
870			{ $$ = lookup_union (copy_name ($2),
871					     expression_context_block); }
872	|	ENUM name
873			{ $$ = lookup_enum (copy_name ($2),
874					    expression_context_block); }
875	|	UNSIGNED typename
876			{ $$ = lookup_unsigned_typename (TYPE_NAME($2.type)); }
877	|	UNSIGNED
878			{ $$ = builtin_type_unsigned_int; }
879	|	SIGNED_KEYWORD typename
880			{ $$ = lookup_signed_typename (TYPE_NAME($2.type)); }
881	|	SIGNED_KEYWORD
882			{ $$ = builtin_type_int; }
883                /* It appears that this rule for templates is never
884                   reduced; template recognition happens by lookahead
885                   in the token processing code in yylex. */
886	|	TEMPLATE name '<' type '>'
887			{ $$ = lookup_template_type(copy_name($2), $4,
888						    expression_context_block);
889			}
890	| const_or_volatile_or_space_identifier_noopt typebase
891			{ $$ = follow_types ($2); }
892	| typebase const_or_volatile_or_space_identifier_noopt
893			{ $$ = follow_types ($1); }
894	| qualified_type
895	;
896
897/* FIXME: carlton/2003-09-25: This next bit leads to lots of
898   reduce-reduce conflicts, because the parser doesn't know whether or
899   not to use qualified_name or qualified_type: the rules are
900   identical.  If the parser is parsing 'A::B::x', then, when it sees
901   the second '::', it knows that the expression to the left of it has
902   to be a type, so it uses qualified_type.  But if it is parsing just
903   'A::B', then it doesn't have any way of knowing which rule to use,
904   so there's a reduce-reduce conflict; it picks qualified_name, since
905   that occurs earlier in this file than qualified_type.
906
907   There's no good way to fix this with the grammar as it stands; as
908   far as I can tell, some of the problems arise from ambiguities that
909   GDB introduces ('start' can be either an expression or a type), but
910   some of it is inherent to the nature of C++ (you want to treat the
911   input "(FOO)" fairly differently depending on whether FOO is an
912   expression or a type, and if FOO is a complex expression, this can
913   be hard to determine at the right time).  Fortunately, it works
914   pretty well in most cases.  For example, if you do 'ptype A::B',
915   where A::B is a nested type, then the parser will mistakenly
916   misidentify it as an expression; but evaluate_subexp will get
917   called with 'noside' set to EVAL_AVOID_SIDE_EFFECTS, and everything
918   will work out anyways.  But there are situations where the parser
919   will get confused: the most common one that I've run into is when
920   you want to do
921
922     print *((A::B *) x)"
923
924   where the parser doesn't realize that A::B has to be a type until
925   it hits the first right paren, at which point it's too late.  (The
926   workaround is to type "print *(('A::B' *) x)" instead.)  (And
927   another solution is to fix our symbol-handling code so that the
928   user never wants to type something like that in the first place,
929   because we get all the types right without the user's help!)
930
931   Perhaps we could fix this by making the lexer smarter.  Some of
932   this functionality used to be in the lexer, but in a way that
933   worked even less well than the current solution: that attempt
934   involved having the parser sometimes handle '::' and having the
935   lexer sometimes handle it, and without a clear division of
936   responsibility, it quickly degenerated into a big mess.  Probably
937   the eventual correct solution will give more of a role to the lexer
938   (ideally via code that is shared between the lexer and
939   decode_line_1), but I'm not holding my breath waiting for somebody
940   to get around to cleaning this up...  */
941
942qualified_type: typebase COLONCOLON name
943		{
944		  struct type *type = $1;
945		  struct type *new_type;
946		  char *ncopy = alloca ($3.length + 1);
947
948		  memcpy (ncopy, $3.ptr, $3.length);
949		  ncopy[$3.length] = '\0';
950
951		  if (TYPE_CODE (type) != TYPE_CODE_STRUCT
952		      && TYPE_CODE (type) != TYPE_CODE_UNION
953		      && TYPE_CODE (type) != TYPE_CODE_NAMESPACE)
954		    error ("`%s' is not defined as an aggregate type.",
955			   TYPE_NAME (type));
956
957		  new_type = cp_lookup_nested_type (type, ncopy,
958						    expression_context_block);
959		  if (new_type == NULL)
960		    error ("No type \"%s\" within class or namespace \"%s\".",
961			   ncopy, TYPE_NAME (type));
962
963		  $$ = new_type;
964		}
965	;
966
967typename:	TYPENAME
968	|	INT_KEYWORD
969		{
970		  $$.stoken.ptr = "int";
971		  $$.stoken.length = 3;
972		  $$.type = builtin_type_int;
973		}
974	|	LONG
975		{
976		  $$.stoken.ptr = "long";
977		  $$.stoken.length = 4;
978		  $$.type = builtin_type_long;
979		}
980	|	SHORT
981		{
982		  $$.stoken.ptr = "short";
983		  $$.stoken.length = 5;
984		  $$.type = builtin_type_short;
985		}
986	;
987
988nonempty_typelist
989	:	type
990		{ $$ = (struct type **) malloc (sizeof (struct type *) * 2);
991		  $<ivec>$[0] = 1;	/* Number of types in vector */
992		  $$[1] = $1;
993		}
994	|	nonempty_typelist ',' type
995		{ int len = sizeof (struct type *) * (++($<ivec>1[0]) + 1);
996		  $$ = (struct type **) realloc ((char *) $1, len);
997		  $$[$<ivec>$[0]] = $3;
998		}
999	;
1000
1001ptype	:	typebase
1002	|	ptype const_or_volatile_or_space_identifier abs_decl const_or_volatile_or_space_identifier
1003		{ $$ = follow_types ($1); }
1004	;
1005
1006const_and_volatile: 	CONST_KEYWORD VOLATILE_KEYWORD
1007	| 		VOLATILE_KEYWORD CONST_KEYWORD
1008	;
1009
1010const_or_volatile_noopt:  	const_and_volatile
1011			{ push_type (tp_const);
1012			  push_type (tp_volatile);
1013			}
1014	| 		CONST_KEYWORD
1015			{ push_type (tp_const); }
1016	| 		VOLATILE_KEYWORD
1017			{ push_type (tp_volatile); }
1018	;
1019
1020name	:	NAME { $$ = $1.stoken; }
1021	|	BLOCKNAME { $$ = $1.stoken; }
1022	|	TYPENAME { $$ = $1.stoken; }
1023	|	NAME_OR_INT  { $$ = $1.stoken; }
1024	;
1025
1026name_not_typename :	NAME
1027	|	BLOCKNAME
1028/* These would be useful if name_not_typename was useful, but it is just
1029   a fake for "variable", so these cause reduce/reduce conflicts because
1030   the parser can't tell whether NAME_OR_INT is a name_not_typename (=variable,
1031   =exp) or just an exp.  If name_not_typename was ever used in an lvalue
1032   context where only a name could occur, this might be useful.
1033  	|	NAME_OR_INT
1034 */
1035	;
1036
1037%%
1038
1039/* Take care of parsing a number (anything that starts with a digit).
1040   Set yylval and return the token type; update lexptr.
1041   LEN is the number of characters in it.  */
1042
1043/*** Needs some error checking for the float case ***/
1044
1045static int
1046parse_number (p, len, parsed_float, putithere)
1047     char *p;
1048     int len;
1049     int parsed_float;
1050     YYSTYPE *putithere;
1051{
1052  /* FIXME: Shouldn't these be unsigned?  We don't deal with negative values
1053     here, and we do kind of silly things like cast to unsigned.  */
1054  LONGEST n = 0;
1055  LONGEST prevn = 0;
1056  ULONGEST un;
1057
1058  int i = 0;
1059  int c;
1060  int base = input_radix;
1061  int unsigned_p = 0;
1062
1063  /* Number of "L" suffixes encountered.  */
1064  int long_p = 0;
1065
1066  /* We have found a "L" or "U" suffix.  */
1067  int found_suffix = 0;
1068
1069  ULONGEST high_bit;
1070  struct type *signed_type;
1071  struct type *unsigned_type;
1072
1073  if (parsed_float)
1074    {
1075      /* It's a float since it contains a point or an exponent.  */
1076      char c;
1077      int num = 0;	/* number of tokens scanned by scanf */
1078      char saved_char = p[len];
1079
1080      p[len] = 0;	/* null-terminate the token */
1081      if (sizeof (putithere->typed_val_float.dval) <= sizeof (float))
1082	num = sscanf (p, "%g%c", (float *) &putithere->typed_val_float.dval,&c);
1083      else if (sizeof (putithere->typed_val_float.dval) <= sizeof (double))
1084	num = sscanf (p, "%lg%c", (double *) &putithere->typed_val_float.dval,&c);
1085      else
1086	{
1087#ifdef SCANF_HAS_LONG_DOUBLE
1088	  num = sscanf (p, "%Lg%c", &putithere->typed_val_float.dval,&c);
1089#else
1090	  /* Scan it into a double, then assign it to the long double.
1091	     This at least wins with values representable in the range
1092	     of doubles. */
1093	  double temp;
1094	  num = sscanf (p, "%lg%c", &temp,&c);
1095	  putithere->typed_val_float.dval = temp;
1096#endif
1097	}
1098      p[len] = saved_char;	/* restore the input stream */
1099      if (num != 1) 		/* check scanf found ONLY a float ... */
1100	return ERROR;
1101      /* See if it has `f' or `l' suffix (float or long double).  */
1102
1103      c = tolower (p[len - 1]);
1104
1105      if (c == 'f')
1106	putithere->typed_val_float.type = builtin_type_float;
1107      else if (c == 'l')
1108	putithere->typed_val_float.type = builtin_type_long_double;
1109      else if (isdigit (c) || c == '.')
1110	putithere->typed_val_float.type = builtin_type_double;
1111      else
1112	return ERROR;
1113
1114      return FLOAT;
1115    }
1116
1117  /* Handle base-switching prefixes 0x, 0t, 0d, 0 */
1118  if (p[0] == '0')
1119    switch (p[1])
1120      {
1121      case 'x':
1122      case 'X':
1123	if (len >= 3)
1124	  {
1125	    p += 2;
1126	    base = 16;
1127	    len -= 2;
1128	  }
1129	break;
1130
1131      case 't':
1132      case 'T':
1133      case 'd':
1134      case 'D':
1135	if (len >= 3)
1136	  {
1137	    p += 2;
1138	    base = 10;
1139	    len -= 2;
1140	  }
1141	break;
1142
1143      default:
1144	base = 8;
1145	break;
1146      }
1147
1148  while (len-- > 0)
1149    {
1150      c = *p++;
1151      if (c >= 'A' && c <= 'Z')
1152	c += 'a' - 'A';
1153      if (c != 'l' && c != 'u')
1154	n *= base;
1155      if (c >= '0' && c <= '9')
1156	{
1157	  if (found_suffix)
1158	    return ERROR;
1159	  n += i = c - '0';
1160	}
1161      else
1162	{
1163	  if (base > 10 && c >= 'a' && c <= 'f')
1164	    {
1165	      if (found_suffix)
1166		return ERROR;
1167	      n += i = c - 'a' + 10;
1168	    }
1169	  else if (c == 'l')
1170	    {
1171	      ++long_p;
1172	      found_suffix = 1;
1173	    }
1174	  else if (c == 'u')
1175	    {
1176	      unsigned_p = 1;
1177	      found_suffix = 1;
1178	    }
1179	  else
1180	    return ERROR;	/* Char not a digit */
1181	}
1182      if (i >= base)
1183	return ERROR;		/* Invalid digit in this base */
1184
1185      /* Portably test for overflow (only works for nonzero values, so make
1186	 a second check for zero).  FIXME: Can't we just make n and prevn
1187	 unsigned and avoid this?  */
1188      if (c != 'l' && c != 'u' && (prevn >= n) && n != 0)
1189	unsigned_p = 1;		/* Try something unsigned */
1190
1191      /* Portably test for unsigned overflow.
1192	 FIXME: This check is wrong; for example it doesn't find overflow
1193	 on 0x123456789 when LONGEST is 32 bits.  */
1194      if (c != 'l' && c != 'u' && n != 0)
1195	{
1196	  if ((unsigned_p && (ULONGEST) prevn >= (ULONGEST) n))
1197	    error ("Numeric constant too large.");
1198	}
1199      prevn = n;
1200    }
1201
1202  /* An integer constant is an int, a long, or a long long.  An L
1203     suffix forces it to be long; an LL suffix forces it to be long
1204     long.  If not forced to a larger size, it gets the first type of
1205     the above that it fits in.  To figure out whether it fits, we
1206     shift it right and see whether anything remains.  Note that we
1207     can't shift sizeof (LONGEST) * HOST_CHAR_BIT bits or more in one
1208     operation, because many compilers will warn about such a shift
1209     (which always produces a zero result).  Sometimes TARGET_INT_BIT
1210     or TARGET_LONG_BIT will be that big, sometimes not.  To deal with
1211     the case where it is we just always shift the value more than
1212     once, with fewer bits each time.  */
1213
1214  un = (ULONGEST)n >> 2;
1215  if (long_p == 0
1216      && (un >> (TARGET_INT_BIT - 2)) == 0)
1217    {
1218      high_bit = ((ULONGEST)1) << (TARGET_INT_BIT-1);
1219
1220      /* A large decimal (not hex or octal) constant (between INT_MAX
1221	 and UINT_MAX) is a long or unsigned long, according to ANSI,
1222	 never an unsigned int, but this code treats it as unsigned
1223	 int.  This probably should be fixed.  GCC gives a warning on
1224	 such constants.  */
1225
1226      unsigned_type = builtin_type_unsigned_int;
1227      signed_type = builtin_type_int;
1228    }
1229  else if (long_p <= 1
1230	   && (un >> (TARGET_LONG_BIT - 2)) == 0)
1231    {
1232      high_bit = ((ULONGEST)1) << (TARGET_LONG_BIT-1);
1233      unsigned_type = builtin_type_unsigned_long;
1234      signed_type = builtin_type_long;
1235    }
1236  else
1237    {
1238      int shift;
1239      if (sizeof (ULONGEST) * HOST_CHAR_BIT < TARGET_LONG_LONG_BIT)
1240	/* A long long does not fit in a LONGEST.  */
1241	shift = (sizeof (ULONGEST) * HOST_CHAR_BIT - 1);
1242      else
1243	shift = (TARGET_LONG_LONG_BIT - 1);
1244      high_bit = (ULONGEST) 1 << shift;
1245      unsigned_type = builtin_type_unsigned_long_long;
1246      signed_type = builtin_type_long_long;
1247    }
1248
1249   putithere->typed_val_int.val = n;
1250
1251   /* If the high bit of the worked out type is set then this number
1252      has to be unsigned. */
1253
1254   if (unsigned_p || (n & high_bit))
1255     {
1256       putithere->typed_val_int.type = unsigned_type;
1257     }
1258   else
1259     {
1260       putithere->typed_val_int.type = signed_type;
1261     }
1262
1263   return INT;
1264}
1265
1266struct token
1267{
1268  char *operator;
1269  int token;
1270  enum exp_opcode opcode;
1271};
1272
1273static const struct token tokentab3[] =
1274  {
1275    {">>=", ASSIGN_MODIFY, BINOP_RSH},
1276    {"<<=", ASSIGN_MODIFY, BINOP_LSH}
1277  };
1278
1279static const struct token tokentab2[] =
1280  {
1281    {"+=", ASSIGN_MODIFY, BINOP_ADD},
1282    {"-=", ASSIGN_MODIFY, BINOP_SUB},
1283    {"*=", ASSIGN_MODIFY, BINOP_MUL},
1284    {"/=", ASSIGN_MODIFY, BINOP_DIV},
1285    {"%=", ASSIGN_MODIFY, BINOP_REM},
1286    {"|=", ASSIGN_MODIFY, BINOP_BITWISE_IOR},
1287    {"&=", ASSIGN_MODIFY, BINOP_BITWISE_AND},
1288    {"^=", ASSIGN_MODIFY, BINOP_BITWISE_XOR},
1289    {"++", INCREMENT, BINOP_END},
1290    {"--", DECREMENT, BINOP_END},
1291    {"->", ARROW, BINOP_END},
1292    {"&&", ANDAND, BINOP_END},
1293    {"||", OROR, BINOP_END},
1294    {"::", COLONCOLON, BINOP_END},
1295    {"<<", LSH, BINOP_END},
1296    {">>", RSH, BINOP_END},
1297    {"==", EQUAL, BINOP_END},
1298    {"!=", NOTEQUAL, BINOP_END},
1299    {"<=", LEQ, BINOP_END},
1300    {">=", GEQ, BINOP_END}
1301  };
1302
1303/* Read one token, getting characters through lexptr.  */
1304
1305static int
1306yylex ()
1307{
1308  int c;
1309  int namelen;
1310  unsigned int i;
1311  char *tokstart;
1312  char *tokptr;
1313  int tempbufindex;
1314  static char *tempbuf;
1315  static int tempbufsize;
1316  struct symbol * sym_class = NULL;
1317  char * token_string = NULL;
1318  int class_prefix = 0;
1319  int unquoted_expr;
1320
1321 retry:
1322
1323  /* Check if this is a macro invocation that we need to expand.  */
1324  if (! scanning_macro_expansion ())
1325    {
1326      char *expanded = macro_expand_next (&lexptr,
1327                                          expression_macro_lookup_func,
1328                                          expression_macro_lookup_baton);
1329
1330      if (expanded)
1331        scan_macro_expansion (expanded);
1332    }
1333
1334  prev_lexptr = lexptr;
1335  unquoted_expr = 1;
1336
1337  tokstart = lexptr;
1338  /* See if it is a special token of length 3.  */
1339  for (i = 0; i < sizeof tokentab3 / sizeof tokentab3[0]; i++)
1340    if (strncmp (tokstart, tokentab3[i].operator, 3) == 0)
1341      {
1342	lexptr += 3;
1343	yylval.opcode = tokentab3[i].opcode;
1344	return tokentab3[i].token;
1345      }
1346
1347  /* See if it is a special token of length 2.  */
1348  for (i = 0; i < sizeof tokentab2 / sizeof tokentab2[0]; i++)
1349    if (strncmp (tokstart, tokentab2[i].operator, 2) == 0)
1350      {
1351	lexptr += 2;
1352	yylval.opcode = tokentab2[i].opcode;
1353	return tokentab2[i].token;
1354      }
1355
1356  switch (c = *tokstart)
1357    {
1358    case 0:
1359      /* If we were just scanning the result of a macro expansion,
1360         then we need to resume scanning the original text.
1361         Otherwise, we were already scanning the original text, and
1362         we're really done.  */
1363      if (scanning_macro_expansion ())
1364        {
1365          finished_macro_expansion ();
1366          goto retry;
1367        }
1368      else
1369        return 0;
1370
1371    case ' ':
1372    case '\t':
1373    case '\n':
1374      lexptr++;
1375      goto retry;
1376
1377    case '\'':
1378      /* We either have a character constant ('0' or '\177' for example)
1379	 or we have a quoted symbol reference ('foo(int,int)' in C++
1380	 for example). */
1381      lexptr++;
1382      c = *lexptr++;
1383      if (c == '\\')
1384	c = parse_escape (&lexptr);
1385      else if (c == '\'')
1386	error ("Empty character constant.");
1387      else if (! host_char_to_target (c, &c))
1388        {
1389          int toklen = lexptr - tokstart + 1;
1390          char *tok = alloca (toklen + 1);
1391          memcpy (tok, tokstart, toklen);
1392          tok[toklen] = '\0';
1393          error ("There is no character corresponding to %s in the target "
1394                 "character set `%s'.", tok, target_charset ());
1395        }
1396
1397      yylval.typed_val_int.val = c;
1398      yylval.typed_val_int.type = builtin_type_char;
1399
1400      c = *lexptr++;
1401      if (c != '\'')
1402	{
1403	  namelen = skip_quoted (tokstart) - tokstart;
1404	  if (namelen > 2)
1405	    {
1406	      lexptr = tokstart + namelen;
1407              unquoted_expr = 0;
1408	      if (lexptr[-1] != '\'')
1409		error ("Unmatched single quote.");
1410	      namelen -= 2;
1411	      tokstart++;
1412	      goto tryname;
1413	    }
1414	  error ("Invalid character constant.");
1415	}
1416      return INT;
1417
1418    case '(':
1419      paren_depth++;
1420      lexptr++;
1421      return c;
1422
1423    case ')':
1424      if (paren_depth == 0)
1425	return 0;
1426      paren_depth--;
1427      lexptr++;
1428      return c;
1429
1430    case ',':
1431      if (comma_terminates
1432          && paren_depth == 0
1433          && ! scanning_macro_expansion ())
1434	return 0;
1435      lexptr++;
1436      return c;
1437
1438    case '.':
1439      /* Might be a floating point number.  */
1440      if (lexptr[1] < '0' || lexptr[1] > '9')
1441	goto symbol;		/* Nope, must be a symbol. */
1442      /* FALL THRU into number case.  */
1443
1444    case '0':
1445    case '1':
1446    case '2':
1447    case '3':
1448    case '4':
1449    case '5':
1450    case '6':
1451    case '7':
1452    case '8':
1453    case '9':
1454      {
1455	/* It's a number.  */
1456	int got_dot = 0, got_e = 0, toktype;
1457	char *p = tokstart;
1458	int hex = input_radix > 10;
1459
1460	if (c == '0' && (p[1] == 'x' || p[1] == 'X'))
1461	  {
1462	    p += 2;
1463	    hex = 1;
1464	  }
1465	else if (c == '0' && (p[1]=='t' || p[1]=='T' || p[1]=='d' || p[1]=='D'))
1466	  {
1467	    p += 2;
1468	    hex = 0;
1469	  }
1470
1471	for (;; ++p)
1472	  {
1473	    /* This test includes !hex because 'e' is a valid hex digit
1474	       and thus does not indicate a floating point number when
1475	       the radix is hex.  */
1476	    if (!hex && !got_e && (*p == 'e' || *p == 'E'))
1477	      got_dot = got_e = 1;
1478	    /* This test does not include !hex, because a '.' always indicates
1479	       a decimal floating point number regardless of the radix.  */
1480	    else if (!got_dot && *p == '.')
1481	      got_dot = 1;
1482	    else if (got_e && (p[-1] == 'e' || p[-1] == 'E')
1483		     && (*p == '-' || *p == '+'))
1484	      /* This is the sign of the exponent, not the end of the
1485		 number.  */
1486	      continue;
1487	    /* We will take any letters or digits.  parse_number will
1488	       complain if past the radix, or if L or U are not final.  */
1489	    else if ((*p < '0' || *p > '9')
1490		     && ((*p < 'a' || *p > 'z')
1491				  && (*p < 'A' || *p > 'Z')))
1492	      break;
1493	  }
1494	toktype = parse_number (tokstart, p - tokstart, got_dot|got_e, &yylval);
1495        if (toktype == ERROR)
1496	  {
1497	    char *err_copy = (char *) alloca (p - tokstart + 1);
1498
1499	    memcpy (err_copy, tokstart, p - tokstart);
1500	    err_copy[p - tokstart] = 0;
1501	    error ("Invalid number \"%s\".", err_copy);
1502	  }
1503	lexptr = p;
1504	return toktype;
1505      }
1506
1507    case '+':
1508    case '-':
1509    case '*':
1510    case '/':
1511    case '%':
1512    case '|':
1513    case '&':
1514    case '^':
1515    case '~':
1516    case '!':
1517    case '@':
1518    case '<':
1519    case '>':
1520    case '[':
1521    case ']':
1522    case '?':
1523    case ':':
1524    case '=':
1525    case '{':
1526    case '}':
1527    symbol:
1528      lexptr++;
1529      return c;
1530
1531    case '"':
1532
1533      /* Build the gdb internal form of the input string in tempbuf,
1534	 translating any standard C escape forms seen.  Note that the
1535	 buffer is null byte terminated *only* for the convenience of
1536	 debugging gdb itself and printing the buffer contents when
1537	 the buffer contains no embedded nulls.  Gdb does not depend
1538	 upon the buffer being null byte terminated, it uses the length
1539	 string instead.  This allows gdb to handle C strings (as well
1540	 as strings in other languages) with embedded null bytes */
1541
1542      tokptr = ++tokstart;
1543      tempbufindex = 0;
1544
1545      do {
1546        char *char_start_pos = tokptr;
1547
1548	/* Grow the static temp buffer if necessary, including allocating
1549	   the first one on demand. */
1550	if (tempbufindex + 1 >= tempbufsize)
1551	  {
1552	    tempbuf = (char *) realloc (tempbuf, tempbufsize += 64);
1553	  }
1554	switch (*tokptr)
1555	  {
1556	  case '\0':
1557	  case '"':
1558	    /* Do nothing, loop will terminate. */
1559	    break;
1560	  case '\\':
1561	    tokptr++;
1562	    c = parse_escape (&tokptr);
1563	    if (c == -1)
1564	      {
1565		continue;
1566	      }
1567	    tempbuf[tempbufindex++] = c;
1568	    break;
1569	  default:
1570	    c = *tokptr++;
1571            if (! host_char_to_target (c, &c))
1572              {
1573                int len = tokptr - char_start_pos;
1574                char *copy = alloca (len + 1);
1575                memcpy (copy, char_start_pos, len);
1576                copy[len] = '\0';
1577
1578                error ("There is no character corresponding to `%s' "
1579                       "in the target character set `%s'.",
1580                       copy, target_charset ());
1581              }
1582            tempbuf[tempbufindex++] = c;
1583	    break;
1584	  }
1585      } while ((*tokptr != '"') && (*tokptr != '\0'));
1586      if (*tokptr++ != '"')
1587	{
1588	  error ("Unterminated string in expression.");
1589	}
1590      tempbuf[tempbufindex] = '\0';	/* See note above */
1591      yylval.sval.ptr = tempbuf;
1592      yylval.sval.length = tempbufindex;
1593      lexptr = tokptr;
1594      return (STRING);
1595    }
1596
1597  if (!(c == '_' || c == '$'
1598	|| (c >= 'a' && c <= 'z') || (c >= 'A' && c <= 'Z')))
1599    /* We must have come across a bad character (e.g. ';').  */
1600    error ("Invalid character '%c' in expression.", c);
1601
1602  /* It's a name.  See how long it is.  */
1603  namelen = 0;
1604  for (c = tokstart[namelen];
1605       (c == '_' || c == '$' || (c >= '0' && c <= '9')
1606	|| (c >= 'a' && c <= 'z') || (c >= 'A' && c <= 'Z') || c == '<');)
1607    {
1608      /* Template parameter lists are part of the name.
1609	 FIXME: This mishandles `print $a<4&&$a>3'.  */
1610
1611      if (c == '<')
1612	{
1613               /* Scan ahead to get rest of the template specification.  Note
1614                  that we look ahead only when the '<' adjoins non-whitespace
1615                  characters; for comparison expressions, e.g. "a < b > c",
1616                  there must be spaces before the '<', etc. */
1617
1618               char * p = find_template_name_end (tokstart + namelen);
1619               if (p)
1620                 namelen = p - tokstart;
1621               break;
1622	}
1623      c = tokstart[++namelen];
1624    }
1625
1626  /* The token "if" terminates the expression and is NOT removed from
1627     the input stream.  It doesn't count if it appears in the
1628     expansion of a macro.  */
1629  if (namelen == 2
1630      && tokstart[0] == 'i'
1631      && tokstart[1] == 'f'
1632      && ! scanning_macro_expansion ())
1633    {
1634      return 0;
1635    }
1636
1637  lexptr += namelen;
1638
1639  tryname:
1640
1641  /* Catch specific keywords.  Should be done with a data structure.  */
1642  switch (namelen)
1643    {
1644    case 8:
1645      if (strncmp (tokstart, "unsigned", 8) == 0)
1646	return UNSIGNED;
1647      if (current_language->la_language == language_cplus
1648	  && strncmp (tokstart, "template", 8) == 0)
1649	return TEMPLATE;
1650      if (strncmp (tokstart, "volatile", 8) == 0)
1651	return VOLATILE_KEYWORD;
1652      break;
1653    case 6:
1654      if (strncmp (tokstart, "struct", 6) == 0)
1655	return STRUCT;
1656      if (strncmp (tokstart, "signed", 6) == 0)
1657	return SIGNED_KEYWORD;
1658      if (strncmp (tokstart, "sizeof", 6) == 0)
1659	return SIZEOF;
1660      if (strncmp (tokstart, "double", 6) == 0)
1661	return DOUBLE_KEYWORD;
1662      break;
1663    case 5:
1664      if (current_language->la_language == language_cplus)
1665        {
1666          if (strncmp (tokstart, "false", 5) == 0)
1667            return FALSEKEYWORD;
1668          if (strncmp (tokstart, "class", 5) == 0)
1669            return CLASS;
1670        }
1671      if (strncmp (tokstart, "union", 5) == 0)
1672	return UNION;
1673      if (strncmp (tokstart, "short", 5) == 0)
1674	return SHORT;
1675      if (strncmp (tokstart, "const", 5) == 0)
1676	return CONST_KEYWORD;
1677      break;
1678    case 4:
1679      if (strncmp (tokstart, "enum", 4) == 0)
1680	return ENUM;
1681      if (strncmp (tokstart, "long", 4) == 0)
1682	return LONG;
1683      if (current_language->la_language == language_cplus)
1684          {
1685            if (strncmp (tokstart, "true", 4) == 0)
1686              return TRUEKEYWORD;
1687          }
1688      break;
1689    case 3:
1690      if (strncmp (tokstart, "int", 3) == 0)
1691	return INT_KEYWORD;
1692      break;
1693    default:
1694      break;
1695    }
1696
1697  yylval.sval.ptr = tokstart;
1698  yylval.sval.length = namelen;
1699
1700  if (*tokstart == '$')
1701    {
1702      write_dollar_variable (yylval.sval);
1703      return VARIABLE;
1704    }
1705
1706  /* Look ahead and see if we can consume more of the input
1707     string to get a reasonable class/namespace spec or a
1708     fully-qualified name.  This is a kludge to get around the
1709     HP aCC compiler's generation of symbol names with embedded
1710     colons for namespace and nested classes. */
1711
1712  /* NOTE: carlton/2003-09-24: I don't entirely understand the
1713     HP-specific code, either here or in linespec.  Having said that,
1714     I suspect that we're actually moving towards their model: we want
1715     symbols whose names are fully qualified, which matches the
1716     description above.  */
1717  if (unquoted_expr)
1718    {
1719      /* Only do it if not inside single quotes */
1720      sym_class = parse_nested_classes_for_hpacc (yylval.sval.ptr, yylval.sval.length,
1721                                                  &token_string, &class_prefix, &lexptr);
1722      if (sym_class)
1723        {
1724          /* Replace the current token with the bigger one we found */
1725          yylval.sval.ptr = token_string;
1726          yylval.sval.length = strlen (token_string);
1727        }
1728    }
1729
1730  /* Use token-type BLOCKNAME for symbols that happen to be defined as
1731     functions or symtabs.  If this is not so, then ...
1732     Use token-type TYPENAME for symbols that happen to be defined
1733     currently as names of types; NAME for other symbols.
1734     The caller is not constrained to care about the distinction.  */
1735  {
1736    char *tmp = copy_name (yylval.sval);
1737    struct symbol *sym;
1738    int is_a_field_of_this = 0;
1739    int hextype;
1740
1741    sym = lookup_symbol (tmp, expression_context_block,
1742			 VAR_DOMAIN,
1743			 current_language->la_language == language_cplus
1744			 ? &is_a_field_of_this : (int *) NULL,
1745			 (struct symtab **) NULL);
1746    /* Call lookup_symtab, not lookup_partial_symtab, in case there are
1747       no psymtabs (coff, xcoff, or some future change to blow away the
1748       psymtabs once once symbols are read).  */
1749    if (sym && SYMBOL_CLASS (sym) == LOC_BLOCK)
1750      {
1751	yylval.ssym.sym = sym;
1752	yylval.ssym.is_a_field_of_this = is_a_field_of_this;
1753	return BLOCKNAME;
1754      }
1755    else if (!sym)
1756      {				/* See if it's a file name. */
1757	struct symtab *symtab;
1758
1759	symtab = lookup_symtab (tmp);
1760
1761	if (symtab)
1762	  {
1763	    yylval.bval = BLOCKVECTOR_BLOCK (BLOCKVECTOR (symtab), STATIC_BLOCK);
1764	    return FILENAME;
1765	  }
1766      }
1767
1768    if (sym && SYMBOL_CLASS (sym) == LOC_TYPEDEF)
1769        {
1770	  /* NOTE: carlton/2003-09-25: There used to be code here to
1771	     handle nested types.  It didn't work very well.  See the
1772	     comment before qualified_type for more info.  */
1773	  yylval.tsym.type = SYMBOL_TYPE (sym);
1774	  return TYPENAME;
1775        }
1776    if ((yylval.tsym.type = lookup_primitive_typename (tmp)) != 0)
1777      return TYPENAME;
1778
1779    /* Input names that aren't symbols but ARE valid hex numbers,
1780       when the input radix permits them, can be names or numbers
1781       depending on the parse.  Note we support radixes > 16 here.  */
1782    if (!sym &&
1783        ((tokstart[0] >= 'a' && tokstart[0] < 'a' + input_radix - 10) ||
1784         (tokstart[0] >= 'A' && tokstart[0] < 'A' + input_radix - 10)))
1785      {
1786 	YYSTYPE newlval;	/* Its value is ignored.  */
1787	hextype = parse_number (tokstart, namelen, 0, &newlval);
1788	if (hextype == INT)
1789	  {
1790	    yylval.ssym.sym = sym;
1791	    yylval.ssym.is_a_field_of_this = is_a_field_of_this;
1792	    return NAME_OR_INT;
1793	  }
1794      }
1795
1796    /* Any other kind of symbol */
1797    yylval.ssym.sym = sym;
1798    yylval.ssym.is_a_field_of_this = is_a_field_of_this;
1799    return NAME;
1800  }
1801}
1802
1803void
1804yyerror (msg)
1805     char *msg;
1806{
1807  if (prev_lexptr)
1808    lexptr = prev_lexptr;
1809
1810  error ("A %s in expression, near `%s'.", (msg ? msg : "error"), lexptr);
1811}
1812