]> Git Repo - binutils.git/blob - gdb/c-exp.y
* main.c (source_command): Require an explicit pathname of file
[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, 0, NULL);
550                           if (!tem || SYMBOL_CLASS (tem) != LOC_BLOCK)
551                             error ("No function \"%s\" in specified context.",
552                                    copy_name ($3));
553                           $$ = SYMBOL_BLOCK_VALUE (tem); }
554         ;
555
556 variable:       block COLONCOLON name
557                         { struct symbol *sym;
558                           sym = lookup_symbol (copy_name ($3), $1,
559                                                VAR_NAMESPACE, 0, NULL);
560                           if (sym == 0)
561                             error ("No symbol \"%s\" in specified context.",
562                                    copy_name ($3));
563
564                           write_exp_elt_opcode (OP_VAR_VALUE);
565                           write_exp_elt_sym (sym);
566                           write_exp_elt_opcode (OP_VAR_VALUE); }
567         ;
568
569 qualified_name: typebase COLONCOLON name
570                         {
571                           struct type *type = $1;
572                           if (TYPE_CODE (type) != TYPE_CODE_STRUCT
573                               && TYPE_CODE (type) != TYPE_CODE_UNION)
574                             error ("`%s' is not defined as an aggregate type.",
575                                    TYPE_NAME (type));
576
577                           write_exp_elt_opcode (OP_SCOPE);
578                           write_exp_elt_type (type);
579                           write_exp_string ($3);
580                           write_exp_elt_opcode (OP_SCOPE);
581                         }
582         |       typebase COLONCOLON '~' name
583                         {
584                           struct type *type = $1;
585                           struct stoken tmp_token;
586                           if (TYPE_CODE (type) != TYPE_CODE_STRUCT
587                               && TYPE_CODE (type) != TYPE_CODE_UNION)
588                             error ("`%s' is not defined as an aggregate type.",
589                                    TYPE_NAME (type));
590
591                           if (!STREQ (type_name_no_tag (type), $4.ptr))
592                             error ("invalid destructor `%s::~%s'",
593                                    type_name_no_tag (type), $4.ptr);
594
595                           tmp_token.ptr = (char*) alloca ($4.length + 2);
596                           tmp_token.length = $4.length + 1;
597                           tmp_token.ptr[0] = '~';
598                           memcpy (tmp_token.ptr+1, $4.ptr, $4.length);
599                           tmp_token.ptr[tmp_token.length] = 0;
600                           write_exp_elt_opcode (OP_SCOPE);
601                           write_exp_elt_type (type);
602                           write_exp_string (tmp_token);
603                           write_exp_elt_opcode (OP_SCOPE);
604                         }
605         ;
606
607 variable:       qualified_name
608         |       COLONCOLON name
609                         {
610                           char *name = copy_name ($2);
611                           struct symbol *sym;
612                           struct minimal_symbol *msymbol;
613
614                           sym =
615                             lookup_symbol (name, 0, VAR_NAMESPACE, 0, NULL);
616                           if (sym)
617                             {
618                               write_exp_elt_opcode (OP_VAR_VALUE);
619                               write_exp_elt_sym (sym);
620                               write_exp_elt_opcode (OP_VAR_VALUE);
621                               break;
622                             }
623
624                           msymbol = lookup_minimal_symbol (name,
625                                       (struct objfile *) NULL);
626                           if (msymbol != NULL)
627                             {
628                               write_exp_elt_opcode (OP_LONG);
629                               write_exp_elt_type (builtin_type_int);
630                               write_exp_elt_longcst ((LONGEST) SYMBOL_VALUE_ADDRESS (msymbol));
631                               write_exp_elt_opcode (OP_LONG);
632                               write_exp_elt_opcode (UNOP_MEMVAL);
633                               if (msymbol -> type == mst_data ||
634                                   msymbol -> type == mst_bss)
635                                 write_exp_elt_type (builtin_type_int);
636                               else if (msymbol -> type == mst_text)
637                                 write_exp_elt_type (lookup_function_type (builtin_type_int));
638                               else
639                                 write_exp_elt_type (builtin_type_char);
640                               write_exp_elt_opcode (UNOP_MEMVAL);
641                             }
642                           else
643                             if (!have_full_symbols () && !have_partial_symbols ())
644                               error ("No symbol table is loaded.  Use the \"file\" command.");
645                             else
646                               error ("No symbol \"%s\" in current context.", name);
647                         }
648         ;
649
650 variable:       name_not_typename
651                         { struct symbol *sym = $1.sym;
652
653                           if (sym)
654                             {
655                               switch (SYMBOL_CLASS (sym))
656                                 {
657                                 case LOC_REGISTER:
658                                 case LOC_ARG:
659                                 case LOC_REF_ARG:
660                                 case LOC_REGPARM:
661                                 case LOC_LOCAL:
662                                 case LOC_LOCAL_ARG:
663                                   if (innermost_block == 0 ||
664                                       contained_in (block_found, 
665                                                     innermost_block))
666                                     innermost_block = block_found;
667                                 case LOC_UNDEF:
668                                 case LOC_CONST:
669                                 case LOC_STATIC:
670                                 case LOC_TYPEDEF:
671                                 case LOC_LABEL:
672                                 case LOC_BLOCK:
673                                 case LOC_CONST_BYTES:
674
675                                   /* In this case the expression can
676                                      be evaluated regardless of what
677                                      frame we are in, so there is no
678                                      need to check for the
679                                      innermost_block.  These cases are
680                                      listed so that gcc -Wall will
681                                      report types that may not have
682                                      been considered.  */
683
684                                   break;
685                                 }
686                               write_exp_elt_opcode (OP_VAR_VALUE);
687                               write_exp_elt_sym (sym);
688                               write_exp_elt_opcode (OP_VAR_VALUE);
689                             }
690                           else if ($1.is_a_field_of_this)
691                             {
692                               /* C++: it hangs off of `this'.  Must
693                                  not inadvertently convert from a method call
694                                  to data ref.  */
695                               if (innermost_block == 0 || 
696                                   contained_in (block_found, innermost_block))
697                                 innermost_block = block_found;
698                               write_exp_elt_opcode (OP_THIS);
699                               write_exp_elt_opcode (OP_THIS);
700                               write_exp_elt_opcode (STRUCTOP_PTR);
701                               write_exp_string ($1.stoken);
702                               write_exp_elt_opcode (STRUCTOP_PTR);
703                             }
704                           else
705                             {
706                               struct minimal_symbol *msymbol;
707                               register char *arg = copy_name ($1.stoken);
708
709                               msymbol = lookup_minimal_symbol (arg,
710                                           (struct objfile *) NULL);
711                               if (msymbol != NULL)
712                                 {
713                                   write_exp_elt_opcode (OP_LONG);
714                                   write_exp_elt_type (builtin_type_int);
715                                   write_exp_elt_longcst ((LONGEST) SYMBOL_VALUE_ADDRESS (msymbol));
716                                   write_exp_elt_opcode (OP_LONG);
717                                   write_exp_elt_opcode (UNOP_MEMVAL);
718                                   if (msymbol -> type == mst_data ||
719                                       msymbol -> type == mst_bss)
720                                     write_exp_elt_type (builtin_type_int);
721                                   else if (msymbol -> type == mst_text)
722                                     write_exp_elt_type (lookup_function_type (builtin_type_int));
723                                   else
724                                     write_exp_elt_type (builtin_type_char);
725                                   write_exp_elt_opcode (UNOP_MEMVAL);
726                                 }
727                               else if (!have_full_symbols () && !have_partial_symbols ())
728                                 error ("No symbol table is loaded.  Use the \"file\" command.");
729                               else
730                                 error ("No symbol \"%s\" in current context.",
731                                        copy_name ($1.stoken));
732                             }
733                         }
734         ;
735
736
737 ptype   :       typebase
738         |       typebase abs_decl
739                 {
740                   /* This is where the interesting stuff happens.  */
741                   int done = 0;
742                   int array_size;
743                   struct type *follow_type = $1;
744                   struct type *range_type;
745                   
746                   while (!done)
747                     switch (pop_type ())
748                       {
749                       case tp_end:
750                         done = 1;
751                         break;
752                       case tp_pointer:
753                         follow_type = lookup_pointer_type (follow_type);
754                         break;
755                       case tp_reference:
756                         follow_type = lookup_reference_type (follow_type);
757                         break;
758                       case tp_array:
759                         array_size = pop_type_int ();
760                         if (array_size != -1)
761                           {
762                             range_type =
763                               create_range_type ((struct type *) NULL,
764                                                  builtin_type_int, 0,
765                                                  array_size - 1);
766                             follow_type =
767                               create_array_type ((struct type *) NULL,
768                                                  follow_type, range_type);
769                           }
770                         else
771                           follow_type = lookup_pointer_type (follow_type);
772                         break;
773                       case tp_function:
774                         follow_type = lookup_function_type (follow_type);
775                         break;
776                       }
777                   $$ = follow_type;
778                 }
779         ;
780
781 abs_decl:       '*'
782                         { push_type (tp_pointer); $$ = 0; }
783         |       '*' abs_decl
784                         { push_type (tp_pointer); $$ = $2; }
785         |       '&'
786                         { push_type (tp_reference); $$ = 0; }
787         |       '&' abs_decl
788                         { push_type (tp_reference); $$ = $2; }
789         |       direct_abs_decl
790         ;
791
792 direct_abs_decl: '(' abs_decl ')'
793                         { $$ = $2; }
794         |       direct_abs_decl array_mod
795                         {
796                           push_type_int ($2);
797                           push_type (tp_array);
798                         }
799         |       array_mod
800                         {
801                           push_type_int ($1);
802                           push_type (tp_array);
803                           $$ = 0;
804                         }
805         |       direct_abs_decl func_mod
806                         { push_type (tp_function); }
807         |       func_mod
808                         { push_type (tp_function); }
809         ;
810
811 array_mod:      '[' ']'
812                         { $$ = -1; }
813         |       '[' INT ']'
814                         { $$ = $2.val; }
815         ;
816
817 func_mod:       '(' ')'
818                         { $$ = 0; }
819         |       '(' nonempty_typelist ')'
820                         { free ((PTR)$2); $$ = 0; }
821         ;
822
823 type    :       ptype
824         |       typebase COLONCOLON '*'
825                         { $$ = lookup_member_type (builtin_type_int, $1); }
826         |       type '(' typebase COLONCOLON '*' ')'
827                         { $$ = lookup_member_type ($1, $3); }
828         |       type '(' typebase COLONCOLON '*' ')' '(' ')'
829                         { $$ = lookup_member_type
830                             (lookup_function_type ($1), $3); }
831         |       type '(' typebase COLONCOLON '*' ')' '(' nonempty_typelist ')'
832                         { $$ = lookup_member_type
833                             (lookup_function_type ($1), $3);
834                           free ((PTR)$8); }
835         ;
836
837 typebase  /* Implements (approximately): (type-qualifier)* type-specifier */
838         :       TYPENAME
839                         { $$ = $1.type; }
840         |       INT_KEYWORD
841                         { $$ = builtin_type_int; }
842         |       LONG
843                         { $$ = builtin_type_long; }
844         |       SHORT
845                         { $$ = builtin_type_short; }
846         |       LONG INT_KEYWORD
847                         { $$ = builtin_type_long; }
848         |       UNSIGNED LONG INT_KEYWORD
849                         { $$ = builtin_type_unsigned_long; }
850         |       LONG LONG
851                         { $$ = builtin_type_long_long; }
852         |       LONG LONG INT_KEYWORD
853                         { $$ = builtin_type_long_long; }
854         |       UNSIGNED LONG LONG
855                         { $$ = builtin_type_unsigned_long_long; }
856         |       UNSIGNED LONG LONG INT_KEYWORD
857                         { $$ = builtin_type_unsigned_long_long; }
858         |       SHORT INT_KEYWORD
859                         { $$ = builtin_type_short; }
860         |       UNSIGNED SHORT INT_KEYWORD
861                         { $$ = builtin_type_unsigned_short; }
862         |       STRUCT name
863                         { $$ = lookup_struct (copy_name ($2),
864                                               expression_context_block); }
865         |       CLASS name
866                         { $$ = lookup_struct (copy_name ($2),
867                                               expression_context_block); }
868         |       UNION name
869                         { $$ = lookup_union (copy_name ($2),
870                                              expression_context_block); }
871         |       ENUM name
872                         { $$ = lookup_enum (copy_name ($2),
873                                             expression_context_block); }
874         |       UNSIGNED typename
875                         { $$ = lookup_unsigned_typename (TYPE_NAME($2.type)); }
876         |       UNSIGNED
877                         { $$ = builtin_type_unsigned_int; }
878         |       SIGNED_KEYWORD typename
879                         { $$ = lookup_signed_typename (TYPE_NAME($2.type)); }
880         |       SIGNED_KEYWORD
881                         { $$ = builtin_type_int; }
882         |       TEMPLATE name '<' type '>'
883                         { $$ = lookup_template_type(copy_name($2), $4,
884                                                     expression_context_block);
885                         }
886         /* "const" and "volatile" are curently ignored. */
887         |       CONST_KEYWORD typebase { $$ = $2; }
888         |       VOLATILE_KEYWORD typebase { $$ = $2; }
889         ;
890
891 typename:       TYPENAME
892         |       INT_KEYWORD
893                 {
894                   $$.stoken.ptr = "int";
895                   $$.stoken.length = 3;
896                   $$.type = builtin_type_int;
897                 }
898         |       LONG
899                 {
900                   $$.stoken.ptr = "long";
901                   $$.stoken.length = 4;
902                   $$.type = builtin_type_long;
903                 }
904         |       SHORT
905                 {
906                   $$.stoken.ptr = "short";
907                   $$.stoken.length = 5;
908                   $$.type = builtin_type_short;
909                 }
910         ;
911
912 nonempty_typelist
913         :       type
914                 { $$ = (struct type **) malloc (sizeof (struct type *) * 2);
915                   $<ivec>$[0] = 1;      /* Number of types in vector */
916                   $$[1] = $1;
917                 }
918         |       nonempty_typelist ',' type
919                 { int len = sizeof (struct type *) * (++($<ivec>1[0]) + 1);
920                   $$ = (struct type **) realloc ((char *) $1, len);
921                   $$[$<ivec>$[0]] = $3;
922                 }
923         ;
924
925 name    :       NAME { $$ = $1.stoken; }
926         |       BLOCKNAME { $$ = $1.stoken; }
927         |       TYPENAME { $$ = $1.stoken; }
928         |       NAME_OR_INT  { $$ = $1.stoken; }
929         ;
930
931 name_not_typename :     NAME
932         |       BLOCKNAME
933 /* These would be useful if name_not_typename was useful, but it is just
934    a fake for "variable", so these cause reduce/reduce conflicts because
935    the parser can't tell whether NAME_OR_INT is a name_not_typename (=variable,
936    =exp) or just an exp.  If name_not_typename was ever used in an lvalue
937    context where only a name could occur, this might be useful.
938         |       NAME_OR_INT
939  */
940         ;
941
942 %%
943
944 /* Take care of parsing a number (anything that starts with a digit).
945    Set yylval and return the token type; update lexptr.
946    LEN is the number of characters in it.  */
947
948 /*** Needs some error checking for the float case ***/
949
950 static int
951 parse_number (p, len, parsed_float, putithere)
952      register char *p;
953      register int len;
954      int parsed_float;
955      YYSTYPE *putithere;
956 {
957   register LONGEST n = 0;
958   register LONGEST prevn = 0;
959   register int i;
960   register int c;
961   register int base = input_radix;
962   int unsigned_p = 0;
963   int long_p = 0;
964   unsigned LONGEST high_bit;
965   struct type *signed_type;
966   struct type *unsigned_type;
967
968   if (parsed_float)
969     {
970       /* It's a float since it contains a point or an exponent.  */
971       putithere->dval = atof (p);
972       return FLOAT;
973     }
974
975   /* Handle base-switching prefixes 0x, 0t, 0d, 0 */
976   if (p[0] == '0')
977     switch (p[1])
978       {
979       case 'x':
980       case 'X':
981         if (len >= 3)
982           {
983             p += 2;
984             base = 16;
985             len -= 2;
986           }
987         break;
988
989       case 't':
990       case 'T':
991       case 'd':
992       case 'D':
993         if (len >= 3)
994           {
995             p += 2;
996             base = 10;
997             len -= 2;
998           }
999         break;
1000
1001       default:
1002         base = 8;
1003         break;
1004       }
1005
1006   while (len-- > 0)
1007     {
1008       c = *p++;
1009       if (c >= 'A' && c <= 'Z')
1010         c += 'a' - 'A';
1011       if (c != 'l' && c != 'u')
1012         n *= base;
1013       if (c >= '0' && c <= '9')
1014         n += i = c - '0';
1015       else
1016         {
1017           if (base > 10 && c >= 'a' && c <= 'f')
1018             n += i = c - 'a' + 10;
1019           else if (len == 0 && c == 'l') 
1020             long_p = 1;
1021           else if (len == 0 && c == 'u')
1022             unsigned_p = 1;
1023           else
1024             return ERROR;       /* Char not a digit */
1025         }
1026       if (i >= base)
1027         return ERROR;           /* Invalid digit in this base */
1028
1029       /* Portably test for overflow (only works for nonzero values, so make
1030          a second check for zero).  */
1031       if((prevn >= n) && n != 0)
1032          unsigned_p=1;          /* Try something unsigned */
1033       /* If range checking enabled, portably test for unsigned overflow.  */
1034       if(RANGE_CHECK && n!=0)
1035       { 
1036          if((unsigned_p && (unsigned)prevn >= (unsigned)n))
1037             range_error("Overflow on numeric constant.");        
1038       }
1039       prevn=n;
1040     }
1041  
1042      /* If the number is too big to be an int, or it's got an l suffix
1043         then it's a long.  Work out if this has to be a long by
1044         shifting right and and seeing if anything remains, and the
1045         target int size is different to the target long size. */
1046
1047     if ((TARGET_INT_BIT != TARGET_LONG_BIT && (n >> TARGET_INT_BIT)) || long_p)
1048       {
1049          high_bit = ((unsigned LONGEST)1) << (TARGET_LONG_BIT-1);
1050          unsigned_type = builtin_type_unsigned_long;
1051          signed_type = builtin_type_long;
1052       }
1053     else 
1054       {
1055          high_bit = ((unsigned LONGEST)1) << (TARGET_INT_BIT-1);
1056          unsigned_type = builtin_type_unsigned_int;
1057          signed_type = builtin_type_int;
1058       }    
1059
1060    putithere->typed_val.val = n;
1061
1062    /* If the high bit of the worked out type is set then this number
1063       has to be unsigned. */
1064
1065    if (unsigned_p || (n & high_bit)) 
1066      {
1067         putithere->typed_val.type = unsigned_type;
1068      }
1069    else 
1070      {
1071         putithere->typed_val.type = signed_type;
1072      }
1073
1074    return INT;
1075 }
1076
1077 struct token
1078 {
1079   char *operator;
1080   int token;
1081   enum exp_opcode opcode;
1082 };
1083
1084 static const struct token tokentab3[] =
1085   {
1086     {">>=", ASSIGN_MODIFY, BINOP_RSH},
1087     {"<<=", ASSIGN_MODIFY, BINOP_LSH}
1088   };
1089
1090 static const struct token tokentab2[] =
1091   {
1092     {"+=", ASSIGN_MODIFY, BINOP_ADD},
1093     {"-=", ASSIGN_MODIFY, BINOP_SUB},
1094     {"*=", ASSIGN_MODIFY, BINOP_MUL},
1095     {"/=", ASSIGN_MODIFY, BINOP_DIV},
1096     {"%=", ASSIGN_MODIFY, BINOP_REM},
1097     {"|=", ASSIGN_MODIFY, BINOP_BITWISE_IOR},
1098     {"&=", ASSIGN_MODIFY, BINOP_BITWISE_AND},
1099     {"^=", ASSIGN_MODIFY, BINOP_BITWISE_XOR},
1100     {"++", INCREMENT, BINOP_END},
1101     {"--", DECREMENT, BINOP_END},
1102     {"->", ARROW, BINOP_END},
1103     {"&&", ANDAND, BINOP_END},
1104     {"||", OROR, BINOP_END},
1105     {"::", COLONCOLON, BINOP_END},
1106     {"<<", LSH, BINOP_END},
1107     {">>", RSH, BINOP_END},
1108     {"==", EQUAL, BINOP_END},
1109     {"!=", NOTEQUAL, BINOP_END},
1110     {"<=", LEQ, BINOP_END},
1111     {">=", GEQ, BINOP_END}
1112   };
1113
1114 /* Read one token, getting characters through lexptr.  */
1115
1116 static int
1117 yylex ()
1118 {
1119   int c;
1120   int namelen;
1121   unsigned int i;
1122   char *tokstart;
1123   char *tokptr;
1124   int tempbufindex;
1125   static char *tempbuf;
1126   static int tempbufsize;
1127   
1128  retry:
1129
1130   tokstart = lexptr;
1131   /* See if it is a special token of length 3.  */
1132   for (i = 0; i < sizeof tokentab3 / sizeof tokentab3[0]; i++)
1133     if (STREQN (tokstart, tokentab3[i].operator, 3))
1134       {
1135         lexptr += 3;
1136         yylval.opcode = tokentab3[i].opcode;
1137         return tokentab3[i].token;
1138       }
1139
1140   /* See if it is a special token of length 2.  */
1141   for (i = 0; i < sizeof tokentab2 / sizeof tokentab2[0]; i++)
1142     if (STREQN (tokstart, tokentab2[i].operator, 2))
1143       {
1144         lexptr += 2;
1145         yylval.opcode = tokentab2[i].opcode;
1146         return tokentab2[i].token;
1147       }
1148
1149   switch (c = *tokstart)
1150     {
1151     case 0:
1152       return 0;
1153
1154     case ' ':
1155     case '\t':
1156     case '\n':
1157       lexptr++;
1158       goto retry;
1159
1160     case '\'':
1161       /* We either have a character constant ('0' or '\177' for example)
1162          or we have a quoted symbol reference ('foo(int,int)' in C++
1163          for example). */
1164       lexptr++;
1165       c = *lexptr++;
1166       if (c == '\\')
1167         c = parse_escape (&lexptr);
1168
1169       yylval.typed_val.val = c;
1170       yylval.typed_val.type = builtin_type_char;
1171
1172       c = *lexptr++;
1173       if (c != '\'')
1174         {
1175           namelen = skip_quoted (tokstart) - tokstart;
1176           if (namelen > 2)
1177             {
1178               lexptr = tokstart + namelen;
1179               namelen -= 2;
1180               tokstart++;
1181               goto tryname;
1182             }
1183           error ("Invalid character constant.");
1184         }
1185       return INT;
1186
1187     case '(':
1188       paren_depth++;
1189       lexptr++;
1190       return c;
1191
1192     case ')':
1193       if (paren_depth == 0)
1194         return 0;
1195       paren_depth--;
1196       lexptr++;
1197       return c;
1198
1199     case ',':
1200       if (comma_terminates && paren_depth == 0)
1201         return 0;
1202       lexptr++;
1203       return c;
1204
1205     case '.':
1206       /* Might be a floating point number.  */
1207       if (lexptr[1] < '0' || lexptr[1] > '9')
1208         goto symbol;            /* Nope, must be a symbol. */
1209       /* FALL THRU into number case.  */
1210
1211     case '0':
1212     case '1':
1213     case '2':
1214     case '3':
1215     case '4':
1216     case '5':
1217     case '6':
1218     case '7':
1219     case '8':
1220     case '9':
1221       {
1222         /* It's a number.  */
1223         int got_dot = 0, got_e = 0, toktype;
1224         register char *p = tokstart;
1225         int hex = input_radix > 10;
1226
1227         if (c == '0' && (p[1] == 'x' || p[1] == 'X'))
1228           {
1229             p += 2;
1230             hex = 1;
1231           }
1232         else if (c == '0' && (p[1]=='t' || p[1]=='T' || p[1]=='d' || p[1]=='D'))
1233           {
1234             p += 2;
1235             hex = 0;
1236           }
1237
1238         for (;; ++p)
1239           {
1240             if (!hex && !got_e && (*p == 'e' || *p == 'E'))
1241               got_dot = got_e = 1;
1242             else if (!hex && !got_dot && *p == '.')
1243               got_dot = 1;
1244             else if (got_e && (p[-1] == 'e' || p[-1] == 'E')
1245                      && (*p == '-' || *p == '+'))
1246               /* This is the sign of the exponent, not the end of the
1247                  number.  */
1248               continue;
1249             /* We will take any letters or digits.  parse_number will
1250                complain if past the radix, or if L or U are not final.  */
1251             else if ((*p < '0' || *p > '9')
1252                      && ((*p < 'a' || *p > 'z')
1253                                   && (*p < 'A' || *p > 'Z')))
1254               break;
1255           }
1256         toktype = parse_number (tokstart, p - tokstart, got_dot|got_e, &yylval);
1257         if (toktype == ERROR)
1258           {
1259             char *err_copy = (char *) alloca (p - tokstart + 1);
1260
1261             memcpy (err_copy, tokstart, p - tokstart);
1262             err_copy[p - tokstart] = 0;
1263             error ("Invalid number \"%s\".", err_copy);
1264           }
1265         lexptr = p;
1266         return toktype;
1267       }
1268
1269     case '+':
1270     case '-':
1271     case '*':
1272     case '/':
1273     case '%':
1274     case '|':
1275     case '&':
1276     case '^':
1277     case '~':
1278     case '!':
1279     case '@':
1280     case '<':
1281     case '>':
1282     case '[':
1283     case ']':
1284     case '?':
1285     case ':':
1286     case '=':
1287     case '{':
1288     case '}':
1289     symbol:
1290       lexptr++;
1291       return c;
1292
1293     case '"':
1294
1295       /* Build the gdb internal form of the input string in tempbuf,
1296          translating any standard C escape forms seen.  Note that the
1297          buffer is null byte terminated *only* for the convenience of
1298          debugging gdb itself and printing the buffer contents when
1299          the buffer contains no embedded nulls.  Gdb does not depend
1300          upon the buffer being null byte terminated, it uses the length
1301          string instead.  This allows gdb to handle C strings (as well
1302          as strings in other languages) with embedded null bytes */
1303
1304       tokptr = ++tokstart;
1305       tempbufindex = 0;
1306
1307       do {
1308         /* Grow the static temp buffer if necessary, including allocating
1309            the first one on demand. */
1310         if (tempbufindex + 1 >= tempbufsize)
1311           {
1312             tempbuf = (char *) realloc (tempbuf, tempbufsize += 64);
1313           }
1314         switch (*tokptr)
1315           {
1316           case '\0':
1317           case '"':
1318             /* Do nothing, loop will terminate. */
1319             break;
1320           case '\\':
1321             tokptr++;
1322             c = parse_escape (&tokptr);
1323             if (c == -1)
1324               {
1325                 continue;
1326               }
1327             tempbuf[tempbufindex++] = c;
1328             break;
1329           default:
1330             tempbuf[tempbufindex++] = *tokptr++;
1331             break;
1332           }
1333       } while ((*tokptr != '"') && (*tokptr != '\0'));
1334       if (*tokptr++ != '"')
1335         {
1336           error ("Unterminated string in expression.");
1337         }
1338       tempbuf[tempbufindex] = '\0';     /* See note above */
1339       yylval.sval.ptr = tempbuf;
1340       yylval.sval.length = tempbufindex;
1341       lexptr = tokptr;
1342       return (STRING);
1343     }
1344
1345   if (!(c == '_' || c == '$'
1346         || (c >= 'a' && c <= 'z') || (c >= 'A' && c <= 'Z')))
1347     /* We must have come across a bad character (e.g. ';').  */
1348     error ("Invalid character '%c' in expression.", c);
1349
1350   /* It's a name.  See how long it is.  */
1351   namelen = 0;
1352   for (c = tokstart[namelen];
1353        (c == '_' || c == '$' || (c >= '0' && c <= '9')
1354         || (c >= 'a' && c <= 'z') || (c >= 'A' && c <= 'Z'));
1355        c = tokstart[++namelen])
1356     ;
1357
1358   /* The token "if" terminates the expression and is NOT 
1359      removed from the input stream.  */
1360   if (namelen == 2 && tokstart[0] == 'i' && tokstart[1] == 'f')
1361     {
1362       return 0;
1363     }
1364
1365   lexptr += namelen;
1366
1367   /* Handle the tokens $digits; also $ (short for $0) and $$ (short for $$1)
1368      and $$digits (equivalent to $<-digits> if you could type that).
1369      Make token type LAST, and put the number (the digits) in yylval.  */
1370
1371   tryname:
1372   if (*tokstart == '$')
1373     {
1374       register int negate = 0;
1375       c = 1;
1376       /* Double dollar means negate the number and add -1 as well.
1377          Thus $$ alone means -1.  */
1378       if (namelen >= 2 && tokstart[1] == '$')
1379         {
1380           negate = 1;
1381           c = 2;
1382         }
1383       if (c == namelen)
1384         {
1385           /* Just dollars (one or two) */
1386           yylval.lval = - negate;
1387           return LAST;
1388         }
1389       /* Is the rest of the token digits?  */
1390       for (; c < namelen; c++)
1391         if (!(tokstart[c] >= '0' && tokstart[c] <= '9'))
1392           break;
1393       if (c == namelen)
1394         {
1395           yylval.lval = atoi (tokstart + 1 + negate);
1396           if (negate)
1397             yylval.lval = - yylval.lval;
1398           return LAST;
1399         }
1400     }
1401
1402   /* Handle tokens that refer to machine registers:
1403      $ followed by a register name.  */
1404
1405   if (*tokstart == '$') {
1406     for (c = 0; c < NUM_REGS; c++)
1407       if (namelen - 1 == strlen (reg_names[c])
1408           && STREQN (tokstart + 1, reg_names[c], namelen - 1))
1409         {
1410           yylval.lval = c;
1411           return REGNAME;
1412         }
1413     for (c = 0; c < num_std_regs; c++)
1414      if (namelen - 1 == strlen (std_regs[c].name)
1415          && STREQN (tokstart + 1, std_regs[c].name, namelen - 1))
1416        {
1417          yylval.lval = std_regs[c].regnum;
1418          return REGNAME;
1419        }
1420   }
1421   /* Catch specific keywords.  Should be done with a data structure.  */
1422   switch (namelen)
1423     {
1424     case 8:
1425       if (STREQN (tokstart, "unsigned", 8))
1426         return UNSIGNED;
1427       if (current_language->la_language == language_cplus
1428           && STREQN (tokstart, "template", 8))
1429         return TEMPLATE;
1430       if (STREQN (tokstart, "volatile", 8))
1431         return VOLATILE_KEYWORD;
1432       break;
1433     case 6:
1434       if (STREQN (tokstart, "struct", 6))
1435         return STRUCT;
1436       if (STREQN (tokstart, "signed", 6))
1437         return SIGNED_KEYWORD;
1438       if (STREQN (tokstart, "sizeof", 6))      
1439         return SIZEOF;
1440       break;
1441     case 5:
1442       if (current_language->la_language == language_cplus
1443           && STREQN (tokstart, "class", 5))
1444         return CLASS;
1445       if (STREQN (tokstart, "union", 5))
1446         return UNION;
1447       if (STREQN (tokstart, "short", 5))
1448         return SHORT;
1449       if (STREQN (tokstart, "const", 5))
1450         return CONST_KEYWORD;
1451       break;
1452     case 4:
1453       if (STREQN (tokstart, "enum", 4))
1454         return ENUM;
1455       if (STREQN (tokstart, "long", 4))
1456         return LONG;
1457       if (current_language->la_language == language_cplus
1458           && STREQN (tokstart, "this", 4))
1459         {
1460           static const char this_name[] =
1461                                  { CPLUS_MARKER, 't', 'h', 'i', 's', '\0' };
1462
1463           if (lookup_symbol (this_name, expression_context_block,
1464                              VAR_NAMESPACE, 0, NULL))
1465             return THIS;
1466         }
1467       break;
1468     case 3:
1469       if (STREQN (tokstart, "int", 3))
1470         return INT_KEYWORD;
1471       break;
1472     default:
1473       break;
1474     }
1475
1476   yylval.sval.ptr = tokstart;
1477   yylval.sval.length = namelen;
1478
1479   /* Any other names starting in $ are debugger internal variables.  */
1480
1481   if (*tokstart == '$')
1482     {
1483       yylval.ivar =  lookup_internalvar (copy_name (yylval.sval) + 1);
1484       return VARIABLE;
1485     }
1486
1487   /* Use token-type BLOCKNAME for symbols that happen to be defined as
1488      functions or symtabs.  If this is not so, then ...
1489      Use token-type TYPENAME for symbols that happen to be defined
1490      currently as names of types; NAME for other symbols.
1491      The caller is not constrained to care about the distinction.  */
1492   {
1493     char *tmp = copy_name (yylval.sval);
1494     struct symbol *sym;
1495     int is_a_field_of_this = 0;
1496     int hextype;
1497
1498     sym = lookup_symbol (tmp, expression_context_block,
1499                          VAR_NAMESPACE,
1500                          current_language->la_language == language_cplus
1501                          ? &is_a_field_of_this : NULL,
1502                          NULL);
1503     if ((sym && SYMBOL_CLASS (sym) == LOC_BLOCK) ||
1504         lookup_partial_symtab (tmp))
1505       {
1506         yylval.ssym.sym = sym;
1507         yylval.ssym.is_a_field_of_this = is_a_field_of_this;
1508         return BLOCKNAME;
1509       }
1510     if (sym && SYMBOL_CLASS (sym) == LOC_TYPEDEF)
1511         {
1512           yylval.tsym.type = SYMBOL_TYPE (sym);
1513           return TYPENAME;
1514         }
1515     if ((yylval.tsym.type = lookup_primitive_typename (tmp)) != 0)
1516         return TYPENAME;
1517
1518     /* Input names that aren't symbols but ARE valid hex numbers,
1519        when the input radix permits them, can be names or numbers
1520        depending on the parse.  Note we support radixes > 16 here.  */
1521     if (!sym && 
1522         ((tokstart[0] >= 'a' && tokstart[0] < 'a' + input_radix - 10) ||
1523          (tokstart[0] >= 'A' && tokstart[0] < 'A' + input_radix - 10)))
1524       {
1525         YYSTYPE newlval;        /* Its value is ignored.  */
1526         hextype = parse_number (tokstart, namelen, 0, &newlval);
1527         if (hextype == INT)
1528           {
1529             yylval.ssym.sym = sym;
1530             yylval.ssym.is_a_field_of_this = is_a_field_of_this;
1531             return NAME_OR_INT;
1532           }
1533       }
1534
1535     /* Any other kind of symbol */
1536     yylval.ssym.sym = sym;
1537     yylval.ssym.is_a_field_of_this = is_a_field_of_this;
1538     return NAME;
1539   }
1540 }
1541
1542 void
1543 yyerror (msg)
1544      char *msg;
1545 {
1546   error (msg ? msg : "Invalid syntax in expression.");
1547 }
This page took 0.112956 seconds and 4 git commands to generate.