1/* YACC parser for C expressions, for GDB.
2   Copyright 1986, 1989, 1990, 1991, 1992, 1993, 1994, 1995, 1996, 1997,
3   1998, 1999, 2000, 2003, 2004
4   Free Software Foundation, Inc.
5
6This file is part of GDB.
7
8This program is free software; you can redistribute it and/or modify
9it under the terms of the GNU General Public License as published by
10the Free Software Foundation; either version 2 of the License, or
11(at your option) any later version.
12
13This program is distributed in the hope that it will be useful,
14but WITHOUT ANY WARRANTY; without even the implied warranty of
15MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE.  See the
16GNU General Public License for more details.
17
18You should have received a copy of the GNU General Public License
19along with this program; if not, write to the Free Software
20Foundation, Inc., 59 Temple Place - Suite 330, Boston, MA 02111-1307, USA.  */
21
22/* Parse a C expression from text in a string,
23   and return the result as a  struct expression  pointer.
24   That structure contains arithmetic operations in reverse polish,
25   with constants represented by operations that are followed by special data.
26   See expression.h for the details of the format.
27   What is important here is that it can be built up sequentially
28   during the process of parsing; the lower levels of the tree always
29   come first in the result.
30
31   Note that malloc's and realloc's in this file are transformed to
32   xmalloc and xrealloc respectively by the same sed command in the
33   makefile that remaps any other malloc/realloc inserted by the parser
34   generator.  Doing this with #defines and trying to control the interaction
35   with include files (<malloc.h> and <stdlib.h> for example) just became
36   too messy, particularly when such includes can be inserted at random
37   times by the parser generator.  */
38
39%{
40
41#include "defs.h"
42#include "gdb_string.h"
43#include <ctype.h>
44#include "expression.h"
45#include "value.h"
46#include "parser-defs.h"
47#include "language.h"
48#include "c-lang.h"
49#include "bfd.h" /* Required by objfiles.h.  */
50#include "symfile.h" /* Required by objfiles.h.  */
51#include "objfiles.h" /* For have_full_symbols and have_partial_symbols */
52#include "charset.h"
53#include "block.h"
54#include "cp-support.h"
55
56/* Remap normal yacc parser interface names (yyparse, yylex, yyerror, etc),
57   as well as gratuitiously global symbol names, so we can have multiple
58   yacc generated parsers in gdb.  Note that these are only the variables
59   produced by yacc.  If other parser generators (bison, byacc, etc) produce
60   additional global names that conflict at link time, then those parser
61   generators need to be fixed instead of adding those names to this list. */
62
63#define	yymaxdepth c_maxdepth
64#define	yyparse	c_parse
65#define	yylex	c_lex
66#define	yyerror	c_error
67#define	yylval	c_lval
68#define	yychar	c_char
69#define	yydebug	c_debug
70#define	yypact	c_pact
71#define	yyr1	c_r1
72#define	yyr2	c_r2
73#define	yydef	c_def
74#define	yychk	c_chk
75#define	yypgo	c_pgo
76#define	yyact	c_act
77#define	yyexca	c_exca
78#define yyerrflag c_errflag
79#define yynerrs	c_nerrs
80#define	yyps	c_ps
81#define	yypv	c_pv
82#define	yys	c_s
83#define	yy_yys	c_yys
84#define	yystate	c_state
85#define	yytmp	c_tmp
86#define	yyv	c_v
87#define	yy_yyv	c_yyv
88#define	yyval	c_val
89#define	yylloc	c_lloc
90#define yyreds	c_reds		/* With YYDEBUG defined */
91#define yytoks	c_toks		/* With YYDEBUG defined */
92#define yyname	c_name		/* With YYDEBUG defined */
93#define yyrule	c_rule		/* With YYDEBUG defined */
94#define yylhs	c_yylhs
95#define yylen	c_yylen
96#define yydefred c_yydefred
97#define yydgoto	c_yydgoto
98#define yysindex c_yysindex
99#define yyrindex c_yyrindex
100#define yygindex c_yygindex
101#define yytable	 c_yytable
102#define yycheck	 c_yycheck
103
104#ifndef YYDEBUG
105#define	YYDEBUG 1		/* Default to yydebug support */
106#endif
107
108#define YYFPRINTF parser_fprintf
109
110int yyparse (void);
111
112static int yylex (void);
113
114void yyerror (char *);
115
116%}
117
118/* Although the yacc "value" of an expression is not used,
119   since the result is stored in the structure being created,
120   other node types do have values.  */
121
122%union
123  {
124    LONGEST lval;
125    struct {
126      LONGEST val;
127      struct type *type;
128    } typed_val_int;
129    struct {
130      DOUBLEST dval;
131      struct type *type;
132    } typed_val_float;
133    struct symbol *sym;
134    struct type *tval;
135    struct stoken sval;
136    struct ttype tsym;
137    struct symtoken ssym;
138    int voidval;
139    struct block *bval;
140    enum exp_opcode opcode;
141    struct internalvar *ivar;
142
143    struct type **tvec;
144    int *ivec;
145  }
146
147%{
148/* YYSTYPE gets defined by %union */
149static int parse_number (char *, int, int, YYSTYPE *);
150%}
151
152%type <voidval> exp exp1 type_exp start variable qualified_name lcurly
153%type <lval> rcurly
154%type <tval> type typebase qualified_type
155%type <tvec> nonempty_typelist
156/* %type <bval> block */
157
158/* Fancy type parsing.  */
159%type <voidval> func_mod direct_abs_decl abs_decl
160%type <tval> ptype
161%type <lval> array_mod
162
163%token <typed_val_int> INT
164%token <typed_val_float> FLOAT
165
166/* Both NAME and TYPENAME tokens represent symbols in the input,
167   and both convey their data as strings.
168   But a TYPENAME is a string that happens to be defined as a typedef
169   or builtin type name (such as int or char)
170   and a NAME is any other symbol.
171   Contexts where this distinction is not important can use the
172   nonterminal "name", which matches either NAME or TYPENAME.  */
173
174%token <sval> STRING
175%token <ssym> NAME /* BLOCKNAME defined below to give it higher precedence. */
176%token <tsym> TYPENAME
177%type <sval> name
178%type <ssym> name_not_typename
179%type <tsym> typename
180
181/* A NAME_OR_INT is a symbol which is not known in the symbol table,
182   but which would parse as a valid number in the current input radix.
183   E.g. "c" when input_radix==16.  Depending on the parse, it will be
184   turned into a name or into a number.  */
185
186%token <ssym> NAME_OR_INT
187
188%token STRUCT CLASS UNION ENUM SIZEOF UNSIGNED COLONCOLON
189%token TEMPLATE
190%token ERROR
191
192/* Special type cases, put in to allow the parser to distinguish different
193   legal basetypes.  */
194%token SIGNED_KEYWORD LONG SHORT INT_KEYWORD CONST_KEYWORD VOLATILE_KEYWORD DOUBLE_KEYWORD
195
196%token <voidval> VARIABLE
197
198%token <opcode> ASSIGN_MODIFY
199
200/* C++ */
201%token TRUEKEYWORD
202%token FALSEKEYWORD
203
204
205%left ','
206%left ABOVE_COMMA
207%right '=' ASSIGN_MODIFY
208%right '?'
209%left OROR
210%left ANDAND
211%left '|'
212%left '^'
213%left '&'
214%left EQUAL NOTEQUAL
215%left '<' '>' LEQ GEQ
216%left LSH RSH
217%left '@'
218%left '+' '-'
219%left '*' '/' '%'
220%right UNARY INCREMENT DECREMENT
221%right ARROW '.' '[' '('
222%token <ssym> BLOCKNAME
223%token <bval> FILENAME
224%type <bval> block
225%left COLONCOLON
226
227
228%%
229
230start   :	exp1
231	|	type_exp
232	;
233
234type_exp:	type
235			{ write_exp_elt_opcode(OP_TYPE);
236			  write_exp_elt_type($1);
237			  write_exp_elt_opcode(OP_TYPE);}
238	;
239
240/* Expressions, including the comma operator.  */
241exp1	:	exp
242	|	exp1 ',' exp
243			{ write_exp_elt_opcode (BINOP_COMMA); }
244	;
245
246/* Expressions, not including the comma operator.  */
247exp	:	'*' exp    %prec UNARY
248			{ write_exp_elt_opcode (UNOP_IND); }
249	;
250
251exp	:	'&' exp    %prec UNARY
252			{ write_exp_elt_opcode (UNOP_ADDR); }
253	;
254
255exp	:	'-' exp    %prec UNARY
256			{ write_exp_elt_opcode (UNOP_NEG); }
257	;
258
259exp	:	'!' exp    %prec UNARY
260			{ write_exp_elt_opcode (UNOP_LOGICAL_NOT); }
261	;
262
263exp	:	'~' exp    %prec UNARY
264			{ write_exp_elt_opcode (UNOP_COMPLEMENT); }
265	;
266
267exp	:	INCREMENT exp    %prec UNARY
268			{ write_exp_elt_opcode (UNOP_PREINCREMENT); }
269	;
270
271exp	:	DECREMENT exp    %prec UNARY
272			{ write_exp_elt_opcode (UNOP_PREDECREMENT); }
273	;
274
275exp	:	exp INCREMENT    %prec UNARY
276			{ write_exp_elt_opcode (UNOP_POSTINCREMENT); }
277	;
278
279exp	:	exp DECREMENT    %prec UNARY
280			{ write_exp_elt_opcode (UNOP_POSTDECREMENT); }
281	;
282
283exp	:	SIZEOF exp       %prec UNARY
284			{ write_exp_elt_opcode (UNOP_SIZEOF); }
285	;
286
287exp	:	exp ARROW name
288			{ write_exp_elt_opcode (STRUCTOP_PTR);
289			  write_exp_string ($3);
290			  write_exp_elt_opcode (STRUCTOP_PTR); }
291	;
292
293exp	:	exp ARROW qualified_name
294			{ /* exp->type::name becomes exp->*(&type::name) */
295			  /* Note: this doesn't work if name is a
296			     static member!  FIXME */
297			  write_exp_elt_opcode (UNOP_ADDR);
298			  write_exp_elt_opcode (STRUCTOP_MPTR); }
299	;
300
301exp	:	exp ARROW '*' exp
302			{ write_exp_elt_opcode (STRUCTOP_MPTR); }
303	;
304
305exp	:	exp '.' name
306			{ write_exp_elt_opcode (STRUCTOP_STRUCT);
307			  write_exp_string ($3);
308			  write_exp_elt_opcode (STRUCTOP_STRUCT); }
309	;
310
311exp	:	exp '.' qualified_name
312			{ /* exp.type::name becomes exp.*(&type::name) */
313			  /* Note: this doesn't work if name is a
314			     static member!  FIXME */
315			  write_exp_elt_opcode (UNOP_ADDR);
316			  write_exp_elt_opcode (STRUCTOP_MEMBER); }
317	;
318
319exp	:	exp '.' '*' exp
320			{ write_exp_elt_opcode (STRUCTOP_MEMBER); }
321	;
322
323exp	:	exp '[' exp1 ']'
324			{ write_exp_elt_opcode (BINOP_SUBSCRIPT); }
325	;
326
327exp	:	exp '('
328			/* This is to save the value of arglist_len
329			   being accumulated by an outer function call.  */
330			{ start_arglist (); }
331		arglist ')'	%prec ARROW
332			{ write_exp_elt_opcode (OP_FUNCALL);
333			  write_exp_elt_longcst ((LONGEST) end_arglist ());
334			  write_exp_elt_opcode (OP_FUNCALL); }
335	;
336
337lcurly	:	'{'
338			{ start_arglist (); }
339	;
340
341arglist	:
342	;
343
344arglist	:	exp
345			{ arglist_len = 1; }
346	;
347
348arglist	:	arglist ',' exp   %prec ABOVE_COMMA
349			{ arglist_len++; }
350	;
351
352rcurly	:	'}'
353			{ $$ = end_arglist () - 1; }
354	;
355exp	:	lcurly arglist rcurly	%prec ARROW
356			{ write_exp_elt_opcode (OP_ARRAY);
357			  write_exp_elt_longcst ((LONGEST) 0);
358			  write_exp_elt_longcst ((LONGEST) $3);
359			  write_exp_elt_opcode (OP_ARRAY); }
360	;
361
362exp	:	lcurly type rcurly exp  %prec UNARY
363			{ write_exp_elt_opcode (UNOP_MEMVAL);
364			  write_exp_elt_type ($2);
365			  write_exp_elt_opcode (UNOP_MEMVAL); }
366	;
367
368exp	:	'(' type ')' exp  %prec UNARY
369			{ write_exp_elt_opcode (UNOP_CAST);
370			  write_exp_elt_type ($2);
371			  write_exp_elt_opcode (UNOP_CAST); }
372	;
373
374exp	:	'(' exp1 ')'
375			{ }
376	;
377
378/* Binary operators in order of decreasing precedence.  */
379
380exp	:	exp '@' exp
381			{ write_exp_elt_opcode (BINOP_REPEAT); }
382	;
383
384exp	:	exp '*' exp
385			{ write_exp_elt_opcode (BINOP_MUL); }
386	;
387
388exp	:	exp '/' exp
389			{ write_exp_elt_opcode (BINOP_DIV); }
390	;
391
392exp	:	exp '%' exp
393			{ write_exp_elt_opcode (BINOP_REM); }
394	;
395
396exp	:	exp '+' exp
397			{ write_exp_elt_opcode (BINOP_ADD); }
398	;
399
400exp	:	exp '-' exp
401			{ write_exp_elt_opcode (BINOP_SUB); }
402	;
403
404exp	:	exp LSH exp
405			{ write_exp_elt_opcode (BINOP_LSH); }
406	;
407
408exp	:	exp RSH exp
409			{ write_exp_elt_opcode (BINOP_RSH); }
410	;
411
412exp	:	exp EQUAL exp
413			{ write_exp_elt_opcode (BINOP_EQUAL); }
414	;
415
416exp	:	exp NOTEQUAL exp
417			{ write_exp_elt_opcode (BINOP_NOTEQUAL); }
418	;
419
420exp	:	exp LEQ exp
421			{ write_exp_elt_opcode (BINOP_LEQ); }
422	;
423
424exp	:	exp GEQ exp
425			{ write_exp_elt_opcode (BINOP_GEQ); }
426	;
427
428exp	:	exp '<' exp
429			{ write_exp_elt_opcode (BINOP_LESS); }
430	;
431
432exp	:	exp '>' exp
433			{ write_exp_elt_opcode (BINOP_GTR); }
434	;
435
436exp	:	exp '&' exp
437			{ write_exp_elt_opcode (BINOP_BITWISE_AND); }
438	;
439
440exp	:	exp '^' exp
441			{ write_exp_elt_opcode (BINOP_BITWISE_XOR); }
442	;
443
444exp	:	exp '|' exp
445			{ write_exp_elt_opcode (BINOP_BITWISE_IOR); }
446	;
447
448exp	:	exp ANDAND exp
449			{ write_exp_elt_opcode (BINOP_LOGICAL_AND); }
450	;
451
452exp	:	exp OROR exp
453			{ write_exp_elt_opcode (BINOP_LOGICAL_OR); }
454	;
455
456exp	:	exp '?' exp ':' exp	%prec '?'
457			{ write_exp_elt_opcode (TERNOP_COND); }
458	;
459
460exp	:	exp '=' exp
461			{ write_exp_elt_opcode (BINOP_ASSIGN); }
462	;
463
464exp	:	exp ASSIGN_MODIFY exp
465			{ write_exp_elt_opcode (BINOP_ASSIGN_MODIFY);
466			  write_exp_elt_opcode ($2);
467			  write_exp_elt_opcode (BINOP_ASSIGN_MODIFY); }
468	;
469
470exp	:	INT
471			{ write_exp_elt_opcode (OP_LONG);
472			  write_exp_elt_type ($1.type);
473			  write_exp_elt_longcst ((LONGEST)($1.val));
474			  write_exp_elt_opcode (OP_LONG); }
475	;
476
477exp	:	NAME_OR_INT
478			{ YYSTYPE val;
479			  parse_number ($1.stoken.ptr, $1.stoken.length, 0, &val);
480			  write_exp_elt_opcode (OP_LONG);
481			  write_exp_elt_type (val.typed_val_int.type);
482			  write_exp_elt_longcst ((LONGEST)val.typed_val_int.val);
483			  write_exp_elt_opcode (OP_LONG);
484			}
485	;
486
487
488exp	:	FLOAT
489			{ write_exp_elt_opcode (OP_DOUBLE);
490			  write_exp_elt_type ($1.type);
491			  write_exp_elt_dblcst ($1.dval);
492			  write_exp_elt_opcode (OP_DOUBLE); }
493	;
494
495exp	:	variable
496	;
497
498exp	:	VARIABLE
499			/* Already written by write_dollar_variable. */
500	;
501
502exp	:	SIZEOF '(' type ')'	%prec UNARY
503			{ write_exp_elt_opcode (OP_LONG);
504			  write_exp_elt_type (builtin_type (current_gdbarch)->builtin_int);
505			  CHECK_TYPEDEF ($3);
506			  write_exp_elt_longcst ((LONGEST) TYPE_LENGTH ($3));
507			  write_exp_elt_opcode (OP_LONG); }
508	;
509
510exp	:	STRING
511			{ /* C strings are converted into array constants with
512			     an explicit null byte added at the end.  Thus
513			     the array upper bound is the string length.
514			     There is no such thing in C as a completely empty
515			     string. */
516			  char *sp = $1.ptr; int count = $1.length;
517			  while (count-- > 0)
518			    {
519			      write_exp_elt_opcode (OP_LONG);
520			      write_exp_elt_type (builtin_type (current_gdbarch)->builtin_char);
521			      write_exp_elt_longcst ((LONGEST)(*sp++));
522			      write_exp_elt_opcode (OP_LONG);
523			    }
524			  write_exp_elt_opcode (OP_LONG);
525			  write_exp_elt_type (builtin_type (current_gdbarch)->builtin_char);
526			  write_exp_elt_longcst ((LONGEST)'\0');
527			  write_exp_elt_opcode (OP_LONG);
528			  write_exp_elt_opcode (OP_ARRAY);
529			  write_exp_elt_longcst ((LONGEST) 0);
530			  write_exp_elt_longcst ((LONGEST) ($1.length));
531			  write_exp_elt_opcode (OP_ARRAY); }
532	;
533
534/* C++.  */
535exp     :       TRUEKEYWORD
536                        { write_exp_elt_opcode (OP_LONG);
537                          write_exp_elt_type (builtin_type (current_gdbarch)->builtin_bool);
538                          write_exp_elt_longcst ((LONGEST) 1);
539                          write_exp_elt_opcode (OP_LONG); }
540	;
541
542exp     :       FALSEKEYWORD
543                        { write_exp_elt_opcode (OP_LONG);
544                          write_exp_elt_type (builtin_type (current_gdbarch)->builtin_bool);
545                          write_exp_elt_longcst ((LONGEST) 0);
546                          write_exp_elt_opcode (OP_LONG); }
547	;
548
549/* end of C++.  */
550
551block	:	BLOCKNAME
552			{
553			  if ($1.sym)
554			    $$ = SYMBOL_BLOCK_VALUE ($1.sym);
555			  else
556			    error ("No file or function \"%s\".",
557				   copy_name ($1.stoken));
558			}
559	|	FILENAME
560			{
561			  $$ = $1;
562			}
563	;
564
565block	:	block COLONCOLON name
566			{ struct symbol *tem
567			    = lookup_symbol (copy_name ($3), $1,
568					     VAR_DOMAIN, (int *) NULL,
569					     (struct symtab **) NULL);
570			  if (!tem || SYMBOL_CLASS (tem) != LOC_BLOCK)
571			    error ("No function \"%s\" in specified context.",
572				   copy_name ($3));
573			  $$ = SYMBOL_BLOCK_VALUE (tem); }
574	;
575
576variable:	block COLONCOLON name
577			{ struct symbol *sym;
578			  sym = lookup_symbol (copy_name ($3), $1,
579					       VAR_DOMAIN, (int *) NULL,
580					       (struct symtab **) NULL);
581			  if (sym == 0)
582			    error ("No symbol \"%s\" in specified context.",
583				   copy_name ($3));
584
585			  write_exp_elt_opcode (OP_VAR_VALUE);
586			  /* block_found is set by lookup_symbol.  */
587			  write_exp_elt_block (block_found);
588			  write_exp_elt_sym (sym);
589			  write_exp_elt_opcode (OP_VAR_VALUE); }
590	;
591
592qualified_name:	typebase COLONCOLON name
593			{
594			  struct type *type = $1;
595			  if (TYPE_CODE (type) != TYPE_CODE_STRUCT
596			      && TYPE_CODE (type) != TYPE_CODE_UNION
597			      && TYPE_CODE (type) != TYPE_CODE_NAMESPACE)
598			    error ("`%s' is not defined as an aggregate type.",
599				   TYPE_NAME (type));
600
601			  write_exp_elt_opcode (OP_SCOPE);
602			  write_exp_elt_type (type);
603			  write_exp_string ($3);
604			  write_exp_elt_opcode (OP_SCOPE);
605			}
606	|	typebase COLONCOLON '~' name
607			{
608			  struct type *type = $1;
609			  struct stoken tmp_token;
610			  if (TYPE_CODE (type) != TYPE_CODE_STRUCT
611			      && TYPE_CODE (type) != TYPE_CODE_UNION
612			      && TYPE_CODE (type) != TYPE_CODE_NAMESPACE)
613			    error ("`%s' is not defined as an aggregate type.",
614				   TYPE_NAME (type));
615
616			  tmp_token.ptr = (char*) alloca ($4.length + 2);
617			  tmp_token.length = $4.length + 1;
618			  tmp_token.ptr[0] = '~';
619			  memcpy (tmp_token.ptr+1, $4.ptr, $4.length);
620			  tmp_token.ptr[tmp_token.length] = 0;
621
622			  /* Check for valid destructor name.  */
623			  destructor_name_p (tmp_token.ptr, type);
624			  write_exp_elt_opcode (OP_SCOPE);
625			  write_exp_elt_type (type);
626			  write_exp_string (tmp_token);
627			  write_exp_elt_opcode (OP_SCOPE);
628			}
629	;
630
631variable:	qualified_name
632	|	COLONCOLON name
633			{
634			  char *name = copy_name ($2);
635			  struct symbol *sym;
636			  struct minimal_symbol *msymbol;
637
638			  sym =
639			    lookup_symbol (name, (const struct block *) NULL,
640					   VAR_DOMAIN, (int *) NULL,
641					   (struct symtab **) NULL);
642			  if (sym)
643			    {
644			      write_exp_elt_opcode (OP_VAR_VALUE);
645			      write_exp_elt_block (NULL);
646			      write_exp_elt_sym (sym);
647			      write_exp_elt_opcode (OP_VAR_VALUE);
648			      break;
649			    }
650
651			  msymbol = lookup_minimal_symbol (name, NULL, NULL);
652			  if (msymbol != NULL)
653			    {
654			      write_exp_msymbol (msymbol,
655						 lookup_function_type (builtin_type (current_gdbarch)->builtin_int),
656						 builtin_type (current_gdbarch)->builtin_int);
657			    }
658			  else
659			    if (!have_full_symbols () && !have_partial_symbols ())
660			      error ("No symbol table is loaded.  Use the \"file\" command.");
661			    else
662			      error ("No symbol \"%s\" in current context.", name);
663			}
664	;
665
666variable:	name_not_typename
667			{ struct symbol *sym = $1.sym;
668
669			  if (sym)
670			    {
671			      if (symbol_read_needs_frame (sym))
672				{
673				  if (innermost_block == 0 ||
674				      contained_in (block_found,
675						    innermost_block))
676				    innermost_block = block_found;
677				}
678
679			      write_exp_elt_opcode (OP_VAR_VALUE);
680			      /* We want to use the selected frame, not
681				 another more inner frame which happens to
682				 be in the same block.  */
683			      write_exp_elt_block (NULL);
684			      write_exp_elt_sym (sym);
685			      write_exp_elt_opcode (OP_VAR_VALUE);
686			    }
687			  else if ($1.is_a_field_of_this)
688			    {
689			      /* C++: it hangs off of `this'.  Must
690			         not inadvertently convert from a method call
691				 to data ref.  */
692			      if (innermost_block == 0 ||
693				  contained_in (block_found, innermost_block))
694				innermost_block = block_found;
695			      write_exp_elt_opcode (OP_THIS);
696			      write_exp_elt_opcode (OP_THIS);
697			      write_exp_elt_opcode (STRUCTOP_PTR);
698			      write_exp_string ($1.stoken);
699			      write_exp_elt_opcode (STRUCTOP_PTR);
700			    }
701			  else
702			    {
703			      struct minimal_symbol *msymbol;
704			      char *arg = copy_name ($1.stoken);
705
706			      msymbol =
707				lookup_minimal_symbol (arg, NULL, NULL);
708			      if (msymbol != NULL)
709				{
710				  write_exp_msymbol (msymbol,
711						     lookup_function_type (builtin_type (current_gdbarch)->builtin_int),
712						     builtin_type (current_gdbarch)->builtin_int);
713				}
714			      else if (!have_full_symbols () && !have_partial_symbols ())
715				error ("No symbol table is loaded.  Use the \"file\" command.");
716			      else
717				error ("No symbol \"%s\" in current context.",
718				       copy_name ($1.stoken));
719			    }
720			}
721	;
722
723space_identifier : '@' NAME
724		{ push_type_address_space (copy_name ($2.stoken));
725		  push_type (tp_space_identifier);
726		}
727	;
728
729const_or_volatile: const_or_volatile_noopt
730	|
731	;
732
733cv_with_space_id : const_or_volatile space_identifier const_or_volatile
734	;
735
736const_or_volatile_or_space_identifier_noopt: cv_with_space_id
737	| const_or_volatile_noopt
738	;
739
740const_or_volatile_or_space_identifier:
741		const_or_volatile_or_space_identifier_noopt
742	|
743	;
744
745abs_decl:	'*'
746			{ push_type (tp_pointer); $$ = 0; }
747	|	'*' abs_decl
748			{ push_type (tp_pointer); $$ = $2; }
749	|	'&'
750			{ push_type (tp_reference); $$ = 0; }
751	|	'&' abs_decl
752			{ push_type (tp_reference); $$ = $2; }
753	|	direct_abs_decl
754	;
755
756direct_abs_decl: '(' abs_decl ')'
757			{ $$ = $2; }
758	|	direct_abs_decl array_mod
759			{
760			  push_type_int ($2);
761			  push_type (tp_array);
762			}
763	|	array_mod
764			{
765			  push_type_int ($1);
766			  push_type (tp_array);
767			  $$ = 0;
768			}
769
770	| 	direct_abs_decl func_mod
771			{ push_type (tp_function); }
772	|	func_mod
773			{ push_type (tp_function); }
774	;
775
776array_mod:	'[' ']'
777			{ $$ = -1; }
778	|	'[' INT ']'
779			{ $$ = $2.val; }
780	;
781
782func_mod:	'(' ')'
783			{ $$ = 0; }
784	|	'(' nonempty_typelist ')'
785			{ free ($2); $$ = 0; }
786	;
787
788/* We used to try to recognize more pointer to member types here, but
789   that didn't work (shift/reduce conflicts meant that these rules never
790   got executed).  The problem is that
791     int (foo::bar::baz::bizzle)
792   is a function type but
793     int (foo::bar::baz::bizzle::*)
794   is a pointer to member type.  Stroustrup loses again!  */
795
796type	:	ptype
797	|	typebase COLONCOLON '*'
798			{ $$ = lookup_member_type (builtin_type (current_gdbarch)->builtin_int, $1); }
799	;
800
801typebase  /* Implements (approximately): (type-qualifier)* type-specifier */
802	:	TYPENAME
803			{ $$ = $1.type; }
804	|	INT_KEYWORD
805			{ $$ = builtin_type (current_gdbarch)->builtin_int; }
806	|	LONG
807			{ $$ = builtin_type (current_gdbarch)->builtin_long; }
808	|	SHORT
809			{ $$ = builtin_type (current_gdbarch)->builtin_short; }
810	|	LONG INT_KEYWORD
811			{ $$ = builtin_type (current_gdbarch)->builtin_long; }
812	|	LONG SIGNED_KEYWORD INT_KEYWORD
813			{ $$ = builtin_type (current_gdbarch)->builtin_long; }
814	|	LONG SIGNED_KEYWORD
815			{ $$ = builtin_type (current_gdbarch)->builtin_long; }
816	|	SIGNED_KEYWORD LONG INT_KEYWORD
817			{ $$ = builtin_type (current_gdbarch)->builtin_long; }
818	|	UNSIGNED LONG INT_KEYWORD
819			{ $$ = builtin_type (current_gdbarch)->builtin_unsigned_long; }
820	|	LONG UNSIGNED INT_KEYWORD
821			{ $$ = builtin_type (current_gdbarch)->builtin_unsigned_long; }
822	|	LONG UNSIGNED
823			{ $$ = builtin_type (current_gdbarch)->builtin_unsigned_long; }
824	|	LONG LONG
825			{ $$ = builtin_type (current_gdbarch)->builtin_long_long; }
826	|	LONG LONG INT_KEYWORD
827			{ $$ = builtin_type (current_gdbarch)->builtin_long_long; }
828	|	LONG LONG SIGNED_KEYWORD INT_KEYWORD
829			{ $$ = builtin_type (current_gdbarch)->builtin_long_long; }
830	|	LONG LONG SIGNED_KEYWORD
831			{ $$ = builtin_type (current_gdbarch)->builtin_long_long; }
832	|	SIGNED_KEYWORD LONG LONG
833			{ $$ = builtin_type (current_gdbarch)->builtin_long_long; }
834	|	SIGNED_KEYWORD LONG LONG INT_KEYWORD
835			{ $$ = builtin_type (current_gdbarch)->builtin_long_long; }
836	|	UNSIGNED LONG LONG
837			{ $$ = builtin_type (current_gdbarch)->builtin_unsigned_long_long; }
838	|	UNSIGNED LONG LONG INT_KEYWORD
839			{ $$ = builtin_type (current_gdbarch)->builtin_unsigned_long_long; }
840	|	LONG LONG UNSIGNED
841			{ $$ = builtin_type (current_gdbarch)->builtin_unsigned_long_long; }
842	|	LONG LONG UNSIGNED INT_KEYWORD
843			{ $$ = builtin_type (current_gdbarch)->builtin_unsigned_long_long; }
844	|	SHORT INT_KEYWORD
845			{ $$ = builtin_type (current_gdbarch)->builtin_short; }
846	|	SHORT SIGNED_KEYWORD INT_KEYWORD
847			{ $$ = builtin_type (current_gdbarch)->builtin_short; }
848	|	SHORT SIGNED_KEYWORD
849			{ $$ = builtin_type (current_gdbarch)->builtin_short; }
850	|	UNSIGNED SHORT INT_KEYWORD
851			{ $$ = builtin_type (current_gdbarch)->builtin_unsigned_short; }
852	|	SHORT UNSIGNED
853			{ $$ = builtin_type (current_gdbarch)->builtin_unsigned_short; }
854	|	SHORT UNSIGNED INT_KEYWORD
855			{ $$ = builtin_type (current_gdbarch)->builtin_unsigned_short; }
856	|	DOUBLE_KEYWORD
857			{ $$ = builtin_type (current_gdbarch)->builtin_double; }
858	|	LONG DOUBLE_KEYWORD
859			{ $$ = builtin_type (current_gdbarch)->builtin_long_double; }
860	|	STRUCT name
861			{ $$ = lookup_struct (copy_name ($2),
862					      expression_context_block); }
863	|	CLASS name
864			{ $$ = lookup_struct (copy_name ($2),
865					      expression_context_block); }
866	|	UNION name
867			{ $$ = lookup_union (copy_name ($2),
868					     expression_context_block); }
869	|	ENUM name
870			{ $$ = lookup_enum (copy_name ($2),
871					    expression_context_block); }
872	|	UNSIGNED typename
873			{ $$ = lookup_unsigned_typename (TYPE_NAME($2.type)); }
874	|	UNSIGNED
875			{ $$ = builtin_type (current_gdbarch)->builtin_unsigned_int; }
876	|	SIGNED_KEYWORD typename
877			{ $$ = lookup_signed_typename (TYPE_NAME($2.type)); }
878	|	SIGNED_KEYWORD
879			{ $$ = builtin_type (current_gdbarch)->builtin_int; }
880                /* It appears that this rule for templates is never
881                   reduced; template recognition happens by lookahead
882                   in the token processing code in yylex. */
883	|	TEMPLATE name '<' type '>'
884			{ $$ = lookup_template_type(copy_name($2), $4,
885						    expression_context_block);
886			}
887	| const_or_volatile_or_space_identifier_noopt typebase
888			{ $$ = follow_types ($2); }
889	| typebase const_or_volatile_or_space_identifier_noopt
890			{ $$ = follow_types ($1); }
891	| qualified_type
892	;
893
894/* FIXME: carlton/2003-09-25: This next bit leads to lots of
895   reduce-reduce conflicts, because the parser doesn't know whether or
896   not to use qualified_name or qualified_type: the rules are
897   identical.  If the parser is parsing 'A::B::x', then, when it sees
898   the second '::', it knows that the expression to the left of it has
899   to be a type, so it uses qualified_type.  But if it is parsing just
900   'A::B', then it doesn't have any way of knowing which rule to use,
901   so there's a reduce-reduce conflict; it picks qualified_name, since
902   that occurs earlier in this file than qualified_type.
903
904   There's no good way to fix this with the grammar as it stands; as
905   far as I can tell, some of the problems arise from ambiguities that
906   GDB introduces ('start' can be either an expression or a type), but
907   some of it is inherent to the nature of C++ (you want to treat the
908   input "(FOO)" fairly differently depending on whether FOO is an
909   expression or a type, and if FOO is a complex expression, this can
910   be hard to determine at the right time).  Fortunately, it works
911   pretty well in most cases.  For example, if you do 'ptype A::B',
912   where A::B is a nested type, then the parser will mistakenly
913   misidentify it as an expression; but evaluate_subexp will get
914   called with 'noside' set to EVAL_AVOID_SIDE_EFFECTS, and everything
915   will work out anyways.  But there are situations where the parser
916   will get confused: the most common one that I've run into is when
917   you want to do
918
919     print *((A::B *) x)"
920
921   where the parser doesn't realize that A::B has to be a type until
922   it hits the first right paren, at which point it's too late.  (The
923   workaround is to type "print *(('A::B' *) x)" instead.)  (And
924   another solution is to fix our symbol-handling code so that the
925   user never wants to type something like that in the first place,
926   because we get all the types right without the user's help!)
927
928   Perhaps we could fix this by making the lexer smarter.  Some of
929   this functionality used to be in the lexer, but in a way that
930   worked even less well than the current solution: that attempt
931   involved having the parser sometimes handle '::' and having the
932   lexer sometimes handle it, and without a clear division of
933   responsibility, it quickly degenerated into a big mess.  Probably
934   the eventual correct solution will give more of a role to the lexer
935   (ideally via code that is shared between the lexer and
936   decode_line_1), but I'm not holding my breath waiting for somebody
937   to get around to cleaning this up...  */
938
939qualified_type: typebase COLONCOLON name
940		{
941		  struct type *type = $1;
942		  struct type *new_type;
943		  char *ncopy = alloca ($3.length + 1);
944
945		  memcpy (ncopy, $3.ptr, $3.length);
946		  ncopy[$3.length] = '\0';
947
948		  if (TYPE_CODE (type) != TYPE_CODE_STRUCT
949		      && TYPE_CODE (type) != TYPE_CODE_UNION
950		      && TYPE_CODE (type) != TYPE_CODE_NAMESPACE)
951		    error ("`%s' is not defined as an aggregate type.",
952			   TYPE_NAME (type));
953
954		  new_type = cp_lookup_nested_type (type, ncopy,
955						    expression_context_block);
956		  if (new_type == NULL)
957		    error ("No type \"%s\" within class or namespace \"%s\".",
958			   ncopy, TYPE_NAME (type));
959
960		  $$ = new_type;
961		}
962	;
963
964typename:	TYPENAME
965	|	INT_KEYWORD
966		{
967		  $$.stoken.ptr = "int";
968		  $$.stoken.length = 3;
969		  $$.type = builtin_type (current_gdbarch)->builtin_int;
970		}
971	|	LONG
972		{
973		  $$.stoken.ptr = "long";
974		  $$.stoken.length = 4;
975		  $$.type = builtin_type (current_gdbarch)->builtin_long;
976		}
977	|	SHORT
978		{
979		  $$.stoken.ptr = "short";
980		  $$.stoken.length = 5;
981		  $$.type = builtin_type (current_gdbarch)->builtin_short;
982		}
983	;
984
985nonempty_typelist
986	:	type
987		{ $$ = (struct type **) malloc (sizeof (struct type *) * 2);
988		  $<ivec>$[0] = 1;	/* Number of types in vector */
989		  $$[1] = $1;
990		}
991	|	nonempty_typelist ',' type
992		{ int len = sizeof (struct type *) * (++($<ivec>1[0]) + 1);
993		  $$ = (struct type **) realloc ((char *) $1, len);
994		  $$[$<ivec>$[0]] = $3;
995		}
996	;
997
998ptype	:	typebase
999	|	ptype const_or_volatile_or_space_identifier abs_decl const_or_volatile_or_space_identifier
1000		{ $$ = follow_types ($1); }
1001	;
1002
1003const_and_volatile: 	CONST_KEYWORD VOLATILE_KEYWORD
1004	| 		VOLATILE_KEYWORD CONST_KEYWORD
1005	;
1006
1007const_or_volatile_noopt:  	const_and_volatile
1008			{ push_type (tp_const);
1009			  push_type (tp_volatile);
1010			}
1011	| 		CONST_KEYWORD
1012			{ push_type (tp_const); }
1013	| 		VOLATILE_KEYWORD
1014			{ push_type (tp_volatile); }
1015	;
1016
1017name	:	NAME { $$ = $1.stoken; }
1018	|	BLOCKNAME { $$ = $1.stoken; }
1019	|	TYPENAME { $$ = $1.stoken; }
1020	|	NAME_OR_INT  { $$ = $1.stoken; }
1021	;
1022
1023name_not_typename :	NAME
1024	|	BLOCKNAME
1025/* These would be useful if name_not_typename was useful, but it is just
1026   a fake for "variable", so these cause reduce/reduce conflicts because
1027   the parser can't tell whether NAME_OR_INT is a name_not_typename (=variable,
1028   =exp) or just an exp.  If name_not_typename was ever used in an lvalue
1029   context where only a name could occur, this might be useful.
1030  	|	NAME_OR_INT
1031 */
1032	;
1033
1034%%
1035
1036/* Take care of parsing a number (anything that starts with a digit).
1037   Set yylval and return the token type; update lexptr.
1038   LEN is the number of characters in it.  */
1039
1040/*** Needs some error checking for the float case ***/
1041
1042static int
1043parse_number (p, len, parsed_float, putithere)
1044     char *p;
1045     int len;
1046     int parsed_float;
1047     YYSTYPE *putithere;
1048{
1049  /* FIXME: Shouldn't these be unsigned?  We don't deal with negative values
1050     here, and we do kind of silly things like cast to unsigned.  */
1051  LONGEST n = 0;
1052  LONGEST prevn = 0;
1053  ULONGEST un;
1054
1055  int i = 0;
1056  int c;
1057  int base = input_radix;
1058  int unsigned_p = 0;
1059
1060  /* Number of "L" suffixes encountered.  */
1061  int long_p = 0;
1062
1063  /* We have found a "L" or "U" suffix.  */
1064  int found_suffix = 0;
1065
1066  ULONGEST high_bit;
1067  struct type *signed_type;
1068  struct type *unsigned_type;
1069
1070  if (parsed_float)
1071    {
1072      /* It's a float since it contains a point or an exponent.  */
1073      char c;
1074      int num = 0;	/* number of tokens scanned by scanf */
1075      char saved_char = p[len];
1076
1077      p[len] = 0;	/* null-terminate the token */
1078      if (sizeof (putithere->typed_val_float.dval) <= sizeof (float))
1079	num = sscanf (p, "%g%c", (float *) &putithere->typed_val_float.dval,&c);
1080      else if (sizeof (putithere->typed_val_float.dval) <= sizeof (double))
1081	num = sscanf (p, "%lg%c", (double *) &putithere->typed_val_float.dval,&c);
1082      else
1083	{
1084#ifdef SCANF_HAS_LONG_DOUBLE
1085	  num = sscanf (p, "%Lg%c", &putithere->typed_val_float.dval,&c);
1086#else
1087	  /* Scan it into a double, then assign it to the long double.
1088	     This at least wins with values representable in the range
1089	     of doubles. */
1090	  double temp;
1091	  num = sscanf (p, "%lg%c", &temp,&c);
1092	  putithere->typed_val_float.dval = temp;
1093#endif
1094	}
1095      p[len] = saved_char;	/* restore the input stream */
1096      if (num != 1) 		/* check scanf found ONLY a float ... */
1097	return ERROR;
1098      /* See if it has `f' or `l' suffix (float or long double).  */
1099
1100      c = tolower (p[len - 1]);
1101
1102      if (c == 'f')
1103	putithere->typed_val_float.type = builtin_type (current_gdbarch)->builtin_float;
1104      else if (c == 'l')
1105	putithere->typed_val_float.type = builtin_type (current_gdbarch)->builtin_long_double;
1106      else if (isdigit (c) || c == '.')
1107	putithere->typed_val_float.type = builtin_type (current_gdbarch)->builtin_double;
1108      else
1109	return ERROR;
1110
1111      return FLOAT;
1112    }
1113
1114  /* Handle base-switching prefixes 0x, 0t, 0d, 0 */
1115  if (p[0] == '0')
1116    switch (p[1])
1117      {
1118      case 'x':
1119      case 'X':
1120	if (len >= 3)
1121	  {
1122	    p += 2;
1123	    base = 16;
1124	    len -= 2;
1125	  }
1126	break;
1127
1128      case 't':
1129      case 'T':
1130      case 'd':
1131      case 'D':
1132	if (len >= 3)
1133	  {
1134	    p += 2;
1135	    base = 10;
1136	    len -= 2;
1137	  }
1138	break;
1139
1140      default:
1141	base = 8;
1142	break;
1143      }
1144
1145  while (len-- > 0)
1146    {
1147      c = *p++;
1148      if (c >= 'A' && c <= 'Z')
1149	c += 'a' - 'A';
1150      if (c != 'l' && c != 'u')
1151	n *= base;
1152      if (c >= '0' && c <= '9')
1153	{
1154	  if (found_suffix)
1155	    return ERROR;
1156	  n += i = c - '0';
1157	}
1158      else
1159	{
1160	  if (base > 10 && c >= 'a' && c <= 'f')
1161	    {
1162	      if (found_suffix)
1163		return ERROR;
1164	      n += i = c - 'a' + 10;
1165	    }
1166	  else if (c == 'l')
1167	    {
1168	      ++long_p;
1169	      found_suffix = 1;
1170	    }
1171	  else if (c == 'u')
1172	    {
1173	      unsigned_p = 1;
1174	      found_suffix = 1;
1175	    }
1176	  else
1177	    return ERROR;	/* Char not a digit */
1178	}
1179      if (i >= base)
1180	return ERROR;		/* Invalid digit in this base */
1181
1182      /* Portably test for overflow (only works for nonzero values, so make
1183	 a second check for zero).  FIXME: Can't we just make n and prevn
1184	 unsigned and avoid this?  */
1185      if (c != 'l' && c != 'u' && (prevn >= n) && n != 0)
1186	unsigned_p = 1;		/* Try something unsigned */
1187
1188      /* Portably test for unsigned overflow.
1189	 FIXME: This check is wrong; for example it doesn't find overflow
1190	 on 0x123456789 when LONGEST is 32 bits.  */
1191      if (c != 'l' && c != 'u' && n != 0)
1192	{
1193	  if ((unsigned_p && (ULONGEST) prevn >= (ULONGEST) n))
1194	    error ("Numeric constant too large.");
1195	}
1196      prevn = n;
1197    }
1198
1199  /* An integer constant is an int, a long, or a long long.  An L
1200     suffix forces it to be long; an LL suffix forces it to be long
1201     long.  If not forced to a larger size, it gets the first type of
1202     the above that it fits in.  To figure out whether it fits, we
1203     shift it right and see whether anything remains.  Note that we
1204     can't shift sizeof (LONGEST) * HOST_CHAR_BIT bits or more in one
1205     operation, because many compilers will warn about such a shift
1206     (which always produces a zero result).  Sometimes TARGET_INT_BIT
1207     or TARGET_LONG_BIT will be that big, sometimes not.  To deal with
1208     the case where it is we just always shift the value more than
1209     once, with fewer bits each time.  */
1210
1211  un = (ULONGEST)n >> 2;
1212  if (long_p == 0
1213      && (un >> (TARGET_INT_BIT - 2)) == 0)
1214    {
1215      high_bit = ((ULONGEST)1) << (TARGET_INT_BIT-1);
1216
1217      /* A large decimal (not hex or octal) constant (between INT_MAX
1218	 and UINT_MAX) is a long or unsigned long, according to ANSI,
1219	 never an unsigned int, but this code treats it as unsigned
1220	 int.  This probably should be fixed.  GCC gives a warning on
1221	 such constants.  */
1222
1223      unsigned_type = builtin_type (current_gdbarch)->builtin_unsigned_int;
1224      signed_type = builtin_type (current_gdbarch)->builtin_int;
1225    }
1226  else if (long_p <= 1
1227	   && (un >> (TARGET_LONG_BIT - 2)) == 0)
1228    {
1229      high_bit = ((ULONGEST)1) << (TARGET_LONG_BIT-1);
1230      unsigned_type = builtin_type (current_gdbarch)->builtin_unsigned_long;
1231      signed_type = builtin_type (current_gdbarch)->builtin_long;
1232    }
1233  else
1234    {
1235      int shift;
1236      if (sizeof (ULONGEST) * HOST_CHAR_BIT < TARGET_LONG_LONG_BIT)
1237	/* A long long does not fit in a LONGEST.  */
1238	shift = (sizeof (ULONGEST) * HOST_CHAR_BIT - 1);
1239      else
1240	shift = (TARGET_LONG_LONG_BIT - 1);
1241      high_bit = (ULONGEST) 1 << shift;
1242      unsigned_type = builtin_type (current_gdbarch)->builtin_unsigned_long_long;
1243      signed_type = builtin_type (current_gdbarch)->builtin_long_long;
1244    }
1245
1246   putithere->typed_val_int.val = n;
1247
1248   /* If the high bit of the worked out type is set then this number
1249      has to be unsigned. */
1250
1251   if (unsigned_p || (n & high_bit))
1252     {
1253       putithere->typed_val_int.type = unsigned_type;
1254     }
1255   else
1256     {
1257       putithere->typed_val_int.type = signed_type;
1258     }
1259
1260   return INT;
1261}
1262
1263struct token
1264{
1265  char *operator;
1266  int token;
1267  enum exp_opcode opcode;
1268};
1269
1270static const struct token tokentab3[] =
1271  {
1272    {">>=", ASSIGN_MODIFY, BINOP_RSH},
1273    {"<<=", ASSIGN_MODIFY, BINOP_LSH}
1274  };
1275
1276static const struct token tokentab2[] =
1277  {
1278    {"+=", ASSIGN_MODIFY, BINOP_ADD},
1279    {"-=", ASSIGN_MODIFY, BINOP_SUB},
1280    {"*=", ASSIGN_MODIFY, BINOP_MUL},
1281    {"/=", ASSIGN_MODIFY, BINOP_DIV},
1282    {"%=", ASSIGN_MODIFY, BINOP_REM},
1283    {"|=", ASSIGN_MODIFY, BINOP_BITWISE_IOR},
1284    {"&=", ASSIGN_MODIFY, BINOP_BITWISE_AND},
1285    {"^=", ASSIGN_MODIFY, BINOP_BITWISE_XOR},
1286    {"++", INCREMENT, BINOP_END},
1287    {"--", DECREMENT, BINOP_END},
1288    {"->", ARROW, BINOP_END},
1289    {"&&", ANDAND, BINOP_END},
1290    {"||", OROR, BINOP_END},
1291    {"::", COLONCOLON, BINOP_END},
1292    {"<<", LSH, BINOP_END},
1293    {">>", RSH, BINOP_END},
1294    {"==", EQUAL, BINOP_END},
1295    {"!=", NOTEQUAL, BINOP_END},
1296    {"<=", LEQ, BINOP_END},
1297    {">=", GEQ, BINOP_END}
1298  };
1299
1300/* Read one token, getting characters through lexptr.  */
1301
1302static int
1303yylex ()
1304{
1305  int c;
1306  int namelen;
1307  unsigned int i;
1308  char *tokstart;
1309  char *tokptr;
1310  int tempbufindex;
1311  static char *tempbuf;
1312  static int tempbufsize;
1313  struct symbol * sym_class = NULL;
1314  char * token_string = NULL;
1315  int class_prefix = 0;
1316  int unquoted_expr;
1317
1318 retry:
1319
1320  /* Check if this is a macro invocation that we need to expand.  */
1321  if (! scanning_macro_expansion ())
1322    {
1323      char *expanded = macro_expand_next (&lexptr,
1324                                          expression_macro_lookup_func,
1325                                          expression_macro_lookup_baton);
1326
1327      if (expanded)
1328        scan_macro_expansion (expanded);
1329    }
1330
1331  prev_lexptr = lexptr;
1332  unquoted_expr = 1;
1333
1334  tokstart = lexptr;
1335  /* See if it is a special token of length 3.  */
1336  for (i = 0; i < sizeof tokentab3 / sizeof tokentab3[0]; i++)
1337    if (strncmp (tokstart, tokentab3[i].operator, 3) == 0)
1338      {
1339	lexptr += 3;
1340	yylval.opcode = tokentab3[i].opcode;
1341	return tokentab3[i].token;
1342      }
1343
1344  /* See if it is a special token of length 2.  */
1345  for (i = 0; i < sizeof tokentab2 / sizeof tokentab2[0]; i++)
1346    if (strncmp (tokstart, tokentab2[i].operator, 2) == 0)
1347      {
1348	lexptr += 2;
1349	yylval.opcode = tokentab2[i].opcode;
1350	return tokentab2[i].token;
1351      }
1352
1353  switch (c = *tokstart)
1354    {
1355    case 0:
1356      /* If we were just scanning the result of a macro expansion,
1357         then we need to resume scanning the original text.
1358         Otherwise, we were already scanning the original text, and
1359         we're really done.  */
1360      if (scanning_macro_expansion ())
1361        {
1362          finished_macro_expansion ();
1363          goto retry;
1364        }
1365      else
1366        return 0;
1367
1368    case ' ':
1369    case '\t':
1370    case '\n':
1371      lexptr++;
1372      goto retry;
1373
1374    case '\'':
1375      /* We either have a character constant ('0' or '\177' for example)
1376	 or we have a quoted symbol reference ('foo(int,int)' in C++
1377	 for example). */
1378      lexptr++;
1379      c = *lexptr++;
1380      if (c == '\\')
1381	c = parse_escape (&lexptr);
1382      else if (c == '\'')
1383	error ("Empty character constant.");
1384      else if (! host_char_to_target (c, &c))
1385        {
1386          int toklen = lexptr - tokstart + 1;
1387          char *tok = alloca (toklen + 1);
1388          memcpy (tok, tokstart, toklen);
1389          tok[toklen] = '\0';
1390          error ("There is no character corresponding to %s in the target "
1391                 "character set `%s'.", tok, target_charset ());
1392        }
1393
1394      yylval.typed_val_int.val = c;
1395      yylval.typed_val_int.type = builtin_type (current_gdbarch)->builtin_char;
1396
1397      c = *lexptr++;
1398      if (c != '\'')
1399	{
1400	  namelen = skip_quoted (tokstart) - tokstart;
1401	  if (namelen > 2)
1402	    {
1403	      lexptr = tokstart + namelen;
1404              unquoted_expr = 0;
1405	      if (lexptr[-1] != '\'')
1406		error ("Unmatched single quote.");
1407	      namelen -= 2;
1408	      tokstart++;
1409	      goto tryname;
1410	    }
1411	  error ("Invalid character constant.");
1412	}
1413      return INT;
1414
1415    case '(':
1416      paren_depth++;
1417      lexptr++;
1418      return c;
1419
1420    case ')':
1421      if (paren_depth == 0)
1422	return 0;
1423      paren_depth--;
1424      lexptr++;
1425      return c;
1426
1427    case ',':
1428      if (comma_terminates
1429          && paren_depth == 0
1430          && ! scanning_macro_expansion ())
1431	return 0;
1432      lexptr++;
1433      return c;
1434
1435    case '.':
1436      /* Might be a floating point number.  */
1437      if (lexptr[1] < '0' || lexptr[1] > '9')
1438	goto symbol;		/* Nope, must be a symbol. */
1439      /* FALL THRU into number case.  */
1440
1441    case '0':
1442    case '1':
1443    case '2':
1444    case '3':
1445    case '4':
1446    case '5':
1447    case '6':
1448    case '7':
1449    case '8':
1450    case '9':
1451      {
1452	/* It's a number.  */
1453	int got_dot = 0, got_e = 0, toktype;
1454	char *p = tokstart;
1455	int hex = input_radix > 10;
1456
1457	if (c == '0' && (p[1] == 'x' || p[1] == 'X'))
1458	  {
1459	    p += 2;
1460	    hex = 1;
1461	  }
1462	else if (c == '0' && (p[1]=='t' || p[1]=='T' || p[1]=='d' || p[1]=='D'))
1463	  {
1464	    p += 2;
1465	    hex = 0;
1466	  }
1467
1468	for (;; ++p)
1469	  {
1470	    /* This test includes !hex because 'e' is a valid hex digit
1471	       and thus does not indicate a floating point number when
1472	       the radix is hex.  */
1473	    if (!hex && !got_e && (*p == 'e' || *p == 'E'))
1474	      got_dot = got_e = 1;
1475	    /* This test does not include !hex, because a '.' always indicates
1476	       a decimal floating point number regardless of the radix.  */
1477	    else if (!got_dot && *p == '.')
1478	      got_dot = 1;
1479	    else if (got_e && (p[-1] == 'e' || p[-1] == 'E')
1480		     && (*p == '-' || *p == '+'))
1481	      /* This is the sign of the exponent, not the end of the
1482		 number.  */
1483	      continue;
1484	    /* We will take any letters or digits.  parse_number will
1485	       complain if past the radix, or if L or U are not final.  */
1486	    else if ((*p < '0' || *p > '9')
1487		     && ((*p < 'a' || *p > 'z')
1488				  && (*p < 'A' || *p > 'Z')))
1489	      break;
1490	  }
1491	toktype = parse_number (tokstart, p - tokstart, got_dot|got_e, &yylval);
1492        if (toktype == ERROR)
1493	  {
1494	    char *err_copy = (char *) alloca (p - tokstart + 1);
1495
1496	    memcpy (err_copy, tokstart, p - tokstart);
1497	    err_copy[p - tokstart] = 0;
1498	    error ("Invalid number \"%s\".", err_copy);
1499	  }
1500	lexptr = p;
1501	return toktype;
1502      }
1503
1504    case '+':
1505    case '-':
1506    case '*':
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    symbol:
1525      lexptr++;
1526      return c;
1527
1528    case '"':
1529
1530      /* Build the gdb internal form of the input string in tempbuf,
1531	 translating any standard C escape forms seen.  Note that the
1532	 buffer is null byte terminated *only* for the convenience of
1533	 debugging gdb itself and printing the buffer contents when
1534	 the buffer contains no embedded nulls.  Gdb does not depend
1535	 upon the buffer being null byte terminated, it uses the length
1536	 string instead.  This allows gdb to handle C strings (as well
1537	 as strings in other languages) with embedded null bytes */
1538
1539      tokptr = ++tokstart;
1540      tempbufindex = 0;
1541
1542      do {
1543        char *char_start_pos = tokptr;
1544
1545	/* Grow the static temp buffer if necessary, including allocating
1546	   the first one on demand. */
1547	if (tempbufindex + 1 >= tempbufsize)
1548	  {
1549	    tempbuf = (char *) realloc (tempbuf, tempbufsize += 64);
1550	  }
1551	switch (*tokptr)
1552	  {
1553	  case '\0':
1554	  case '"':
1555	    /* Do nothing, loop will terminate. */
1556	    break;
1557	  case '\\':
1558	    tokptr++;
1559	    c = parse_escape (&tokptr);
1560	    if (c == -1)
1561	      {
1562		continue;
1563	      }
1564	    tempbuf[tempbufindex++] = c;
1565	    break;
1566	  default:
1567	    c = *tokptr++;
1568            if (! host_char_to_target (c, &c))
1569              {
1570                int len = tokptr - char_start_pos;
1571                char *copy = alloca (len + 1);
1572                memcpy (copy, char_start_pos, len);
1573                copy[len] = '\0';
1574
1575                error ("There is no character corresponding to `%s' "
1576                       "in the target character set `%s'.",
1577                       copy, target_charset ());
1578              }
1579            tempbuf[tempbufindex++] = c;
1580	    break;
1581	  }
1582      } while ((*tokptr != '"') && (*tokptr != '\0'));
1583      if (*tokptr++ != '"')
1584	{
1585	  error ("Unterminated string in expression.");
1586	}
1587      tempbuf[tempbufindex] = '\0';	/* See note above */
1588      yylval.sval.ptr = tempbuf;
1589      yylval.sval.length = tempbufindex;
1590      lexptr = tokptr;
1591      return (STRING);
1592    }
1593
1594  if (!(c == '_' || c == '$'
1595	|| (c >= 'a' && c <= 'z') || (c >= 'A' && c <= 'Z')))
1596    /* We must have come across a bad character (e.g. ';').  */
1597    error ("Invalid character '%c' in expression.", c);
1598
1599  /* It's a name.  See how long it is.  */
1600  namelen = 0;
1601  for (c = tokstart[namelen];
1602       (c == '_' || c == '$' || (c >= '0' && c <= '9')
1603	|| (c >= 'a' && c <= 'z') || (c >= 'A' && c <= 'Z') || c == '<');)
1604    {
1605      /* Template parameter lists are part of the name.
1606	 FIXME: This mishandles `print $a<4&&$a>3'.  */
1607
1608      if (c == '<')
1609	{
1610               /* Scan ahead to get rest of the template specification.  Note
1611                  that we look ahead only when the '<' adjoins non-whitespace
1612                  characters; for comparison expressions, e.g. "a < b > c",
1613                  there must be spaces before the '<', etc. */
1614
1615               char * p = find_template_name_end (tokstart + namelen);
1616               if (p)
1617                 namelen = p - tokstart;
1618               break;
1619	}
1620      c = tokstart[++namelen];
1621    }
1622
1623  /* The token "if" terminates the expression and is NOT removed from
1624     the input stream.  It doesn't count if it appears in the
1625     expansion of a macro.  */
1626  if (namelen == 2
1627      && tokstart[0] == 'i'
1628      && tokstart[1] == 'f'
1629      && ! scanning_macro_expansion ())
1630    {
1631      return 0;
1632    }
1633
1634  lexptr += namelen;
1635
1636  tryname:
1637
1638  /* Catch specific keywords.  Should be done with a data structure.  */
1639  switch (namelen)
1640    {
1641    case 8:
1642      if (strncmp (tokstart, "unsigned", 8) == 0)
1643	return UNSIGNED;
1644      if (current_language->la_language == language_cplus
1645	  && strncmp (tokstart, "template", 8) == 0)
1646	return TEMPLATE;
1647      if (strncmp (tokstart, "volatile", 8) == 0)
1648	return VOLATILE_KEYWORD;
1649      break;
1650    case 6:
1651      if (strncmp (tokstart, "struct", 6) == 0)
1652	return STRUCT;
1653      if (strncmp (tokstart, "signed", 6) == 0)
1654	return SIGNED_KEYWORD;
1655      if (strncmp (tokstart, "sizeof", 6) == 0)
1656	return SIZEOF;
1657      if (strncmp (tokstart, "double", 6) == 0)
1658	return DOUBLE_KEYWORD;
1659      break;
1660    case 5:
1661      if (current_language->la_language == language_cplus)
1662        {
1663          if (strncmp (tokstart, "false", 5) == 0)
1664            return FALSEKEYWORD;
1665          if (strncmp (tokstart, "class", 5) == 0)
1666            return CLASS;
1667        }
1668      if (strncmp (tokstart, "union", 5) == 0)
1669	return UNION;
1670      if (strncmp (tokstart, "short", 5) == 0)
1671	return SHORT;
1672      if (strncmp (tokstart, "const", 5) == 0)
1673	return CONST_KEYWORD;
1674      break;
1675    case 4:
1676      if (strncmp (tokstart, "enum", 4) == 0)
1677	return ENUM;
1678      if (strncmp (tokstart, "long", 4) == 0)
1679	return LONG;
1680      if (current_language->la_language == language_cplus)
1681          {
1682            if (strncmp (tokstart, "true", 4) == 0)
1683              return TRUEKEYWORD;
1684          }
1685      break;
1686    case 3:
1687      if (strncmp (tokstart, "int", 3) == 0)
1688	return INT_KEYWORD;
1689      break;
1690    default:
1691      break;
1692    }
1693
1694  yylval.sval.ptr = tokstart;
1695  yylval.sval.length = namelen;
1696
1697  if (*tokstart == '$')
1698    {
1699      write_dollar_variable (yylval.sval);
1700      return VARIABLE;
1701    }
1702
1703  /* Look ahead and see if we can consume more of the input
1704     string to get a reasonable class/namespace spec or a
1705     fully-qualified name.  This is a kludge to get around the
1706     HP aCC compiler's generation of symbol names with embedded
1707     colons for namespace and nested classes. */
1708
1709  /* NOTE: carlton/2003-09-24: I don't entirely understand the
1710     HP-specific code, either here or in linespec.  Having said that,
1711     I suspect that we're actually moving towards their model: we want
1712     symbols whose names are fully qualified, which matches the
1713     description above.  */
1714  if (unquoted_expr)
1715    {
1716      /* Only do it if not inside single quotes */
1717      sym_class = parse_nested_classes_for_hpacc (yylval.sval.ptr, yylval.sval.length,
1718                                                  &token_string, &class_prefix, &lexptr);
1719      if (sym_class)
1720        {
1721          /* Replace the current token with the bigger one we found */
1722          yylval.sval.ptr = token_string;
1723          yylval.sval.length = strlen (token_string);
1724        }
1725    }
1726
1727  /* Use token-type BLOCKNAME for symbols that happen to be defined as
1728     functions or symtabs.  If this is not so, then ...
1729     Use token-type TYPENAME for symbols that happen to be defined
1730     currently as names of types; NAME for other symbols.
1731     The caller is not constrained to care about the distinction.  */
1732  {
1733    char *tmp = copy_name (yylval.sval);
1734    struct symbol *sym;
1735    int is_a_field_of_this = 0;
1736    int hextype;
1737
1738    sym = lookup_symbol (tmp, expression_context_block,
1739			 VAR_DOMAIN,
1740			 current_language->la_language == language_cplus
1741			 ? &is_a_field_of_this : (int *) NULL,
1742			 (struct symtab **) NULL);
1743    /* Call lookup_symtab, not lookup_partial_symtab, in case there are
1744       no psymtabs (coff, xcoff, or some future change to blow away the
1745       psymtabs once once symbols are read).  */
1746    if (sym && SYMBOL_CLASS (sym) == LOC_BLOCK)
1747      {
1748	yylval.ssym.sym = sym;
1749	yylval.ssym.is_a_field_of_this = is_a_field_of_this;
1750	return BLOCKNAME;
1751      }
1752    else if (!sym)
1753      {				/* See if it's a file name. */
1754	struct symtab *symtab;
1755
1756	symtab = lookup_symtab (tmp);
1757
1758	if (symtab)
1759	  {
1760	    yylval.bval = BLOCKVECTOR_BLOCK (BLOCKVECTOR (symtab), STATIC_BLOCK);
1761	    return FILENAME;
1762	  }
1763      }
1764
1765    if (sym && SYMBOL_CLASS (sym) == LOC_TYPEDEF)
1766        {
1767	  /* NOTE: carlton/2003-09-25: There used to be code here to
1768	     handle nested types.  It didn't work very well.  See the
1769	     comment before qualified_type for more info.  */
1770	  yylval.tsym.type = SYMBOL_TYPE (sym);
1771	  return TYPENAME;
1772        }
1773    yylval.tsym.type
1774      = language_lookup_primitive_type_by_name (current_language,
1775						current_gdbarch, tmp);
1776    if (yylval.tsym.type != NULL)
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