1 /* YACC parser for C expressions, for GDB.
2 Copyright (C) 1986, 1989, 1990, 1991 Free Software Foundation, Inc.
4 This file is part of GDB.
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.
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.
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. */
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.
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. */
40 #include "expression.h"
41 #include "parser-defs.h"
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. */
53 #define yymaxdepth c_maxdepth
54 #define yyparse c_parse
56 #define yyerror c_error
59 #define yydebug c_debug
68 #define yyerrflag c_errflag
69 #define yynerrs c_nerrs
74 #define yystate c_state
80 #define yyreds c_reds /* With YYDEBUG defined */
81 #define yytoks c_toks /* With YYDEBUG defined */
84 #define YYDEBUG 0 /* Default to no yydebug support */
88 yyparse PARAMS ((void));
91 yylex PARAMS ((void));
94 yyerror PARAMS ((char *));
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. */
114 struct symtoken ssym;
117 enum exp_opcode opcode;
118 struct internalvar *ivar;
125 /* YYSTYPE gets defined by %union */
127 parse_number PARAMS ((char *, int, int, YYSTYPE *));
130 %type <voidval> exp exp1 type_exp start variable qualified_name lcurly
132 %type <tval> type typebase
133 %type <tvec> nonempty_typelist
134 /* %type <bval> block */
136 /* Fancy type parsing. */
137 %type <voidval> func_mod direct_abs_decl abs_decl
139 %type <lval> array_mod
141 %token <typed_val> INT
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. */
153 %token <ssym> NAME /* BLOCKNAME defined below to give it higher precedence. */
154 %token <tsym> TYPENAME
156 %type <ssym> name_not_typename
157 %type <tsym> typename
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. */
164 %token <ssym> NAME_OR_INT
166 %token STRUCT CLASS UNION ENUM SIZEOF UNSIGNED COLONCOLON
170 /* Special type cases, put in to allow the parser to distinguish different
172 %token SIGNED_KEYWORD LONG SHORT INT_KEYWORD CONST_KEYWORD VOLATILE_KEYWORD
173 %token <lval> LAST REGNAME
175 %token <ivar> VARIABLE
177 %token <opcode> ASSIGN_MODIFY
184 %right '=' ASSIGN_MODIFY
192 %left '<' '>' LEQ GEQ
197 %right UNARY INCREMENT DECREMENT
198 %right ARROW '.' '[' '('
199 %token <ssym> BLOCKNAME
211 { write_exp_elt_opcode(OP_TYPE);
212 write_exp_elt_type($1);
213 write_exp_elt_opcode(OP_TYPE);}
216 /* Expressions, including the comma operator. */
219 { write_exp_elt_opcode (BINOP_COMMA); }
222 /* Expressions, not including the comma operator. */
223 exp : '*' exp %prec UNARY
224 { write_exp_elt_opcode (UNOP_IND); }
226 exp : '&' exp %prec UNARY
227 { write_exp_elt_opcode (UNOP_ADDR); }
229 exp : '-' exp %prec UNARY
230 { write_exp_elt_opcode (UNOP_NEG); }
233 exp : '!' exp %prec UNARY
234 { write_exp_elt_opcode (UNOP_LOGICAL_NOT); }
237 exp : '~' exp %prec UNARY
238 { write_exp_elt_opcode (UNOP_COMPLEMENT); }
241 exp : INCREMENT exp %prec UNARY
242 { write_exp_elt_opcode (UNOP_PREINCREMENT); }
245 exp : DECREMENT exp %prec UNARY
246 { write_exp_elt_opcode (UNOP_PREDECREMENT); }
249 exp : exp INCREMENT %prec UNARY
250 { write_exp_elt_opcode (UNOP_POSTINCREMENT); }
253 exp : exp DECREMENT %prec UNARY
254 { write_exp_elt_opcode (UNOP_POSTDECREMENT); }
257 exp : SIZEOF exp %prec UNARY
258 { write_exp_elt_opcode (UNOP_SIZEOF); }
262 { write_exp_elt_opcode (STRUCTOP_PTR);
263 write_exp_string ($3);
264 write_exp_elt_opcode (STRUCTOP_PTR); }
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); }
274 exp : exp ARROW '*' exp
275 { write_exp_elt_opcode (STRUCTOP_MPTR); }
279 { write_exp_elt_opcode (STRUCTOP_STRUCT);
280 write_exp_string ($3);
281 write_exp_elt_opcode (STRUCTOP_STRUCT); }
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); }
292 exp : exp '.' '*' exp
293 { write_exp_elt_opcode (STRUCTOP_MEMBER); }
296 exp : exp '[' exp1 ']'
297 { write_exp_elt_opcode (BINOP_SUBSCRIPT); }
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); }
311 { start_arglist (); }
321 arglist : arglist ',' exp %prec ABOVE_COMMA
326 { $$ = end_arglist () - 1; }
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); }
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); }
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); }
351 /* Binary operators in order of decreasing precedence. */
354 { write_exp_elt_opcode (BINOP_REPEAT); }
358 { write_exp_elt_opcode (BINOP_MUL); }
362 { write_exp_elt_opcode (BINOP_DIV); }
366 { write_exp_elt_opcode (BINOP_REM); }
370 { write_exp_elt_opcode (BINOP_ADD); }
374 { write_exp_elt_opcode (BINOP_SUB); }
378 { write_exp_elt_opcode (BINOP_LSH); }
382 { write_exp_elt_opcode (BINOP_RSH); }
386 { write_exp_elt_opcode (BINOP_EQUAL); }
389 exp : exp NOTEQUAL exp
390 { write_exp_elt_opcode (BINOP_NOTEQUAL); }
394 { write_exp_elt_opcode (BINOP_LEQ); }
398 { write_exp_elt_opcode (BINOP_GEQ); }
402 { write_exp_elt_opcode (BINOP_LESS); }
406 { write_exp_elt_opcode (BINOP_GTR); }
410 { write_exp_elt_opcode (BINOP_BITWISE_AND); }
414 { write_exp_elt_opcode (BINOP_BITWISE_XOR); }
418 { write_exp_elt_opcode (BINOP_BITWISE_IOR); }
422 { write_exp_elt_opcode (BINOP_LOGICAL_AND); }
426 { write_exp_elt_opcode (BINOP_LOGICAL_OR); }
429 exp : exp '?' exp ':' exp %prec '?'
430 { write_exp_elt_opcode (TERNOP_COND); }
434 { write_exp_elt_opcode (BINOP_ASSIGN); }
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); }
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); }
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);
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); }
472 { write_exp_elt_opcode (OP_LAST);
473 write_exp_elt_longcst ((LONGEST) $1);
474 write_exp_elt_opcode (OP_LAST); }
478 { write_exp_elt_opcode (OP_REGISTER);
479 write_exp_elt_longcst ((LONGEST) $1);
480 write_exp_elt_opcode (OP_REGISTER); }
484 { write_exp_elt_opcode (OP_INTERNALVAR);
485 write_exp_elt_intern ($1);
486 write_exp_elt_opcode (OP_INTERNALVAR); }
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); }
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
502 char *sp = $1.ptr; int count = $1.length;
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);
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); }
522 { write_exp_elt_opcode (OP_THIS);
523 write_exp_elt_opcode (OP_THIS); }
531 $$ = SYMBOL_BLOCK_VALUE ($1.sym);
535 lookup_symtab (copy_name ($1.stoken));
537 $$ = BLOCKVECTOR_BLOCK
538 (BLOCKVECTOR (tem), STATIC_BLOCK);
540 error ("No file or function \"%s\".",
541 copy_name ($1.stoken));
546 block : block COLONCOLON name
548 = lookup_symbol (copy_name ($3), $1,
549 VAR_NAMESPACE, (int *) NULL,
550 (struct symtab **) NULL);
551 if (!tem || SYMBOL_CLASS (tem) != LOC_BLOCK)
552 error ("No function \"%s\" in specified context.",
554 $$ = SYMBOL_BLOCK_VALUE (tem); }
557 variable: block COLONCOLON name
558 { struct symbol *sym;
559 sym = lookup_symbol (copy_name ($3), $1,
560 VAR_NAMESPACE, (int *) NULL,
561 (struct symtab **) NULL);
563 error ("No symbol \"%s\" in specified context.",
566 write_exp_elt_opcode (OP_VAR_VALUE);
567 /* block_found is set by lookup_symbol. */
568 write_exp_elt_block (block_found);
569 write_exp_elt_sym (sym);
570 write_exp_elt_opcode (OP_VAR_VALUE); }
573 qualified_name: typebase COLONCOLON name
575 struct type *type = $1;
576 if (TYPE_CODE (type) != TYPE_CODE_STRUCT
577 && TYPE_CODE (type) != TYPE_CODE_UNION)
578 error ("`%s' is not defined as an aggregate type.",
581 write_exp_elt_opcode (OP_SCOPE);
582 write_exp_elt_type (type);
583 write_exp_string ($3);
584 write_exp_elt_opcode (OP_SCOPE);
586 | typebase COLONCOLON '~' name
588 struct type *type = $1;
589 struct stoken tmp_token;
590 if (TYPE_CODE (type) != TYPE_CODE_STRUCT
591 && TYPE_CODE (type) != TYPE_CODE_UNION)
592 error ("`%s' is not defined as an aggregate type.",
595 if (!STREQ (type_name_no_tag (type), $4.ptr))
596 error ("invalid destructor `%s::~%s'",
597 type_name_no_tag (type), $4.ptr);
599 tmp_token.ptr = (char*) alloca ($4.length + 2);
600 tmp_token.length = $4.length + 1;
601 tmp_token.ptr[0] = '~';
602 memcpy (tmp_token.ptr+1, $4.ptr, $4.length);
603 tmp_token.ptr[tmp_token.length] = 0;
604 write_exp_elt_opcode (OP_SCOPE);
605 write_exp_elt_type (type);
606 write_exp_string (tmp_token);
607 write_exp_elt_opcode (OP_SCOPE);
611 variable: qualified_name
614 char *name = copy_name ($2);
616 struct minimal_symbol *msymbol;
619 lookup_symbol (name, (const struct block *) NULL,
620 VAR_NAMESPACE, (int *) NULL,
621 (struct symtab **) NULL);
624 write_exp_elt_opcode (OP_VAR_VALUE);
625 write_exp_elt_block (NULL);
626 write_exp_elt_sym (sym);
627 write_exp_elt_opcode (OP_VAR_VALUE);
631 msymbol = lookup_minimal_symbol (name,
632 (struct objfile *) NULL);
635 write_exp_elt_opcode (OP_LONG);
636 write_exp_elt_type (builtin_type_int);
637 write_exp_elt_longcst ((LONGEST) SYMBOL_VALUE_ADDRESS (msymbol));
638 write_exp_elt_opcode (OP_LONG);
639 write_exp_elt_opcode (UNOP_MEMVAL);
640 if (msymbol -> type == mst_data ||
641 msymbol -> type == mst_bss)
642 write_exp_elt_type (builtin_type_int);
643 else if (msymbol -> type == mst_text)
644 write_exp_elt_type (lookup_function_type (builtin_type_int));
646 write_exp_elt_type (builtin_type_char);
647 write_exp_elt_opcode (UNOP_MEMVAL);
650 if (!have_full_symbols () && !have_partial_symbols ())
651 error ("No symbol table is loaded. Use the \"file\" command.");
653 error ("No symbol \"%s\" in current context.", name);
657 variable: name_not_typename
658 { struct symbol *sym = $1.sym;
662 switch (SYMBOL_CLASS (sym))
668 case LOC_REGPARM_ADDR:
672 case LOC_BASEREG_ARG:
673 if (innermost_block == 0 ||
674 contained_in (block_found,
676 innermost_block = block_found;
683 case LOC_CONST_BYTES:
684 case LOC_OPTIMIZED_OUT:
686 /* In this case the expression can
687 be evaluated regardless of what
688 frame we are in, so there is no
689 need to check for the
690 innermost_block. These cases are
691 listed so that gcc -Wall will
692 report types that may not have
697 write_exp_elt_opcode (OP_VAR_VALUE);
698 /* We want to use the selected frame, not
699 another more inner frame which happens to
700 be in the same block. */
701 write_exp_elt_block (NULL);
702 write_exp_elt_sym (sym);
703 write_exp_elt_opcode (OP_VAR_VALUE);
705 else if ($1.is_a_field_of_this)
707 /* C++: it hangs off of `this'. Must
708 not inadvertently convert from a method call
710 if (innermost_block == 0 ||
711 contained_in (block_found, innermost_block))
712 innermost_block = block_found;
713 write_exp_elt_opcode (OP_THIS);
714 write_exp_elt_opcode (OP_THIS);
715 write_exp_elt_opcode (STRUCTOP_PTR);
716 write_exp_string ($1.stoken);
717 write_exp_elt_opcode (STRUCTOP_PTR);
721 struct minimal_symbol *msymbol;
722 register char *arg = copy_name ($1.stoken);
724 msymbol = lookup_minimal_symbol (arg,
725 (struct objfile *) NULL);
728 write_exp_elt_opcode (OP_LONG);
729 write_exp_elt_type (builtin_type_int);
730 write_exp_elt_longcst ((LONGEST) SYMBOL_VALUE_ADDRESS (msymbol));
731 write_exp_elt_opcode (OP_LONG);
732 write_exp_elt_opcode (UNOP_MEMVAL);
733 if (msymbol -> type == mst_data ||
734 msymbol -> type == mst_bss)
735 write_exp_elt_type (builtin_type_int);
736 else if (msymbol -> type == mst_text)
737 write_exp_elt_type (lookup_function_type (builtin_type_int));
739 write_exp_elt_type (builtin_type_char);
740 write_exp_elt_opcode (UNOP_MEMVAL);
742 else if (!have_full_symbols () && !have_partial_symbols ())
743 error ("No symbol table is loaded. Use the \"file\" command.");
745 error ("No symbol \"%s\" in current context.",
746 copy_name ($1.stoken));
755 /* This is where the interesting stuff happens. */
758 struct type *follow_type = $1;
759 struct type *range_type;
768 follow_type = lookup_pointer_type (follow_type);
771 follow_type = lookup_reference_type (follow_type);
774 array_size = pop_type_int ();
775 if (array_size != -1)
778 create_range_type ((struct type *) NULL,
782 create_array_type ((struct type *) NULL,
783 follow_type, range_type);
786 follow_type = lookup_pointer_type (follow_type);
789 follow_type = lookup_function_type (follow_type);
797 { push_type (tp_pointer); $$ = 0; }
799 { push_type (tp_pointer); $$ = $2; }
801 { push_type (tp_reference); $$ = 0; }
803 { push_type (tp_reference); $$ = $2; }
807 direct_abs_decl: '(' abs_decl ')'
809 | direct_abs_decl array_mod
812 push_type (tp_array);
817 push_type (tp_array);
820 | direct_abs_decl func_mod
821 { push_type (tp_function); }
823 { push_type (tp_function); }
834 | '(' nonempty_typelist ')'
835 { free ((PTR)$2); $$ = 0; }
839 | typebase COLONCOLON '*'
840 { $$ = lookup_member_type (builtin_type_int, $1); }
841 | type '(' typebase COLONCOLON '*' ')'
842 { $$ = lookup_member_type ($1, $3); }
843 | type '(' typebase COLONCOLON '*' ')' '(' ')'
844 { $$ = lookup_member_type
845 (lookup_function_type ($1), $3); }
846 | type '(' typebase COLONCOLON '*' ')' '(' nonempty_typelist ')'
847 { $$ = lookup_member_type
848 (lookup_function_type ($1), $3);
852 typebase /* Implements (approximately): (type-qualifier)* type-specifier */
856 { $$ = builtin_type_int; }
858 { $$ = builtin_type_long; }
860 { $$ = builtin_type_short; }
862 { $$ = builtin_type_long; }
863 | UNSIGNED LONG INT_KEYWORD
864 { $$ = builtin_type_unsigned_long; }
866 { $$ = builtin_type_long_long; }
867 | LONG LONG INT_KEYWORD
868 { $$ = builtin_type_long_long; }
870 { $$ = builtin_type_unsigned_long_long; }
871 | UNSIGNED LONG LONG INT_KEYWORD
872 { $$ = builtin_type_unsigned_long_long; }
874 { $$ = builtin_type_short; }
875 | UNSIGNED SHORT INT_KEYWORD
876 { $$ = builtin_type_unsigned_short; }
878 { $$ = lookup_struct (copy_name ($2),
879 expression_context_block); }
881 { $$ = lookup_struct (copy_name ($2),
882 expression_context_block); }
884 { $$ = lookup_union (copy_name ($2),
885 expression_context_block); }
887 { $$ = lookup_enum (copy_name ($2),
888 expression_context_block); }
890 { $$ = lookup_unsigned_typename (TYPE_NAME($2.type)); }
892 { $$ = builtin_type_unsigned_int; }
893 | SIGNED_KEYWORD typename
894 { $$ = lookup_signed_typename (TYPE_NAME($2.type)); }
896 { $$ = builtin_type_int; }
897 | TEMPLATE name '<' type '>'
898 { $$ = lookup_template_type(copy_name($2), $4,
899 expression_context_block);
901 /* "const" and "volatile" are curently ignored. */
902 | CONST_KEYWORD typebase { $$ = $2; }
903 | VOLATILE_KEYWORD typebase { $$ = $2; }
909 $$.stoken.ptr = "int";
910 $$.stoken.length = 3;
911 $$.type = builtin_type_int;
915 $$.stoken.ptr = "long";
916 $$.stoken.length = 4;
917 $$.type = builtin_type_long;
921 $$.stoken.ptr = "short";
922 $$.stoken.length = 5;
923 $$.type = builtin_type_short;
929 { $$ = (struct type **) malloc (sizeof (struct type *) * 2);
930 $<ivec>$[0] = 1; /* Number of types in vector */
933 | nonempty_typelist ',' type
934 { int len = sizeof (struct type *) * (++($<ivec>1[0]) + 1);
935 $$ = (struct type **) realloc ((char *) $1, len);
936 $$[$<ivec>$[0]] = $3;
940 name : NAME { $$ = $1.stoken; }
941 | BLOCKNAME { $$ = $1.stoken; }
942 | TYPENAME { $$ = $1.stoken; }
943 | NAME_OR_INT { $$ = $1.stoken; }
946 name_not_typename : NAME
948 /* These would be useful if name_not_typename was useful, but it is just
949 a fake for "variable", so these cause reduce/reduce conflicts because
950 the parser can't tell whether NAME_OR_INT is a name_not_typename (=variable,
951 =exp) or just an exp. If name_not_typename was ever used in an lvalue
952 context where only a name could occur, this might be useful.
959 /* Take care of parsing a number (anything that starts with a digit).
960 Set yylval and return the token type; update lexptr.
961 LEN is the number of characters in it. */
963 /*** Needs some error checking for the float case ***/
966 parse_number (p, len, parsed_float, putithere)
972 register LONGEST n = 0;
973 register LONGEST prevn = 0;
976 register int base = input_radix;
979 unsigned LONGEST high_bit;
980 struct type *signed_type;
981 struct type *unsigned_type;
985 /* It's a float since it contains a point or an exponent. */
986 putithere->dval = atof (p);
990 /* Handle base-switching prefixes 0x, 0t, 0d, 0 */
1024 if (c >= 'A' && c <= 'Z')
1026 if (c != 'l' && c != 'u')
1028 if (c >= '0' && c <= '9')
1032 if (base > 10 && c >= 'a' && c <= 'f')
1033 n += i = c - 'a' + 10;
1034 else if (len == 0 && c == 'l')
1036 else if (len == 0 && c == 'u')
1039 return ERROR; /* Char not a digit */
1042 return ERROR; /* Invalid digit in this base */
1044 /* Portably test for overflow (only works for nonzero values, so make
1045 a second check for zero). */
1046 if((prevn >= n) && n != 0)
1047 unsigned_p=1; /* Try something unsigned */
1048 /* If range checking enabled, portably test for unsigned overflow. */
1049 if(RANGE_CHECK && n!=0)
1051 if((unsigned_p && (unsigned)prevn >= (unsigned)n))
1052 range_error("Overflow on numeric constant.");
1057 /* If the number is too big to be an int, or it's got an l suffix
1058 then it's a long. Work out if this has to be a long by
1059 shifting right and and seeing if anything remains, and the
1060 target int size is different to the target long size.
1062 In the expression below, we could have tested
1063 (n >> TARGET_INT_BIT)
1064 to see if it was zero,
1065 but too many compilers warn about that, when ints and longs
1066 are the same size. So we shift it twice, with fewer bits
1067 each time, for the same result. */
1069 if ( (TARGET_INT_BIT != TARGET_LONG_BIT
1070 && ((n >> 2) >> (TARGET_INT_BIT-2))) /* Avoid shift warning */
1073 high_bit = ((unsigned LONGEST)1) << (TARGET_LONG_BIT-1);
1074 unsigned_type = builtin_type_unsigned_long;
1075 signed_type = builtin_type_long;
1079 high_bit = ((unsigned LONGEST)1) << (TARGET_INT_BIT-1);
1080 unsigned_type = builtin_type_unsigned_int;
1081 signed_type = builtin_type_int;
1084 putithere->typed_val.val = n;
1086 /* If the high bit of the worked out type is set then this number
1087 has to be unsigned. */
1089 if (unsigned_p || (n & high_bit))
1091 putithere->typed_val.type = unsigned_type;
1095 putithere->typed_val.type = signed_type;
1105 enum exp_opcode opcode;
1108 static const struct token tokentab3[] =
1110 {">>=", ASSIGN_MODIFY, BINOP_RSH},
1111 {"<<=", ASSIGN_MODIFY, BINOP_LSH}
1114 static const struct token tokentab2[] =
1116 {"+=", ASSIGN_MODIFY, BINOP_ADD},
1117 {"-=", ASSIGN_MODIFY, BINOP_SUB},
1118 {"*=", ASSIGN_MODIFY, BINOP_MUL},
1119 {"/=", ASSIGN_MODIFY, BINOP_DIV},
1120 {"%=", ASSIGN_MODIFY, BINOP_REM},
1121 {"|=", ASSIGN_MODIFY, BINOP_BITWISE_IOR},
1122 {"&=", ASSIGN_MODIFY, BINOP_BITWISE_AND},
1123 {"^=", ASSIGN_MODIFY, BINOP_BITWISE_XOR},
1124 {"++", INCREMENT, BINOP_END},
1125 {"--", DECREMENT, BINOP_END},
1126 {"->", ARROW, BINOP_END},
1127 {"&&", ANDAND, BINOP_END},
1128 {"||", OROR, BINOP_END},
1129 {"::", COLONCOLON, BINOP_END},
1130 {"<<", LSH, BINOP_END},
1131 {">>", RSH, BINOP_END},
1132 {"==", EQUAL, BINOP_END},
1133 {"!=", NOTEQUAL, BINOP_END},
1134 {"<=", LEQ, BINOP_END},
1135 {">=", GEQ, BINOP_END}
1138 /* Read one token, getting characters through lexptr. */
1149 static char *tempbuf;
1150 static int tempbufsize;
1155 /* See if it is a special token of length 3. */
1156 for (i = 0; i < sizeof tokentab3 / sizeof tokentab3[0]; i++)
1157 if (STREQN (tokstart, tokentab3[i].operator, 3))
1160 yylval.opcode = tokentab3[i].opcode;
1161 return tokentab3[i].token;
1164 /* See if it is a special token of length 2. */
1165 for (i = 0; i < sizeof tokentab2 / sizeof tokentab2[0]; i++)
1166 if (STREQN (tokstart, tokentab2[i].operator, 2))
1169 yylval.opcode = tokentab2[i].opcode;
1170 return tokentab2[i].token;
1173 switch (c = *tokstart)
1185 /* We either have a character constant ('0' or '\177' for example)
1186 or we have a quoted symbol reference ('foo(int,int)' in C++
1191 c = parse_escape (&lexptr);
1193 yylval.typed_val.val = c;
1194 yylval.typed_val.type = builtin_type_char;
1199 namelen = skip_quoted (tokstart) - tokstart;
1202 lexptr = tokstart + namelen;
1203 if (lexptr[-1] != '\'')
1204 error ("Unmatched single quote.");
1209 error ("Invalid character constant.");
1219 if (paren_depth == 0)
1226 if (comma_terminates && paren_depth == 0)
1232 /* Might be a floating point number. */
1233 if (lexptr[1] < '0' || lexptr[1] > '9')
1234 goto symbol; /* Nope, must be a symbol. */
1235 /* FALL THRU into number case. */
1248 /* It's a number. */
1249 int got_dot = 0, got_e = 0, toktype;
1250 register char *p = tokstart;
1251 int hex = input_radix > 10;
1253 if (c == '0' && (p[1] == 'x' || p[1] == 'X'))
1258 else if (c == '0' && (p[1]=='t' || p[1]=='T' || p[1]=='d' || p[1]=='D'))
1266 /* This test includes !hex because 'e' is a valid hex digit
1267 and thus does not indicate a floating point number when
1268 the radix is hex. */
1269 if (!hex && !got_e && (*p == 'e' || *p == 'E'))
1270 got_dot = got_e = 1;
1271 /* This test does not include !hex, because a '.' always indicates
1272 a decimal floating point number regardless of the radix. */
1273 else if (!got_dot && *p == '.')
1275 else if (got_e && (p[-1] == 'e' || p[-1] == 'E')
1276 && (*p == '-' || *p == '+'))
1277 /* This is the sign of the exponent, not the end of the
1280 /* We will take any letters or digits. parse_number will
1281 complain if past the radix, or if L or U are not final. */
1282 else if ((*p < '0' || *p > '9')
1283 && ((*p < 'a' || *p > 'z')
1284 && (*p < 'A' || *p > 'Z')))
1287 toktype = parse_number (tokstart, p - tokstart, got_dot|got_e, &yylval);
1288 if (toktype == ERROR)
1290 char *err_copy = (char *) alloca (p - tokstart + 1);
1292 memcpy (err_copy, tokstart, p - tokstart);
1293 err_copy[p - tokstart] = 0;
1294 error ("Invalid number \"%s\".", err_copy);
1326 /* Build the gdb internal form of the input string in tempbuf,
1327 translating any standard C escape forms seen. Note that the
1328 buffer is null byte terminated *only* for the convenience of
1329 debugging gdb itself and printing the buffer contents when
1330 the buffer contains no embedded nulls. Gdb does not depend
1331 upon the buffer being null byte terminated, it uses the length
1332 string instead. This allows gdb to handle C strings (as well
1333 as strings in other languages) with embedded null bytes */
1335 tokptr = ++tokstart;
1339 /* Grow the static temp buffer if necessary, including allocating
1340 the first one on demand. */
1341 if (tempbufindex + 1 >= tempbufsize)
1343 tempbuf = (char *) realloc (tempbuf, tempbufsize += 64);
1349 /* Do nothing, loop will terminate. */
1353 c = parse_escape (&tokptr);
1358 tempbuf[tempbufindex++] = c;
1361 tempbuf[tempbufindex++] = *tokptr++;
1364 } while ((*tokptr != '"') && (*tokptr != '\0'));
1365 if (*tokptr++ != '"')
1367 error ("Unterminated string in expression.");
1369 tempbuf[tempbufindex] = '\0'; /* See note above */
1370 yylval.sval.ptr = tempbuf;
1371 yylval.sval.length = tempbufindex;
1376 if (!(c == '_' || c == '$'
1377 || (c >= 'a' && c <= 'z') || (c >= 'A' && c <= 'Z')))
1378 /* We must have come across a bad character (e.g. ';'). */
1379 error ("Invalid character '%c' in expression.", c);
1381 /* It's a name. See how long it is. */
1383 for (c = tokstart[namelen];
1384 (c == '_' || c == '$' || (c >= '0' && c <= '9')
1385 || (c >= 'a' && c <= 'z') || (c >= 'A' && c <= 'Z'));
1386 c = tokstart[++namelen])
1389 /* The token "if" terminates the expression and is NOT
1390 removed from the input stream. */
1391 if (namelen == 2 && tokstart[0] == 'i' && tokstart[1] == 'f')
1398 /* Handle the tokens $digits; also $ (short for $0) and $$ (short for $$1)
1399 and $$digits (equivalent to $<-digits> if you could type that).
1400 Make token type LAST, and put the number (the digits) in yylval. */
1403 if (*tokstart == '$')
1405 register int negate = 0;
1407 /* Double dollar means negate the number and add -1 as well.
1408 Thus $$ alone means -1. */
1409 if (namelen >= 2 && tokstart[1] == '$')
1416 /* Just dollars (one or two) */
1417 yylval.lval = - negate;
1420 /* Is the rest of the token digits? */
1421 for (; c < namelen; c++)
1422 if (!(tokstart[c] >= '0' && tokstart[c] <= '9'))
1426 yylval.lval = atoi (tokstart + 1 + negate);
1428 yylval.lval = - yylval.lval;
1433 /* Handle tokens that refer to machine registers:
1434 $ followed by a register name. */
1436 if (*tokstart == '$') {
1437 for (c = 0; c < NUM_REGS; c++)
1438 if (namelen - 1 == strlen (reg_names[c])
1439 && STREQN (tokstart + 1, reg_names[c], namelen - 1))
1444 for (c = 0; c < num_std_regs; c++)
1445 if (namelen - 1 == strlen (std_regs[c].name)
1446 && STREQN (tokstart + 1, std_regs[c].name, namelen - 1))
1448 yylval.lval = std_regs[c].regnum;
1452 /* Catch specific keywords. Should be done with a data structure. */
1456 if (STREQN (tokstart, "unsigned", 8))
1458 if (current_language->la_language == language_cplus
1459 && STREQN (tokstart, "template", 8))
1461 if (STREQN (tokstart, "volatile", 8))
1462 return VOLATILE_KEYWORD;
1465 if (STREQN (tokstart, "struct", 6))
1467 if (STREQN (tokstart, "signed", 6))
1468 return SIGNED_KEYWORD;
1469 if (STREQN (tokstart, "sizeof", 6))
1473 if (current_language->la_language == language_cplus
1474 && STREQN (tokstart, "class", 5))
1476 if (STREQN (tokstart, "union", 5))
1478 if (STREQN (tokstart, "short", 5))
1480 if (STREQN (tokstart, "const", 5))
1481 return CONST_KEYWORD;
1484 if (STREQN (tokstart, "enum", 4))
1486 if (STREQN (tokstart, "long", 4))
1488 if (current_language->la_language == language_cplus
1489 && STREQN (tokstart, "this", 4))
1491 static const char this_name[] =
1492 { CPLUS_MARKER, 't', 'h', 'i', 's', '\0' };
1494 if (lookup_symbol (this_name, expression_context_block,
1495 VAR_NAMESPACE, (int *) NULL,
1496 (struct symtab **) NULL))
1501 if (STREQN (tokstart, "int", 3))
1508 yylval.sval.ptr = tokstart;
1509 yylval.sval.length = namelen;
1511 /* Any other names starting in $ are debugger internal variables. */
1513 if (*tokstart == '$')
1515 yylval.ivar = lookup_internalvar (copy_name (yylval.sval) + 1);
1519 /* Use token-type BLOCKNAME for symbols that happen to be defined as
1520 functions or symtabs. If this is not so, then ...
1521 Use token-type TYPENAME for symbols that happen to be defined
1522 currently as names of types; NAME for other symbols.
1523 The caller is not constrained to care about the distinction. */
1525 char *tmp = copy_name (yylval.sval);
1527 int is_a_field_of_this = 0;
1530 sym = lookup_symbol (tmp, expression_context_block,
1532 current_language->la_language == language_cplus
1533 ? &is_a_field_of_this : (int *) NULL,
1534 (struct symtab **) NULL);
1535 if ((sym && SYMBOL_CLASS (sym) == LOC_BLOCK) ||
1536 lookup_partial_symtab (tmp))
1538 yylval.ssym.sym = sym;
1539 yylval.ssym.is_a_field_of_this = is_a_field_of_this;
1542 if (sym && SYMBOL_CLASS (sym) == LOC_TYPEDEF)
1546 struct symbol *best_sym;
1548 /* Look ahead to detect nested types. This probably should be
1549 done in the grammar, but trying seemed to introduce a lot
1550 of shift/reduce and reduce/reduce conflicts. It's possible
1551 that it could be done, though. Or perhaps a non-grammar, but
1552 less ad hoc, approach would work well. */
1554 /* Since we do not currently have any way of distinguishing
1555 a nested type from a non-nested one (the stabs don't tell
1556 us whether a type is nested), we just ignore the
1563 /* Skip whitespace. */
1564 while (*p == ' ' || *p == '\t' || *p == '\n')
1566 if (*p == ':' && p[1] == ':')
1568 /* Skip the `::'. */
1570 /* Skip whitespace. */
1571 while (*p == ' ' || *p == '\t' || *p == '\n')
1574 while (*p == '_' || *p == '$' || (*p >= '0' && *p <= '9')
1575 || (*p >= 'a' && *p <= 'z')
1576 || (*p >= 'A' && *p <= 'Z'))
1580 struct symbol *cur_sym;
1581 /* As big as the whole rest of the expression, which is
1582 at least big enough. */
1583 char *tmp = alloca (strlen (namestart));
1585 memcpy (tmp, namestart, p - namestart);
1586 tmp[p - namestart] = '\0';
1587 cur_sym = lookup_symbol (tmp, expression_context_block,
1588 VAR_NAMESPACE, (int *) NULL,
1589 (struct symtab **) NULL);
1592 if (SYMBOL_CLASS (cur_sym) == LOC_TYPEDEF)
1610 yylval.tsym.type = SYMBOL_TYPE (best_sym);
1613 if ((yylval.tsym.type = lookup_primitive_typename (tmp)) != 0)
1616 /* Input names that aren't symbols but ARE valid hex numbers,
1617 when the input radix permits them, can be names or numbers
1618 depending on the parse. Note we support radixes > 16 here. */
1620 ((tokstart[0] >= 'a' && tokstart[0] < 'a' + input_radix - 10) ||
1621 (tokstart[0] >= 'A' && tokstart[0] < 'A' + input_radix - 10)))
1623 YYSTYPE newlval; /* Its value is ignored. */
1624 hextype = parse_number (tokstart, namelen, 0, &newlval);
1627 yylval.ssym.sym = sym;
1628 yylval.ssym.is_a_field_of_this = is_a_field_of_this;
1633 /* Any other kind of symbol */
1634 yylval.ssym.sym = sym;
1635 yylval.ssym.is_a_field_of_this = is_a_field_of_this;
1644 error (msg ? msg : "Invalid syntax in expression.");