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, 0, NULL);
550 if (!tem || SYMBOL_CLASS (tem) != LOC_BLOCK)
551 error ("No function \"%s\" in specified context.",
553 $$ = SYMBOL_BLOCK_VALUE (tem); }
556 variable: block COLONCOLON name
557 { struct symbol *sym;
558 sym = lookup_symbol (copy_name ($3), $1,
559 VAR_NAMESPACE, 0, NULL);
561 error ("No symbol \"%s\" in specified context.",
564 write_exp_elt_opcode (OP_VAR_VALUE);
565 write_exp_elt_sym (sym);
566 write_exp_elt_opcode (OP_VAR_VALUE); }
569 qualified_name: typebase COLONCOLON name
571 struct type *type = $1;
572 if (TYPE_CODE (type) != TYPE_CODE_STRUCT
573 && TYPE_CODE (type) != TYPE_CODE_UNION)
574 error ("`%s' is not defined as an aggregate type.",
577 write_exp_elt_opcode (OP_SCOPE);
578 write_exp_elt_type (type);
579 write_exp_string ($3);
580 write_exp_elt_opcode (OP_SCOPE);
582 | typebase COLONCOLON '~' name
584 struct type *type = $1;
585 struct stoken tmp_token;
586 if (TYPE_CODE (type) != TYPE_CODE_STRUCT
587 && TYPE_CODE (type) != TYPE_CODE_UNION)
588 error ("`%s' is not defined as an aggregate type.",
591 if (!STREQ (type_name_no_tag (type), $4.ptr))
592 error ("invalid destructor `%s::~%s'",
593 type_name_no_tag (type), $4.ptr);
595 tmp_token.ptr = (char*) alloca ($4.length + 2);
596 tmp_token.length = $4.length + 1;
597 tmp_token.ptr[0] = '~';
598 memcpy (tmp_token.ptr+1, $4.ptr, $4.length);
599 tmp_token.ptr[tmp_token.length] = 0;
600 write_exp_elt_opcode (OP_SCOPE);
601 write_exp_elt_type (type);
602 write_exp_string (tmp_token);
603 write_exp_elt_opcode (OP_SCOPE);
607 variable: qualified_name
610 char *name = copy_name ($2);
612 struct minimal_symbol *msymbol;
615 lookup_symbol (name, 0, VAR_NAMESPACE, 0, NULL);
618 write_exp_elt_opcode (OP_VAR_VALUE);
619 write_exp_elt_sym (sym);
620 write_exp_elt_opcode (OP_VAR_VALUE);
624 msymbol = lookup_minimal_symbol (name,
625 (struct objfile *) NULL);
628 write_exp_elt_opcode (OP_LONG);
629 write_exp_elt_type (builtin_type_int);
630 write_exp_elt_longcst ((LONGEST) SYMBOL_VALUE_ADDRESS (msymbol));
631 write_exp_elt_opcode (OP_LONG);
632 write_exp_elt_opcode (UNOP_MEMVAL);
633 if (msymbol -> type == mst_data ||
634 msymbol -> type == mst_bss)
635 write_exp_elt_type (builtin_type_int);
636 else if (msymbol -> type == mst_text)
637 write_exp_elt_type (lookup_function_type (builtin_type_int));
639 write_exp_elt_type (builtin_type_char);
640 write_exp_elt_opcode (UNOP_MEMVAL);
643 if (!have_full_symbols () && !have_partial_symbols ())
644 error ("No symbol table is loaded. Use the \"file\" command.");
646 error ("No symbol \"%s\" in current context.", name);
650 variable: name_not_typename
651 { struct symbol *sym = $1.sym;
655 switch (SYMBOL_CLASS (sym))
663 if (innermost_block == 0 ||
664 contained_in (block_found,
666 innermost_block = block_found;
673 case LOC_CONST_BYTES:
674 case LOC_OPTIMIZED_OUT:
676 /* In this case the expression can
677 be evaluated regardless of what
678 frame we are in, so there is no
679 need to check for the
680 innermost_block. These cases are
681 listed so that gcc -Wall will
682 report types that may not have
687 write_exp_elt_opcode (OP_VAR_VALUE);
688 write_exp_elt_sym (sym);
689 write_exp_elt_opcode (OP_VAR_VALUE);
691 else if ($1.is_a_field_of_this)
693 /* C++: it hangs off of `this'. Must
694 not inadvertently convert from a method call
696 if (innermost_block == 0 ||
697 contained_in (block_found, innermost_block))
698 innermost_block = block_found;
699 write_exp_elt_opcode (OP_THIS);
700 write_exp_elt_opcode (OP_THIS);
701 write_exp_elt_opcode (STRUCTOP_PTR);
702 write_exp_string ($1.stoken);
703 write_exp_elt_opcode (STRUCTOP_PTR);
707 struct minimal_symbol *msymbol;
708 register char *arg = copy_name ($1.stoken);
710 msymbol = lookup_minimal_symbol (arg,
711 (struct objfile *) NULL);
714 write_exp_elt_opcode (OP_LONG);
715 write_exp_elt_type (builtin_type_int);
716 write_exp_elt_longcst ((LONGEST) SYMBOL_VALUE_ADDRESS (msymbol));
717 write_exp_elt_opcode (OP_LONG);
718 write_exp_elt_opcode (UNOP_MEMVAL);
719 if (msymbol -> type == mst_data ||
720 msymbol -> type == mst_bss)
721 write_exp_elt_type (builtin_type_int);
722 else if (msymbol -> type == mst_text)
723 write_exp_elt_type (lookup_function_type (builtin_type_int));
725 write_exp_elt_type (builtin_type_char);
726 write_exp_elt_opcode (UNOP_MEMVAL);
728 else if (!have_full_symbols () && !have_partial_symbols ())
729 error ("No symbol table is loaded. Use the \"file\" command.");
731 error ("No symbol \"%s\" in current context.",
732 copy_name ($1.stoken));
741 /* This is where the interesting stuff happens. */
744 struct type *follow_type = $1;
745 struct type *range_type;
754 follow_type = lookup_pointer_type (follow_type);
757 follow_type = lookup_reference_type (follow_type);
760 array_size = pop_type_int ();
761 if (array_size != -1)
764 create_range_type ((struct type *) NULL,
768 create_array_type ((struct type *) NULL,
769 follow_type, range_type);
772 follow_type = lookup_pointer_type (follow_type);
775 follow_type = lookup_function_type (follow_type);
783 { push_type (tp_pointer); $$ = 0; }
785 { push_type (tp_pointer); $$ = $2; }
787 { push_type (tp_reference); $$ = 0; }
789 { push_type (tp_reference); $$ = $2; }
793 direct_abs_decl: '(' abs_decl ')'
795 | direct_abs_decl array_mod
798 push_type (tp_array);
803 push_type (tp_array);
806 | direct_abs_decl func_mod
807 { push_type (tp_function); }
809 { push_type (tp_function); }
820 | '(' nonempty_typelist ')'
821 { free ((PTR)$2); $$ = 0; }
825 | typebase COLONCOLON '*'
826 { $$ = lookup_member_type (builtin_type_int, $1); }
827 | type '(' typebase COLONCOLON '*' ')'
828 { $$ = lookup_member_type ($1, $3); }
829 | type '(' typebase COLONCOLON '*' ')' '(' ')'
830 { $$ = lookup_member_type
831 (lookup_function_type ($1), $3); }
832 | type '(' typebase COLONCOLON '*' ')' '(' nonempty_typelist ')'
833 { $$ = lookup_member_type
834 (lookup_function_type ($1), $3);
838 typebase /* Implements (approximately): (type-qualifier)* type-specifier */
842 { $$ = builtin_type_int; }
844 { $$ = builtin_type_long; }
846 { $$ = builtin_type_short; }
848 { $$ = builtin_type_long; }
849 | UNSIGNED LONG INT_KEYWORD
850 { $$ = builtin_type_unsigned_long; }
852 { $$ = builtin_type_long_long; }
853 | LONG LONG INT_KEYWORD
854 { $$ = builtin_type_long_long; }
856 { $$ = builtin_type_unsigned_long_long; }
857 | UNSIGNED LONG LONG INT_KEYWORD
858 { $$ = builtin_type_unsigned_long_long; }
860 { $$ = builtin_type_short; }
861 | UNSIGNED SHORT INT_KEYWORD
862 { $$ = builtin_type_unsigned_short; }
864 { $$ = lookup_struct (copy_name ($2),
865 expression_context_block); }
867 { $$ = lookup_struct (copy_name ($2),
868 expression_context_block); }
870 { $$ = lookup_union (copy_name ($2),
871 expression_context_block); }
873 { $$ = lookup_enum (copy_name ($2),
874 expression_context_block); }
876 { $$ = lookup_unsigned_typename (TYPE_NAME($2.type)); }
878 { $$ = builtin_type_unsigned_int; }
879 | SIGNED_KEYWORD typename
880 { $$ = lookup_signed_typename (TYPE_NAME($2.type)); }
882 { $$ = builtin_type_int; }
883 | TEMPLATE name '<' type '>'
884 { $$ = lookup_template_type(copy_name($2), $4,
885 expression_context_block);
887 /* "const" and "volatile" are curently ignored. */
888 | CONST_KEYWORD typebase { $$ = $2; }
889 | VOLATILE_KEYWORD typebase { $$ = $2; }
895 $$.stoken.ptr = "int";
896 $$.stoken.length = 3;
897 $$.type = builtin_type_int;
901 $$.stoken.ptr = "long";
902 $$.stoken.length = 4;
903 $$.type = builtin_type_long;
907 $$.stoken.ptr = "short";
908 $$.stoken.length = 5;
909 $$.type = builtin_type_short;
915 { $$ = (struct type **) malloc (sizeof (struct type *) * 2);
916 $<ivec>$[0] = 1; /* Number of types in vector */
919 | nonempty_typelist ',' type
920 { int len = sizeof (struct type *) * (++($<ivec>1[0]) + 1);
921 $$ = (struct type **) realloc ((char *) $1, len);
922 $$[$<ivec>$[0]] = $3;
926 name : NAME { $$ = $1.stoken; }
927 | BLOCKNAME { $$ = $1.stoken; }
928 | TYPENAME { $$ = $1.stoken; }
929 | NAME_OR_INT { $$ = $1.stoken; }
932 name_not_typename : NAME
934 /* These would be useful if name_not_typename was useful, but it is just
935 a fake for "variable", so these cause reduce/reduce conflicts because
936 the parser can't tell whether NAME_OR_INT is a name_not_typename (=variable,
937 =exp) or just an exp. If name_not_typename was ever used in an lvalue
938 context where only a name could occur, this might be useful.
945 /* Take care of parsing a number (anything that starts with a digit).
946 Set yylval and return the token type; update lexptr.
947 LEN is the number of characters in it. */
949 /*** Needs some error checking for the float case ***/
952 parse_number (p, len, parsed_float, putithere)
958 register LONGEST n = 0;
959 register LONGEST prevn = 0;
962 register int base = input_radix;
965 unsigned LONGEST high_bit;
966 struct type *signed_type;
967 struct type *unsigned_type;
971 /* It's a float since it contains a point or an exponent. */
972 putithere->dval = atof (p);
976 /* Handle base-switching prefixes 0x, 0t, 0d, 0 */
1010 if (c >= 'A' && c <= 'Z')
1012 if (c != 'l' && c != 'u')
1014 if (c >= '0' && c <= '9')
1018 if (base > 10 && c >= 'a' && c <= 'f')
1019 n += i = c - 'a' + 10;
1020 else if (len == 0 && c == 'l')
1022 else if (len == 0 && c == 'u')
1025 return ERROR; /* Char not a digit */
1028 return ERROR; /* Invalid digit in this base */
1030 /* Portably test for overflow (only works for nonzero values, so make
1031 a second check for zero). */
1032 if((prevn >= n) && n != 0)
1033 unsigned_p=1; /* Try something unsigned */
1034 /* If range checking enabled, portably test for unsigned overflow. */
1035 if(RANGE_CHECK && n!=0)
1037 if((unsigned_p && (unsigned)prevn >= (unsigned)n))
1038 range_error("Overflow on numeric constant.");
1043 /* If the number is too big to be an int, or it's got an l suffix
1044 then it's a long. Work out if this has to be a long by
1045 shifting right and and seeing if anything remains, and the
1046 target int size is different to the target long size.
1048 In the expression below, we could have tested
1049 (n >> TARGET_INT_BIT)
1050 to see if it was zero,
1051 but too many compilers warn about that, when ints and longs
1052 are the same size. So we shift it twice, with fewer bits
1053 each time, for the same result. */
1055 if ( (TARGET_INT_BIT != TARGET_LONG_BIT
1056 && ((n >> 2) >> (TARGET_INT_BIT-2))) /* Avoid shift warning */
1059 high_bit = ((unsigned LONGEST)1) << (TARGET_LONG_BIT-1);
1060 unsigned_type = builtin_type_unsigned_long;
1061 signed_type = builtin_type_long;
1065 high_bit = ((unsigned LONGEST)1) << (TARGET_INT_BIT-1);
1066 unsigned_type = builtin_type_unsigned_int;
1067 signed_type = builtin_type_int;
1070 putithere->typed_val.val = n;
1072 /* If the high bit of the worked out type is set then this number
1073 has to be unsigned. */
1075 if (unsigned_p || (n & high_bit))
1077 putithere->typed_val.type = unsigned_type;
1081 putithere->typed_val.type = signed_type;
1091 enum exp_opcode opcode;
1094 static const struct token tokentab3[] =
1096 {">>=", ASSIGN_MODIFY, BINOP_RSH},
1097 {"<<=", ASSIGN_MODIFY, BINOP_LSH}
1100 static const struct token tokentab2[] =
1102 {"+=", ASSIGN_MODIFY, BINOP_ADD},
1103 {"-=", ASSIGN_MODIFY, BINOP_SUB},
1104 {"*=", ASSIGN_MODIFY, BINOP_MUL},
1105 {"/=", ASSIGN_MODIFY, BINOP_DIV},
1106 {"%=", ASSIGN_MODIFY, BINOP_REM},
1107 {"|=", ASSIGN_MODIFY, BINOP_BITWISE_IOR},
1108 {"&=", ASSIGN_MODIFY, BINOP_BITWISE_AND},
1109 {"^=", ASSIGN_MODIFY, BINOP_BITWISE_XOR},
1110 {"++", INCREMENT, BINOP_END},
1111 {"--", DECREMENT, BINOP_END},
1112 {"->", ARROW, BINOP_END},
1113 {"&&", ANDAND, BINOP_END},
1114 {"||", OROR, BINOP_END},
1115 {"::", COLONCOLON, BINOP_END},
1116 {"<<", LSH, BINOP_END},
1117 {">>", RSH, BINOP_END},
1118 {"==", EQUAL, BINOP_END},
1119 {"!=", NOTEQUAL, BINOP_END},
1120 {"<=", LEQ, BINOP_END},
1121 {">=", GEQ, BINOP_END}
1124 /* Read one token, getting characters through lexptr. */
1135 static char *tempbuf;
1136 static int tempbufsize;
1141 /* See if it is a special token of length 3. */
1142 for (i = 0; i < sizeof tokentab3 / sizeof tokentab3[0]; i++)
1143 if (STREQN (tokstart, tokentab3[i].operator, 3))
1146 yylval.opcode = tokentab3[i].opcode;
1147 return tokentab3[i].token;
1150 /* See if it is a special token of length 2. */
1151 for (i = 0; i < sizeof tokentab2 / sizeof tokentab2[0]; i++)
1152 if (STREQN (tokstart, tokentab2[i].operator, 2))
1155 yylval.opcode = tokentab2[i].opcode;
1156 return tokentab2[i].token;
1159 switch (c = *tokstart)
1171 /* We either have a character constant ('0' or '\177' for example)
1172 or we have a quoted symbol reference ('foo(int,int)' in C++
1177 c = parse_escape (&lexptr);
1179 yylval.typed_val.val = c;
1180 yylval.typed_val.type = builtin_type_char;
1185 namelen = skip_quoted (tokstart) - tokstart;
1188 lexptr = tokstart + namelen;
1193 error ("Invalid character constant.");
1203 if (paren_depth == 0)
1210 if (comma_terminates && paren_depth == 0)
1216 /* Might be a floating point number. */
1217 if (lexptr[1] < '0' || lexptr[1] > '9')
1218 goto symbol; /* Nope, must be a symbol. */
1219 /* FALL THRU into number case. */
1232 /* It's a number. */
1233 int got_dot = 0, got_e = 0, toktype;
1234 register char *p = tokstart;
1235 int hex = input_radix > 10;
1237 if (c == '0' && (p[1] == 'x' || p[1] == 'X'))
1242 else if (c == '0' && (p[1]=='t' || p[1]=='T' || p[1]=='d' || p[1]=='D'))
1250 if (!hex && !got_e && (*p == 'e' || *p == 'E'))
1251 got_dot = got_e = 1;
1252 else if (!hex && !got_dot && *p == '.')
1254 else if (got_e && (p[-1] == 'e' || p[-1] == 'E')
1255 && (*p == '-' || *p == '+'))
1256 /* This is the sign of the exponent, not the end of the
1259 /* We will take any letters or digits. parse_number will
1260 complain if past the radix, or if L or U are not final. */
1261 else if ((*p < '0' || *p > '9')
1262 && ((*p < 'a' || *p > 'z')
1263 && (*p < 'A' || *p > 'Z')))
1266 toktype = parse_number (tokstart, p - tokstart, got_dot|got_e, &yylval);
1267 if (toktype == ERROR)
1269 char *err_copy = (char *) alloca (p - tokstart + 1);
1271 memcpy (err_copy, tokstart, p - tokstart);
1272 err_copy[p - tokstart] = 0;
1273 error ("Invalid number \"%s\".", err_copy);
1305 /* Build the gdb internal form of the input string in tempbuf,
1306 translating any standard C escape forms seen. Note that the
1307 buffer is null byte terminated *only* for the convenience of
1308 debugging gdb itself and printing the buffer contents when
1309 the buffer contains no embedded nulls. Gdb does not depend
1310 upon the buffer being null byte terminated, it uses the length
1311 string instead. This allows gdb to handle C strings (as well
1312 as strings in other languages) with embedded null bytes */
1314 tokptr = ++tokstart;
1318 /* Grow the static temp buffer if necessary, including allocating
1319 the first one on demand. */
1320 if (tempbufindex + 1 >= tempbufsize)
1322 tempbuf = (char *) realloc (tempbuf, tempbufsize += 64);
1328 /* Do nothing, loop will terminate. */
1332 c = parse_escape (&tokptr);
1337 tempbuf[tempbufindex++] = c;
1340 tempbuf[tempbufindex++] = *tokptr++;
1343 } while ((*tokptr != '"') && (*tokptr != '\0'));
1344 if (*tokptr++ != '"')
1346 error ("Unterminated string in expression.");
1348 tempbuf[tempbufindex] = '\0'; /* See note above */
1349 yylval.sval.ptr = tempbuf;
1350 yylval.sval.length = tempbufindex;
1355 if (!(c == '_' || c == '$'
1356 || (c >= 'a' && c <= 'z') || (c >= 'A' && c <= 'Z')))
1357 /* We must have come across a bad character (e.g. ';'). */
1358 error ("Invalid character '%c' in expression.", c);
1360 /* It's a name. See how long it is. */
1362 for (c = tokstart[namelen];
1363 (c == '_' || c == '$' || (c >= '0' && c <= '9')
1364 || (c >= 'a' && c <= 'z') || (c >= 'A' && c <= 'Z'));
1365 c = tokstart[++namelen])
1368 /* The token "if" terminates the expression and is NOT
1369 removed from the input stream. */
1370 if (namelen == 2 && tokstart[0] == 'i' && tokstart[1] == 'f')
1377 /* Handle the tokens $digits; also $ (short for $0) and $$ (short for $$1)
1378 and $$digits (equivalent to $<-digits> if you could type that).
1379 Make token type LAST, and put the number (the digits) in yylval. */
1382 if (*tokstart == '$')
1384 register int negate = 0;
1386 /* Double dollar means negate the number and add -1 as well.
1387 Thus $$ alone means -1. */
1388 if (namelen >= 2 && tokstart[1] == '$')
1395 /* Just dollars (one or two) */
1396 yylval.lval = - negate;
1399 /* Is the rest of the token digits? */
1400 for (; c < namelen; c++)
1401 if (!(tokstart[c] >= '0' && tokstart[c] <= '9'))
1405 yylval.lval = atoi (tokstart + 1 + negate);
1407 yylval.lval = - yylval.lval;
1412 /* Handle tokens that refer to machine registers:
1413 $ followed by a register name. */
1415 if (*tokstart == '$') {
1416 for (c = 0; c < NUM_REGS; c++)
1417 if (namelen - 1 == strlen (reg_names[c])
1418 && STREQN (tokstart + 1, reg_names[c], namelen - 1))
1423 for (c = 0; c < num_std_regs; c++)
1424 if (namelen - 1 == strlen (std_regs[c].name)
1425 && STREQN (tokstart + 1, std_regs[c].name, namelen - 1))
1427 yylval.lval = std_regs[c].regnum;
1431 /* Catch specific keywords. Should be done with a data structure. */
1435 if (STREQN (tokstart, "unsigned", 8))
1437 if (current_language->la_language == language_cplus
1438 && STREQN (tokstart, "template", 8))
1440 if (STREQN (tokstart, "volatile", 8))
1441 return VOLATILE_KEYWORD;
1444 if (STREQN (tokstart, "struct", 6))
1446 if (STREQN (tokstart, "signed", 6))
1447 return SIGNED_KEYWORD;
1448 if (STREQN (tokstart, "sizeof", 6))
1452 if (current_language->la_language == language_cplus
1453 && STREQN (tokstart, "class", 5))
1455 if (STREQN (tokstart, "union", 5))
1457 if (STREQN (tokstart, "short", 5))
1459 if (STREQN (tokstart, "const", 5))
1460 return CONST_KEYWORD;
1463 if (STREQN (tokstart, "enum", 4))
1465 if (STREQN (tokstart, "long", 4))
1467 if (current_language->la_language == language_cplus
1468 && STREQN (tokstart, "this", 4))
1470 static const char this_name[] =
1471 { CPLUS_MARKER, 't', 'h', 'i', 's', '\0' };
1473 if (lookup_symbol (this_name, expression_context_block,
1474 VAR_NAMESPACE, 0, NULL))
1479 if (STREQN (tokstart, "int", 3))
1486 yylval.sval.ptr = tokstart;
1487 yylval.sval.length = namelen;
1489 /* Any other names starting in $ are debugger internal variables. */
1491 if (*tokstart == '$')
1493 yylval.ivar = lookup_internalvar (copy_name (yylval.sval) + 1);
1497 /* Use token-type BLOCKNAME for symbols that happen to be defined as
1498 functions or symtabs. If this is not so, then ...
1499 Use token-type TYPENAME for symbols that happen to be defined
1500 currently as names of types; NAME for other symbols.
1501 The caller is not constrained to care about the distinction. */
1503 char *tmp = copy_name (yylval.sval);
1505 int is_a_field_of_this = 0;
1508 sym = lookup_symbol (tmp, expression_context_block,
1510 current_language->la_language == language_cplus
1511 ? &is_a_field_of_this : NULL,
1513 if ((sym && SYMBOL_CLASS (sym) == LOC_BLOCK) ||
1514 lookup_partial_symtab (tmp))
1516 yylval.ssym.sym = sym;
1517 yylval.ssym.is_a_field_of_this = is_a_field_of_this;
1520 if (sym && SYMBOL_CLASS (sym) == LOC_TYPEDEF)
1522 yylval.tsym.type = SYMBOL_TYPE (sym);
1525 if ((yylval.tsym.type = lookup_primitive_typename (tmp)) != 0)
1528 /* Input names that aren't symbols but ARE valid hex numbers,
1529 when the input radix permits them, can be names or numbers
1530 depending on the parse. Note we support radixes > 16 here. */
1532 ((tokstart[0] >= 'a' && tokstart[0] < 'a' + input_radix - 10) ||
1533 (tokstart[0] >= 'A' && tokstart[0] < 'A' + input_radix - 10)))
1535 YYSTYPE newlval; /* Its value is ignored. */
1536 hextype = parse_number (tokstart, namelen, 0, &newlval);
1539 yylval.ssym.sym = sym;
1540 yylval.ssym.is_a_field_of_this = is_a_field_of_this;
1545 /* Any other kind of symbol */
1546 yylval.ssym.sym = sym;
1547 yylval.ssym.is_a_field_of_this = is_a_field_of_this;
1556 error (msg ? msg : "Invalid syntax in expression.");