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