1 /* YACC parser for C expressions, for GDB.
2 Copyright 1986, 1989, 1990, 1991, 1992, 1993, 1994, 1995, 1996, 1997,
4 Free Software Foundation, Inc.
6 This file is part of GDB.
8 This program is free software; you can redistribute it and/or modify
9 it under the terms of the GNU General Public License as published by
10 the Free Software Foundation; either version 2 of the License, or
11 (at your option) any later version.
13 This program is distributed in the hope that it will be useful,
14 but WITHOUT ANY WARRANTY; without even the implied warranty of
15 MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the
16 GNU General Public License for more details.
18 You should have received a copy of the GNU General Public License
19 along with this program; if not, write to the Free Software
20 Foundation, Inc., 59 Temple Place - Suite 330, Boston, MA 02111-1307, USA. */
22 /* Parse a C expression from text in a string,
23 and return the result as a struct expression pointer.
24 That structure contains arithmetic operations in reverse polish,
25 with constants represented by operations that are followed by special data.
26 See expression.h for the details of the format.
27 What is important here is that it can be built up sequentially
28 during the process of parsing; the lower levels of the tree always
29 come first in the result.
31 Note that malloc's and realloc's in this file are transformed to
32 xmalloc and xrealloc respectively by the same sed command in the
33 makefile that remaps any other malloc/realloc inserted by the parser
34 generator. Doing this with #defines and trying to control the interaction
35 with include files (<malloc.h> and <stdlib.h> for example) just became
36 too messy, particularly when such includes can be inserted at random
37 times by the parser generator. */
42 #include "gdb_string.h"
44 #include "expression.h"
46 #include "parser-defs.h"
49 #include "bfd.h" /* Required by objfiles.h. */
50 #include "symfile.h" /* Required by objfiles.h. */
51 #include "objfiles.h" /* For have_full_symbols and have_partial_symbols */
53 /* Flag indicating we're dealing with HP-compiled objects */
54 extern int hp_som_som_object_present;
56 /* Remap normal yacc parser interface names (yyparse, yylex, yyerror, etc),
57 as well as gratuitiously global symbol names, so we can have multiple
58 yacc generated parsers in gdb. Note that these are only the variables
59 produced by yacc. If other parser generators (bison, byacc, etc) produce
60 additional global names that conflict at link time, then those parser
61 generators need to be fixed instead of adding those names to this list. */
63 #define yymaxdepth c_maxdepth
64 #define yyparse c_parse
66 #define yyerror c_error
69 #define yydebug c_debug
78 #define yyerrflag c_errflag
79 #define yynerrs c_nerrs
84 #define yystate c_state
90 #define yyreds c_reds /* With YYDEBUG defined */
91 #define yytoks c_toks /* With YYDEBUG defined */
92 #define yyname c_name /* With YYDEBUG defined */
93 #define yyrule c_rule /* With YYDEBUG defined */
96 #define yydefred c_yydefred
97 #define yydgoto c_yydgoto
98 #define yysindex c_yysindex
99 #define yyrindex c_yyrindex
100 #define yygindex c_yygindex
101 #define yytable c_yytable
102 #define yycheck c_yycheck
105 #define YYDEBUG 1 /* Default to yydebug support */
108 #define YYFPRINTF parser_fprintf
112 static int yylex (void);
114 void yyerror (char *);
118 /* Although the yacc "value" of an expression is not used,
119 since the result is stored in the structure being created,
120 other node types do have values. */
137 struct symtoken ssym;
140 enum exp_opcode opcode;
141 struct internalvar *ivar;
148 /* YYSTYPE gets defined by %union */
149 static int parse_number (char *, int, int, YYSTYPE *);
152 %type <voidval> exp exp1 type_exp start variable qualified_name lcurly
154 %type <tval> type typebase
155 %type <tvec> nonempty_typelist
156 /* %type <bval> block */
158 /* Fancy type parsing. */
159 %type <voidval> func_mod direct_abs_decl abs_decl
161 %type <lval> array_mod
163 %token <typed_val_int> INT
164 %token <typed_val_float> FLOAT
166 /* Both NAME and TYPENAME tokens represent symbols in the input,
167 and both convey their data as strings.
168 But a TYPENAME is a string that happens to be defined as a typedef
169 or builtin type name (such as int or char)
170 and a NAME is any other symbol.
171 Contexts where this distinction is not important can use the
172 nonterminal "name", which matches either NAME or TYPENAME. */
175 %token <ssym> NAME /* BLOCKNAME defined below to give it higher precedence. */
176 %token <tsym> TYPENAME
178 %type <ssym> name_not_typename
179 %type <tsym> typename
181 /* A NAME_OR_INT is a symbol which is not known in the symbol table,
182 but which would parse as a valid number in the current input radix.
183 E.g. "c" when input_radix==16. Depending on the parse, it will be
184 turned into a name or into a number. */
186 %token <ssym> NAME_OR_INT
188 %token STRUCT CLASS UNION ENUM SIZEOF UNSIGNED COLONCOLON
192 /* Special type cases, put in to allow the parser to distinguish different
194 %token SIGNED_KEYWORD LONG SHORT INT_KEYWORD CONST_KEYWORD VOLATILE_KEYWORD DOUBLE_KEYWORD
196 %token <voidval> VARIABLE
198 %token <opcode> ASSIGN_MODIFY
208 %right '=' ASSIGN_MODIFY
216 %left '<' '>' LEQ GEQ
221 %right UNARY INCREMENT DECREMENT
222 %right ARROW '.' '[' '('
223 %token <ssym> BLOCKNAME
224 %token <bval> FILENAME
236 { write_exp_elt_opcode(OP_TYPE);
237 write_exp_elt_type($1);
238 write_exp_elt_opcode(OP_TYPE);}
241 /* Expressions, including the comma operator. */
244 { write_exp_elt_opcode (BINOP_COMMA); }
247 /* Expressions, not including the comma operator. */
248 exp : '*' exp %prec UNARY
249 { write_exp_elt_opcode (UNOP_IND); }
251 exp : '&' exp %prec UNARY
252 { write_exp_elt_opcode (UNOP_ADDR); }
254 exp : '-' exp %prec UNARY
255 { write_exp_elt_opcode (UNOP_NEG); }
258 exp : '!' exp %prec UNARY
259 { write_exp_elt_opcode (UNOP_LOGICAL_NOT); }
262 exp : '~' exp %prec UNARY
263 { write_exp_elt_opcode (UNOP_COMPLEMENT); }
266 exp : INCREMENT exp %prec UNARY
267 { write_exp_elt_opcode (UNOP_PREINCREMENT); }
270 exp : DECREMENT exp %prec UNARY
271 { write_exp_elt_opcode (UNOP_PREDECREMENT); }
274 exp : exp INCREMENT %prec UNARY
275 { write_exp_elt_opcode (UNOP_POSTINCREMENT); }
278 exp : exp DECREMENT %prec UNARY
279 { write_exp_elt_opcode (UNOP_POSTDECREMENT); }
282 exp : SIZEOF exp %prec UNARY
283 { write_exp_elt_opcode (UNOP_SIZEOF); }
287 { write_exp_elt_opcode (STRUCTOP_PTR);
288 write_exp_string ($3);
289 write_exp_elt_opcode (STRUCTOP_PTR); }
292 exp : exp ARROW qualified_name
293 { /* exp->type::name becomes exp->*(&type::name) */
294 /* Note: this doesn't work if name is a
295 static member! FIXME */
296 write_exp_elt_opcode (UNOP_ADDR);
297 write_exp_elt_opcode (STRUCTOP_MPTR); }
300 exp : exp ARROW '*' exp
301 { write_exp_elt_opcode (STRUCTOP_MPTR); }
305 { write_exp_elt_opcode (STRUCTOP_STRUCT);
306 write_exp_string ($3);
307 write_exp_elt_opcode (STRUCTOP_STRUCT); }
310 exp : exp '.' qualified_name
311 { /* exp.type::name becomes exp.*(&type::name) */
312 /* Note: this doesn't work if name is a
313 static member! FIXME */
314 write_exp_elt_opcode (UNOP_ADDR);
315 write_exp_elt_opcode (STRUCTOP_MEMBER); }
318 exp : exp '.' '*' exp
319 { write_exp_elt_opcode (STRUCTOP_MEMBER); }
322 exp : exp '[' exp1 ']'
323 { write_exp_elt_opcode (BINOP_SUBSCRIPT); }
327 /* This is to save the value of arglist_len
328 being accumulated by an outer function call. */
329 { start_arglist (); }
330 arglist ')' %prec ARROW
331 { write_exp_elt_opcode (OP_FUNCALL);
332 write_exp_elt_longcst ((LONGEST) end_arglist ());
333 write_exp_elt_opcode (OP_FUNCALL); }
337 { start_arglist (); }
347 arglist : arglist ',' exp %prec ABOVE_COMMA
352 { $$ = end_arglist () - 1; }
354 exp : lcurly arglist rcurly %prec ARROW
355 { write_exp_elt_opcode (OP_ARRAY);
356 write_exp_elt_longcst ((LONGEST) 0);
357 write_exp_elt_longcst ((LONGEST) $3);
358 write_exp_elt_opcode (OP_ARRAY); }
361 exp : lcurly type rcurly exp %prec UNARY
362 { write_exp_elt_opcode (UNOP_MEMVAL);
363 write_exp_elt_type ($2);
364 write_exp_elt_opcode (UNOP_MEMVAL); }
367 exp : '(' type ')' exp %prec UNARY
368 { write_exp_elt_opcode (UNOP_CAST);
369 write_exp_elt_type ($2);
370 write_exp_elt_opcode (UNOP_CAST); }
377 /* Binary operators in order of decreasing precedence. */
380 { write_exp_elt_opcode (BINOP_REPEAT); }
384 { write_exp_elt_opcode (BINOP_MUL); }
388 { write_exp_elt_opcode (BINOP_DIV); }
392 { write_exp_elt_opcode (BINOP_REM); }
396 { write_exp_elt_opcode (BINOP_ADD); }
400 { write_exp_elt_opcode (BINOP_SUB); }
404 { write_exp_elt_opcode (BINOP_LSH); }
408 { write_exp_elt_opcode (BINOP_RSH); }
412 { write_exp_elt_opcode (BINOP_EQUAL); }
415 exp : exp NOTEQUAL exp
416 { write_exp_elt_opcode (BINOP_NOTEQUAL); }
420 { write_exp_elt_opcode (BINOP_LEQ); }
424 { write_exp_elt_opcode (BINOP_GEQ); }
428 { write_exp_elt_opcode (BINOP_LESS); }
432 { write_exp_elt_opcode (BINOP_GTR); }
436 { write_exp_elt_opcode (BINOP_BITWISE_AND); }
440 { write_exp_elt_opcode (BINOP_BITWISE_XOR); }
444 { write_exp_elt_opcode (BINOP_BITWISE_IOR); }
448 { write_exp_elt_opcode (BINOP_LOGICAL_AND); }
452 { write_exp_elt_opcode (BINOP_LOGICAL_OR); }
455 exp : exp '?' exp ':' exp %prec '?'
456 { write_exp_elt_opcode (TERNOP_COND); }
460 { write_exp_elt_opcode (BINOP_ASSIGN); }
463 exp : exp ASSIGN_MODIFY exp
464 { write_exp_elt_opcode (BINOP_ASSIGN_MODIFY);
465 write_exp_elt_opcode ($2);
466 write_exp_elt_opcode (BINOP_ASSIGN_MODIFY); }
470 { write_exp_elt_opcode (OP_LONG);
471 write_exp_elt_type ($1.type);
472 write_exp_elt_longcst ((LONGEST)($1.val));
473 write_exp_elt_opcode (OP_LONG); }
478 parse_number ($1.stoken.ptr, $1.stoken.length, 0, &val);
479 write_exp_elt_opcode (OP_LONG);
480 write_exp_elt_type (val.typed_val_int.type);
481 write_exp_elt_longcst ((LONGEST)val.typed_val_int.val);
482 write_exp_elt_opcode (OP_LONG);
488 { write_exp_elt_opcode (OP_DOUBLE);
489 write_exp_elt_type ($1.type);
490 write_exp_elt_dblcst ($1.dval);
491 write_exp_elt_opcode (OP_DOUBLE); }
498 /* Already written by write_dollar_variable. */
501 exp : SIZEOF '(' type ')' %prec UNARY
502 { write_exp_elt_opcode (OP_LONG);
503 write_exp_elt_type (builtin_type_int);
505 write_exp_elt_longcst ((LONGEST) TYPE_LENGTH ($3));
506 write_exp_elt_opcode (OP_LONG); }
510 { /* C strings are converted into array constants with
511 an explicit null byte added at the end. Thus
512 the array upper bound is the string length.
513 There is no such thing in C as a completely empty
515 char *sp = $1.ptr; int count = $1.length;
518 write_exp_elt_opcode (OP_LONG);
519 write_exp_elt_type (builtin_type_char);
520 write_exp_elt_longcst ((LONGEST)(*sp++));
521 write_exp_elt_opcode (OP_LONG);
523 write_exp_elt_opcode (OP_LONG);
524 write_exp_elt_type (builtin_type_char);
525 write_exp_elt_longcst ((LONGEST)'\0');
526 write_exp_elt_opcode (OP_LONG);
527 write_exp_elt_opcode (OP_ARRAY);
528 write_exp_elt_longcst ((LONGEST) 0);
529 write_exp_elt_longcst ((LONGEST) ($1.length));
530 write_exp_elt_opcode (OP_ARRAY); }
535 { write_exp_elt_opcode (OP_THIS);
536 write_exp_elt_opcode (OP_THIS); }
540 { write_exp_elt_opcode (OP_LONG);
541 write_exp_elt_type (builtin_type_bool);
542 write_exp_elt_longcst ((LONGEST) 1);
543 write_exp_elt_opcode (OP_LONG); }
547 { write_exp_elt_opcode (OP_LONG);
548 write_exp_elt_type (builtin_type_bool);
549 write_exp_elt_longcst ((LONGEST) 0);
550 write_exp_elt_opcode (OP_LONG); }
558 $$ = SYMBOL_BLOCK_VALUE ($1.sym);
560 error ("No file or function \"%s\".",
561 copy_name ($1.stoken));
569 block : block COLONCOLON name
571 = lookup_symbol (copy_name ($3), $1,
572 VAR_NAMESPACE, (int *) NULL,
573 (struct symtab **) NULL);
574 if (!tem || SYMBOL_CLASS (tem) != LOC_BLOCK)
575 error ("No function \"%s\" in specified context.",
577 $$ = SYMBOL_BLOCK_VALUE (tem); }
580 variable: block COLONCOLON name
581 { struct symbol *sym;
582 sym = lookup_symbol (copy_name ($3), $1,
583 VAR_NAMESPACE, (int *) NULL,
584 (struct symtab **) NULL);
586 error ("No symbol \"%s\" in specified context.",
589 write_exp_elt_opcode (OP_VAR_VALUE);
590 /* block_found is set by lookup_symbol. */
591 write_exp_elt_block (block_found);
592 write_exp_elt_sym (sym);
593 write_exp_elt_opcode (OP_VAR_VALUE); }
596 qualified_name: typebase COLONCOLON name
598 struct type *type = $1;
599 if (TYPE_CODE (type) != TYPE_CODE_STRUCT
600 && TYPE_CODE (type) != TYPE_CODE_UNION)
601 error ("`%s' is not defined as an aggregate type.",
604 write_exp_elt_opcode (OP_SCOPE);
605 write_exp_elt_type (type);
606 write_exp_string ($3);
607 write_exp_elt_opcode (OP_SCOPE);
609 | typebase COLONCOLON '~' name
611 struct type *type = $1;
612 struct stoken tmp_token;
613 if (TYPE_CODE (type) != TYPE_CODE_STRUCT
614 && TYPE_CODE (type) != TYPE_CODE_UNION)
615 error ("`%s' is not defined as an aggregate type.",
618 tmp_token.ptr = (char*) alloca ($4.length + 2);
619 tmp_token.length = $4.length + 1;
620 tmp_token.ptr[0] = '~';
621 memcpy (tmp_token.ptr+1, $4.ptr, $4.length);
622 tmp_token.ptr[tmp_token.length] = 0;
624 /* Check for valid destructor name. */
625 destructor_name_p (tmp_token.ptr, type);
626 write_exp_elt_opcode (OP_SCOPE);
627 write_exp_elt_type (type);
628 write_exp_string (tmp_token);
629 write_exp_elt_opcode (OP_SCOPE);
633 variable: qualified_name
636 char *name = copy_name ($2);
638 struct minimal_symbol *msymbol;
641 lookup_symbol (name, (const struct block *) NULL,
642 VAR_NAMESPACE, (int *) NULL,
643 (struct symtab **) NULL);
646 write_exp_elt_opcode (OP_VAR_VALUE);
647 write_exp_elt_block (NULL);
648 write_exp_elt_sym (sym);
649 write_exp_elt_opcode (OP_VAR_VALUE);
653 msymbol = lookup_minimal_symbol (name, NULL, NULL);
656 write_exp_msymbol (msymbol,
657 lookup_function_type (builtin_type_int),
661 if (!have_full_symbols () && !have_partial_symbols ())
662 error ("No symbol table is loaded. Use the \"file\" command.");
664 error ("No symbol \"%s\" in current context.", name);
668 variable: name_not_typename
669 { struct symbol *sym = $1.sym;
673 if (symbol_read_needs_frame (sym))
675 if (innermost_block == 0 ||
676 contained_in (block_found,
678 innermost_block = block_found;
681 write_exp_elt_opcode (OP_VAR_VALUE);
682 /* We want to use the selected frame, not
683 another more inner frame which happens to
684 be in the same block. */
685 write_exp_elt_block (NULL);
686 write_exp_elt_sym (sym);
687 write_exp_elt_opcode (OP_VAR_VALUE);
689 else if ($1.is_a_field_of_this)
691 /* C++: it hangs off of `this'. Must
692 not inadvertently convert from a method call
694 if (innermost_block == 0 ||
695 contained_in (block_found, innermost_block))
696 innermost_block = block_found;
697 write_exp_elt_opcode (OP_THIS);
698 write_exp_elt_opcode (OP_THIS);
699 write_exp_elt_opcode (STRUCTOP_PTR);
700 write_exp_string ($1.stoken);
701 write_exp_elt_opcode (STRUCTOP_PTR);
705 struct minimal_symbol *msymbol;
706 register char *arg = copy_name ($1.stoken);
709 lookup_minimal_symbol (arg, NULL, NULL);
712 write_exp_msymbol (msymbol,
713 lookup_function_type (builtin_type_int),
716 else if (!have_full_symbols () && !have_partial_symbols ())
717 error ("No symbol table is loaded. Use the \"file\" command.");
719 error ("No symbol \"%s\" in current context.",
720 copy_name ($1.stoken));
725 space_identifier : '@' NAME
726 { push_type_address_space (copy_name ($2.stoken));
727 push_type (tp_space_identifier);
731 const_or_volatile: const_or_volatile_noopt
735 cv_with_space_id : const_or_volatile space_identifier const_or_volatile
738 const_or_volatile_or_space_identifier_noopt: cv_with_space_id
739 | const_or_volatile_noopt
742 const_or_volatile_or_space_identifier:
743 const_or_volatile_or_space_identifier_noopt
748 { push_type (tp_pointer); $$ = 0; }
750 { push_type (tp_pointer); $$ = $2; }
752 { push_type (tp_reference); $$ = 0; }
754 { push_type (tp_reference); $$ = $2; }
758 direct_abs_decl: '(' abs_decl ')'
760 | direct_abs_decl array_mod
763 push_type (tp_array);
768 push_type (tp_array);
772 | direct_abs_decl func_mod
773 { push_type (tp_function); }
775 { push_type (tp_function); }
786 | '(' nonempty_typelist ')'
787 { free ((PTR)$2); $$ = 0; }
790 /* We used to try to recognize more pointer to member types here, but
791 that didn't work (shift/reduce conflicts meant that these rules never
792 got executed). The problem is that
793 int (foo::bar::baz::bizzle)
794 is a function type but
795 int (foo::bar::baz::bizzle::*)
796 is a pointer to member type. Stroustrup loses again! */
799 | typebase COLONCOLON '*'
800 { $$ = lookup_member_type (builtin_type_int, $1); }
803 typebase /* Implements (approximately): (type-qualifier)* type-specifier */
807 { $$ = builtin_type_int; }
809 { $$ = builtin_type_long; }
811 { $$ = builtin_type_short; }
813 { $$ = builtin_type_long; }
814 | LONG SIGNED_KEYWORD INT_KEYWORD
815 { $$ = builtin_type_long; }
816 | LONG SIGNED_KEYWORD
817 { $$ = builtin_type_long; }
818 | SIGNED_KEYWORD LONG INT_KEYWORD
819 { $$ = builtin_type_long; }
820 | UNSIGNED LONG INT_KEYWORD
821 { $$ = builtin_type_unsigned_long; }
822 | LONG UNSIGNED INT_KEYWORD
823 { $$ = builtin_type_unsigned_long; }
825 { $$ = builtin_type_unsigned_long; }
827 { $$ = builtin_type_long_long; }
828 | LONG LONG INT_KEYWORD
829 { $$ = builtin_type_long_long; }
830 | LONG LONG SIGNED_KEYWORD INT_KEYWORD
831 { $$ = builtin_type_long_long; }
832 | LONG LONG SIGNED_KEYWORD
833 { $$ = builtin_type_long_long; }
834 | SIGNED_KEYWORD LONG LONG
835 { $$ = builtin_type_long_long; }
837 { $$ = builtin_type_unsigned_long_long; }
838 | UNSIGNED LONG LONG INT_KEYWORD
839 { $$ = builtin_type_unsigned_long_long; }
841 { $$ = builtin_type_unsigned_long_long; }
842 | LONG LONG UNSIGNED INT_KEYWORD
843 { $$ = builtin_type_unsigned_long_long; }
844 | SIGNED_KEYWORD LONG LONG
845 { $$ = lookup_signed_typename ("long long"); }
846 | SIGNED_KEYWORD LONG LONG INT_KEYWORD
847 { $$ = lookup_signed_typename ("long long"); }
849 { $$ = builtin_type_short; }
850 | SHORT SIGNED_KEYWORD INT_KEYWORD
851 { $$ = builtin_type_short; }
852 | SHORT SIGNED_KEYWORD
853 { $$ = builtin_type_short; }
854 | UNSIGNED SHORT INT_KEYWORD
855 { $$ = builtin_type_unsigned_short; }
857 { $$ = builtin_type_unsigned_short; }
858 | SHORT UNSIGNED INT_KEYWORD
859 { $$ = builtin_type_unsigned_short; }
861 { $$ = builtin_type_double; }
862 | LONG DOUBLE_KEYWORD
863 { $$ = builtin_type_long_double; }
865 { $$ = lookup_struct (copy_name ($2),
866 expression_context_block); }
868 { $$ = lookup_struct (copy_name ($2),
869 expression_context_block); }
871 { $$ = lookup_union (copy_name ($2),
872 expression_context_block); }
874 { $$ = lookup_enum (copy_name ($2),
875 expression_context_block); }
877 { $$ = lookup_unsigned_typename (TYPE_NAME($2.type)); }
879 { $$ = builtin_type_unsigned_int; }
880 | SIGNED_KEYWORD typename
881 { $$ = lookup_signed_typename (TYPE_NAME($2.type)); }
883 { $$ = builtin_type_int; }
884 /* It appears that this rule for templates is never
885 reduced; template recognition happens by lookahead
886 in the token processing code in yylex. */
887 | TEMPLATE name '<' type '>'
888 { $$ = lookup_template_type(copy_name($2), $4,
889 expression_context_block);
891 | const_or_volatile_or_space_identifier_noopt typebase
892 { $$ = follow_types ($2); }
893 | typebase const_or_volatile_or_space_identifier_noopt
894 { $$ = follow_types ($1); }
900 $$.stoken.ptr = "int";
901 $$.stoken.length = 3;
902 $$.type = builtin_type_int;
906 $$.stoken.ptr = "long";
907 $$.stoken.length = 4;
908 $$.type = builtin_type_long;
912 $$.stoken.ptr = "short";
913 $$.stoken.length = 5;
914 $$.type = builtin_type_short;
920 { $$ = (struct type **) malloc (sizeof (struct type *) * 2);
921 $<ivec>$[0] = 1; /* Number of types in vector */
924 | nonempty_typelist ',' type
925 { int len = sizeof (struct type *) * (++($<ivec>1[0]) + 1);
926 $$ = (struct type **) realloc ((char *) $1, len);
927 $$[$<ivec>$[0]] = $3;
932 | ptype const_or_volatile_or_space_identifier abs_decl const_or_volatile_or_space_identifier
933 { $$ = follow_types ($1); }
936 const_and_volatile: CONST_KEYWORD VOLATILE_KEYWORD
937 | VOLATILE_KEYWORD CONST_KEYWORD
940 const_or_volatile_noopt: const_and_volatile
941 { push_type (tp_const);
942 push_type (tp_volatile);
945 { push_type (tp_const); }
947 { push_type (tp_volatile); }
950 name : NAME { $$ = $1.stoken; }
951 | BLOCKNAME { $$ = $1.stoken; }
952 | TYPENAME { $$ = $1.stoken; }
953 | NAME_OR_INT { $$ = $1.stoken; }
956 name_not_typename : NAME
958 /* These would be useful if name_not_typename was useful, but it is just
959 a fake for "variable", so these cause reduce/reduce conflicts because
960 the parser can't tell whether NAME_OR_INT is a name_not_typename (=variable,
961 =exp) or just an exp. If name_not_typename was ever used in an lvalue
962 context where only a name could occur, this might be useful.
969 /* Take care of parsing a number (anything that starts with a digit).
970 Set yylval and return the token type; update lexptr.
971 LEN is the number of characters in it. */
973 /*** Needs some error checking for the float case ***/
976 parse_number (p, len, parsed_float, putithere)
982 /* FIXME: Shouldn't these be unsigned? We don't deal with negative values
983 here, and we do kind of silly things like cast to unsigned. */
984 register LONGEST n = 0;
985 register LONGEST prevn = 0;
990 register int base = input_radix;
993 /* Number of "L" suffixes encountered. */
996 /* We have found a "L" or "U" suffix. */
997 int found_suffix = 0;
1000 struct type *signed_type;
1001 struct type *unsigned_type;
1005 /* It's a float since it contains a point or an exponent. */
1007 int num = 0; /* number of tokens scanned by scanf */
1008 char saved_char = p[len];
1010 p[len] = 0; /* null-terminate the token */
1011 if (sizeof (putithere->typed_val_float.dval) <= sizeof (float))
1012 num = sscanf (p, "%g%c", (float *) &putithere->typed_val_float.dval,&c);
1013 else if (sizeof (putithere->typed_val_float.dval) <= sizeof (double))
1014 num = sscanf (p, "%lg%c", (double *) &putithere->typed_val_float.dval,&c);
1017 #ifdef SCANF_HAS_LONG_DOUBLE
1018 num = sscanf (p, "%Lg%c", &putithere->typed_val_float.dval,&c);
1020 /* Scan it into a double, then assign it to the long double.
1021 This at least wins with values representable in the range
1024 num = sscanf (p, "%lg%c", &temp,&c);
1025 putithere->typed_val_float.dval = temp;
1028 p[len] = saved_char; /* restore the input stream */
1029 if (num != 1) /* check scanf found ONLY a float ... */
1031 /* See if it has `f' or `l' suffix (float or long double). */
1033 c = tolower (p[len - 1]);
1036 putithere->typed_val_float.type = builtin_type_float;
1038 putithere->typed_val_float.type = builtin_type_long_double;
1039 else if (isdigit (c) || c == '.')
1040 putithere->typed_val_float.type = builtin_type_double;
1047 /* Handle base-switching prefixes 0x, 0t, 0d, 0 */
1081 if (c >= 'A' && c <= 'Z')
1083 if (c != 'l' && c != 'u')
1085 if (c >= '0' && c <= '9')
1093 if (base > 10 && c >= 'a' && c <= 'f')
1097 n += i = c - 'a' + 10;
1110 return ERROR; /* Char not a digit */
1113 return ERROR; /* Invalid digit in this base */
1115 /* Portably test for overflow (only works for nonzero values, so make
1116 a second check for zero). FIXME: Can't we just make n and prevn
1117 unsigned and avoid this? */
1118 if (c != 'l' && c != 'u' && (prevn >= n) && n != 0)
1119 unsigned_p = 1; /* Try something unsigned */
1121 /* Portably test for unsigned overflow.
1122 FIXME: This check is wrong; for example it doesn't find overflow
1123 on 0x123456789 when LONGEST is 32 bits. */
1124 if (c != 'l' && c != 'u' && n != 0)
1126 if ((unsigned_p && (ULONGEST) prevn >= (ULONGEST) n))
1127 error ("Numeric constant too large.");
1132 /* An integer constant is an int, a long, or a long long. An L
1133 suffix forces it to be long; an LL suffix forces it to be long
1134 long. If not forced to a larger size, it gets the first type of
1135 the above that it fits in. To figure out whether it fits, we
1136 shift it right and see whether anything remains. Note that we
1137 can't shift sizeof (LONGEST) * HOST_CHAR_BIT bits or more in one
1138 operation, because many compilers will warn about such a shift
1139 (which always produces a zero result). Sometimes TARGET_INT_BIT
1140 or TARGET_LONG_BIT will be that big, sometimes not. To deal with
1141 the case where it is we just always shift the value more than
1142 once, with fewer bits each time. */
1144 un = (ULONGEST)n >> 2;
1146 && (un >> (TARGET_INT_BIT - 2)) == 0)
1148 high_bit = ((ULONGEST)1) << (TARGET_INT_BIT-1);
1150 /* A large decimal (not hex or octal) constant (between INT_MAX
1151 and UINT_MAX) is a long or unsigned long, according to ANSI,
1152 never an unsigned int, but this code treats it as unsigned
1153 int. This probably should be fixed. GCC gives a warning on
1156 unsigned_type = builtin_type_unsigned_int;
1157 signed_type = builtin_type_int;
1159 else if (long_p <= 1
1160 && (un >> (TARGET_LONG_BIT - 2)) == 0)
1162 high_bit = ((ULONGEST)1) << (TARGET_LONG_BIT-1);
1163 unsigned_type = builtin_type_unsigned_long;
1164 signed_type = builtin_type_long;
1169 if (sizeof (ULONGEST) * HOST_CHAR_BIT < TARGET_LONG_LONG_BIT)
1170 /* A long long does not fit in a LONGEST. */
1171 shift = (sizeof (ULONGEST) * HOST_CHAR_BIT - 1);
1173 shift = (TARGET_LONG_LONG_BIT - 1);
1174 high_bit = (ULONGEST) 1 << shift;
1175 unsigned_type = builtin_type_unsigned_long_long;
1176 signed_type = builtin_type_long_long;
1179 putithere->typed_val_int.val = n;
1181 /* If the high bit of the worked out type is set then this number
1182 has to be unsigned. */
1184 if (unsigned_p || (n & high_bit))
1186 putithere->typed_val_int.type = unsigned_type;
1190 putithere->typed_val_int.type = signed_type;
1200 enum exp_opcode opcode;
1203 static const struct token tokentab3[] =
1205 {">>=", ASSIGN_MODIFY, BINOP_RSH},
1206 {"<<=", ASSIGN_MODIFY, BINOP_LSH}
1209 static const struct token tokentab2[] =
1211 {"+=", ASSIGN_MODIFY, BINOP_ADD},
1212 {"-=", ASSIGN_MODIFY, BINOP_SUB},
1213 {"*=", ASSIGN_MODIFY, BINOP_MUL},
1214 {"/=", ASSIGN_MODIFY, BINOP_DIV},
1215 {"%=", ASSIGN_MODIFY, BINOP_REM},
1216 {"|=", ASSIGN_MODIFY, BINOP_BITWISE_IOR},
1217 {"&=", ASSIGN_MODIFY, BINOP_BITWISE_AND},
1218 {"^=", ASSIGN_MODIFY, BINOP_BITWISE_XOR},
1219 {"++", INCREMENT, BINOP_END},
1220 {"--", DECREMENT, BINOP_END},
1221 {"->", ARROW, BINOP_END},
1222 {"&&", ANDAND, BINOP_END},
1223 {"||", OROR, BINOP_END},
1224 {"::", COLONCOLON, BINOP_END},
1225 {"<<", LSH, BINOP_END},
1226 {">>", RSH, BINOP_END},
1227 {"==", EQUAL, BINOP_END},
1228 {"!=", NOTEQUAL, BINOP_END},
1229 {"<=", LEQ, BINOP_END},
1230 {">=", GEQ, BINOP_END}
1233 /* Read one token, getting characters through lexptr. */
1244 static char *tempbuf;
1245 static int tempbufsize;
1246 struct symbol * sym_class = NULL;
1247 char * token_string = NULL;
1248 int class_prefix = 0;
1253 /* Check if this is a macro invocation that we need to expand. */
1254 if (! scanning_macro_expansion ())
1256 char *expanded = macro_expand_next (&lexptr,
1257 expression_macro_lookup_func,
1258 expression_macro_lookup_baton);
1261 scan_macro_expansion (expanded);
1264 prev_lexptr = lexptr;
1268 /* See if it is a special token of length 3. */
1269 for (i = 0; i < sizeof tokentab3 / sizeof tokentab3[0]; i++)
1270 if (STREQN (tokstart, tokentab3[i].operator, 3))
1273 yylval.opcode = tokentab3[i].opcode;
1274 return tokentab3[i].token;
1277 /* See if it is a special token of length 2. */
1278 for (i = 0; i < sizeof tokentab2 / sizeof tokentab2[0]; i++)
1279 if (STREQN (tokstart, tokentab2[i].operator, 2))
1282 yylval.opcode = tokentab2[i].opcode;
1283 return tokentab2[i].token;
1286 switch (c = *tokstart)
1289 /* If we were just scanning the result of a macro expansion,
1290 then we need to resume scanning the original text.
1291 Otherwise, we were already scanning the original text, and
1292 we're really done. */
1293 if (scanning_macro_expansion ())
1295 finished_macro_expansion ();
1308 /* We either have a character constant ('0' or '\177' for example)
1309 or we have a quoted symbol reference ('foo(int,int)' in C++
1314 c = parse_escape (&lexptr);
1316 error ("Empty character constant.");
1318 yylval.typed_val_int.val = c;
1319 yylval.typed_val_int.type = builtin_type_char;
1324 namelen = skip_quoted (tokstart) - tokstart;
1327 lexptr = tokstart + namelen;
1329 if (lexptr[-1] != '\'')
1330 error ("Unmatched single quote.");
1335 error ("Invalid character constant.");
1345 if (paren_depth == 0)
1352 if (comma_terminates
1354 && ! scanning_macro_expansion ())
1360 /* Might be a floating point number. */
1361 if (lexptr[1] < '0' || lexptr[1] > '9')
1362 goto symbol; /* Nope, must be a symbol. */
1363 /* FALL THRU into number case. */
1376 /* It's a number. */
1377 int got_dot = 0, got_e = 0, toktype;
1378 register char *p = tokstart;
1379 int hex = input_radix > 10;
1381 if (c == '0' && (p[1] == 'x' || p[1] == 'X'))
1386 else if (c == '0' && (p[1]=='t' || p[1]=='T' || p[1]=='d' || p[1]=='D'))
1394 /* This test includes !hex because 'e' is a valid hex digit
1395 and thus does not indicate a floating point number when
1396 the radix is hex. */
1397 if (!hex && !got_e && (*p == 'e' || *p == 'E'))
1398 got_dot = got_e = 1;
1399 /* This test does not include !hex, because a '.' always indicates
1400 a decimal floating point number regardless of the radix. */
1401 else if (!got_dot && *p == '.')
1403 else if (got_e && (p[-1] == 'e' || p[-1] == 'E')
1404 && (*p == '-' || *p == '+'))
1405 /* This is the sign of the exponent, not the end of the
1408 /* We will take any letters or digits. parse_number will
1409 complain if past the radix, or if L or U are not final. */
1410 else if ((*p < '0' || *p > '9')
1411 && ((*p < 'a' || *p > 'z')
1412 && (*p < 'A' || *p > 'Z')))
1415 toktype = parse_number (tokstart, p - tokstart, got_dot|got_e, &yylval);
1416 if (toktype == ERROR)
1418 char *err_copy = (char *) alloca (p - tokstart + 1);
1420 memcpy (err_copy, tokstart, p - tokstart);
1421 err_copy[p - tokstart] = 0;
1422 error ("Invalid number \"%s\".", err_copy);
1454 /* Build the gdb internal form of the input string in tempbuf,
1455 translating any standard C escape forms seen. Note that the
1456 buffer is null byte terminated *only* for the convenience of
1457 debugging gdb itself and printing the buffer contents when
1458 the buffer contains no embedded nulls. Gdb does not depend
1459 upon the buffer being null byte terminated, it uses the length
1460 string instead. This allows gdb to handle C strings (as well
1461 as strings in other languages) with embedded null bytes */
1463 tokptr = ++tokstart;
1467 /* Grow the static temp buffer if necessary, including allocating
1468 the first one on demand. */
1469 if (tempbufindex + 1 >= tempbufsize)
1471 tempbuf = (char *) realloc (tempbuf, tempbufsize += 64);
1477 /* Do nothing, loop will terminate. */
1481 c = parse_escape (&tokptr);
1486 tempbuf[tempbufindex++] = c;
1489 tempbuf[tempbufindex++] = *tokptr++;
1492 } while ((*tokptr != '"') && (*tokptr != '\0'));
1493 if (*tokptr++ != '"')
1495 error ("Unterminated string in expression.");
1497 tempbuf[tempbufindex] = '\0'; /* See note above */
1498 yylval.sval.ptr = tempbuf;
1499 yylval.sval.length = tempbufindex;
1504 if (!(c == '_' || c == '$'
1505 || (c >= 'a' && c <= 'z') || (c >= 'A' && c <= 'Z')))
1506 /* We must have come across a bad character (e.g. ';'). */
1507 error ("Invalid character '%c' in expression.", c);
1509 /* It's a name. See how long it is. */
1511 for (c = tokstart[namelen];
1512 (c == '_' || c == '$' || (c >= '0' && c <= '9')
1513 || (c >= 'a' && c <= 'z') || (c >= 'A' && c <= 'Z') || c == '<');)
1515 /* Template parameter lists are part of the name.
1516 FIXME: This mishandles `print $a<4&&$a>3'. */
1520 /* Scan ahead to get rest of the template specification. Note
1521 that we look ahead only when the '<' adjoins non-whitespace
1522 characters; for comparison expressions, e.g. "a < b > c",
1523 there must be spaces before the '<', etc. */
1525 char * p = find_template_name_end (tokstart + namelen);
1527 namelen = p - tokstart;
1530 c = tokstart[++namelen];
1533 /* The token "if" terminates the expression and is NOT removed from
1534 the input stream. It doesn't count if it appears in the
1535 expansion of a macro. */
1537 && tokstart[0] == 'i'
1538 && tokstart[1] == 'f'
1539 && ! scanning_macro_expansion ())
1548 /* Catch specific keywords. Should be done with a data structure. */
1552 if (STREQN (tokstart, "unsigned", 8))
1554 if (current_language->la_language == language_cplus
1555 && STREQN (tokstart, "template", 8))
1557 if (STREQN (tokstart, "volatile", 8))
1558 return VOLATILE_KEYWORD;
1561 if (STREQN (tokstart, "struct", 6))
1563 if (STREQN (tokstart, "signed", 6))
1564 return SIGNED_KEYWORD;
1565 if (STREQN (tokstart, "sizeof", 6))
1567 if (STREQN (tokstart, "double", 6))
1568 return DOUBLE_KEYWORD;
1571 if (current_language->la_language == language_cplus)
1573 if (STREQN (tokstart, "false", 5))
1574 return FALSEKEYWORD;
1575 if (STREQN (tokstart, "class", 5))
1578 if (STREQN (tokstart, "union", 5))
1580 if (STREQN (tokstart, "short", 5))
1582 if (STREQN (tokstart, "const", 5))
1583 return CONST_KEYWORD;
1586 if (STREQN (tokstart, "enum", 4))
1588 if (STREQN (tokstart, "long", 4))
1590 if (current_language->la_language == language_cplus)
1592 if (STREQN (tokstart, "true", 4))
1595 if (STREQN (tokstart, "this", 4))
1597 static const char this_name[] =
1598 { CPLUS_MARKER, 't', 'h', 'i', 's', '\0' };
1600 if (lookup_symbol (this_name, expression_context_block,
1601 VAR_NAMESPACE, (int *) NULL,
1602 (struct symtab **) NULL))
1608 if (STREQN (tokstart, "int", 3))
1615 yylval.sval.ptr = tokstart;
1616 yylval.sval.length = namelen;
1618 if (*tokstart == '$')
1620 write_dollar_variable (yylval.sval);
1624 /* Look ahead and see if we can consume more of the input
1625 string to get a reasonable class/namespace spec or a
1626 fully-qualified name. This is a kludge to get around the
1627 HP aCC compiler's generation of symbol names with embedded
1628 colons for namespace and nested classes. */
1631 /* Only do it if not inside single quotes */
1632 sym_class = parse_nested_classes_for_hpacc (yylval.sval.ptr, yylval.sval.length,
1633 &token_string, &class_prefix, &lexptr);
1636 /* Replace the current token with the bigger one we found */
1637 yylval.sval.ptr = token_string;
1638 yylval.sval.length = strlen (token_string);
1642 /* Use token-type BLOCKNAME for symbols that happen to be defined as
1643 functions or symtabs. If this is not so, then ...
1644 Use token-type TYPENAME for symbols that happen to be defined
1645 currently as names of types; NAME for other symbols.
1646 The caller is not constrained to care about the distinction. */
1648 char *tmp = copy_name (yylval.sval);
1650 int is_a_field_of_this = 0;
1653 sym = lookup_symbol (tmp, expression_context_block,
1655 current_language->la_language == language_cplus
1656 ? &is_a_field_of_this : (int *) NULL,
1657 (struct symtab **) NULL);
1658 /* Call lookup_symtab, not lookup_partial_symtab, in case there are
1659 no psymtabs (coff, xcoff, or some future change to blow away the
1660 psymtabs once once symbols are read). */
1661 if (sym && SYMBOL_CLASS (sym) == LOC_BLOCK)
1663 yylval.ssym.sym = sym;
1664 yylval.ssym.is_a_field_of_this = is_a_field_of_this;
1668 { /* See if it's a file name. */
1669 struct symtab *symtab;
1671 symtab = lookup_symtab (tmp);
1675 yylval.bval = BLOCKVECTOR_BLOCK (BLOCKVECTOR (symtab), STATIC_BLOCK);
1680 if (sym && SYMBOL_CLASS (sym) == LOC_TYPEDEF)
1683 /* Despite the following flaw, we need to keep this code enabled.
1684 Because we can get called from check_stub_method, if we don't
1685 handle nested types then it screws many operations in any
1686 program which uses nested types. */
1687 /* In "A::x", if x is a member function of A and there happens
1688 to be a type (nested or not, since the stabs don't make that
1689 distinction) named x, then this code incorrectly thinks we
1690 are dealing with nested types rather than a member function. */
1694 struct symbol *best_sym;
1696 /* Look ahead to detect nested types. This probably should be
1697 done in the grammar, but trying seemed to introduce a lot
1698 of shift/reduce and reduce/reduce conflicts. It's possible
1699 that it could be done, though. Or perhaps a non-grammar, but
1700 less ad hoc, approach would work well. */
1702 /* Since we do not currently have any way of distinguishing
1703 a nested type from a non-nested one (the stabs don't tell
1704 us whether a type is nested), we just ignore the
1711 /* Skip whitespace. */
1712 while (*p == ' ' || *p == '\t' || *p == '\n')
1714 if (*p == ':' && p[1] == ':')
1716 /* Skip the `::'. */
1718 /* Skip whitespace. */
1719 while (*p == ' ' || *p == '\t' || *p == '\n')
1722 while (*p == '_' || *p == '$' || (*p >= '0' && *p <= '9')
1723 || (*p >= 'a' && *p <= 'z')
1724 || (*p >= 'A' && *p <= 'Z'))
1728 struct symbol *cur_sym;
1729 /* As big as the whole rest of the expression, which is
1730 at least big enough. */
1731 char *ncopy = alloca (strlen (tmp)+strlen (namestart)+3);
1735 memcpy (tmp1, tmp, strlen (tmp));
1736 tmp1 += strlen (tmp);
1737 memcpy (tmp1, "::", 2);
1739 memcpy (tmp1, namestart, p - namestart);
1740 tmp1[p - namestart] = '\0';
1741 cur_sym = lookup_symbol (ncopy, expression_context_block,
1742 VAR_NAMESPACE, (int *) NULL,
1743 (struct symtab **) NULL);
1746 if (SYMBOL_CLASS (cur_sym) == LOC_TYPEDEF)
1764 yylval.tsym.type = SYMBOL_TYPE (best_sym);
1766 yylval.tsym.type = SYMBOL_TYPE (sym);
1770 if ((yylval.tsym.type = lookup_primitive_typename (tmp)) != 0)
1773 /* Input names that aren't symbols but ARE valid hex numbers,
1774 when the input radix permits them, can be names or numbers
1775 depending on the parse. Note we support radixes > 16 here. */
1777 ((tokstart[0] >= 'a' && tokstart[0] < 'a' + input_radix - 10) ||
1778 (tokstart[0] >= 'A' && tokstart[0] < 'A' + input_radix - 10)))
1780 YYSTYPE newlval; /* Its value is ignored. */
1781 hextype = parse_number (tokstart, namelen, 0, &newlval);
1784 yylval.ssym.sym = sym;
1785 yylval.ssym.is_a_field_of_this = is_a_field_of_this;
1790 /* Any other kind of symbol */
1791 yylval.ssym.sym = sym;
1792 yylval.ssym.is_a_field_of_this = is_a_field_of_this;
1802 lexptr = prev_lexptr;
1804 error ("A %s in expression, near `%s'.", (msg ? msg : "error"), lexptr);