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/* Flag indicating we're dealing with HP-compiled objects */
57extern int hp_som_som_object_present;
58
59/* Remap normal yacc parser interface names (yyparse, yylex, yyerror, etc),
60   as well as gratuitiously global symbol names, so we can have multiple
61   yacc generated parsers in gdb.  Note that these are only the variables
62   produced by yacc.  If other parser generators (bison, byacc, etc) produce
63   additional global names that conflict at link time, then those parser
64   generators need to be fixed instead of adding those names to this list. */
65
66#define	yymaxdepth c_maxdepth
67#define	yyparse	c_parse
68#define	yylex	c_lex
69#define	yyerror	c_error
70#define	yylval	c_lval
71#define	yychar	c_char
72#define	yydebug	c_debug
73#define	yypact	c_pact
74#define	yyr1	c_r1
75#define	yyr2	c_r2
76#define	yydef	c_def
77#define	yychk	c_chk
78#define	yypgo	c_pgo
79#define	yyact	c_act
80#define	yyexca	c_exca
81#define yyerrflag c_errflag
82#define yynerrs	c_nerrs
83#define	yyps	c_ps
84#define	yypv	c_pv
85#define	yys	c_s
86#define	yy_yys	c_yys
87#define	yystate	c_state
88#define	yytmp	c_tmp
89#define	yyv	c_v
90#define	yy_yyv	c_yyv
91#define	yyval	c_val
92#define	yylloc	c_lloc
93#define yyreds	c_reds		/* With YYDEBUG defined */
94#define yytoks	c_toks		/* With YYDEBUG defined */
95#define yyname	c_name		/* With YYDEBUG defined */
96#define yyrule	c_rule		/* With YYDEBUG defined */
97#define yylhs	c_yylhs
98#define yylen	c_yylen
99#define yydefred c_yydefred
100#define yydgoto	c_yydgoto
101#define yysindex c_yysindex
102#define yyrindex c_yyrindex
103#define yygindex c_yygindex
104#define yytable	 c_yytable
105#define yycheck	 c_yycheck
106
107#ifndef YYDEBUG
108#define	YYDEBUG 1		/* Default to yydebug support */
109#endif
110
111#define YYFPRINTF parser_fprintf
112
113int yyparse (void);
114
115static int yylex (void);
116
117void yyerror (char *);
118
119%}
120
121/* Although the yacc "value" of an expression is not used,
122   since the result is stored in the structure being created,
123   other node types do have values.  */
124
125%union
126  {
127    LONGEST lval;
128    struct {
129      LONGEST val;
130      struct type *type;
131    } typed_val_int;
132    struct {
133      DOUBLEST dval;
134      struct type *type;
135    } typed_val_float;
136    struct symbol *sym;
137    struct type *tval;
138    struct stoken sval;
139    struct ttype tsym;
140    struct symtoken ssym;
141    int voidval;
142    struct block *bval;
143    enum exp_opcode opcode;
144    struct internalvar *ivar;
145
146    struct type **tvec;
147    int *ivec;
148  }
149
150%{
151/* YYSTYPE gets defined by %union */
152static int parse_number (char *, int, int, YYSTYPE *);
153%}
154
155%type <voidval> exp exp1 type_exp start variable qualified_name lcurly
156%type <lval> rcurly
157%type <tval> type typebase qualified_type
158%type <tvec> nonempty_typelist
159/* %type <bval> block */
160
161/* Fancy type parsing.  */
162%type <voidval> func_mod direct_abs_decl abs_decl
163%type <tval> ptype
164%type <lval> array_mod
165
166%token <typed_val_int> INT
167%token <typed_val_float> FLOAT
168
169/* Both NAME and TYPENAME tokens represent symbols in the input,
170   and both convey their data as strings.
171   But a TYPENAME is a string that happens to be defined as a typedef
172   or builtin type name (such as int or char)
173   and a NAME is any other symbol.
174   Contexts where this distinction is not important can use the
175   nonterminal "name", which matches either NAME or TYPENAME.  */
176
177%token <sval> STRING
178%token <ssym> NAME /* BLOCKNAME defined below to give it higher precedence. */
179%token <tsym> TYPENAME
180%type <sval> name
181%type <ssym> name_not_typename
182%type <tsym> typename
183
184/* A NAME_OR_INT is a symbol which is not known in the symbol table,
185   but which would parse as a valid number in the current input radix.
186   E.g. "c" when input_radix==16.  Depending on the parse, it will be
187   turned into a name or into a number.  */
188
189%token <ssym> NAME_OR_INT
190
191%token STRUCT CLASS UNION ENUM SIZEOF UNSIGNED COLONCOLON
192%token TEMPLATE
193%token ERROR
194
195/* Special type cases, put in to allow the parser to distinguish different
196   legal basetypes.  */
197%token SIGNED_KEYWORD LONG SHORT INT_KEYWORD CONST_KEYWORD VOLATILE_KEYWORD DOUBLE_KEYWORD
198
199%token <voidval> VARIABLE
200
201%token <opcode> ASSIGN_MODIFY
202
203/* C++ */
204%token TRUEKEYWORD
205%token FALSEKEYWORD
206
207
208%left ','
209%left ABOVE_COMMA
210%right '=' ASSIGN_MODIFY
211%right '?'
212%left OROR
213%left ANDAND
214%left '|'
215%left '^'
216%left '&'
217%left EQUAL NOTEQUAL
218%left '<' '>' LEQ GEQ
219%left LSH RSH
220%left '@'
221%left '+' '-'
222%left '*' '/' '%'
223%right UNARY INCREMENT DECREMENT
224%right ARROW '.' '[' '('
225%token <ssym> BLOCKNAME
226%token <bval> FILENAME
227%type <bval> block
228%left COLONCOLON
229
230
231%%
232
233start   :	exp1
234	|	type_exp
235	;
236
237type_exp:	type
238			{ write_exp_elt_opcode(OP_TYPE);
239			  write_exp_elt_type($1);
240			  write_exp_elt_opcode(OP_TYPE);}
241	;
242
243/* Expressions, including the comma operator.  */
244exp1	:	exp
245	|	exp1 ',' exp
246			{ write_exp_elt_opcode (BINOP_COMMA); }
247	;
248
249/* Expressions, not including the comma operator.  */
250exp	:	'*' exp    %prec UNARY
251			{ write_exp_elt_opcode (UNOP_IND); }
252	;
253
254exp	:	'&' exp    %prec UNARY
255			{ write_exp_elt_opcode (UNOP_ADDR); }
256	;
257
258exp	:	'-' exp    %prec UNARY
259			{ write_exp_elt_opcode (UNOP_NEG); }
260	;
261
262exp	:	'!' exp    %prec UNARY
263			{ write_exp_elt_opcode (UNOP_LOGICAL_NOT); }
264	;
265
266exp	:	'~' exp    %prec UNARY
267			{ write_exp_elt_opcode (UNOP_COMPLEMENT); }
268	;
269
270exp	:	INCREMENT exp    %prec UNARY
271			{ write_exp_elt_opcode (UNOP_PREINCREMENT); }
272	;
273
274exp	:	DECREMENT exp    %prec UNARY
275			{ write_exp_elt_opcode (UNOP_PREDECREMENT); }
276	;
277
278exp	:	exp INCREMENT    %prec UNARY
279			{ write_exp_elt_opcode (UNOP_POSTINCREMENT); }
280	;
281
282exp	:	exp DECREMENT    %prec UNARY
283			{ write_exp_elt_opcode (UNOP_POSTDECREMENT); }
284	;
285
286exp	:	SIZEOF exp       %prec UNARY
287			{ write_exp_elt_opcode (UNOP_SIZEOF); }
288	;
289
290exp	:	exp ARROW name
291			{ write_exp_elt_opcode (STRUCTOP_PTR);
292			  write_exp_string ($3);
293			  write_exp_elt_opcode (STRUCTOP_PTR); }
294	;
295
296exp	:	exp ARROW qualified_name
297			{ /* exp->type::name becomes exp->*(&type::name) */
298			  /* Note: this doesn't work if name is a
299			     static member!  FIXME */
300			  write_exp_elt_opcode (UNOP_ADDR);
301			  write_exp_elt_opcode (STRUCTOP_MPTR); }
302	;
303
304exp	:	exp ARROW '*' exp
305			{ write_exp_elt_opcode (STRUCTOP_MPTR); }
306	;
307
308exp	:	exp '.' name
309			{ write_exp_elt_opcode (STRUCTOP_STRUCT);
310			  write_exp_string ($3);
311			  write_exp_elt_opcode (STRUCTOP_STRUCT); }
312	;
313
314exp	:	exp '.' qualified_name
315			{ /* exp.type::name becomes exp.*(&type::name) */
316			  /* Note: this doesn't work if name is a
317			     static member!  FIXME */
318			  write_exp_elt_opcode (UNOP_ADDR);
319			  write_exp_elt_opcode (STRUCTOP_MEMBER); }
320	;
321
322exp	:	exp '.' '*' exp
323			{ write_exp_elt_opcode (STRUCTOP_MEMBER); }
324	;
325
326exp	:	exp '[' exp1 ']'
327			{ write_exp_elt_opcode (BINOP_SUBSCRIPT); }
328	;
329
330exp	:	exp '('
331			/* This is to save the value of arglist_len
332			   being accumulated by an outer function call.  */
333			{ start_arglist (); }
334		arglist ')'	%prec ARROW
335			{ write_exp_elt_opcode (OP_FUNCALL);
336			  write_exp_elt_longcst ((LONGEST) end_arglist ());
337			  write_exp_elt_opcode (OP_FUNCALL); }
338	;
339
340lcurly	:	'{'
341			{ start_arglist (); }
342	;
343
344arglist	:
345	;
346
347arglist	:	exp
348			{ arglist_len = 1; }
349	;
350
351arglist	:	arglist ',' exp   %prec ABOVE_COMMA
352			{ arglist_len++; }
353	;
354
355rcurly	:	'}'
356			{ $$ = end_arglist () - 1; }
357	;
358exp	:	lcurly arglist rcurly	%prec ARROW
359			{ write_exp_elt_opcode (OP_ARRAY);
360			  write_exp_elt_longcst ((LONGEST) 0);
361			  write_exp_elt_longcst ((LONGEST) $3);
362			  write_exp_elt_opcode (OP_ARRAY); }
363	;
364
365exp	:	lcurly type rcurly exp  %prec UNARY
366			{ write_exp_elt_opcode (UNOP_MEMVAL);
367			  write_exp_elt_type ($2);
368			  write_exp_elt_opcode (UNOP_MEMVAL); }
369	;
370
371exp	:	'(' type ')' exp  %prec UNARY
372			{ write_exp_elt_opcode (UNOP_CAST);
373			  write_exp_elt_type ($2);
374			  write_exp_elt_opcode (UNOP_CAST); }
375	;
376
377exp	:	'(' exp1 ')'
378			{ }
379	;
380
381/* Binary operators in order of decreasing precedence.  */
382
383exp	:	exp '@' exp
384			{ write_exp_elt_opcode (BINOP_REPEAT); }
385	;
386
387exp	:	exp '*' exp
388			{ write_exp_elt_opcode (BINOP_MUL); }
389	;
390
391exp	:	exp '/' exp
392			{ write_exp_elt_opcode (BINOP_DIV); }
393	;
394
395exp	:	exp '%' exp
396			{ write_exp_elt_opcode (BINOP_REM); }
397	;
398
399exp	:	exp '+' exp
400			{ write_exp_elt_opcode (BINOP_ADD); }
401	;
402
403exp	:	exp '-' exp
404			{ write_exp_elt_opcode (BINOP_SUB); }
405	;
406
407exp	:	exp LSH exp
408			{ write_exp_elt_opcode (BINOP_LSH); }
409	;
410
411exp	:	exp RSH exp
412			{ write_exp_elt_opcode (BINOP_RSH); }
413	;
414
415exp	:	exp EQUAL exp
416			{ write_exp_elt_opcode (BINOP_EQUAL); }
417	;
418
419exp	:	exp NOTEQUAL exp
420			{ write_exp_elt_opcode (BINOP_NOTEQUAL); }
421	;
422
423exp	:	exp LEQ exp
424			{ write_exp_elt_opcode (BINOP_LEQ); }
425	;
426
427exp	:	exp GEQ exp
428			{ write_exp_elt_opcode (BINOP_GEQ); }
429	;
430
431exp	:	exp '<' exp
432			{ write_exp_elt_opcode (BINOP_LESS); }
433	;
434
435exp	:	exp '>' exp
436			{ write_exp_elt_opcode (BINOP_GTR); }
437	;
438
439exp	:	exp '&' exp
440			{ write_exp_elt_opcode (BINOP_BITWISE_AND); }
441	;
442
443exp	:	exp '^' exp
444			{ write_exp_elt_opcode (BINOP_BITWISE_XOR); }
445	;
446
447exp	:	exp '|' exp
448			{ write_exp_elt_opcode (BINOP_BITWISE_IOR); }
449	;
450
451exp	:	exp ANDAND exp
452			{ write_exp_elt_opcode (BINOP_LOGICAL_AND); }
453	;
454
455exp	:	exp OROR exp
456			{ write_exp_elt_opcode (BINOP_LOGICAL_OR); }
457	;
458
459exp	:	exp '?' exp ':' exp	%prec '?'
460			{ write_exp_elt_opcode (TERNOP_COND); }
461	;
462
463exp	:	exp '=' exp
464			{ write_exp_elt_opcode (BINOP_ASSIGN); }
465	;
466
467exp	:	exp ASSIGN_MODIFY exp
468			{ write_exp_elt_opcode (BINOP_ASSIGN_MODIFY);
469			  write_exp_elt_opcode ($2);
470			  write_exp_elt_opcode (BINOP_ASSIGN_MODIFY); }
471	;
472
473exp	:	INT
474			{ write_exp_elt_opcode (OP_LONG);
475			  write_exp_elt_type ($1.type);
476			  write_exp_elt_longcst ((LONGEST)($1.val));
477			  write_exp_elt_opcode (OP_LONG); }
478	;
479
480exp	:	NAME_OR_INT
481			{ YYSTYPE val;
482			  parse_number ($1.stoken.ptr, $1.stoken.length, 0, &val);
483			  write_exp_elt_opcode (OP_LONG);
484			  write_exp_elt_type (val.typed_val_int.type);
485			  write_exp_elt_longcst ((LONGEST)val.typed_val_int.val);
486			  write_exp_elt_opcode (OP_LONG);
487			}
488	;
489
490
491exp	:	FLOAT
492			{ write_exp_elt_opcode (OP_DOUBLE);
493			  write_exp_elt_type ($1.type);
494			  write_exp_elt_dblcst ($1.dval);
495			  write_exp_elt_opcode (OP_DOUBLE); }
496	;
497
498exp	:	variable
499	;
500
501exp	:	VARIABLE
502			/* Already written by write_dollar_variable. */
503	;
504
505exp	:	SIZEOF '(' type ')'	%prec UNARY
506			{ write_exp_elt_opcode (OP_LONG);
507			  write_exp_elt_type (builtin_type_int);
508			  CHECK_TYPEDEF ($3);
509			  write_exp_elt_longcst ((LONGEST) TYPE_LENGTH ($3));
510			  write_exp_elt_opcode (OP_LONG); }
511	;
512
513exp	:	STRING
514			{ /* C strings are converted into array constants with
515			     an explicit null byte added at the end.  Thus
516			     the array upper bound is the string length.
517			     There is no such thing in C as a completely empty
518			     string. */
519			  char *sp = $1.ptr; int count = $1.length;
520			  while (count-- > 0)
521			    {
522			      write_exp_elt_opcode (OP_LONG);
523			      write_exp_elt_type (builtin_type_char);
524			      write_exp_elt_longcst ((LONGEST)(*sp++));
525			      write_exp_elt_opcode (OP_LONG);
526			    }
527			  write_exp_elt_opcode (OP_LONG);
528			  write_exp_elt_type (builtin_type_char);
529			  write_exp_elt_longcst ((LONGEST)'\0');
530			  write_exp_elt_opcode (OP_LONG);
531			  write_exp_elt_opcode (OP_ARRAY);
532			  write_exp_elt_longcst ((LONGEST) 0);
533			  write_exp_elt_longcst ((LONGEST) ($1.length));
534			  write_exp_elt_opcode (OP_ARRAY); }
535	;
536
537/* C++.  */
538exp     :       TRUEKEYWORD
539                        { write_exp_elt_opcode (OP_LONG);
540                          write_exp_elt_type (builtin_type_bool);
541                          write_exp_elt_longcst ((LONGEST) 1);
542                          write_exp_elt_opcode (OP_LONG); }
543	;
544
545exp     :       FALSEKEYWORD
546                        { write_exp_elt_opcode (OP_LONG);
547                          write_exp_elt_type (builtin_type_bool);
548                          write_exp_elt_longcst ((LONGEST) 0);
549                          write_exp_elt_opcode (OP_LONG); }
550	;
551
552/* end of C++.  */
553
554block	:	BLOCKNAME
555			{
556			  if ($1.sym)
557			    $$ = SYMBOL_BLOCK_VALUE ($1.sym);
558			  else
559			    error ("No file or function \"%s\".",
560				   copy_name ($1.stoken));
561			}
562	|	FILENAME
563			{
564			  $$ = $1;
565			}
566	;
567
568block	:	block COLONCOLON name
569			{ struct symbol *tem
570			    = lookup_symbol (copy_name ($3), $1,
571					     VAR_DOMAIN, (int *) NULL,
572					     (struct symtab **) NULL);
573			  if (!tem || SYMBOL_CLASS (tem) != LOC_BLOCK)
574			    error ("No function \"%s\" in specified context.",
575				   copy_name ($3));
576			  $$ = SYMBOL_BLOCK_VALUE (tem); }
577	;
578
579variable:	block COLONCOLON name
580			{ struct symbol *sym;
581			  sym = lookup_symbol (copy_name ($3), $1,
582					       VAR_DOMAIN, (int *) NULL,
583					       (struct symtab **) NULL);
584			  if (sym == 0)
585			    error ("No symbol \"%s\" in specified context.",
586				   copy_name ($3));
587
588			  write_exp_elt_opcode (OP_VAR_VALUE);
589			  /* block_found is set by lookup_symbol.  */
590			  write_exp_elt_block (block_found);
591			  write_exp_elt_sym (sym);
592			  write_exp_elt_opcode (OP_VAR_VALUE); }
593	;
594
595qualified_name:	typebase COLONCOLON name
596			{
597			  struct type *type = $1;
598			  if (TYPE_CODE (type) != TYPE_CODE_STRUCT
599			      && TYPE_CODE (type) != TYPE_CODE_UNION
600			      && TYPE_CODE (type) != TYPE_CODE_NAMESPACE)
601			    error ("`%s' is not defined as an aggregate type.",
602				   TYPE_NAME (type));
603
604			  write_exp_elt_opcode (OP_SCOPE);
605			  write_exp_elt_type (type);
606			  write_exp_string ($3);
607			  write_exp_elt_opcode (OP_SCOPE);
608			}
609	|	typebase COLONCOLON '~' name
610			{
611			  struct type *type = $1;
612			  struct stoken tmp_token;
613			  if (TYPE_CODE (type) != TYPE_CODE_STRUCT
614			      && TYPE_CODE (type) != TYPE_CODE_UNION
615			      && TYPE_CODE (type) != TYPE_CODE_NAMESPACE)
616			    error ("`%s' is not defined as an aggregate type.",
617				   TYPE_NAME (type));
618
619			  tmp_token.ptr = (char*) alloca ($4.length + 2);
620			  tmp_token.length = $4.length + 1;
621			  tmp_token.ptr[0] = '~';
622			  memcpy (tmp_token.ptr+1, $4.ptr, $4.length);
623			  tmp_token.ptr[tmp_token.length] = 0;
624
625			  /* Check for valid destructor name.  */
626			  destructor_name_p (tmp_token.ptr, type);
627			  write_exp_elt_opcode (OP_SCOPE);
628			  write_exp_elt_type (type);
629			  write_exp_string (tmp_token);
630			  write_exp_elt_opcode (OP_SCOPE);
631			}
632	;
633
634variable:	qualified_name
635	|	COLONCOLON name
636			{
637			  char *name = copy_name ($2);
638			  struct symbol *sym;
639			  struct minimal_symbol *msymbol;
640
641			  sym =
642			    lookup_symbol (name, (const struct block *) NULL,
643					   VAR_DOMAIN, (int *) NULL,
644					   (struct symtab **) NULL);
645			  if (sym)
646			    {
647			      write_exp_elt_opcode (OP_VAR_VALUE);
648			      write_exp_elt_block (NULL);
649			      write_exp_elt_sym (sym);
650			      write_exp_elt_opcode (OP_VAR_VALUE);
651			      break;
652			    }
653
654			  msymbol = lookup_minimal_symbol (name, NULL, NULL);
655			  if (msymbol != NULL)
656			    {
657			      write_exp_msymbol (msymbol,
658						 lookup_function_type (builtin_type_int),
659						 builtin_type_int);
660			    }
661			  else
662			    if (!have_full_symbols () && !have_partial_symbols ())
663			      error ("No symbol table is loaded.  Use the \"file\" command.");
664			    else
665			      error ("No symbol \"%s\" in current context.", name);
666			}
667	;
668
669variable:	name_not_typename
670			{ struct symbol *sym = $1.sym;
671
672			  if (sym)
673			    {
674			      if (symbol_read_needs_frame (sym))
675				{
676				  if (innermost_block == 0 ||
677				      contained_in (block_found,
678						    innermost_block))
679				    innermost_block = block_found;
680				}
681
682			      write_exp_elt_opcode (OP_VAR_VALUE);
683			      /* We want to use the selected frame, not
684				 another more inner frame which happens to
685				 be in the same block.  */
686			      write_exp_elt_block (NULL);
687			      write_exp_elt_sym (sym);
688			      write_exp_elt_opcode (OP_VAR_VALUE);
689			    }
690			  else if ($1.is_a_field_of_this)
691			    {
692			      /* C++: it hangs off of `this'.  Must
693			         not inadvertently convert from a method call
694				 to data ref.  */
695			      if (innermost_block == 0 ||
696				  contained_in (block_found, innermost_block))
697				innermost_block = block_found;
698			      write_exp_elt_opcode (OP_THIS);
699			      write_exp_elt_opcode (OP_THIS);
700			      write_exp_elt_opcode (STRUCTOP_PTR);
701			      write_exp_string ($1.stoken);
702			      write_exp_elt_opcode (STRUCTOP_PTR);
703			    }
704			  else
705			    {
706			      struct minimal_symbol *msymbol;
707			      char *arg = copy_name ($1.stoken);
708
709			      msymbol =
710				lookup_minimal_symbol (arg, NULL, NULL);
711			      if (msymbol != NULL)
712				{
713				  write_exp_msymbol (msymbol,
714						     lookup_function_type (builtin_type_int),
715						     builtin_type_int);
716				}
717			      else if (!have_full_symbols () && !have_partial_symbols ())
718				error ("No symbol table is loaded.  Use the \"file\" command.");
719			      else
720				error ("No symbol \"%s\" in current context.",
721				       copy_name ($1.stoken));
722			    }
723			}
724	;
725
726space_identifier : '@' NAME
727		{ push_type_address_space (copy_name ($2.stoken));
728		  push_type (tp_space_identifier);
729		}
730	;
731
732const_or_volatile: const_or_volatile_noopt
733	|
734	;
735
736cv_with_space_id : const_or_volatile space_identifier const_or_volatile
737	;
738
739const_or_volatile_or_space_identifier_noopt: cv_with_space_id
740	| const_or_volatile_noopt
741	;
742
743const_or_volatile_or_space_identifier:
744		const_or_volatile_or_space_identifier_noopt
745	|
746	;
747
748abs_decl:	'*'
749			{ push_type (tp_pointer); $$ = 0; }
750	|	'*' abs_decl
751			{ push_type (tp_pointer); $$ = $2; }
752	|	'&'
753			{ push_type (tp_reference); $$ = 0; }
754	|	'&' abs_decl
755			{ push_type (tp_reference); $$ = $2; }
756	|	direct_abs_decl
757	;
758
759direct_abs_decl: '(' abs_decl ')'
760			{ $$ = $2; }
761	|	direct_abs_decl array_mod
762			{
763			  push_type_int ($2);
764			  push_type (tp_array);
765			}
766	|	array_mod
767			{
768			  push_type_int ($1);
769			  push_type (tp_array);
770			  $$ = 0;
771			}
772
773	| 	direct_abs_decl func_mod
774			{ push_type (tp_function); }
775	|	func_mod
776			{ push_type (tp_function); }
777	;
778
779array_mod:	'[' ']'
780			{ $$ = -1; }
781	|	'[' INT ']'
782			{ $$ = $2.val; }
783	;
784
785func_mod:	'(' ')'
786			{ $$ = 0; }
787	|	'(' nonempty_typelist ')'
788			{ free ($2); $$ = 0; }
789	;
790
791/* We used to try to recognize more pointer to member types here, but
792   that didn't work (shift/reduce conflicts meant that these rules never
793   got executed).  The problem is that
794     int (foo::bar::baz::bizzle)
795   is a function type but
796     int (foo::bar::baz::bizzle::*)
797   is a pointer to member type.  Stroustrup loses again!  */
798
799type	:	ptype
800	|	typebase COLONCOLON '*'
801			{ $$ = lookup_member_type (builtin_type_int, $1); }
802	;
803
804typebase  /* Implements (approximately): (type-qualifier)* type-specifier */
805	:	TYPENAME
806			{ $$ = $1.type; }
807	|	INT_KEYWORD
808			{ $$ = builtin_type_int; }
809	|	LONG
810			{ $$ = builtin_type_long; }
811	|	SHORT
812			{ $$ = builtin_type_short; }
813	|	LONG INT_KEYWORD
814			{ $$ = builtin_type_long; }
815	|	LONG SIGNED_KEYWORD INT_KEYWORD
816			{ $$ = builtin_type_long; }
817	|	LONG SIGNED_KEYWORD
818			{ $$ = builtin_type_long; }
819	|	SIGNED_KEYWORD LONG INT_KEYWORD
820			{ $$ = builtin_type_long; }
821	|	UNSIGNED LONG INT_KEYWORD
822			{ $$ = builtin_type_unsigned_long; }
823	|	LONG UNSIGNED INT_KEYWORD
824			{ $$ = builtin_type_unsigned_long; }
825	|	LONG UNSIGNED
826			{ $$ = builtin_type_unsigned_long; }
827	|	LONG LONG
828			{ $$ = builtin_type_long_long; }
829	|	LONG LONG INT_KEYWORD
830			{ $$ = builtin_type_long_long; }
831	|	LONG LONG SIGNED_KEYWORD INT_KEYWORD
832			{ $$ = builtin_type_long_long; }
833	|	LONG LONG SIGNED_KEYWORD
834			{ $$ = builtin_type_long_long; }
835	|	SIGNED_KEYWORD LONG LONG
836			{ $$ = builtin_type_long_long; }
837	|	SIGNED_KEYWORD LONG LONG INT_KEYWORD
838			{ $$ = builtin_type_long_long; }
839	|	UNSIGNED LONG LONG
840			{ $$ = builtin_type_unsigned_long_long; }
841	|	UNSIGNED LONG LONG INT_KEYWORD
842			{ $$ = builtin_type_unsigned_long_long; }
843	|	LONG LONG UNSIGNED
844			{ $$ = builtin_type_unsigned_long_long; }
845	|	LONG LONG UNSIGNED INT_KEYWORD
846			{ $$ = builtin_type_unsigned_long_long; }
847	|	SHORT INT_KEYWORD
848			{ $$ = builtin_type_short; }
849	|	SHORT SIGNED_KEYWORD INT_KEYWORD
850			{ $$ = builtin_type_short; }
851	|	SHORT SIGNED_KEYWORD
852			{ $$ = builtin_type_short; }
853	|	UNSIGNED SHORT INT_KEYWORD
854			{ $$ = builtin_type_unsigned_short; }
855	|	SHORT UNSIGNED
856			{ $$ = builtin_type_unsigned_short; }
857	|	SHORT UNSIGNED INT_KEYWORD
858			{ $$ = builtin_type_unsigned_short; }
859	|	DOUBLE_KEYWORD
860			{ $$ = builtin_type_double; }
861	|	LONG DOUBLE_KEYWORD
862			{ $$ = builtin_type_long_double; }
863	|	STRUCT name
864			{ $$ = 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