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