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_long);
637 write_exp_elt_longcst ((LONGEST) SYMBOL_VALUE_ADDRESS (msymbol));
638 write_exp_elt_opcode (OP_LONG);
639 write_exp_elt_opcode (UNOP_MEMVAL);
640 if (msymbol -> type == mst_data ||
641 msymbol -> type == mst_bss)
642 write_exp_elt_type (builtin_type_int);
643 else if (msymbol -> type == mst_text)
644 write_exp_elt_type (lookup_function_type (builtin_type_int));
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 if (symbol_read_needs_frame (sym))
664 if (innermost_block == 0 ||
665 contained_in (block_found,
667 innermost_block = block_found;
670 write_exp_elt_opcode (OP_VAR_VALUE);
671 /* We want to use the selected frame, not
672 another more inner frame which happens to
673 be in the same block. */
674 write_exp_elt_block (NULL);
675 write_exp_elt_sym (sym);
676 write_exp_elt_opcode (OP_VAR_VALUE);
678 else if ($1.is_a_field_of_this)
680 /* C++: it hangs off of `this'. Must
681 not inadvertently convert from a method call
683 if (innermost_block == 0 ||
684 contained_in (block_found, innermost_block))
685 innermost_block = block_found;
686 write_exp_elt_opcode (OP_THIS);
687 write_exp_elt_opcode (OP_THIS);
688 write_exp_elt_opcode (STRUCTOP_PTR);
689 write_exp_string ($1.stoken);
690 write_exp_elt_opcode (STRUCTOP_PTR);
694 struct minimal_symbol *msymbol;
695 register char *arg = copy_name ($1.stoken);
697 msymbol = lookup_minimal_symbol (arg,
698 (struct objfile *) NULL);
701 write_exp_elt_opcode (OP_LONG);
702 write_exp_elt_type (builtin_type_long);
703 write_exp_elt_longcst ((LONGEST) SYMBOL_VALUE_ADDRESS (msymbol));
704 write_exp_elt_opcode (OP_LONG);
705 write_exp_elt_opcode (UNOP_MEMVAL);
706 if (msymbol -> type == mst_data ||
707 msymbol -> type == mst_bss)
708 write_exp_elt_type (builtin_type_int);
709 else if (msymbol -> type == mst_text)
710 write_exp_elt_type (lookup_function_type (builtin_type_int));
712 write_exp_elt_type (builtin_type_char);
713 write_exp_elt_opcode (UNOP_MEMVAL);
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));
725 /* shift/reduce conflict: "typebase ." and the token is '('. (Shows up
726 twice, once where qualified_name is a possibility and once where
728 /* shift/reduce conflict: "typebase CONST_KEYWORD ." and the token is '('. */
729 /* shift/reduce conflict: "typebase VOLATILE_KEYWORD ." and the token is
732 /* "const" and "volatile" are curently ignored. A type qualifier
733 before the type is currently handled in the typebase rule. */
734 | typebase CONST_KEYWORD
735 | typebase VOLATILE_KEYWORD
737 { $$ = follow_types ($1); }
738 | typebase CONST_KEYWORD abs_decl
739 { $$ = follow_types ($1); }
740 | typebase VOLATILE_KEYWORD abs_decl
741 { $$ = follow_types ($1); }
745 { push_type (tp_pointer); $$ = 0; }
747 { push_type (tp_pointer); $$ = $2; }
749 { push_type (tp_reference); $$ = 0; }
751 { push_type (tp_reference); $$ = $2; }
755 direct_abs_decl: '(' abs_decl ')'
757 | direct_abs_decl array_mod
760 push_type (tp_array);
765 push_type (tp_array);
769 /* shift/reduce conflict. "direct_abs_decl . func_mod", and the token
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 /* shift/reduce conflict: "type '(' typebase COLONCOLON '*' ')' ." and the
793 | typebase COLONCOLON '*'
794 { $$ = lookup_member_type (builtin_type_int, $1); }
795 | type '(' typebase COLONCOLON '*' ')'
796 { $$ = lookup_member_type ($1, $3); }
797 | type '(' typebase COLONCOLON '*' ')' '(' ')'
798 { $$ = lookup_member_type
799 (lookup_function_type ($1), $3); }
800 | type '(' typebase COLONCOLON '*' ')' '(' nonempty_typelist ')'
801 { $$ = lookup_member_type
802 (lookup_function_type ($1), $3);
806 typebase /* Implements (approximately): (type-qualifier)* type-specifier */
810 { $$ = builtin_type_int; }
812 { $$ = builtin_type_long; }
814 { $$ = builtin_type_short; }
816 { $$ = builtin_type_long; }
817 | UNSIGNED LONG INT_KEYWORD
818 { $$ = builtin_type_unsigned_long; }
820 { $$ = builtin_type_long_long; }
821 | LONG LONG INT_KEYWORD
822 { $$ = builtin_type_long_long; }
824 { $$ = builtin_type_unsigned_long_long; }
825 | UNSIGNED LONG LONG INT_KEYWORD
826 { $$ = builtin_type_unsigned_long_long; }
828 { $$ = builtin_type_short; }
829 | UNSIGNED SHORT INT_KEYWORD
830 { $$ = builtin_type_unsigned_short; }
832 { $$ = lookup_struct (copy_name ($2),
833 expression_context_block); }
835 { $$ = lookup_struct (copy_name ($2),
836 expression_context_block); }
838 { $$ = lookup_union (copy_name ($2),
839 expression_context_block); }
841 { $$ = lookup_enum (copy_name ($2),
842 expression_context_block); }
844 { $$ = lookup_unsigned_typename (TYPE_NAME($2.type)); }
846 { $$ = builtin_type_unsigned_int; }
847 | SIGNED_KEYWORD typename
848 { $$ = lookup_signed_typename (TYPE_NAME($2.type)); }
850 { $$ = builtin_type_int; }
851 | TEMPLATE name '<' type '>'
852 { $$ = lookup_template_type(copy_name($2), $4,
853 expression_context_block);
855 /* "const" and "volatile" are curently ignored. A type qualifier
856 after the type is handled in the ptype rule. I think these could
858 | CONST_KEYWORD typebase { $$ = $2; }
859 | VOLATILE_KEYWORD typebase { $$ = $2; }
865 $$.stoken.ptr = "int";
866 $$.stoken.length = 3;
867 $$.type = builtin_type_int;
871 $$.stoken.ptr = "long";
872 $$.stoken.length = 4;
873 $$.type = builtin_type_long;
877 $$.stoken.ptr = "short";
878 $$.stoken.length = 5;
879 $$.type = builtin_type_short;
885 { $$ = (struct type **) malloc (sizeof (struct type *) * 2);
886 $<ivec>$[0] = 1; /* Number of types in vector */
889 | nonempty_typelist ',' type
890 { int len = sizeof (struct type *) * (++($<ivec>1[0]) + 1);
891 $$ = (struct type **) realloc ((char *) $1, len);
892 $$[$<ivec>$[0]] = $3;
896 name : NAME { $$ = $1.stoken; }
897 | BLOCKNAME { $$ = $1.stoken; }
898 | TYPENAME { $$ = $1.stoken; }
899 | NAME_OR_INT { $$ = $1.stoken; }
902 name_not_typename : NAME
904 /* These would be useful if name_not_typename was useful, but it is just
905 a fake for "variable", so these cause reduce/reduce conflicts because
906 the parser can't tell whether NAME_OR_INT is a name_not_typename (=variable,
907 =exp) or just an exp. If name_not_typename was ever used in an lvalue
908 context where only a name could occur, this might be useful.
915 /* Take care of parsing a number (anything that starts with a digit).
916 Set yylval and return the token type; update lexptr.
917 LEN is the number of characters in it. */
919 /*** Needs some error checking for the float case ***/
922 parse_number (p, len, parsed_float, putithere)
928 register LONGEST n = 0;
929 register LONGEST prevn = 0;
932 register int base = input_radix;
935 unsigned LONGEST high_bit;
936 struct type *signed_type;
937 struct type *unsigned_type;
941 /* It's a float since it contains a point or an exponent. */
942 putithere->dval = atof (p);
946 /* Handle base-switching prefixes 0x, 0t, 0d, 0 */
980 if (c >= 'A' && c <= 'Z')
982 if (c != 'l' && c != 'u')
984 if (c >= '0' && c <= '9')
988 if (base > 10 && c >= 'a' && c <= 'f')
989 n += i = c - 'a' + 10;
990 else if (len == 0 && c == 'l')
992 else if (len == 0 && c == 'u')
995 return ERROR; /* Char not a digit */
998 return ERROR; /* Invalid digit in this base */
1000 /* Portably test for overflow (only works for nonzero values, so make
1001 a second check for zero). */
1002 if((prevn >= n) && n != 0)
1003 unsigned_p=1; /* Try something unsigned */
1004 /* If range checking enabled, portably test for unsigned overflow. */
1005 if(RANGE_CHECK && n!=0)
1007 if((unsigned_p && (unsigned)prevn >= (unsigned)n))
1008 range_error("Overflow on numeric constant.");
1013 /* If the number is too big to be an int, or it's got an l suffix
1014 then it's a long. Work out if this has to be a long by
1015 shifting right and and seeing if anything remains, and the
1016 target int size is different to the target long size.
1018 In the expression below, we could have tested
1019 (n >> TARGET_INT_BIT)
1020 to see if it was zero,
1021 but too many compilers warn about that, when ints and longs
1022 are the same size. So we shift it twice, with fewer bits
1023 each time, for the same result. */
1025 if ( (TARGET_INT_BIT != TARGET_LONG_BIT
1026 && ((n >> 2) >> (TARGET_INT_BIT-2))) /* Avoid shift warning */
1029 high_bit = ((unsigned LONGEST)1) << (TARGET_LONG_BIT-1);
1030 unsigned_type = builtin_type_unsigned_long;
1031 signed_type = builtin_type_long;
1035 high_bit = ((unsigned LONGEST)1) << (TARGET_INT_BIT-1);
1036 unsigned_type = builtin_type_unsigned_int;
1037 signed_type = builtin_type_int;
1040 putithere->typed_val.val = n;
1042 /* If the high bit of the worked out type is set then this number
1043 has to be unsigned. */
1045 if (unsigned_p || (n & high_bit))
1047 putithere->typed_val.type = unsigned_type;
1051 putithere->typed_val.type = signed_type;
1061 enum exp_opcode opcode;
1064 static const struct token tokentab3[] =
1066 {">>=", ASSIGN_MODIFY, BINOP_RSH},
1067 {"<<=", ASSIGN_MODIFY, BINOP_LSH}
1070 static const struct token tokentab2[] =
1072 {"+=", ASSIGN_MODIFY, BINOP_ADD},
1073 {"-=", ASSIGN_MODIFY, BINOP_SUB},
1074 {"*=", ASSIGN_MODIFY, BINOP_MUL},
1075 {"/=", ASSIGN_MODIFY, BINOP_DIV},
1076 {"%=", ASSIGN_MODIFY, BINOP_REM},
1077 {"|=", ASSIGN_MODIFY, BINOP_BITWISE_IOR},
1078 {"&=", ASSIGN_MODIFY, BINOP_BITWISE_AND},
1079 {"^=", ASSIGN_MODIFY, BINOP_BITWISE_XOR},
1080 {"++", INCREMENT, BINOP_END},
1081 {"--", DECREMENT, BINOP_END},
1082 {"->", ARROW, BINOP_END},
1083 {"&&", ANDAND, BINOP_END},
1084 {"||", OROR, BINOP_END},
1085 {"::", COLONCOLON, BINOP_END},
1086 {"<<", LSH, BINOP_END},
1087 {">>", RSH, BINOP_END},
1088 {"==", EQUAL, BINOP_END},
1089 {"!=", NOTEQUAL, BINOP_END},
1090 {"<=", LEQ, BINOP_END},
1091 {">=", GEQ, BINOP_END}
1094 /* Read one token, getting characters through lexptr. */
1105 static char *tempbuf;
1106 static int tempbufsize;
1111 /* See if it is a special token of length 3. */
1112 for (i = 0; i < sizeof tokentab3 / sizeof tokentab3[0]; i++)
1113 if (STREQN (tokstart, tokentab3[i].operator, 3))
1116 yylval.opcode = tokentab3[i].opcode;
1117 return tokentab3[i].token;
1120 /* See if it is a special token of length 2. */
1121 for (i = 0; i < sizeof tokentab2 / sizeof tokentab2[0]; i++)
1122 if (STREQN (tokstart, tokentab2[i].operator, 2))
1125 yylval.opcode = tokentab2[i].opcode;
1126 return tokentab2[i].token;
1129 switch (c = *tokstart)
1141 /* We either have a character constant ('0' or '\177' for example)
1142 or we have a quoted symbol reference ('foo(int,int)' in C++
1147 c = parse_escape (&lexptr);
1149 yylval.typed_val.val = c;
1150 yylval.typed_val.type = builtin_type_char;
1155 namelen = skip_quoted (tokstart) - tokstart;
1158 lexptr = tokstart + namelen;
1159 if (lexptr[-1] != '\'')
1160 error ("Unmatched single quote.");
1165 error ("Invalid character constant.");
1175 if (paren_depth == 0)
1182 if (comma_terminates && paren_depth == 0)
1188 /* Might be a floating point number. */
1189 if (lexptr[1] < '0' || lexptr[1] > '9')
1190 goto symbol; /* Nope, must be a symbol. */
1191 /* FALL THRU into number case. */
1204 /* It's a number. */
1205 int got_dot = 0, got_e = 0, toktype;
1206 register char *p = tokstart;
1207 int hex = input_radix > 10;
1209 if (c == '0' && (p[1] == 'x' || p[1] == 'X'))
1214 else if (c == '0' && (p[1]=='t' || p[1]=='T' || p[1]=='d' || p[1]=='D'))
1222 /* This test includes !hex because 'e' is a valid hex digit
1223 and thus does not indicate a floating point number when
1224 the radix is hex. */
1225 if (!hex && !got_e && (*p == 'e' || *p == 'E'))
1226 got_dot = got_e = 1;
1227 /* This test does not include !hex, because a '.' always indicates
1228 a decimal floating point number regardless of the radix. */
1229 else if (!got_dot && *p == '.')
1231 else if (got_e && (p[-1] == 'e' || p[-1] == 'E')
1232 && (*p == '-' || *p == '+'))
1233 /* This is the sign of the exponent, not the end of the
1236 /* We will take any letters or digits. parse_number will
1237 complain if past the radix, or if L or U are not final. */
1238 else if ((*p < '0' || *p > '9')
1239 && ((*p < 'a' || *p > 'z')
1240 && (*p < 'A' || *p > 'Z')))
1243 toktype = parse_number (tokstart, p - tokstart, got_dot|got_e, &yylval);
1244 if (toktype == ERROR)
1246 char *err_copy = (char *) alloca (p - tokstart + 1);
1248 memcpy (err_copy, tokstart, p - tokstart);
1249 err_copy[p - tokstart] = 0;
1250 error ("Invalid number \"%s\".", err_copy);
1282 /* Build the gdb internal form of the input string in tempbuf,
1283 translating any standard C escape forms seen. Note that the
1284 buffer is null byte terminated *only* for the convenience of
1285 debugging gdb itself and printing the buffer contents when
1286 the buffer contains no embedded nulls. Gdb does not depend
1287 upon the buffer being null byte terminated, it uses the length
1288 string instead. This allows gdb to handle C strings (as well
1289 as strings in other languages) with embedded null bytes */
1291 tokptr = ++tokstart;
1295 /* Grow the static temp buffer if necessary, including allocating
1296 the first one on demand. */
1297 if (tempbufindex + 1 >= tempbufsize)
1299 tempbuf = (char *) realloc (tempbuf, tempbufsize += 64);
1305 /* Do nothing, loop will terminate. */
1309 c = parse_escape (&tokptr);
1314 tempbuf[tempbufindex++] = c;
1317 tempbuf[tempbufindex++] = *tokptr++;
1320 } while ((*tokptr != '"') && (*tokptr != '\0'));
1321 if (*tokptr++ != '"')
1323 error ("Unterminated string in expression.");
1325 tempbuf[tempbufindex] = '\0'; /* See note above */
1326 yylval.sval.ptr = tempbuf;
1327 yylval.sval.length = tempbufindex;
1332 if (!(c == '_' || c == '$'
1333 || (c >= 'a' && c <= 'z') || (c >= 'A' && c <= 'Z')))
1334 /* We must have come across a bad character (e.g. ';'). */
1335 error ("Invalid character '%c' in expression.", c);
1337 /* It's a name. See how long it is. */
1339 for (c = tokstart[namelen];
1340 (c == '_' || c == '$' || (c >= '0' && c <= '9')
1341 || (c >= 'a' && c <= 'z') || (c >= 'A' && c <= 'Z'));
1342 c = tokstart[++namelen])
1345 /* The token "if" terminates the expression and is NOT
1346 removed from the input stream. */
1347 if (namelen == 2 && tokstart[0] == 'i' && tokstart[1] == 'f')
1354 /* Handle the tokens $digits; also $ (short for $0) and $$ (short for $$1)
1355 and $$digits (equivalent to $<-digits> if you could type that).
1356 Make token type LAST, and put the number (the digits) in yylval. */
1359 if (*tokstart == '$')
1361 register int negate = 0;
1363 /* Double dollar means negate the number and add -1 as well.
1364 Thus $$ alone means -1. */
1365 if (namelen >= 2 && tokstart[1] == '$')
1372 /* Just dollars (one or two) */
1373 yylval.lval = - negate;
1376 /* Is the rest of the token digits? */
1377 for (; c < namelen; c++)
1378 if (!(tokstart[c] >= '0' && tokstart[c] <= '9'))
1382 yylval.lval = atoi (tokstart + 1 + negate);
1384 yylval.lval = - yylval.lval;
1389 /* Handle tokens that refer to machine registers:
1390 $ followed by a register name. */
1392 if (*tokstart == '$') {
1393 for (c = 0; c < NUM_REGS; c++)
1394 if (namelen - 1 == strlen (reg_names[c])
1395 && STREQN (tokstart + 1, reg_names[c], namelen - 1))
1400 for (c = 0; c < num_std_regs; c++)
1401 if (namelen - 1 == strlen (std_regs[c].name)
1402 && STREQN (tokstart + 1, std_regs[c].name, namelen - 1))
1404 yylval.lval = std_regs[c].regnum;
1408 /* Catch specific keywords. Should be done with a data structure. */
1412 if (STREQN (tokstart, "unsigned", 8))
1414 if (current_language->la_language == language_cplus
1415 && STREQN (tokstart, "template", 8))
1417 if (STREQN (tokstart, "volatile", 8))
1418 return VOLATILE_KEYWORD;
1421 if (STREQN (tokstart, "struct", 6))
1423 if (STREQN (tokstart, "signed", 6))
1424 return SIGNED_KEYWORD;
1425 if (STREQN (tokstart, "sizeof", 6))
1429 if (current_language->la_language == language_cplus
1430 && STREQN (tokstart, "class", 5))
1432 if (STREQN (tokstart, "union", 5))
1434 if (STREQN (tokstart, "short", 5))
1436 if (STREQN (tokstart, "const", 5))
1437 return CONST_KEYWORD;
1440 if (STREQN (tokstart, "enum", 4))
1442 if (STREQN (tokstart, "long", 4))
1444 if (current_language->la_language == language_cplus
1445 && STREQN (tokstart, "this", 4))
1447 static const char this_name[] =
1448 { CPLUS_MARKER, 't', 'h', 'i', 's', '\0' };
1450 if (lookup_symbol (this_name, expression_context_block,
1451 VAR_NAMESPACE, (int *) NULL,
1452 (struct symtab **) NULL))
1457 if (STREQN (tokstart, "int", 3))
1464 yylval.sval.ptr = tokstart;
1465 yylval.sval.length = namelen;
1467 /* Any other names starting in $ are debugger internal variables. */
1469 if (*tokstart == '$')
1471 yylval.ivar = lookup_internalvar (copy_name (yylval.sval) + 1);
1475 /* Use token-type BLOCKNAME for symbols that happen to be defined as
1476 functions or symtabs. If this is not so, then ...
1477 Use token-type TYPENAME for symbols that happen to be defined
1478 currently as names of types; NAME for other symbols.
1479 The caller is not constrained to care about the distinction. */
1481 char *tmp = copy_name (yylval.sval);
1483 int is_a_field_of_this = 0;
1486 sym = lookup_symbol (tmp, expression_context_block,
1488 current_language->la_language == language_cplus
1489 ? &is_a_field_of_this : (int *) NULL,
1490 (struct symtab **) NULL);
1491 if ((sym && SYMBOL_CLASS (sym) == LOC_BLOCK) ||
1492 lookup_partial_symtab (tmp))
1494 yylval.ssym.sym = sym;
1495 yylval.ssym.is_a_field_of_this = is_a_field_of_this;
1498 if (sym && SYMBOL_CLASS (sym) == LOC_TYPEDEF)
1502 struct symbol *best_sym;
1504 /* Look ahead to detect nested types. This probably should be
1505 done in the grammar, but trying seemed to introduce a lot
1506 of shift/reduce and reduce/reduce conflicts. It's possible
1507 that it could be done, though. Or perhaps a non-grammar, but
1508 less ad hoc, approach would work well. */
1510 /* Since we do not currently have any way of distinguishing
1511 a nested type from a non-nested one (the stabs don't tell
1512 us whether a type is nested), we just ignore the
1519 /* Skip whitespace. */
1520 while (*p == ' ' || *p == '\t' || *p == '\n')
1522 if (*p == ':' && p[1] == ':')
1524 /* Skip the `::'. */
1526 /* Skip whitespace. */
1527 while (*p == ' ' || *p == '\t' || *p == '\n')
1530 while (*p == '_' || *p == '$' || (*p >= '0' && *p <= '9')
1531 || (*p >= 'a' && *p <= 'z')
1532 || (*p >= 'A' && *p <= 'Z'))
1536 struct symbol *cur_sym;
1537 /* As big as the whole rest of the expression, which is
1538 at least big enough. */
1539 char *tmp = alloca (strlen (namestart));
1541 memcpy (tmp, namestart, p - namestart);
1542 tmp[p - namestart] = '\0';
1543 cur_sym = lookup_symbol (tmp, expression_context_block,
1544 VAR_NAMESPACE, (int *) NULL,
1545 (struct symtab **) NULL);
1548 if (SYMBOL_CLASS (cur_sym) == LOC_TYPEDEF)
1566 yylval.tsym.type = SYMBOL_TYPE (best_sym);
1569 if ((yylval.tsym.type = lookup_primitive_typename (tmp)) != 0)
1572 /* Input names that aren't symbols but ARE valid hex numbers,
1573 when the input radix permits them, can be names or numbers
1574 depending on the parse. Note we support radixes > 16 here. */
1576 ((tokstart[0] >= 'a' && tokstart[0] < 'a' + input_radix - 10) ||
1577 (tokstart[0] >= 'A' && tokstart[0] < 'A' + input_radix - 10)))
1579 YYSTYPE newlval; /* Its value is ignored. */
1580 hextype = parse_number (tokstart, namelen, 0, &newlval);
1583 yylval.ssym.sym = sym;
1584 yylval.ssym.is_a_field_of_this = is_a_field_of_this;
1589 /* Any other kind of symbol */
1590 yylval.ssym.sym = sym;
1591 yylval.ssym.is_a_field_of_this = is_a_field_of_this;
1600 error (msg ? msg : "Invalid syntax in expression.");