OSDN Git Service

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