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 write_exp_elt_sym (sym);
568 write_exp_elt_opcode (OP_VAR_VALUE); }
571 qualified_name: typebase COLONCOLON name
573 struct type *type = $1;
574 if (TYPE_CODE (type) != TYPE_CODE_STRUCT
575 && TYPE_CODE (type) != TYPE_CODE_UNION)
576 error ("`%s' is not defined as an aggregate type.",
579 write_exp_elt_opcode (OP_SCOPE);
580 write_exp_elt_type (type);
581 write_exp_string ($3);
582 write_exp_elt_opcode (OP_SCOPE);
584 | typebase COLONCOLON '~' name
586 struct type *type = $1;
587 struct stoken tmp_token;
588 if (TYPE_CODE (type) != TYPE_CODE_STRUCT
589 && TYPE_CODE (type) != TYPE_CODE_UNION)
590 error ("`%s' is not defined as an aggregate type.",
593 if (!STREQ (type_name_no_tag (type), $4.ptr))
594 error ("invalid destructor `%s::~%s'",
595 type_name_no_tag (type), $4.ptr);
597 tmp_token.ptr = (char*) alloca ($4.length + 2);
598 tmp_token.length = $4.length + 1;
599 tmp_token.ptr[0] = '~';
600 memcpy (tmp_token.ptr+1, $4.ptr, $4.length);
601 tmp_token.ptr[tmp_token.length] = 0;
602 write_exp_elt_opcode (OP_SCOPE);
603 write_exp_elt_type (type);
604 write_exp_string (tmp_token);
605 write_exp_elt_opcode (OP_SCOPE);
609 variable: qualified_name
612 char *name = copy_name ($2);
614 struct minimal_symbol *msymbol;
617 lookup_symbol (name, (const struct block *) NULL,
618 VAR_NAMESPACE, (int *) NULL,
619 (struct symtab **) NULL);
622 write_exp_elt_opcode (OP_VAR_VALUE);
623 write_exp_elt_sym (sym);
624 write_exp_elt_opcode (OP_VAR_VALUE);
628 msymbol = lookup_minimal_symbol (name,
629 (struct objfile *) NULL);
632 write_exp_elt_opcode (OP_LONG);
633 write_exp_elt_type (builtin_type_int);
634 write_exp_elt_longcst ((LONGEST) SYMBOL_VALUE_ADDRESS (msymbol));
635 write_exp_elt_opcode (OP_LONG);
636 write_exp_elt_opcode (UNOP_MEMVAL);
637 if (msymbol -> type == mst_data ||
638 msymbol -> type == mst_bss)
639 write_exp_elt_type (builtin_type_int);
640 else if (msymbol -> type == mst_text)
641 write_exp_elt_type (lookup_function_type (builtin_type_int));
643 write_exp_elt_type (builtin_type_char);
644 write_exp_elt_opcode (UNOP_MEMVAL);
647 if (!have_full_symbols () && !have_partial_symbols ())
648 error ("No symbol table is loaded. Use the \"file\" command.");
650 error ("No symbol \"%s\" in current context.", name);
654 variable: name_not_typename
655 { struct symbol *sym = $1.sym;
659 switch (SYMBOL_CLASS (sym))
667 if (innermost_block == 0 ||
668 contained_in (block_found,
670 innermost_block = block_found;
677 case LOC_CONST_BYTES:
678 case LOC_OPTIMIZED_OUT:
680 /* In this case the expression can
681 be evaluated regardless of what
682 frame we are in, so there is no
683 need to check for the
684 innermost_block. These cases are
685 listed so that gcc -Wall will
686 report types that may not have
691 write_exp_elt_opcode (OP_VAR_VALUE);
692 write_exp_elt_sym (sym);
693 write_exp_elt_opcode (OP_VAR_VALUE);
695 else if ($1.is_a_field_of_this)
697 /* C++: it hangs off of `this'. Must
698 not inadvertently convert from a method call
700 if (innermost_block == 0 ||
701 contained_in (block_found, innermost_block))
702 innermost_block = block_found;
703 write_exp_elt_opcode (OP_THIS);
704 write_exp_elt_opcode (OP_THIS);
705 write_exp_elt_opcode (STRUCTOP_PTR);
706 write_exp_string ($1.stoken);
707 write_exp_elt_opcode (STRUCTOP_PTR);
711 struct minimal_symbol *msymbol;
712 register char *arg = copy_name ($1.stoken);
714 msymbol = lookup_minimal_symbol (arg,
715 (struct objfile *) NULL);
718 write_exp_elt_opcode (OP_LONG);
719 write_exp_elt_type (builtin_type_int);
720 write_exp_elt_longcst ((LONGEST) SYMBOL_VALUE_ADDRESS (msymbol));
721 write_exp_elt_opcode (OP_LONG);
722 write_exp_elt_opcode (UNOP_MEMVAL);
723 if (msymbol -> type == mst_data ||
724 msymbol -> type == mst_bss)
725 write_exp_elt_type (builtin_type_int);
726 else if (msymbol -> type == mst_text)
727 write_exp_elt_type (lookup_function_type (builtin_type_int));
729 write_exp_elt_type (builtin_type_char);
730 write_exp_elt_opcode (UNOP_MEMVAL);
732 else if (!have_full_symbols () && !have_partial_symbols ())
733 error ("No symbol table is loaded. Use the \"file\" command.");
735 error ("No symbol \"%s\" in current context.",
736 copy_name ($1.stoken));
745 /* This is where the interesting stuff happens. */
748 struct type *follow_type = $1;
749 struct type *range_type;
758 follow_type = lookup_pointer_type (follow_type);
761 follow_type = lookup_reference_type (follow_type);
764 array_size = pop_type_int ();
765 if (array_size != -1)
768 create_range_type ((struct type *) NULL,
772 create_array_type ((struct type *) NULL,
773 follow_type, range_type);
776 follow_type = lookup_pointer_type (follow_type);
779 follow_type = lookup_function_type (follow_type);
787 { push_type (tp_pointer); $$ = 0; }
789 { push_type (tp_pointer); $$ = $2; }
791 { push_type (tp_reference); $$ = 0; }
793 { push_type (tp_reference); $$ = $2; }
797 direct_abs_decl: '(' abs_decl ')'
799 | direct_abs_decl array_mod
802 push_type (tp_array);
807 push_type (tp_array);
810 | direct_abs_decl func_mod
811 { push_type (tp_function); }
813 { push_type (tp_function); }
824 | '(' nonempty_typelist ')'
825 { free ((PTR)$2); $$ = 0; }
829 | typebase COLONCOLON '*'
830 { $$ = lookup_member_type (builtin_type_int, $1); }
831 | type '(' typebase COLONCOLON '*' ')'
832 { $$ = lookup_member_type ($1, $3); }
833 | type '(' typebase COLONCOLON '*' ')' '(' ')'
834 { $$ = lookup_member_type
835 (lookup_function_type ($1), $3); }
836 | type '(' typebase COLONCOLON '*' ')' '(' nonempty_typelist ')'
837 { $$ = lookup_member_type
838 (lookup_function_type ($1), $3);
842 typebase /* Implements (approximately): (type-qualifier)* type-specifier */
846 { $$ = builtin_type_int; }
848 { $$ = builtin_type_long; }
850 { $$ = builtin_type_short; }
852 { $$ = builtin_type_long; }
853 | UNSIGNED LONG INT_KEYWORD
854 { $$ = builtin_type_unsigned_long; }
856 { $$ = builtin_type_long_long; }
857 | LONG LONG INT_KEYWORD
858 { $$ = builtin_type_long_long; }
860 { $$ = builtin_type_unsigned_long_long; }
861 | UNSIGNED LONG LONG INT_KEYWORD
862 { $$ = builtin_type_unsigned_long_long; }
864 { $$ = builtin_type_short; }
865 | UNSIGNED SHORT INT_KEYWORD
866 { $$ = builtin_type_unsigned_short; }
868 { $$ = lookup_struct (copy_name ($2),
869 expression_context_block); }
871 { $$ = lookup_struct (copy_name ($2),
872 expression_context_block); }
874 { $$ = lookup_union (copy_name ($2),
875 expression_context_block); }
877 { $$ = lookup_enum (copy_name ($2),
878 expression_context_block); }
880 { $$ = lookup_unsigned_typename (TYPE_NAME($2.type)); }
882 { $$ = builtin_type_unsigned_int; }
883 | SIGNED_KEYWORD typename
884 { $$ = lookup_signed_typename (TYPE_NAME($2.type)); }
886 { $$ = builtin_type_int; }
887 | TEMPLATE name '<' type '>'
888 { $$ = lookup_template_type(copy_name($2), $4,
889 expression_context_block);
891 /* "const" and "volatile" are curently ignored. */
892 | CONST_KEYWORD typebase { $$ = $2; }
893 | VOLATILE_KEYWORD typebase { $$ = $2; }
899 $$.stoken.ptr = "int";
900 $$.stoken.length = 3;
901 $$.type = builtin_type_int;
905 $$.stoken.ptr = "long";
906 $$.stoken.length = 4;
907 $$.type = builtin_type_long;
911 $$.stoken.ptr = "short";
912 $$.stoken.length = 5;
913 $$.type = builtin_type_short;
919 { $$ = (struct type **) malloc (sizeof (struct type *) * 2);
920 $<ivec>$[0] = 1; /* Number of types in vector */
923 | nonempty_typelist ',' type
924 { int len = sizeof (struct type *) * (++($<ivec>1[0]) + 1);
925 $$ = (struct type **) realloc ((char *) $1, len);
926 $$[$<ivec>$[0]] = $3;
930 name : NAME { $$ = $1.stoken; }
931 | BLOCKNAME { $$ = $1.stoken; }
932 | TYPENAME { $$ = $1.stoken; }
933 | NAME_OR_INT { $$ = $1.stoken; }
936 name_not_typename : NAME
938 /* These would be useful if name_not_typename was useful, but it is just
939 a fake for "variable", so these cause reduce/reduce conflicts because
940 the parser can't tell whether NAME_OR_INT is a name_not_typename (=variable,
941 =exp) or just an exp. If name_not_typename was ever used in an lvalue
942 context where only a name could occur, this might be useful.
949 /* Take care of parsing a number (anything that starts with a digit).
950 Set yylval and return the token type; update lexptr.
951 LEN is the number of characters in it. */
953 /*** Needs some error checking for the float case ***/
956 parse_number (p, len, parsed_float, putithere)
962 register LONGEST n = 0;
963 register LONGEST prevn = 0;
966 register int base = input_radix;
969 unsigned LONGEST high_bit;
970 struct type *signed_type;
971 struct type *unsigned_type;
975 /* It's a float since it contains a point or an exponent. */
976 putithere->dval = atof (p);
980 /* Handle base-switching prefixes 0x, 0t, 0d, 0 */
1014 if (c >= 'A' && c <= 'Z')
1016 if (c != 'l' && c != 'u')
1018 if (c >= '0' && c <= '9')
1022 if (base > 10 && c >= 'a' && c <= 'f')
1023 n += i = c - 'a' + 10;
1024 else if (len == 0 && c == 'l')
1026 else if (len == 0 && c == 'u')
1029 return ERROR; /* Char not a digit */
1032 return ERROR; /* Invalid digit in this base */
1034 /* Portably test for overflow (only works for nonzero values, so make
1035 a second check for zero). */
1036 if((prevn >= n) && n != 0)
1037 unsigned_p=1; /* Try something unsigned */
1038 /* If range checking enabled, portably test for unsigned overflow. */
1039 if(RANGE_CHECK && n!=0)
1041 if((unsigned_p && (unsigned)prevn >= (unsigned)n))
1042 range_error("Overflow on numeric constant.");
1047 /* If the number is too big to be an int, or it's got an l suffix
1048 then it's a long. Work out if this has to be a long by
1049 shifting right and and seeing if anything remains, and the
1050 target int size is different to the target long size.
1052 In the expression below, we could have tested
1053 (n >> TARGET_INT_BIT)
1054 to see if it was zero,
1055 but too many compilers warn about that, when ints and longs
1056 are the same size. So we shift it twice, with fewer bits
1057 each time, for the same result. */
1059 if ( (TARGET_INT_BIT != TARGET_LONG_BIT
1060 && ((n >> 2) >> (TARGET_INT_BIT-2))) /* Avoid shift warning */
1063 high_bit = ((unsigned LONGEST)1) << (TARGET_LONG_BIT-1);
1064 unsigned_type = builtin_type_unsigned_long;
1065 signed_type = builtin_type_long;
1069 high_bit = ((unsigned LONGEST)1) << (TARGET_INT_BIT-1);
1070 unsigned_type = builtin_type_unsigned_int;
1071 signed_type = builtin_type_int;
1074 putithere->typed_val.val = n;
1076 /* If the high bit of the worked out type is set then this number
1077 has to be unsigned. */
1079 if (unsigned_p || (n & high_bit))
1081 putithere->typed_val.type = unsigned_type;
1085 putithere->typed_val.type = signed_type;
1095 enum exp_opcode opcode;
1098 static const struct token tokentab3[] =
1100 {">>=", ASSIGN_MODIFY, BINOP_RSH},
1101 {"<<=", ASSIGN_MODIFY, BINOP_LSH}
1104 static const struct token tokentab2[] =
1106 {"+=", ASSIGN_MODIFY, BINOP_ADD},
1107 {"-=", ASSIGN_MODIFY, BINOP_SUB},
1108 {"*=", ASSIGN_MODIFY, BINOP_MUL},
1109 {"/=", ASSIGN_MODIFY, BINOP_DIV},
1110 {"%=", ASSIGN_MODIFY, BINOP_REM},
1111 {"|=", ASSIGN_MODIFY, BINOP_BITWISE_IOR},
1112 {"&=", ASSIGN_MODIFY, BINOP_BITWISE_AND},
1113 {"^=", ASSIGN_MODIFY, BINOP_BITWISE_XOR},
1114 {"++", INCREMENT, BINOP_END},
1115 {"--", DECREMENT, BINOP_END},
1116 {"->", ARROW, BINOP_END},
1117 {"&&", ANDAND, BINOP_END},
1118 {"||", OROR, BINOP_END},
1119 {"::", COLONCOLON, BINOP_END},
1120 {"<<", LSH, BINOP_END},
1121 {">>", RSH, BINOP_END},
1122 {"==", EQUAL, BINOP_END},
1123 {"!=", NOTEQUAL, BINOP_END},
1124 {"<=", LEQ, BINOP_END},
1125 {">=", GEQ, BINOP_END}
1128 /* Read one token, getting characters through lexptr. */
1139 static char *tempbuf;
1140 static int tempbufsize;
1145 /* See if it is a special token of length 3. */
1146 for (i = 0; i < sizeof tokentab3 / sizeof tokentab3[0]; i++)
1147 if (STREQN (tokstart, tokentab3[i].operator, 3))
1150 yylval.opcode = tokentab3[i].opcode;
1151 return tokentab3[i].token;
1154 /* See if it is a special token of length 2. */
1155 for (i = 0; i < sizeof tokentab2 / sizeof tokentab2[0]; i++)
1156 if (STREQN (tokstart, tokentab2[i].operator, 2))
1159 yylval.opcode = tokentab2[i].opcode;
1160 return tokentab2[i].token;
1163 switch (c = *tokstart)
1175 /* We either have a character constant ('0' or '\177' for example)
1176 or we have a quoted symbol reference ('foo(int,int)' in C++
1181 c = parse_escape (&lexptr);
1183 yylval.typed_val.val = c;
1184 yylval.typed_val.type = builtin_type_char;
1189 namelen = skip_quoted (tokstart) - tokstart;
1192 lexptr = tokstart + namelen;
1193 if (lexptr[-1] != '\'')
1194 error ("Unmatched single quote.");
1199 error ("Invalid character constant.");
1209 if (paren_depth == 0)
1216 if (comma_terminates && paren_depth == 0)
1222 /* Might be a floating point number. */
1223 if (lexptr[1] < '0' || lexptr[1] > '9')
1224 goto symbol; /* Nope, must be a symbol. */
1225 /* FALL THRU into number case. */
1238 /* It's a number. */
1239 int got_dot = 0, got_e = 0, toktype;
1240 register char *p = tokstart;
1241 int hex = input_radix > 10;
1243 if (c == '0' && (p[1] == 'x' || p[1] == 'X'))
1248 else if (c == '0' && (p[1]=='t' || p[1]=='T' || p[1]=='d' || p[1]=='D'))
1256 /* This test includes !hex because 'e' is a valid hex digit
1257 and thus does not indicate a floating point number when
1258 the radix is hex. */
1259 if (!hex && !got_e && (*p == 'e' || *p == 'E'))
1260 got_dot = got_e = 1;
1261 /* This test does not include !hex, because a '.' always indicates
1262 a decimal floating point number regardless of the radix. */
1263 else if (!got_dot && *p == '.')
1265 else if (got_e && (p[-1] == 'e' || p[-1] == 'E')
1266 && (*p == '-' || *p == '+'))
1267 /* This is the sign of the exponent, not the end of the
1270 /* We will take any letters or digits. parse_number will
1271 complain if past the radix, or if L or U are not final. */
1272 else if ((*p < '0' || *p > '9')
1273 && ((*p < 'a' || *p > 'z')
1274 && (*p < 'A' || *p > 'Z')))
1277 toktype = parse_number (tokstart, p - tokstart, got_dot|got_e, &yylval);
1278 if (toktype == ERROR)
1280 char *err_copy = (char *) alloca (p - tokstart + 1);
1282 memcpy (err_copy, tokstart, p - tokstart);
1283 err_copy[p - tokstart] = 0;
1284 error ("Invalid number \"%s\".", err_copy);
1316 /* Build the gdb internal form of the input string in tempbuf,
1317 translating any standard C escape forms seen. Note that the
1318 buffer is null byte terminated *only* for the convenience of
1319 debugging gdb itself and printing the buffer contents when
1320 the buffer contains no embedded nulls. Gdb does not depend
1321 upon the buffer being null byte terminated, it uses the length
1322 string instead. This allows gdb to handle C strings (as well
1323 as strings in other languages) with embedded null bytes */
1325 tokptr = ++tokstart;
1329 /* Grow the static temp buffer if necessary, including allocating
1330 the first one on demand. */
1331 if (tempbufindex + 1 >= tempbufsize)
1333 tempbuf = (char *) realloc (tempbuf, tempbufsize += 64);
1339 /* Do nothing, loop will terminate. */
1343 c = parse_escape (&tokptr);
1348 tempbuf[tempbufindex++] = c;
1351 tempbuf[tempbufindex++] = *tokptr++;
1354 } while ((*tokptr != '"') && (*tokptr != '\0'));
1355 if (*tokptr++ != '"')
1357 error ("Unterminated string in expression.");
1359 tempbuf[tempbufindex] = '\0'; /* See note above */
1360 yylval.sval.ptr = tempbuf;
1361 yylval.sval.length = tempbufindex;
1366 if (!(c == '_' || c == '$'
1367 || (c >= 'a' && c <= 'z') || (c >= 'A' && c <= 'Z')))
1368 /* We must have come across a bad character (e.g. ';'). */
1369 error ("Invalid character '%c' in expression.", c);
1371 /* It's a name. See how long it is. */
1373 for (c = tokstart[namelen];
1374 (c == '_' || c == '$' || (c >= '0' && c <= '9')
1375 || (c >= 'a' && c <= 'z') || (c >= 'A' && c <= 'Z'));
1376 c = tokstart[++namelen])
1379 /* The token "if" terminates the expression and is NOT
1380 removed from the input stream. */
1381 if (namelen == 2 && tokstart[0] == 'i' && tokstart[1] == 'f')
1388 /* Handle the tokens $digits; also $ (short for $0) and $$ (short for $$1)
1389 and $$digits (equivalent to $<-digits> if you could type that).
1390 Make token type LAST, and put the number (the digits) in yylval. */
1393 if (*tokstart == '$')
1395 register int negate = 0;
1397 /* Double dollar means negate the number and add -1 as well.
1398 Thus $$ alone means -1. */
1399 if (namelen >= 2 && tokstart[1] == '$')
1406 /* Just dollars (one or two) */
1407 yylval.lval = - negate;
1410 /* Is the rest of the token digits? */
1411 for (; c < namelen; c++)
1412 if (!(tokstart[c] >= '0' && tokstart[c] <= '9'))
1416 yylval.lval = atoi (tokstart + 1 + negate);
1418 yylval.lval = - yylval.lval;
1423 /* Handle tokens that refer to machine registers:
1424 $ followed by a register name. */
1426 if (*tokstart == '$') {
1427 for (c = 0; c < NUM_REGS; c++)
1428 if (namelen - 1 == strlen (reg_names[c])
1429 && STREQN (tokstart + 1, reg_names[c], namelen - 1))
1434 for (c = 0; c < num_std_regs; c++)
1435 if (namelen - 1 == strlen (std_regs[c].name)
1436 && STREQN (tokstart + 1, std_regs[c].name, namelen - 1))
1438 yylval.lval = std_regs[c].regnum;
1442 /* Catch specific keywords. Should be done with a data structure. */
1446 if (STREQN (tokstart, "unsigned", 8))
1448 if (current_language->la_language == language_cplus
1449 && STREQN (tokstart, "template", 8))
1451 if (STREQN (tokstart, "volatile", 8))
1452 return VOLATILE_KEYWORD;
1455 if (STREQN (tokstart, "struct", 6))
1457 if (STREQN (tokstart, "signed", 6))
1458 return SIGNED_KEYWORD;
1459 if (STREQN (tokstart, "sizeof", 6))
1463 if (current_language->la_language == language_cplus
1464 && STREQN (tokstart, "class", 5))
1466 if (STREQN (tokstart, "union", 5))
1468 if (STREQN (tokstart, "short", 5))
1470 if (STREQN (tokstart, "const", 5))
1471 return CONST_KEYWORD;
1474 if (STREQN (tokstart, "enum", 4))
1476 if (STREQN (tokstart, "long", 4))
1478 if (current_language->la_language == language_cplus
1479 && STREQN (tokstart, "this", 4))
1481 static const char this_name[] =
1482 { CPLUS_MARKER, 't', 'h', 'i', 's', '\0' };
1484 if (lookup_symbol (this_name, expression_context_block,
1485 VAR_NAMESPACE, (int *) NULL,
1486 (struct symtab **) NULL))
1491 if (STREQN (tokstart, "int", 3))
1498 yylval.sval.ptr = tokstart;
1499 yylval.sval.length = namelen;
1501 /* Any other names starting in $ are debugger internal variables. */
1503 if (*tokstart == '$')
1505 yylval.ivar = lookup_internalvar (copy_name (yylval.sval) + 1);
1509 /* Use token-type BLOCKNAME for symbols that happen to be defined as
1510 functions or symtabs. If this is not so, then ...
1511 Use token-type TYPENAME for symbols that happen to be defined
1512 currently as names of types; NAME for other symbols.
1513 The caller is not constrained to care about the distinction. */
1515 char *tmp = copy_name (yylval.sval);
1517 int is_a_field_of_this = 0;
1520 sym = lookup_symbol (tmp, expression_context_block,
1522 current_language->la_language == language_cplus
1523 ? &is_a_field_of_this : (int *) NULL,
1524 (struct symtab **) NULL);
1525 if ((sym && SYMBOL_CLASS (sym) == LOC_BLOCK) ||
1526 lookup_partial_symtab (tmp))
1528 yylval.ssym.sym = sym;
1529 yylval.ssym.is_a_field_of_this = is_a_field_of_this;
1532 if (sym && SYMBOL_CLASS (sym) == LOC_TYPEDEF)
1536 struct symbol *best_sym;
1538 /* Look ahead to detect nested types. This probably should be
1539 done in the grammar, but trying seemed to introduce a lot
1540 of shift/reduce and reduce/reduce conflicts. It's possible
1541 that it could be done, though. Or perhaps a non-grammar, but
1542 less ad hoc, approach would work well. */
1544 /* Since we do not currently have any way of distinguishing
1545 a nested type from a non-nested one (the stabs don't tell
1546 us whether a type is nested), we just ignore the
1553 /* Skip whitespace. */
1554 while (*p == ' ' || *p == '\t' || *p == '\n')
1556 if (*p == ':' && p[1] == ':')
1558 /* Skip the `::'. */
1560 /* Skip whitespace. */
1561 while (*p == ' ' || *p == '\t' || *p == '\n')
1564 while (*p == '_' || *p == '$' || (*p >= '0' && *p <= '9')
1565 || (*p >= 'a' && *p <= 'z')
1566 || (*p >= 'A' && *p <= 'Z'))
1570 struct symbol *cur_sym;
1571 /* As big as the whole rest of the expression, which is
1572 at least big enough. */
1573 char *tmp = alloca (strlen (namestart));
1575 memcpy (tmp, namestart, p - namestart);
1576 tmp[p - namestart] = '\0';
1577 cur_sym = lookup_symbol (tmp, expression_context_block,
1578 VAR_NAMESPACE, (int *) NULL,
1579 (struct symtab **) NULL);
1582 if (SYMBOL_CLASS (cur_sym) == LOC_TYPEDEF)
1600 yylval.tsym.type = SYMBOL_TYPE (best_sym);
1603 if ((yylval.tsym.type = lookup_primitive_typename (tmp)) != 0)
1606 /* Input names that aren't symbols but ARE valid hex numbers,
1607 when the input radix permits them, can be names or numbers
1608 depending on the parse. Note we support radixes > 16 here. */
1610 ((tokstart[0] >= 'a' && tokstart[0] < 'a' + input_radix - 10) ||
1611 (tokstart[0] >= 'A' && tokstart[0] < 'A' + input_radix - 10)))
1613 YYSTYPE newlval; /* Its value is ignored. */
1614 hextype = parse_number (tokstart, namelen, 0, &newlval);
1617 yylval.ssym.sym = sym;
1618 yylval.ssym.is_a_field_of_this = is_a_field_of_this;
1623 /* Any other kind of symbol */
1624 yylval.ssym.sym = sym;
1625 yylval.ssym.is_a_field_of_this = is_a_field_of_this;
1634 error (msg ? msg : "Invalid syntax in expression.");