OSDN Git Service

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