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