1 /* YACC parser for C expressions, for GDB.
2 Copyright (C) 1986, 1989, 1990, 1991, 1993, 1994, 1996, 1997
3 Free Software Foundation, Inc.
5 This file is part of GDB.
7 This program is free software; you can redistribute it and/or modify
8 it under the terms of the GNU General Public License as published by
9 the Free Software Foundation; either version 2 of the License, or
10 (at your option) any later version.
12 This program is distributed in the hope that it will be useful,
13 but WITHOUT ANY WARRANTY; without even the implied warranty of
14 MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the
15 GNU General Public License for more details.
17 You should have received a copy of the GNU General Public License
18 along with this program; if not, write to the Free Software
19 Foundation, Inc., 59 Temple Place - Suite 330, Boston, MA 02111-1307, USA. */
21 /* Parse a C expression from text in a string,
22 and return the result as a struct expression pointer.
23 That structure contains arithmetic operations in reverse polish,
24 with constants represented by operations that are followed by special data.
25 See expression.h for the details of the format.
26 What is important here is that it can be built up sequentially
27 during the process of parsing; the lower levels of the tree always
28 come first in the result.
30 Note that malloc's and realloc's in this file are transformed to
31 xmalloc and xrealloc respectively by the same sed command in the
32 makefile that remaps any other malloc/realloc inserted by the parser
33 generator. Doing this with #defines and trying to control the interaction
34 with include files (<malloc.h> and <stdlib.h> for example) just became
35 too messy, particularly when such includes can be inserted at random
36 times by the parser generator. */
41 #include "gdb_string.h"
43 #include "expression.h"
45 #include "parser-defs.h"
48 #include "bfd.h" /* Required by objfiles.h. */
49 #include "symfile.h" /* Required by objfiles.h. */
50 #include "objfiles.h" /* For have_full_symbols and have_partial_symbols */
52 /* Flag indicating we're dealing with HP-compiled objects */
53 extern int hp_som_som_object_present;
55 /* Remap normal yacc parser interface names (yyparse, yylex, yyerror, etc),
56 as well as gratuitiously global symbol names, so we can have multiple
57 yacc generated parsers in gdb. Note that these are only the variables
58 produced by yacc. If other parser generators (bison, byacc, etc) produce
59 additional global names that conflict at link time, then those parser
60 generators need to be fixed instead of adding those names to this list. */
62 #define yymaxdepth c_maxdepth
63 #define yyparse c_parse
65 #define yyerror c_error
68 #define yydebug c_debug
77 #define yyerrflag c_errflag
78 #define yynerrs c_nerrs
83 #define yystate c_state
89 #define yyreds c_reds /* With YYDEBUG defined */
90 #define yytoks c_toks /* With YYDEBUG defined */
93 #define yydefred c_yydefred
94 #define yydgoto c_yydgoto
95 #define yysindex c_yysindex
96 #define yyrindex c_yyrindex
97 #define yygindex c_yygindex
98 #define yytable c_yytable
99 #define yycheck c_yycheck
102 #define YYDEBUG 0 /* Default to no yydebug support */
106 yyparse PARAMS ((void));
109 yylex PARAMS ((void));
112 yyerror PARAMS ((char *));
116 /* Although the yacc "value" of an expression is not used,
117 since the result is stored in the structure being created,
118 other node types do have values. */
135 struct symtoken ssym;
138 enum exp_opcode opcode;
139 struct internalvar *ivar;
146 /* YYSTYPE gets defined by %union */
148 parse_number PARAMS ((char *, int, int, YYSTYPE *));
151 %type <voidval> exp exp1 type_exp start variable qualified_name lcurly
153 %type <tval> type typebase
154 %type <tvec> nonempty_typelist
155 /* %type <bval> block */
157 /* Fancy type parsing. */
158 %type <voidval> func_mod direct_abs_decl abs_decl
160 %type <lval> array_mod
162 %token <typed_val_int> INT
163 %token <typed_val_float> FLOAT
165 /* Both NAME and TYPENAME tokens represent symbols in the input,
166 and both convey their data as strings.
167 But a TYPENAME is a string that happens to be defined as a typedef
168 or builtin type name (such as int or char)
169 and a NAME is any other symbol.
170 Contexts where this distinction is not important can use the
171 nonterminal "name", which matches either NAME or TYPENAME. */
174 %token <ssym> NAME /* BLOCKNAME defined below to give it higher precedence. */
175 %token <tsym> TYPENAME
177 %type <ssym> name_not_typename
178 %type <tsym> typename
180 /* A NAME_OR_INT is a symbol which is not known in the symbol table,
181 but which would parse as a valid number in the current input radix.
182 E.g. "c" when input_radix==16. Depending on the parse, it will be
183 turned into a name or into a number. */
185 %token <ssym> NAME_OR_INT
187 %token STRUCT CLASS UNION ENUM SIZEOF UNSIGNED COLONCOLON
191 /* Special type cases, put in to allow the parser to distinguish different
193 %token SIGNED_KEYWORD LONG SHORT INT_KEYWORD CONST_KEYWORD VOLATILE_KEYWORD DOUBLE_KEYWORD
195 %token <voidval> VARIABLE
197 %token <opcode> ASSIGN_MODIFY
207 %right '=' ASSIGN_MODIFY
215 %left '<' '>' LEQ GEQ
220 %right UNARY INCREMENT DECREMENT
221 %right ARROW '.' '[' '('
222 %token <ssym> BLOCKNAME
223 %token <bval> FILENAME
235 { write_exp_elt_opcode(OP_TYPE);
236 write_exp_elt_type($1);
237 write_exp_elt_opcode(OP_TYPE);}
240 /* Expressions, including the comma operator. */
243 { write_exp_elt_opcode (BINOP_COMMA); }
246 /* Expressions, not including the comma operator. */
247 exp : '*' exp %prec UNARY
248 { write_exp_elt_opcode (UNOP_IND); }
250 exp : '&' exp %prec UNARY
251 { write_exp_elt_opcode (UNOP_ADDR); }
253 exp : '-' exp %prec UNARY
254 { write_exp_elt_opcode (UNOP_NEG); }
257 exp : '!' exp %prec UNARY
258 { write_exp_elt_opcode (UNOP_LOGICAL_NOT); }
261 exp : '~' exp %prec UNARY
262 { write_exp_elt_opcode (UNOP_COMPLEMENT); }
265 exp : INCREMENT exp %prec UNARY
266 { write_exp_elt_opcode (UNOP_PREINCREMENT); }
269 exp : DECREMENT exp %prec UNARY
270 { write_exp_elt_opcode (UNOP_PREDECREMENT); }
273 exp : exp INCREMENT %prec UNARY
274 { write_exp_elt_opcode (UNOP_POSTINCREMENT); }
277 exp : exp DECREMENT %prec UNARY
278 { write_exp_elt_opcode (UNOP_POSTDECREMENT); }
281 exp : SIZEOF exp %prec UNARY
282 { write_exp_elt_opcode (UNOP_SIZEOF); }
286 { write_exp_elt_opcode (STRUCTOP_PTR);
287 write_exp_string ($3);
288 write_exp_elt_opcode (STRUCTOP_PTR); }
291 exp : exp ARROW qualified_name
292 { /* exp->type::name becomes exp->*(&type::name) */
293 /* Note: this doesn't work if name is a
294 static member! FIXME */
295 write_exp_elt_opcode (UNOP_ADDR);
296 write_exp_elt_opcode (STRUCTOP_MPTR); }
299 exp : exp ARROW '*' exp
300 { write_exp_elt_opcode (STRUCTOP_MPTR); }
304 { write_exp_elt_opcode (STRUCTOP_STRUCT);
305 write_exp_string ($3);
306 write_exp_elt_opcode (STRUCTOP_STRUCT); }
309 exp : exp '.' qualified_name
310 { /* exp.type::name becomes exp.*(&type::name) */
311 /* Note: this doesn't work if name is a
312 static member! FIXME */
313 write_exp_elt_opcode (UNOP_ADDR);
314 write_exp_elt_opcode (STRUCTOP_MEMBER); }
317 exp : exp '.' '*' exp
318 { write_exp_elt_opcode (STRUCTOP_MEMBER); }
321 exp : exp '[' exp1 ']'
322 { write_exp_elt_opcode (BINOP_SUBSCRIPT); }
326 /* This is to save the value of arglist_len
327 being accumulated by an outer function call. */
328 { start_arglist (); }
329 arglist ')' %prec ARROW
330 { write_exp_elt_opcode (OP_FUNCALL);
331 write_exp_elt_longcst ((LONGEST) end_arglist ());
332 write_exp_elt_opcode (OP_FUNCALL); }
336 { start_arglist (); }
346 arglist : arglist ',' exp %prec ABOVE_COMMA
351 { $$ = end_arglist () - 1; }
353 exp : lcurly arglist rcurly %prec ARROW
354 { write_exp_elt_opcode (OP_ARRAY);
355 write_exp_elt_longcst ((LONGEST) 0);
356 write_exp_elt_longcst ((LONGEST) $3);
357 write_exp_elt_opcode (OP_ARRAY); }
360 exp : lcurly type rcurly exp %prec UNARY
361 { write_exp_elt_opcode (UNOP_MEMVAL);
362 write_exp_elt_type ($2);
363 write_exp_elt_opcode (UNOP_MEMVAL); }
366 exp : '(' type ')' exp %prec UNARY
367 { write_exp_elt_opcode (UNOP_CAST);
368 write_exp_elt_type ($2);
369 write_exp_elt_opcode (UNOP_CAST); }
376 /* Binary operators in order of decreasing precedence. */
379 { write_exp_elt_opcode (BINOP_REPEAT); }
383 { write_exp_elt_opcode (BINOP_MUL); }
387 { write_exp_elt_opcode (BINOP_DIV); }
391 { write_exp_elt_opcode (BINOP_REM); }
395 { write_exp_elt_opcode (BINOP_ADD); }
399 { write_exp_elt_opcode (BINOP_SUB); }
403 { write_exp_elt_opcode (BINOP_LSH); }
407 { write_exp_elt_opcode (BINOP_RSH); }
411 { write_exp_elt_opcode (BINOP_EQUAL); }
414 exp : exp NOTEQUAL exp
415 { write_exp_elt_opcode (BINOP_NOTEQUAL); }
419 { write_exp_elt_opcode (BINOP_LEQ); }
423 { write_exp_elt_opcode (BINOP_GEQ); }
427 { write_exp_elt_opcode (BINOP_LESS); }
431 { write_exp_elt_opcode (BINOP_GTR); }
435 { write_exp_elt_opcode (BINOP_BITWISE_AND); }
439 { write_exp_elt_opcode (BINOP_BITWISE_XOR); }
443 { write_exp_elt_opcode (BINOP_BITWISE_IOR); }
447 { write_exp_elt_opcode (BINOP_LOGICAL_AND); }
451 { write_exp_elt_opcode (BINOP_LOGICAL_OR); }
454 exp : exp '?' exp ':' exp %prec '?'
455 { write_exp_elt_opcode (TERNOP_COND); }
459 { write_exp_elt_opcode (BINOP_ASSIGN); }
462 exp : exp ASSIGN_MODIFY exp
463 { write_exp_elt_opcode (BINOP_ASSIGN_MODIFY);
464 write_exp_elt_opcode ($2);
465 write_exp_elt_opcode (BINOP_ASSIGN_MODIFY); }
469 { write_exp_elt_opcode (OP_LONG);
470 write_exp_elt_type ($1.type);
471 write_exp_elt_longcst ((LONGEST)($1.val));
472 write_exp_elt_opcode (OP_LONG); }
477 parse_number ($1.stoken.ptr, $1.stoken.length, 0, &val);
478 write_exp_elt_opcode (OP_LONG);
479 write_exp_elt_type (val.typed_val_int.type);
480 write_exp_elt_longcst ((LONGEST)val.typed_val_int.val);
481 write_exp_elt_opcode (OP_LONG);
487 { write_exp_elt_opcode (OP_DOUBLE);
488 write_exp_elt_type ($1.type);
489 write_exp_elt_dblcst ($1.dval);
490 write_exp_elt_opcode (OP_DOUBLE); }
497 /* Already written by write_dollar_variable. */
500 exp : SIZEOF '(' type ')' %prec UNARY
501 { write_exp_elt_opcode (OP_LONG);
502 write_exp_elt_type (builtin_type_int);
504 write_exp_elt_longcst ((LONGEST) TYPE_LENGTH ($3));
505 write_exp_elt_opcode (OP_LONG); }
509 { /* C strings are converted into array constants with
510 an explicit null byte added at the end. Thus
511 the array upper bound is the string length.
512 There is no such thing in C as a completely empty
514 char *sp = $1.ptr; int count = $1.length;
517 write_exp_elt_opcode (OP_LONG);
518 write_exp_elt_type (builtin_type_char);
519 write_exp_elt_longcst ((LONGEST)(*sp++));
520 write_exp_elt_opcode (OP_LONG);
522 write_exp_elt_opcode (OP_LONG);
523 write_exp_elt_type (builtin_type_char);
524 write_exp_elt_longcst ((LONGEST)'\0');
525 write_exp_elt_opcode (OP_LONG);
526 write_exp_elt_opcode (OP_ARRAY);
527 write_exp_elt_longcst ((LONGEST) 0);
528 write_exp_elt_longcst ((LONGEST) ($1.length));
529 write_exp_elt_opcode (OP_ARRAY); }
534 { write_exp_elt_opcode (OP_THIS);
535 write_exp_elt_opcode (OP_THIS); }
539 { write_exp_elt_opcode (OP_LONG);
540 write_exp_elt_type (builtin_type_bool);
541 write_exp_elt_longcst ((LONGEST) 1);
542 write_exp_elt_opcode (OP_LONG); }
546 { write_exp_elt_opcode (OP_LONG);
547 write_exp_elt_type (builtin_type_bool);
548 write_exp_elt_longcst ((LONGEST) 0);
549 write_exp_elt_opcode (OP_LONG); }
557 $$ = SYMBOL_BLOCK_VALUE ($1.sym);
559 error ("No file or function \"%s\".",
560 copy_name ($1.stoken));
568 block : block COLONCOLON name
570 = lookup_symbol (copy_name ($3), $1,
571 VAR_NAMESPACE, (int *) NULL,
572 (struct symtab **) NULL);
573 if (!tem || SYMBOL_CLASS (tem) != LOC_BLOCK)
574 error ("No function \"%s\" in specified context.",
576 $$ = SYMBOL_BLOCK_VALUE (tem); }
579 variable: block COLONCOLON name
580 { struct symbol *sym;
581 sym = lookup_symbol (copy_name ($3), $1,
582 VAR_NAMESPACE, (int *) NULL,
583 (struct symtab **) NULL);
585 error ("No symbol \"%s\" in specified context.",
588 write_exp_elt_opcode (OP_VAR_VALUE);
589 /* block_found is set by lookup_symbol. */
590 write_exp_elt_block (block_found);
591 write_exp_elt_sym (sym);
592 write_exp_elt_opcode (OP_VAR_VALUE); }
595 qualified_name: typebase COLONCOLON name
597 struct type *type = $1;
598 if (TYPE_CODE (type) != TYPE_CODE_STRUCT
599 && TYPE_CODE (type) != TYPE_CODE_UNION)
600 error ("`%s' is not defined as an aggregate type.",
603 write_exp_elt_opcode (OP_SCOPE);
604 write_exp_elt_type (type);
605 write_exp_string ($3);
606 write_exp_elt_opcode (OP_SCOPE);
608 | typebase COLONCOLON '~' name
610 struct type *type = $1;
611 struct stoken tmp_token;
612 if (TYPE_CODE (type) != TYPE_CODE_STRUCT
613 && TYPE_CODE (type) != TYPE_CODE_UNION)
614 error ("`%s' is not defined as an aggregate type.",
617 tmp_token.ptr = (char*) alloca ($4.length + 2);
618 tmp_token.length = $4.length + 1;
619 tmp_token.ptr[0] = '~';
620 memcpy (tmp_token.ptr+1, $4.ptr, $4.length);
621 tmp_token.ptr[tmp_token.length] = 0;
623 /* Check for valid destructor name. */
624 destructor_name_p (tmp_token.ptr, type);
625 write_exp_elt_opcode (OP_SCOPE);
626 write_exp_elt_type (type);
627 write_exp_string (tmp_token);
628 write_exp_elt_opcode (OP_SCOPE);
632 variable: qualified_name
635 char *name = copy_name ($2);
637 struct minimal_symbol *msymbol;
640 lookup_symbol (name, (const struct block *) NULL,
641 VAR_NAMESPACE, (int *) NULL,
642 (struct symtab **) NULL);
645 write_exp_elt_opcode (OP_VAR_VALUE);
646 write_exp_elt_block (NULL);
647 write_exp_elt_sym (sym);
648 write_exp_elt_opcode (OP_VAR_VALUE);
652 msymbol = lookup_minimal_symbol (name, NULL, NULL);
655 write_exp_msymbol (msymbol,
656 lookup_function_type (builtin_type_int),
660 if (!have_full_symbols () && !have_partial_symbols ())
661 error ("No symbol table is loaded. Use the \"file\" command.");
663 error ("No symbol \"%s\" in current context.", name);
667 variable: name_not_typename
668 { struct symbol *sym = $1.sym;
672 if (symbol_read_needs_frame (sym))
674 if (innermost_block == 0 ||
675 contained_in (block_found,
677 innermost_block = block_found;
680 write_exp_elt_opcode (OP_VAR_VALUE);
681 /* We want to use the selected frame, not
682 another more inner frame which happens to
683 be in the same block. */
684 write_exp_elt_block (NULL);
685 write_exp_elt_sym (sym);
686 write_exp_elt_opcode (OP_VAR_VALUE);
688 else if ($1.is_a_field_of_this)
690 /* C++: it hangs off of `this'. Must
691 not inadvertently convert from a method call
693 if (innermost_block == 0 ||
694 contained_in (block_found, innermost_block))
695 innermost_block = block_found;
696 write_exp_elt_opcode (OP_THIS);
697 write_exp_elt_opcode (OP_THIS);
698 write_exp_elt_opcode (STRUCTOP_PTR);
699 write_exp_string ($1.stoken);
700 write_exp_elt_opcode (STRUCTOP_PTR);
704 struct minimal_symbol *msymbol;
705 register char *arg = copy_name ($1.stoken);
708 lookup_minimal_symbol (arg, NULL, NULL);
711 write_exp_msymbol (msymbol,
712 lookup_function_type (builtin_type_int),
715 else if (!have_full_symbols () && !have_partial_symbols ())
716 error ("No symbol table is loaded. Use the \"file\" command.");
718 error ("No symbol \"%s\" in current context.",
719 copy_name ($1.stoken));
726 /* "const" and "volatile" are curently ignored. A type qualifier
727 before the type is currently handled in the typebase rule.
728 The reason for recognizing these here (shift/reduce conflicts)
729 might be obsolete now that some pointer to member rules have
731 | typebase CONST_KEYWORD
732 | typebase VOLATILE_KEYWORD
734 { $$ = follow_types ($1); }
735 | typebase CONST_KEYWORD abs_decl
736 { $$ = follow_types ($1); }
737 | typebase VOLATILE_KEYWORD abs_decl
738 { $$ = follow_types ($1); }
742 { push_type (tp_pointer); $$ = 0; }
744 { push_type (tp_pointer); $$ = $2; }
746 { push_type (tp_reference); $$ = 0; }
748 { push_type (tp_reference); $$ = $2; }
752 direct_abs_decl: '(' abs_decl ')'
754 | direct_abs_decl array_mod
757 push_type (tp_array);
762 push_type (tp_array);
766 | direct_abs_decl func_mod
767 { push_type (tp_function); }
769 { push_type (tp_function); }
780 | '(' nonempty_typelist ')'
781 { free ((PTR)$2); $$ = 0; }
784 /* We used to try to recognize more pointer to member types here, but
785 that didn't work (shift/reduce conflicts meant that these rules never
786 got executed). The problem is that
787 int (foo::bar::baz::bizzle)
788 is a function type but
789 int (foo::bar::baz::bizzle::*)
790 is a pointer to member type. Stroustrup loses again! */
793 | typebase COLONCOLON '*'
794 { $$ = lookup_member_type (builtin_type_int, $1); }
797 typebase /* Implements (approximately): (type-qualifier)* type-specifier */
801 { $$ = builtin_type_int; }
803 { $$ = builtin_type_long; }
805 { $$ = builtin_type_short; }
807 { $$ = builtin_type_long; }
808 | UNSIGNED LONG INT_KEYWORD
809 { $$ = builtin_type_unsigned_long; }
811 { $$ = builtin_type_long_long; }
812 | LONG LONG INT_KEYWORD
813 { $$ = builtin_type_long_long; }
815 { $$ = builtin_type_unsigned_long_long; }
816 | UNSIGNED LONG LONG INT_KEYWORD
817 { $$ = builtin_type_unsigned_long_long; }
819 { $$ = builtin_type_short; }
820 | UNSIGNED SHORT INT_KEYWORD
821 { $$ = builtin_type_unsigned_short; }
823 { $$ = builtin_type_double; }
824 | LONG DOUBLE_KEYWORD
825 { $$ = builtin_type_long_double; }
827 { $$ = lookup_struct (copy_name ($2),
828 expression_context_block); }
830 { $$ = lookup_struct (copy_name ($2),
831 expression_context_block); }
833 { $$ = lookup_union (copy_name ($2),
834 expression_context_block); }
836 { $$ = lookup_enum (copy_name ($2),
837 expression_context_block); }
839 { $$ = lookup_unsigned_typename (TYPE_NAME($2.type)); }
841 { $$ = builtin_type_unsigned_int; }
842 | SIGNED_KEYWORD typename
843 { $$ = lookup_signed_typename (TYPE_NAME($2.type)); }
845 { $$ = builtin_type_int; }
846 /* It appears that this rule for templates is never
847 reduced; template recognition happens by lookahead
848 in the token processing code in yylex. */
849 | TEMPLATE name '<' type '>'
850 { $$ = lookup_template_type(copy_name($2), $4,
851 expression_context_block);
853 /* "const" and "volatile" are curently ignored. A type qualifier
854 after the type is handled in the ptype rule. I think these could
856 | CONST_KEYWORD typebase { $$ = $2; }
857 | VOLATILE_KEYWORD typebase { $$ = $2; }
863 $$.stoken.ptr = "int";
864 $$.stoken.length = 3;
865 $$.type = builtin_type_int;
869 $$.stoken.ptr = "long";
870 $$.stoken.length = 4;
871 $$.type = builtin_type_long;
875 $$.stoken.ptr = "short";
876 $$.stoken.length = 5;
877 $$.type = builtin_type_short;
883 { $$ = (struct type **) malloc (sizeof (struct type *) * 2);
884 $<ivec>$[0] = 1; /* Number of types in vector */
887 | nonempty_typelist ',' type
888 { int len = sizeof (struct type *) * (++($<ivec>1[0]) + 1);
889 $$ = (struct type **) realloc ((char *) $1, len);
890 $$[$<ivec>$[0]] = $3;
894 name : NAME { $$ = $1.stoken; }
895 | BLOCKNAME { $$ = $1.stoken; }
896 | TYPENAME { $$ = $1.stoken; }
897 | NAME_OR_INT { $$ = $1.stoken; }
900 name_not_typename : NAME
902 /* These would be useful if name_not_typename was useful, but it is just
903 a fake for "variable", so these cause reduce/reduce conflicts because
904 the parser can't tell whether NAME_OR_INT is a name_not_typename (=variable,
905 =exp) or just an exp. If name_not_typename was ever used in an lvalue
906 context where only a name could occur, this might be useful.
913 /* Take care of parsing a number (anything that starts with a digit).
914 Set yylval and return the token type; update lexptr.
915 LEN is the number of characters in it. */
917 /*** Needs some error checking for the float case ***/
920 parse_number (p, len, parsed_float, putithere)
926 /* FIXME: Shouldn't these be unsigned? We don't deal with negative values
927 here, and we do kind of silly things like cast to unsigned. */
928 register LONGEST n = 0;
929 register LONGEST prevn = 0;
934 register int base = input_radix;
937 /* Number of "L" suffixes encountered. */
940 /* We have found a "L" or "U" suffix. */
941 int found_suffix = 0;
944 struct type *signed_type;
945 struct type *unsigned_type;
949 /* It's a float since it contains a point or an exponent. */
951 int num = 0; /* number of tokens scanned by scanf */
952 char saved_char = p[len];
954 p[len] = 0; /* null-terminate the token */
955 if (sizeof (putithere->typed_val_float.dval) <= sizeof (float))
956 num = sscanf (p, "%g%c", (float *) &putithere->typed_val_float.dval,&c);
957 else if (sizeof (putithere->typed_val_float.dval) <= sizeof (double))
958 num = sscanf (p, "%lg%c", (double *) &putithere->typed_val_float.dval,&c);
961 #ifdef SCANF_HAS_LONG_DOUBLE
962 num = sscanf (p, "%Lg%c", &putithere->typed_val_float.dval,&c);
964 /* Scan it into a double, then assign it to the long double.
965 This at least wins with values representable in the range
968 num = sscanf (p, "%lg%c", &temp,&c);
969 putithere->typed_val_float.dval = temp;
972 p[len] = saved_char; /* restore the input stream */
973 if (num != 1) /* check scanf found ONLY a float ... */
975 /* See if it has `f' or `l' suffix (float or long double). */
977 c = tolower (p[len - 1]);
980 putithere->typed_val_float.type = builtin_type_float;
982 putithere->typed_val_float.type = builtin_type_long_double;
983 else if (isdigit (c) || c == '.')
984 putithere->typed_val_float.type = builtin_type_double;
991 /* Handle base-switching prefixes 0x, 0t, 0d, 0 */
1025 if (c >= 'A' && c <= 'Z')
1027 if (c != 'l' && c != 'u')
1029 if (c >= '0' && c <= '9')
1037 if (base > 10 && c >= 'a' && c <= 'f')
1041 n += i = c - 'a' + 10;
1054 return ERROR; /* Char not a digit */
1057 return ERROR; /* Invalid digit in this base */
1059 /* Portably test for overflow (only works for nonzero values, so make
1060 a second check for zero). FIXME: Can't we just make n and prevn
1061 unsigned and avoid this? */
1062 if (c != 'l' && c != 'u' && (prevn >= n) && n != 0)
1063 unsigned_p = 1; /* Try something unsigned */
1065 /* Portably test for unsigned overflow.
1066 FIXME: This check is wrong; for example it doesn't find overflow
1067 on 0x123456789 when LONGEST is 32 bits. */
1068 if (c != 'l' && c != 'u' && n != 0)
1070 if ((unsigned_p && (ULONGEST) prevn >= (ULONGEST) n))
1071 error ("Numeric constant too large.");
1076 /* An integer constant is an int, a long, or a long long. An L
1077 suffix forces it to be long; an LL suffix forces it to be long
1078 long. If not forced to a larger size, it gets the first type of
1079 the above that it fits in. To figure out whether it fits, we
1080 shift it right and see whether anything remains. Note that we
1081 can't shift sizeof (LONGEST) * HOST_CHAR_BIT bits or more in one
1082 operation, because many compilers will warn about such a shift
1083 (which always produces a zero result). Sometimes TARGET_INT_BIT
1084 or TARGET_LONG_BIT will be that big, sometimes not. To deal with
1085 the case where it is we just always shift the value more than
1086 once, with fewer bits each time. */
1088 un = (ULONGEST)n >> 2;
1090 && (un >> (TARGET_INT_BIT - 2)) == 0)
1092 high_bit = ((ULONGEST)1) << (TARGET_INT_BIT-1);
1094 /* A large decimal (not hex or octal) constant (between INT_MAX
1095 and UINT_MAX) is a long or unsigned long, according to ANSI,
1096 never an unsigned int, but this code treats it as unsigned
1097 int. This probably should be fixed. GCC gives a warning on
1100 unsigned_type = builtin_type_unsigned_int;
1101 signed_type = builtin_type_int;
1103 else if (long_p <= 1
1104 && (un >> (TARGET_LONG_BIT - 2)) == 0)
1106 high_bit = ((ULONGEST)1) << (TARGET_LONG_BIT-1);
1107 unsigned_type = builtin_type_unsigned_long;
1108 signed_type = builtin_type_long;
1113 if (sizeof (ULONGEST) * HOST_CHAR_BIT < TARGET_LONG_LONG_BIT)
1114 /* A long long does not fit in a LONGEST. */
1115 shift = (sizeof (ULONGEST) * HOST_CHAR_BIT - 1);
1117 shift = (TARGET_LONG_LONG_BIT - 1);
1118 high_bit = (ULONGEST) 1 << shift;
1119 unsigned_type = builtin_type_unsigned_long_long;
1120 signed_type = builtin_type_long_long;
1123 putithere->typed_val_int.val = n;
1125 /* If the high bit of the worked out type is set then this number
1126 has to be unsigned. */
1128 if (unsigned_p || (n & high_bit))
1130 putithere->typed_val_int.type = unsigned_type;
1134 putithere->typed_val_int.type = signed_type;
1144 enum exp_opcode opcode;
1147 static const struct token tokentab3[] =
1149 {">>=", ASSIGN_MODIFY, BINOP_RSH},
1150 {"<<=", ASSIGN_MODIFY, BINOP_LSH}
1153 static const struct token tokentab2[] =
1155 {"+=", ASSIGN_MODIFY, BINOP_ADD},
1156 {"-=", ASSIGN_MODIFY, BINOP_SUB},
1157 {"*=", ASSIGN_MODIFY, BINOP_MUL},
1158 {"/=", ASSIGN_MODIFY, BINOP_DIV},
1159 {"%=", ASSIGN_MODIFY, BINOP_REM},
1160 {"|=", ASSIGN_MODIFY, BINOP_BITWISE_IOR},
1161 {"&=", ASSIGN_MODIFY, BINOP_BITWISE_AND},
1162 {"^=", ASSIGN_MODIFY, BINOP_BITWISE_XOR},
1163 {"++", INCREMENT, BINOP_END},
1164 {"--", DECREMENT, BINOP_END},
1165 {"->", ARROW, BINOP_END},
1166 {"&&", ANDAND, BINOP_END},
1167 {"||", OROR, BINOP_END},
1168 {"::", COLONCOLON, BINOP_END},
1169 {"<<", LSH, BINOP_END},
1170 {">>", RSH, BINOP_END},
1171 {"==", EQUAL, BINOP_END},
1172 {"!=", NOTEQUAL, BINOP_END},
1173 {"<=", LEQ, BINOP_END},
1174 {">=", GEQ, BINOP_END}
1177 /* Read one token, getting characters through lexptr. */
1188 static char *tempbuf;
1189 static int tempbufsize;
1190 struct symbol * sym_class = NULL;
1191 char * token_string = NULL;
1192 int class_prefix = 0;
1200 /* See if it is a special token of length 3. */
1201 for (i = 0; i < sizeof tokentab3 / sizeof tokentab3[0]; i++)
1202 if (STREQN (tokstart, tokentab3[i].operator, 3))
1205 yylval.opcode = tokentab3[i].opcode;
1206 return tokentab3[i].token;
1209 /* See if it is a special token of length 2. */
1210 for (i = 0; i < sizeof tokentab2 / sizeof tokentab2[0]; i++)
1211 if (STREQN (tokstart, tokentab2[i].operator, 2))
1214 yylval.opcode = tokentab2[i].opcode;
1215 return tokentab2[i].token;
1218 switch (c = *tokstart)
1230 /* We either have a character constant ('0' or '\177' for example)
1231 or we have a quoted symbol reference ('foo(int,int)' in C++
1236 c = parse_escape (&lexptr);
1238 error ("Empty character constant.");
1240 yylval.typed_val_int.val = c;
1241 yylval.typed_val_int.type = builtin_type_char;
1246 namelen = skip_quoted (tokstart) - tokstart;
1249 lexptr = tokstart + namelen;
1251 if (lexptr[-1] != '\'')
1252 error ("Unmatched single quote.");
1257 error ("Invalid character constant.");
1267 if (paren_depth == 0)
1274 if (comma_terminates && paren_depth == 0)
1280 /* Might be a floating point number. */
1281 if (lexptr[1] < '0' || lexptr[1] > '9')
1282 goto symbol; /* Nope, must be a symbol. */
1283 /* FALL THRU into number case. */
1296 /* It's a number. */
1297 int got_dot = 0, got_e = 0, toktype;
1298 register char *p = tokstart;
1299 int hex = input_radix > 10;
1301 if (c == '0' && (p[1] == 'x' || p[1] == 'X'))
1306 else if (c == '0' && (p[1]=='t' || p[1]=='T' || p[1]=='d' || p[1]=='D'))
1314 /* This test includes !hex because 'e' is a valid hex digit
1315 and thus does not indicate a floating point number when
1316 the radix is hex. */
1317 if (!hex && !got_e && (*p == 'e' || *p == 'E'))
1318 got_dot = got_e = 1;
1319 /* This test does not include !hex, because a '.' always indicates
1320 a decimal floating point number regardless of the radix. */
1321 else if (!got_dot && *p == '.')
1323 else if (got_e && (p[-1] == 'e' || p[-1] == 'E')
1324 && (*p == '-' || *p == '+'))
1325 /* This is the sign of the exponent, not the end of the
1328 /* We will take any letters or digits. parse_number will
1329 complain if past the radix, or if L or U are not final. */
1330 else if ((*p < '0' || *p > '9')
1331 && ((*p < 'a' || *p > 'z')
1332 && (*p < 'A' || *p > 'Z')))
1335 toktype = parse_number (tokstart, p - tokstart, got_dot|got_e, &yylval);
1336 if (toktype == ERROR)
1338 char *err_copy = (char *) alloca (p - tokstart + 1);
1340 memcpy (err_copy, tokstart, p - tokstart);
1341 err_copy[p - tokstart] = 0;
1342 error ("Invalid number \"%s\".", err_copy);
1374 /* Build the gdb internal form of the input string in tempbuf,
1375 translating any standard C escape forms seen. Note that the
1376 buffer is null byte terminated *only* for the convenience of
1377 debugging gdb itself and printing the buffer contents when
1378 the buffer contains no embedded nulls. Gdb does not depend
1379 upon the buffer being null byte terminated, it uses the length
1380 string instead. This allows gdb to handle C strings (as well
1381 as strings in other languages) with embedded null bytes */
1383 tokptr = ++tokstart;
1387 /* Grow the static temp buffer if necessary, including allocating
1388 the first one on demand. */
1389 if (tempbufindex + 1 >= tempbufsize)
1391 tempbuf = (char *) realloc (tempbuf, tempbufsize += 64);
1397 /* Do nothing, loop will terminate. */
1401 c = parse_escape (&tokptr);
1406 tempbuf[tempbufindex++] = c;
1409 tempbuf[tempbufindex++] = *tokptr++;
1412 } while ((*tokptr != '"') && (*tokptr != '\0'));
1413 if (*tokptr++ != '"')
1415 error ("Unterminated string in expression.");
1417 tempbuf[tempbufindex] = '\0'; /* See note above */
1418 yylval.sval.ptr = tempbuf;
1419 yylval.sval.length = tempbufindex;
1424 if (!(c == '_' || c == '$'
1425 || (c >= 'a' && c <= 'z') || (c >= 'A' && c <= 'Z')))
1426 /* We must have come across a bad character (e.g. ';'). */
1427 error ("Invalid character '%c' in expression.", c);
1429 /* It's a name. See how long it is. */
1431 for (c = tokstart[namelen];
1432 (c == '_' || c == '$' || (c >= '0' && c <= '9')
1433 || (c >= 'a' && c <= 'z') || (c >= 'A' && c <= 'Z') || c == '<');)
1435 /* Template parameter lists are part of the name.
1436 FIXME: This mishandles `print $a<4&&$a>3'. */
1440 if (hp_som_som_object_present)
1442 /* Scan ahead to get rest of the template specification. Note
1443 that we look ahead only when the '<' adjoins non-whitespace
1444 characters; for comparison expressions, e.g. "a < b > c",
1445 there must be spaces before the '<', etc. */
1447 char * p = find_template_name_end (tokstart + namelen);
1449 namelen = p - tokstart;
1455 int nesting_level = 1;
1456 while (tokstart[++i])
1458 if (tokstart[i] == '<')
1460 else if (tokstart[i] == '>')
1462 if (--nesting_level == 0)
1466 if (tokstart[i] == '>')
1472 c = tokstart[++namelen];
1475 /* The token "if" terminates the expression and is NOT
1476 removed from the input stream. */
1477 if (namelen == 2 && tokstart[0] == 'i' && tokstart[1] == 'f')
1486 /* Catch specific keywords. Should be done with a data structure. */
1490 if (STREQN (tokstart, "unsigned", 8))
1492 if (current_language->la_language == language_cplus
1493 && STREQN (tokstart, "template", 8))
1495 if (STREQN (tokstart, "volatile", 8))
1496 return VOLATILE_KEYWORD;
1499 if (STREQN (tokstart, "struct", 6))
1501 if (STREQN (tokstart, "signed", 6))
1502 return SIGNED_KEYWORD;
1503 if (STREQN (tokstart, "sizeof", 6))
1505 if (STREQN (tokstart, "double", 6))
1506 return DOUBLE_KEYWORD;
1509 if (current_language->la_language == language_cplus)
1511 if (STREQN (tokstart, "false", 5))
1512 return FALSEKEYWORD;
1513 if (STREQN (tokstart, "class", 5))
1516 if (STREQN (tokstart, "union", 5))
1518 if (STREQN (tokstart, "short", 5))
1520 if (STREQN (tokstart, "const", 5))
1521 return CONST_KEYWORD;
1524 if (STREQN (tokstart, "enum", 4))
1526 if (STREQN (tokstart, "long", 4))
1528 if (current_language->la_language == language_cplus)
1530 if (STREQN (tokstart, "true", 4))
1533 if (STREQN (tokstart, "this", 4))
1535 static const char this_name[] =
1536 { CPLUS_MARKER, 't', 'h', 'i', 's', '\0' };
1538 if (lookup_symbol (this_name, expression_context_block,
1539 VAR_NAMESPACE, (int *) NULL,
1540 (struct symtab **) NULL))
1546 if (STREQN (tokstart, "int", 3))
1553 yylval.sval.ptr = tokstart;
1554 yylval.sval.length = namelen;
1556 if (*tokstart == '$')
1558 write_dollar_variable (yylval.sval);
1562 /* Look ahead and see if we can consume more of the input
1563 string to get a reasonable class/namespace spec or a
1564 fully-qualified name. This is a kludge to get around the
1565 HP aCC compiler's generation of symbol names with embedded
1566 colons for namespace and nested classes. */
1569 /* Only do it if not inside single quotes */
1570 sym_class = parse_nested_classes_for_hpacc (yylval.sval.ptr, yylval.sval.length,
1571 &token_string, &class_prefix, &lexptr);
1574 /* Replace the current token with the bigger one we found */
1575 yylval.sval.ptr = token_string;
1576 yylval.sval.length = strlen (token_string);
1580 /* Use token-type BLOCKNAME for symbols that happen to be defined as
1581 functions or symtabs. If this is not so, then ...
1582 Use token-type TYPENAME for symbols that happen to be defined
1583 currently as names of types; NAME for other symbols.
1584 The caller is not constrained to care about the distinction. */
1586 char *tmp = copy_name (yylval.sval);
1588 int is_a_field_of_this = 0;
1591 sym = lookup_symbol (tmp, expression_context_block,
1593 current_language->la_language == language_cplus
1594 ? &is_a_field_of_this : (int *) NULL,
1595 (struct symtab **) NULL);
1596 /* Call lookup_symtab, not lookup_partial_symtab, in case there are
1597 no psymtabs (coff, xcoff, or some future change to blow away the
1598 psymtabs once once symbols are read). */
1599 if (sym && SYMBOL_CLASS (sym) == LOC_BLOCK)
1601 yylval.ssym.sym = sym;
1602 yylval.ssym.is_a_field_of_this = is_a_field_of_this;
1606 { /* See if it's a file name. */
1607 struct symtab *symtab;
1609 symtab = lookup_symtab (tmp);
1613 yylval.bval = BLOCKVECTOR_BLOCK (BLOCKVECTOR (symtab), STATIC_BLOCK);
1618 if (sym && SYMBOL_CLASS (sym) == LOC_TYPEDEF)
1621 /* Despite the following flaw, we need to keep this code enabled.
1622 Because we can get called from check_stub_method, if we don't
1623 handle nested types then it screws many operations in any
1624 program which uses nested types. */
1625 /* In "A::x", if x is a member function of A and there happens
1626 to be a type (nested or not, since the stabs don't make that
1627 distinction) named x, then this code incorrectly thinks we
1628 are dealing with nested types rather than a member function. */
1632 struct symbol *best_sym;
1634 /* Look ahead to detect nested types. This probably should be
1635 done in the grammar, but trying seemed to introduce a lot
1636 of shift/reduce and reduce/reduce conflicts. It's possible
1637 that it could be done, though. Or perhaps a non-grammar, but
1638 less ad hoc, approach would work well. */
1640 /* Since we do not currently have any way of distinguishing
1641 a nested type from a non-nested one (the stabs don't tell
1642 us whether a type is nested), we just ignore the
1649 /* Skip whitespace. */
1650 while (*p == ' ' || *p == '\t' || *p == '\n')
1652 if (*p == ':' && p[1] == ':')
1654 /* Skip the `::'. */
1656 /* Skip whitespace. */
1657 while (*p == ' ' || *p == '\t' || *p == '\n')
1660 while (*p == '_' || *p == '$' || (*p >= '0' && *p <= '9')
1661 || (*p >= 'a' && *p <= 'z')
1662 || (*p >= 'A' && *p <= 'Z'))
1666 struct symbol *cur_sym;
1667 /* As big as the whole rest of the expression, which is
1668 at least big enough. */
1669 char *ncopy = alloca (strlen (tmp)+strlen (namestart)+3);
1673 memcpy (tmp1, tmp, strlen (tmp));
1674 tmp1 += strlen (tmp);
1675 memcpy (tmp1, "::", 2);
1677 memcpy (tmp1, namestart, p - namestart);
1678 tmp1[p - namestart] = '\0';
1679 cur_sym = lookup_symbol (ncopy, expression_context_block,
1680 VAR_NAMESPACE, (int *) NULL,
1681 (struct symtab **) NULL);
1684 if (SYMBOL_CLASS (cur_sym) == LOC_TYPEDEF)
1702 yylval.tsym.type = SYMBOL_TYPE (best_sym);
1704 yylval.tsym.type = SYMBOL_TYPE (sym);
1708 if ((yylval.tsym.type = lookup_primitive_typename (tmp)) != 0)
1711 /* Input names that aren't symbols but ARE valid hex numbers,
1712 when the input radix permits them, can be names or numbers
1713 depending on the parse. Note we support radixes > 16 here. */
1715 ((tokstart[0] >= 'a' && tokstart[0] < 'a' + input_radix - 10) ||
1716 (tokstart[0] >= 'A' && tokstart[0] < 'A' + input_radix - 10)))
1718 YYSTYPE newlval; /* Its value is ignored. */
1719 hextype = parse_number (tokstart, namelen, 0, &newlval);
1722 yylval.ssym.sym = sym;
1723 yylval.ssym.is_a_field_of_this = is_a_field_of_this;
1728 /* Any other kind of symbol */
1729 yylval.ssym.sym = sym;
1730 yylval.ssym.is_a_field_of_this = is_a_field_of_this;
1739 error ("A %s in expression, near `%s'.", (msg ? msg : "error"), lexptr);