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