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. */
37 #include "expression.h"
38 #include "parser-defs.h"
45 /* Ensure that if the generated parser contains any calls to malloc/realloc,
46 that they get mapped to xmalloc/xrealloc. */
48 #define malloc xmalloc
49 #define realloc xrealloc
51 /* These MUST be included in any grammar file!!!!
52 Please choose unique names! */
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
82 yyparse PARAMS ((void));
85 yylex PARAMS ((void));
88 yyerror PARAMS ((char *));
90 /* #define YYDEBUG 1 */
94 /* Although the yacc "value" of an expression is not used,
95 since the result is stored in the structure being created,
96 other node types do have values. */
101 unsigned LONGEST ulval;
107 struct symtoken ssym;
110 enum exp_opcode opcode;
111 struct internalvar *ivar;
118 /* YYSTYPE gets defined by %union */
120 parse_number PARAMS ((char *, int, int, YYSTYPE *));
123 %type <voidval> exp exp1 type_exp start variable qualified_name
124 %type <tval> type typebase
125 %type <tvec> nonempty_typelist
126 /* %type <bval> block */
128 /* Fancy type parsing. */
129 %type <voidval> func_mod direct_abs_decl abs_decl
131 %type <lval> array_mod
133 %token <lval> INT CHAR
137 /* Both NAME and TYPENAME tokens represent symbols in the input,
138 and both convey their data as strings.
139 But a TYPENAME is a string that happens to be defined as a typedef
140 or builtin type name (such as int or char)
141 and a NAME is any other symbol.
142 Contexts where this distinction is not important can use the
143 nonterminal "name", which matches either NAME or TYPENAME. */
146 %token <ssym> NAME /* BLOCKNAME defined below to give it higher precedence. */
147 %token <tsym> TYPENAME
149 %type <ssym> name_not_typename
150 %type <tsym> typename
152 /* A NAME_OR_INT is a symbol which is not known in the symbol table,
153 but which would parse as a valid number in the current input radix.
154 E.g. "c" when input_radix==16. Depending on the parse, it will be
155 turned into a name or into a number. NAME_OR_UINT ditto. */
157 %token <ssym> NAME_OR_INT NAME_OR_UINT
159 %token STRUCT UNION ENUM SIZEOF UNSIGNED COLONCOLON
163 /* Special type cases, put in to allow the parser to distinguish different
165 %token SIGNED_KEYWORD LONG SHORT INT_KEYWORD
167 %token <lval> LAST REGNAME
169 %token <ivar> VARIABLE
171 %token <opcode> ASSIGN_MODIFY
178 %right '=' ASSIGN_MODIFY
186 %left '<' '>' LEQ GEQ
191 %right UNARY INCREMENT DECREMENT
192 %right ARROW '.' '[' '('
193 %token <ssym> BLOCKNAME
204 { write_exp_elt_opcode(OP_TYPE);
205 write_exp_elt_type($1);
206 write_exp_elt_opcode(OP_TYPE);}
209 /* Expressions, including the comma operator. */
212 { write_exp_elt_opcode (BINOP_COMMA); }
215 /* Expressions, not including the comma operator. */
216 exp : '*' exp %prec UNARY
217 { write_exp_elt_opcode (UNOP_IND); }
219 exp : '&' exp %prec UNARY
220 { write_exp_elt_opcode (UNOP_ADDR); }
222 exp : '-' exp %prec UNARY
223 { write_exp_elt_opcode (UNOP_NEG); }
226 exp : '!' exp %prec UNARY
227 { write_exp_elt_opcode (UNOP_ZEROP); }
230 exp : '~' exp %prec UNARY
231 { write_exp_elt_opcode (UNOP_LOGNOT); }
234 exp : INCREMENT exp %prec UNARY
235 { write_exp_elt_opcode (UNOP_PREINCREMENT); }
238 exp : DECREMENT exp %prec UNARY
239 { write_exp_elt_opcode (UNOP_PREDECREMENT); }
242 exp : exp INCREMENT %prec UNARY
243 { write_exp_elt_opcode (UNOP_POSTINCREMENT); }
246 exp : exp DECREMENT %prec UNARY
247 { write_exp_elt_opcode (UNOP_POSTDECREMENT); }
250 exp : SIZEOF exp %prec UNARY
251 { write_exp_elt_opcode (UNOP_SIZEOF); }
255 { write_exp_elt_opcode (STRUCTOP_PTR);
256 write_exp_string ($3);
257 write_exp_elt_opcode (STRUCTOP_PTR); }
260 exp : exp ARROW qualified_name
261 { /* exp->type::name becomes exp->*(&type::name) */
262 /* Note: this doesn't work if name is a
263 static member! FIXME */
264 write_exp_elt_opcode (UNOP_ADDR);
265 write_exp_elt_opcode (STRUCTOP_MPTR); }
267 exp : exp ARROW '*' exp
268 { write_exp_elt_opcode (STRUCTOP_MPTR); }
272 { write_exp_elt_opcode (STRUCTOP_STRUCT);
273 write_exp_string ($3);
274 write_exp_elt_opcode (STRUCTOP_STRUCT); }
277 exp : exp '.' qualified_name
278 { /* exp.type::name becomes exp.*(&type::name) */
279 /* Note: this doesn't work if name is a
280 static member! FIXME */
281 write_exp_elt_opcode (UNOP_ADDR);
282 write_exp_elt_opcode (STRUCTOP_MEMBER); }
285 exp : exp '.' '*' exp
286 { write_exp_elt_opcode (STRUCTOP_MEMBER); }
289 exp : exp '[' exp1 ']'
290 { write_exp_elt_opcode (BINOP_SUBSCRIPT); }
294 /* This is to save the value of arglist_len
295 being accumulated by an outer function call. */
296 { start_arglist (); }
297 arglist ')' %prec ARROW
298 { write_exp_elt_opcode (OP_FUNCALL);
299 write_exp_elt_longcst ((LONGEST) end_arglist ());
300 write_exp_elt_opcode (OP_FUNCALL); }
310 arglist : arglist ',' exp %prec ABOVE_COMMA
314 exp : '{' type '}' exp %prec UNARY
315 { write_exp_elt_opcode (UNOP_MEMVAL);
316 write_exp_elt_type ($2);
317 write_exp_elt_opcode (UNOP_MEMVAL); }
320 exp : '(' type ')' exp %prec UNARY
321 { write_exp_elt_opcode (UNOP_CAST);
322 write_exp_elt_type ($2);
323 write_exp_elt_opcode (UNOP_CAST); }
330 /* Binary operators in order of decreasing precedence. */
333 { write_exp_elt_opcode (BINOP_REPEAT); }
337 { write_exp_elt_opcode (BINOP_MUL); }
341 { write_exp_elt_opcode (BINOP_DIV); }
345 { write_exp_elt_opcode (BINOP_REM); }
349 { write_exp_elt_opcode (BINOP_ADD); }
353 { write_exp_elt_opcode (BINOP_SUB); }
357 { write_exp_elt_opcode (BINOP_LSH); }
361 { write_exp_elt_opcode (BINOP_RSH); }
365 { write_exp_elt_opcode (BINOP_EQUAL); }
368 exp : exp NOTEQUAL exp
369 { write_exp_elt_opcode (BINOP_NOTEQUAL); }
373 { write_exp_elt_opcode (BINOP_LEQ); }
377 { write_exp_elt_opcode (BINOP_GEQ); }
381 { write_exp_elt_opcode (BINOP_LESS); }
385 { write_exp_elt_opcode (BINOP_GTR); }
389 { write_exp_elt_opcode (BINOP_LOGAND); }
393 { write_exp_elt_opcode (BINOP_LOGXOR); }
397 { write_exp_elt_opcode (BINOP_LOGIOR); }
401 { write_exp_elt_opcode (BINOP_AND); }
405 { write_exp_elt_opcode (BINOP_OR); }
408 exp : exp '?' exp ':' exp %prec '?'
409 { write_exp_elt_opcode (TERNOP_COND); }
413 { write_exp_elt_opcode (BINOP_ASSIGN); }
416 exp : exp ASSIGN_MODIFY exp
417 { write_exp_elt_opcode (BINOP_ASSIGN_MODIFY);
418 write_exp_elt_opcode ($2);
419 write_exp_elt_opcode (BINOP_ASSIGN_MODIFY); }
423 { write_exp_elt_opcode (OP_LONG);
424 if ($1 == (int) $1 || $1 == (unsigned int) $1)
425 write_exp_elt_type (builtin_type_int);
427 write_exp_elt_type (BUILTIN_TYPE_LONGEST);
428 write_exp_elt_longcst ((LONGEST) $1);
429 write_exp_elt_opcode (OP_LONG); }
434 parse_number ($1.stoken.ptr, $1.stoken.length, 0, &val);
435 write_exp_elt_opcode (OP_LONG);
436 if (val.lval == (int) val.lval ||
437 val.lval == (unsigned int) val.lval)
438 write_exp_elt_type (builtin_type_int);
440 write_exp_elt_type (BUILTIN_TYPE_LONGEST);
441 write_exp_elt_longcst (val.lval);
442 write_exp_elt_opcode (OP_LONG); }
447 write_exp_elt_opcode (OP_LONG);
448 if ($1 == (unsigned int) $1)
449 write_exp_elt_type (builtin_type_unsigned_int);
451 write_exp_elt_type (BUILTIN_TYPE_UNSIGNED_LONGEST);
452 write_exp_elt_longcst ((LONGEST) $1);
453 write_exp_elt_opcode (OP_LONG);
459 parse_number ($1.stoken.ptr, $1.stoken.length, 0, &val);
460 write_exp_elt_opcode (OP_LONG);
461 if (val.ulval == (unsigned int) val.ulval)
462 write_exp_elt_type (builtin_type_unsigned_int);
464 write_exp_elt_type (BUILTIN_TYPE_UNSIGNED_LONGEST);
465 write_exp_elt_longcst ((LONGEST)val.ulval);
466 write_exp_elt_opcode (OP_LONG);
471 { write_exp_elt_opcode (OP_LONG);
472 write_exp_elt_type (builtin_type_char);
473 write_exp_elt_longcst ((LONGEST) $1);
474 write_exp_elt_opcode (OP_LONG); }
478 { write_exp_elt_opcode (OP_DOUBLE);
479 write_exp_elt_type (builtin_type_double);
480 write_exp_elt_dblcst ($1);
481 write_exp_elt_opcode (OP_DOUBLE); }
488 { write_exp_elt_opcode (OP_LAST);
489 write_exp_elt_longcst ((LONGEST) $1);
490 write_exp_elt_opcode (OP_LAST); }
494 { write_exp_elt_opcode (OP_REGISTER);
495 write_exp_elt_longcst ((LONGEST) $1);
496 write_exp_elt_opcode (OP_REGISTER); }
500 { write_exp_elt_opcode (OP_INTERNALVAR);
501 write_exp_elt_intern ($1);
502 write_exp_elt_opcode (OP_INTERNALVAR); }
505 exp : SIZEOF '(' type ')' %prec UNARY
506 { write_exp_elt_opcode (OP_LONG);
507 write_exp_elt_type (builtin_type_int);
508 write_exp_elt_longcst ((LONGEST) TYPE_LENGTH ($3));
509 write_exp_elt_opcode (OP_LONG); }
513 { write_exp_elt_opcode (OP_STRING);
514 write_exp_string ($1);
515 write_exp_elt_opcode (OP_STRING); }
520 { write_exp_elt_opcode (OP_THIS);
521 write_exp_elt_opcode (OP_THIS); }
529 $$ = SYMBOL_BLOCK_VALUE ($1.sym);
533 lookup_symtab (copy_name ($1.stoken));
535 $$ = BLOCKVECTOR_BLOCK
536 (BLOCKVECTOR (tem), STATIC_BLOCK);
538 error ("No file or function \"%s\".",
539 copy_name ($1.stoken));
544 block : block COLONCOLON name
546 = lookup_symbol (copy_name ($3), $1,
547 VAR_NAMESPACE, 0, NULL);
548 if (!tem || SYMBOL_CLASS (tem) != LOC_BLOCK)
549 error ("No function \"%s\" in specified context.",
551 $$ = SYMBOL_BLOCK_VALUE (tem); }
554 variable: block COLONCOLON name
555 { struct symbol *sym;
556 sym = lookup_symbol (copy_name ($3), $1,
557 VAR_NAMESPACE, 0, NULL);
559 error ("No symbol \"%s\" in specified context.",
562 write_exp_elt_opcode (OP_VAR_VALUE);
563 write_exp_elt_sym (sym);
564 write_exp_elt_opcode (OP_VAR_VALUE); }
567 qualified_name: typebase COLONCOLON name
569 struct type *type = $1;
570 if (TYPE_CODE (type) != TYPE_CODE_STRUCT
571 && TYPE_CODE (type) != TYPE_CODE_UNION)
572 error ("`%s' is not defined as an aggregate type.",
575 write_exp_elt_opcode (OP_SCOPE);
576 write_exp_elt_type (type);
577 write_exp_string ($3);
578 write_exp_elt_opcode (OP_SCOPE);
580 | typebase COLONCOLON '~' name
582 struct type *type = $1;
583 struct stoken tmp_token;
584 if (TYPE_CODE (type) != TYPE_CODE_STRUCT
585 && TYPE_CODE (type) != TYPE_CODE_UNION)
586 error ("`%s' is not defined as an aggregate type.",
589 if (strcmp (type_name_no_tag (type), $4.ptr))
590 error ("invalid destructor `%s::~%s'",
591 type_name_no_tag (type), $4.ptr);
593 tmp_token.ptr = (char*) alloca ($4.length + 2);
594 tmp_token.length = $4.length + 1;
595 tmp_token.ptr[0] = '~';
596 memcpy (tmp_token.ptr+1, $4.ptr, $4.length);
597 tmp_token.ptr[tmp_token.length] = 0;
598 write_exp_elt_opcode (OP_SCOPE);
599 write_exp_elt_type (type);
600 write_exp_string (tmp_token);
601 write_exp_elt_opcode (OP_SCOPE);
605 variable: qualified_name
608 char *name = copy_name ($2);
610 struct minimal_symbol *msymbol;
613 lookup_symbol (name, 0, VAR_NAMESPACE, 0, NULL);
616 write_exp_elt_opcode (OP_VAR_VALUE);
617 write_exp_elt_sym (sym);
618 write_exp_elt_opcode (OP_VAR_VALUE);
622 msymbol = lookup_minimal_symbol (name,
623 (struct objfile *) NULL);
626 write_exp_elt_opcode (OP_LONG);
627 write_exp_elt_type (builtin_type_int);
628 write_exp_elt_longcst ((LONGEST) msymbol -> address);
629 write_exp_elt_opcode (OP_LONG);
630 write_exp_elt_opcode (UNOP_MEMVAL);
631 if (msymbol -> type == mst_data ||
632 msymbol -> type == mst_bss)
633 write_exp_elt_type (builtin_type_int);
634 else if (msymbol -> type == mst_text)
635 write_exp_elt_type (lookup_function_type (builtin_type_int));
637 write_exp_elt_type (builtin_type_char);
638 write_exp_elt_opcode (UNOP_MEMVAL);
641 if (!have_full_symbols () && !have_partial_symbols ())
642 error ("No symbol table is loaded. Use the \"file\" command.");
644 error ("No symbol \"%s\" in current context.", name);
648 variable: name_not_typename
649 { struct symbol *sym = $1.sym;
653 switch (SYMBOL_CLASS (sym))
661 if (innermost_block == 0 ||
662 contained_in (block_found,
664 innermost_block = block_found;
671 case LOC_CONST_BYTES:
673 /* In this case the expression can
674 be evaluated regardless of what
675 frame we are in, so there is no
676 need to check for the
677 innermost_block. These cases are
678 listed so that gcc -Wall will
679 report types that may not have
684 write_exp_elt_opcode (OP_VAR_VALUE);
685 write_exp_elt_sym (sym);
686 write_exp_elt_opcode (OP_VAR_VALUE);
688 else if ($1.is_a_field_of_this)
690 /* C++: it hangs off of `this'. Must
691 not inadvertently convert from a method call
693 if (innermost_block == 0 ||
694 contained_in (block_found, innermost_block))
695 innermost_block = block_found;
696 write_exp_elt_opcode (OP_THIS);
697 write_exp_elt_opcode (OP_THIS);
698 write_exp_elt_opcode (STRUCTOP_PTR);
699 write_exp_string ($1.stoken);
700 write_exp_elt_opcode (STRUCTOP_PTR);
704 struct minimal_symbol *msymbol;
705 register char *arg = copy_name ($1.stoken);
707 msymbol = lookup_minimal_symbol (arg,
708 (struct objfile *) NULL);
711 write_exp_elt_opcode (OP_LONG);
712 write_exp_elt_type (builtin_type_int);
713 write_exp_elt_longcst ((LONGEST) msymbol -> address);
714 write_exp_elt_opcode (OP_LONG);
715 write_exp_elt_opcode (UNOP_MEMVAL);
716 if (msymbol -> type == mst_data ||
717 msymbol -> type == mst_bss)
718 write_exp_elt_type (builtin_type_int);
719 else if (msymbol -> type == mst_text)
720 write_exp_elt_type (lookup_function_type (builtin_type_int));
722 write_exp_elt_type (builtin_type_char);
723 write_exp_elt_opcode (UNOP_MEMVAL);
725 else if (!have_full_symbols () && !have_partial_symbols ())
726 error ("No symbol table is loaded. Use the \"file\" command.");
728 error ("No symbol \"%s\" in current context.",
729 copy_name ($1.stoken));
738 /* This is where the interesting stuff happens. */
741 struct type *follow_type = $1;
750 follow_type = lookup_pointer_type (follow_type);
753 follow_type = lookup_reference_type (follow_type);
756 array_size = pop_type_int ();
757 if (array_size != -1)
758 follow_type = create_array_type (follow_type,
761 follow_type = lookup_pointer_type (follow_type);
764 follow_type = lookup_function_type (follow_type);
772 { push_type (tp_pointer); $$ = 0; }
774 { push_type (tp_pointer); $$ = $2; }
776 { push_type (tp_reference); $$ = 0; }
778 { push_type (tp_reference); $$ = $2; }
782 direct_abs_decl: '(' abs_decl ')'
784 | direct_abs_decl array_mod
787 push_type (tp_array);
792 push_type (tp_array);
795 | direct_abs_decl func_mod
796 { push_type (tp_function); }
798 { push_type (tp_function); }
809 | '(' nonempty_typelist ')'
810 { free ((PTR)$2); $$ = 0; }
814 | typebase COLONCOLON '*'
815 { $$ = lookup_member_type (builtin_type_int, $1); }
816 | type '(' typebase COLONCOLON '*' ')'
817 { $$ = lookup_member_type ($1, $3); }
818 | type '(' typebase COLONCOLON '*' ')' '(' ')'
819 { $$ = lookup_member_type
820 (lookup_function_type ($1), $3); }
821 | type '(' typebase COLONCOLON '*' ')' '(' nonempty_typelist ')'
822 { $$ = lookup_member_type
823 (lookup_function_type ($1), $3);
831 { $$ = builtin_type_int; }
833 { $$ = builtin_type_long; }
835 { $$ = builtin_type_short; }
837 { $$ = builtin_type_long; }
838 | UNSIGNED LONG INT_KEYWORD
839 { $$ = builtin_type_unsigned_long; }
841 { $$ = builtin_type_long_long; }
842 | LONG LONG INT_KEYWORD
843 { $$ = builtin_type_long_long; }
845 { $$ = builtin_type_unsigned_long_long; }
846 | UNSIGNED LONG LONG INT_KEYWORD
847 { $$ = builtin_type_unsigned_long_long; }
849 { $$ = builtin_type_short; }
850 | UNSIGNED SHORT INT_KEYWORD
851 { $$ = builtin_type_unsigned_short; }
853 { $$ = lookup_struct (copy_name ($2),
854 expression_context_block); }
856 { $$ = lookup_union (copy_name ($2),
857 expression_context_block); }
859 { $$ = lookup_enum (copy_name ($2),
860 expression_context_block); }
862 { $$ = lookup_unsigned_typename (TYPE_NAME($2.type)); }
864 { $$ = builtin_type_unsigned_int; }
865 | SIGNED_KEYWORD typename
868 { $$ = builtin_type_int; }
869 | TEMPLATE name '<' type '>'
870 { $$ = lookup_template_type(copy_name($2), $4,
871 expression_context_block);
878 $$.stoken.ptr = "int";
879 $$.stoken.length = 3;
880 $$.type = builtin_type_int;
884 $$.stoken.ptr = "long";
885 $$.stoken.length = 4;
886 $$.type = builtin_type_long;
890 $$.stoken.ptr = "short";
891 $$.stoken.length = 5;
892 $$.type = builtin_type_short;
898 { $$ = (struct type **) xmalloc (sizeof (struct type *) * 2);
899 $<ivec>$[0] = 1; /* Number of types in vector */
902 | nonempty_typelist ',' type
903 { int len = sizeof (struct type *) * (++($<ivec>1[0]) + 1);
904 $$ = (struct type **) xrealloc ((char *) $1, len);
905 $$[$<ivec>$[0]] = $3;
909 name : NAME { $$ = $1.stoken; }
910 | BLOCKNAME { $$ = $1.stoken; }
911 | TYPENAME { $$ = $1.stoken; }
912 | NAME_OR_INT { $$ = $1.stoken; }
913 | NAME_OR_UINT { $$ = $1.stoken; }
916 name_not_typename : NAME
918 /* These would be useful if name_not_typename was useful, but it is just
919 a fake for "variable", so these cause reduce/reduce conflicts because
920 the parser can't tell whether NAME_OR_INT is a name_not_typename (=variable,
921 =exp) or just an exp. If name_not_typename was ever used in an lvalue
922 context where only a name could occur, this might be useful.
930 /* Take care of parsing a number (anything that starts with a digit).
931 Set yylval and return the token type; update lexptr.
932 LEN is the number of characters in it. */
934 /*** Needs some error checking for the float case ***/
937 parse_number (p, len, parsed_float, putithere)
943 register LONGEST n = 0;
944 register LONGEST prevn = 0;
947 register int base = input_radix;
952 /* It's a float since it contains a point or an exponent. */
953 putithere->dval = atof (p);
957 /* Handle base-switching prefixes 0x, 0t, 0d, 0 */
991 if (c >= 'A' && c <= 'Z')
993 if (c != 'l' && c != 'u')
995 if (c >= '0' && c <= '9')
999 if (base > 10 && c >= 'a' && c <= 'f')
1000 n += i = c - 'a' + 10;
1001 else if (len == 0 && c == 'l')
1003 else if (len == 0 && c == 'u')
1006 return ERROR; /* Char not a digit */
1009 return ERROR; /* Invalid digit in this base */
1010 /* Portably test for overflow (only works for nonzero values, so make
1011 a second check for zero). */
1012 if((prevn >= n) && n != 0)
1013 unsigned_p=1; /* Try something unsigned */
1014 /* If range checking enabled, portably test for unsigned overflow. */
1015 if(RANGE_CHECK && n!=0)
1017 if((unsigned_p && (unsigned)prevn >= (unsigned)n))
1018 range_error("Overflow on numeric constant.");
1025 putithere->ulval = n;
1030 putithere->lval = n;
1039 enum exp_opcode opcode;
1042 const static struct token tokentab3[] =
1044 {">>=", ASSIGN_MODIFY, BINOP_RSH},
1045 {"<<=", ASSIGN_MODIFY, BINOP_LSH}
1048 const static struct token tokentab2[] =
1050 {"+=", ASSIGN_MODIFY, BINOP_ADD},
1051 {"-=", ASSIGN_MODIFY, BINOP_SUB},
1052 {"*=", ASSIGN_MODIFY, BINOP_MUL},
1053 {"/=", ASSIGN_MODIFY, BINOP_DIV},
1054 {"%=", ASSIGN_MODIFY, BINOP_REM},
1055 {"|=", ASSIGN_MODIFY, BINOP_LOGIOR},
1056 {"&=", ASSIGN_MODIFY, BINOP_LOGAND},
1057 {"^=", ASSIGN_MODIFY, BINOP_LOGXOR},
1058 {"++", INCREMENT, BINOP_END},
1059 {"--", DECREMENT, BINOP_END},
1060 {"->", ARROW, BINOP_END},
1061 {"&&", ANDAND, BINOP_END},
1062 {"||", OROR, BINOP_END},
1063 {"::", COLONCOLON, BINOP_END},
1064 {"<<", LSH, BINOP_END},
1065 {">>", RSH, BINOP_END},
1066 {"==", EQUAL, BINOP_END},
1067 {"!=", NOTEQUAL, BINOP_END},
1068 {"<=", LEQ, BINOP_END},
1069 {">=", GEQ, BINOP_END}
1072 /* Read one token, getting characters through lexptr. */
1078 register int namelen;
1079 register unsigned i;
1080 register char *tokstart;
1085 /* See if it is a special token of length 3. */
1086 for (i = 0; i < sizeof tokentab3 / sizeof tokentab3[0]; i++)
1087 if (!strncmp (tokstart, tokentab3[i].operator, 3))
1090 yylval.opcode = tokentab3[i].opcode;
1091 return tokentab3[i].token;
1094 /* See if it is a special token of length 2. */
1095 for (i = 0; i < sizeof tokentab2 / sizeof tokentab2[0]; i++)
1096 if (!strncmp (tokstart, tokentab2[i].operator, 2))
1099 yylval.opcode = tokentab2[i].opcode;
1100 return tokentab2[i].token;
1103 switch (c = *tokstart)
1115 /* We either have a character constant ('0' or '\177' for example)
1116 or we have a quoted symbol reference ('foo(int,int)' in C++
1121 c = parse_escape (&lexptr);
1126 namelen = skip_quoted (tokstart) - tokstart;
1129 lexptr = tokstart + namelen;
1134 error ("Invalid character constant.");
1144 if (paren_depth == 0)
1151 if (comma_terminates && paren_depth == 0)
1157 /* Might be a floating point number. */
1158 if (lexptr[1] < '0' || lexptr[1] > '9')
1159 goto symbol; /* Nope, must be a symbol. */
1160 /* FALL THRU into number case. */
1173 /* It's a number. */
1174 int got_dot = 0, got_e = 0, toktype;
1175 register char *p = tokstart;
1176 int hex = input_radix > 10;
1178 if (c == '0' && (p[1] == 'x' || p[1] == 'X'))
1183 else if (c == '0' && (p[1]=='t' || p[1]=='T' || p[1]=='d' || p[1]=='D'))
1191 if (!hex && !got_e && (*p == 'e' || *p == 'E'))
1192 got_dot = got_e = 1;
1193 else if (!hex && !got_dot && *p == '.')
1195 else if (got_e && (p[-1] == 'e' || p[-1] == 'E')
1196 && (*p == '-' || *p == '+'))
1197 /* This is the sign of the exponent, not the end of the
1200 /* We will take any letters or digits. parse_number will
1201 complain if past the radix, or if L or U are not final. */
1202 else if ((*p < '0' || *p > '9')
1203 && ((*p < 'a' || *p > 'z')
1204 && (*p < 'A' || *p > 'Z')))
1207 toktype = parse_number (tokstart, p - tokstart, got_dot|got_e, &yylval);
1208 if (toktype == ERROR)
1210 char *err_copy = (char *) alloca (p - tokstart + 1);
1212 bcopy (tokstart, err_copy, p - tokstart);
1213 err_copy[p - tokstart] = 0;
1214 error ("Invalid number \"%s\".", err_copy);
1245 for (namelen = 1; (c = tokstart[namelen]) != '"'; namelen++)
1248 c = tokstart[++namelen];
1249 if (c >= '0' && c <= '9')
1251 c = tokstart[++namelen];
1252 if (c >= '0' && c <= '9')
1253 c = tokstart[++namelen];
1256 yylval.sval.ptr = tokstart + 1;
1257 yylval.sval.length = namelen - 1;
1258 lexptr += namelen + 1;
1262 if (!(c == '_' || c == '$'
1263 || (c >= 'a' && c <= 'z') || (c >= 'A' && c <= 'Z')))
1264 /* We must have come across a bad character (e.g. ';'). */
1265 error ("Invalid character '%c' in expression.", c);
1267 /* It's a name. See how long it is. */
1269 for (c = tokstart[namelen];
1270 (c == '_' || c == '$' || (c >= '0' && c <= '9')
1271 || (c >= 'a' && c <= 'z') || (c >= 'A' && c <= 'Z'));
1272 c = tokstart[++namelen])
1275 /* The token "if" terminates the expression and is NOT
1276 removed from the input stream. */
1277 if (namelen == 2 && tokstart[0] == 'i' && tokstart[1] == 'f')
1284 /* Handle the tokens $digits; also $ (short for $0) and $$ (short for $$1)
1285 and $$digits (equivalent to $<-digits> if you could type that).
1286 Make token type LAST, and put the number (the digits) in yylval. */
1289 if (*tokstart == '$')
1291 register int negate = 0;
1293 /* Double dollar means negate the number and add -1 as well.
1294 Thus $$ alone means -1. */
1295 if (namelen >= 2 && tokstart[1] == '$')
1302 /* Just dollars (one or two) */
1303 yylval.lval = - negate;
1306 /* Is the rest of the token digits? */
1307 for (; c < namelen; c++)
1308 if (!(tokstart[c] >= '0' && tokstart[c] <= '9'))
1312 yylval.lval = atoi (tokstart + 1 + negate);
1314 yylval.lval = - yylval.lval;
1319 /* Handle tokens that refer to machine registers:
1320 $ followed by a register name. */
1322 if (*tokstart == '$') {
1323 for (c = 0; c < NUM_REGS; c++)
1324 if (namelen - 1 == strlen (reg_names[c])
1325 && !strncmp (tokstart + 1, reg_names[c], namelen - 1))
1330 for (c = 0; c < num_std_regs; c++)
1331 if (namelen - 1 == strlen (std_regs[c].name)
1332 && !strncmp (tokstart + 1, std_regs[c].name, namelen - 1))
1334 yylval.lval = std_regs[c].regnum;
1338 /* Catch specific keywords. Should be done with a data structure. */
1342 if (!strncmp (tokstart, "unsigned", 8))
1344 if (current_language->la_language == language_cplus
1345 && !strncmp (tokstart, "template", 8))
1349 if (!strncmp (tokstart, "struct", 6))
1351 if (!strncmp (tokstart, "signed", 6))
1352 return SIGNED_KEYWORD;
1353 if (!strncmp (tokstart, "sizeof", 6))
1357 if (!strncmp (tokstart, "union", 5))
1359 if (!strncmp (tokstart, "short", 5))
1363 if (!strncmp (tokstart, "enum", 4))
1365 if (!strncmp (tokstart, "long", 4))
1367 if (current_language->la_language == language_cplus
1368 && !strncmp (tokstart, "this", 4))
1370 static const char this_name[] =
1371 { CPLUS_MARKER, 't', 'h', 'i', 's', '\0' };
1373 if (lookup_symbol (this_name, expression_context_block,
1374 VAR_NAMESPACE, 0, NULL))
1379 if (!strncmp (tokstart, "int", 3))
1386 yylval.sval.ptr = tokstart;
1387 yylval.sval.length = namelen;
1389 /* Any other names starting in $ are debugger internal variables. */
1391 if (*tokstart == '$')
1393 yylval.ivar = lookup_internalvar (copy_name (yylval.sval) + 1);
1397 /* Use token-type BLOCKNAME for symbols that happen to be defined as
1398 functions or symtabs. If this is not so, then ...
1399 Use token-type TYPENAME for symbols that happen to be defined
1400 currently as names of types; NAME for other symbols.
1401 The caller is not constrained to care about the distinction. */
1403 char *tmp = copy_name (yylval.sval);
1405 int is_a_field_of_this = 0;
1408 sym = lookup_symbol (tmp, expression_context_block,
1410 current_language->la_language == language_cplus
1411 ? &is_a_field_of_this : NULL,
1413 if ((sym && SYMBOL_CLASS (sym) == LOC_BLOCK) ||
1414 lookup_partial_symtab (tmp))
1416 yylval.ssym.sym = sym;
1417 yylval.ssym.is_a_field_of_this = is_a_field_of_this;
1420 if (sym && SYMBOL_CLASS (sym) == LOC_TYPEDEF)
1422 yylval.tsym.type = SYMBOL_TYPE (sym);
1425 if ((yylval.tsym.type = lookup_primitive_typename (tmp)) != 0)
1428 /* Input names that aren't symbols but ARE valid hex numbers,
1429 when the input radix permits them, can be names or numbers
1430 depending on the parse. Note we support radixes > 16 here. */
1432 ((tokstart[0] >= 'a' && tokstart[0] < 'a' + input_radix - 10) ||
1433 (tokstart[0] >= 'A' && tokstart[0] < 'A' + input_radix - 10)))
1435 YYSTYPE newlval; /* Its value is ignored. */
1436 hextype = parse_number (tokstart, namelen, 0, &newlval);
1439 yylval.ssym.sym = sym;
1440 yylval.ssym.is_a_field_of_this = is_a_field_of_this;
1443 if (hextype == UINT)
1445 yylval.ssym.sym = sym;
1446 yylval.ssym.is_a_field_of_this = is_a_field_of_this;
1447 return NAME_OR_UINT;
1451 /* Any other kind of symbol */
1452 yylval.ssym.sym = sym;
1453 yylval.ssym.is_a_field_of_this = is_a_field_of_this;
1462 error (msg ? msg : "Invalid syntax in expression.");
1465 /* Table mapping opcodes into strings for printing operators
1466 and precedences of the operators. */
1468 const static struct op_print c_op_print_tab[] =
1470 {",", BINOP_COMMA, PREC_COMMA, 0},
1471 {"=", BINOP_ASSIGN, PREC_ASSIGN, 1},
1472 {"||", BINOP_OR, PREC_OR, 0},
1473 {"&&", BINOP_AND, PREC_AND, 0},
1474 {"|", BINOP_LOGIOR, PREC_LOGIOR, 0},
1475 {"&", BINOP_LOGAND, PREC_LOGAND, 0},
1476 {"^", BINOP_LOGXOR, PREC_LOGXOR, 0},
1477 {"==", BINOP_EQUAL, PREC_EQUAL, 0},
1478 {"!=", BINOP_NOTEQUAL, PREC_EQUAL, 0},
1479 {"<=", BINOP_LEQ, PREC_ORDER, 0},
1480 {">=", BINOP_GEQ, PREC_ORDER, 0},
1481 {">", BINOP_GTR, PREC_ORDER, 0},
1482 {"<", BINOP_LESS, PREC_ORDER, 0},
1483 {">>", BINOP_RSH, PREC_SHIFT, 0},
1484 {"<<", BINOP_LSH, PREC_SHIFT, 0},
1485 {"+", BINOP_ADD, PREC_ADD, 0},
1486 {"-", BINOP_SUB, PREC_ADD, 0},
1487 {"*", BINOP_MUL, PREC_MUL, 0},
1488 {"/", BINOP_DIV, PREC_MUL, 0},
1489 {"%", BINOP_REM, PREC_MUL, 0},
1490 {"@", BINOP_REPEAT, PREC_REPEAT, 0},
1491 {"-", UNOP_NEG, PREC_PREFIX, 0},
1492 {"!", UNOP_ZEROP, PREC_PREFIX, 0},
1493 {"~", UNOP_LOGNOT, PREC_PREFIX, 0},
1494 {"*", UNOP_IND, PREC_PREFIX, 0},
1495 {"&", UNOP_ADDR, PREC_PREFIX, 0},
1496 {"sizeof ", UNOP_SIZEOF, PREC_PREFIX, 0},
1497 {"++", UNOP_PREINCREMENT, PREC_PREFIX, 0},
1498 {"--", UNOP_PREDECREMENT, PREC_PREFIX, 0},
1500 {"::", BINOP_SCOPE, PREC_PREFIX, 0},
1503 /* These variables point to the objects
1504 representing the predefined C data types. */
1506 struct type *builtin_type_void;
1507 struct type *builtin_type_char;
1508 struct type *builtin_type_short;
1509 struct type *builtin_type_int;
1510 struct type *builtin_type_long;
1511 struct type *builtin_type_long_long;
1512 struct type *builtin_type_signed_char;
1513 struct type *builtin_type_unsigned_char;
1514 struct type *builtin_type_unsigned_short;
1515 struct type *builtin_type_unsigned_int;
1516 struct type *builtin_type_unsigned_long;
1517 struct type *builtin_type_unsigned_long_long;
1518 struct type *builtin_type_float;
1519 struct type *builtin_type_double;
1520 struct type *builtin_type_long_double;
1521 struct type *builtin_type_complex;
1522 struct type *builtin_type_double_complex;
1524 struct type ** const (c_builtin_types[]) =
1528 &builtin_type_short,
1530 &builtin_type_float,
1531 &builtin_type_double,
1533 &builtin_type_long_long,
1534 &builtin_type_signed_char,
1535 &builtin_type_unsigned_char,
1536 &builtin_type_unsigned_short,
1537 &builtin_type_unsigned_int,
1538 &builtin_type_unsigned_long,
1539 &builtin_type_unsigned_long_long,
1540 &builtin_type_long_double,
1541 &builtin_type_complex,
1542 &builtin_type_double_complex,
1546 const struct language_defn c_language_defn = {
1547 "c", /* Language name */
1554 &BUILTIN_TYPE_LONGEST, /* longest signed integral type */
1555 &BUILTIN_TYPE_UNSIGNED_LONGEST,/* longest unsigned integral type */
1556 &builtin_type_double, /* longest floating point type */ /*FIXME*/
1557 "0x%x", "0x%", "x", /* Hex format, prefix, suffix */
1558 "0%o", "0%", "o", /* Octal format, prefix, suffix */
1559 c_op_print_tab, /* expression operators for printing */
1563 const struct language_defn cplus_language_defn = {
1564 "c++", /* Language name */
1571 &BUILTIN_TYPE_LONGEST, /* longest signed integral type */
1572 &BUILTIN_TYPE_UNSIGNED_LONGEST,/* longest unsigned integral type */
1573 &builtin_type_double, /* longest floating point type */ /*FIXME*/
1574 "0x%x", "0x%", "x", /* Hex format, prefix, suffix */
1575 "0%o", "0%", "o", /* Octal format, prefix, suffix */
1576 c_op_print_tab, /* expression operators for printing */
1581 _initialize_c_exp ()
1584 init_type (TYPE_CODE_VOID, 1,
1586 "void", (struct objfile *) NULL);
1588 init_type (TYPE_CODE_INT, TARGET_CHAR_BIT / TARGET_CHAR_BIT,
1590 "char", (struct objfile *) NULL);
1591 builtin_type_signed_char =
1592 init_type (TYPE_CODE_INT, TARGET_CHAR_BIT / TARGET_CHAR_BIT,
1594 "signed char", (struct objfile *) NULL);
1595 builtin_type_unsigned_char =
1596 init_type (TYPE_CODE_INT, TARGET_CHAR_BIT / TARGET_CHAR_BIT,
1598 "unsigned char", (struct objfile *) NULL);
1599 builtin_type_short =
1600 init_type (TYPE_CODE_INT, TARGET_SHORT_BIT / TARGET_CHAR_BIT,
1602 "short", (struct objfile *) NULL);
1603 builtin_type_unsigned_short =
1604 init_type (TYPE_CODE_INT, TARGET_SHORT_BIT / TARGET_CHAR_BIT,
1606 "unsigned short", (struct objfile *) NULL);
1608 init_type (TYPE_CODE_INT, TARGET_INT_BIT / TARGET_CHAR_BIT,
1610 "int", (struct objfile *) NULL);
1611 builtin_type_unsigned_int =
1612 init_type (TYPE_CODE_INT, TARGET_INT_BIT / TARGET_CHAR_BIT,
1614 "unsigned int", (struct objfile *) NULL);
1616 init_type (TYPE_CODE_INT, TARGET_LONG_BIT / TARGET_CHAR_BIT,
1618 "long", (struct objfile *) NULL);
1619 builtin_type_unsigned_long =
1620 init_type (TYPE_CODE_INT, TARGET_LONG_BIT / TARGET_CHAR_BIT,
1622 "unsigned long", (struct objfile *) NULL);
1623 builtin_type_long_long =
1624 init_type (TYPE_CODE_INT, TARGET_LONG_LONG_BIT / TARGET_CHAR_BIT,
1626 "long long", (struct objfile *) NULL);
1627 builtin_type_unsigned_long_long =
1628 init_type (TYPE_CODE_INT, TARGET_LONG_LONG_BIT / TARGET_CHAR_BIT,
1630 "unsigned long long", (struct objfile *) NULL);
1631 builtin_type_float =
1632 init_type (TYPE_CODE_FLT, TARGET_FLOAT_BIT / TARGET_CHAR_BIT,
1634 "float", (struct objfile *) NULL);
1635 builtin_type_double =
1636 init_type (TYPE_CODE_FLT, TARGET_DOUBLE_BIT / TARGET_CHAR_BIT,
1638 "double", (struct objfile *) NULL);
1639 builtin_type_long_double =
1640 init_type (TYPE_CODE_FLT, TARGET_LONG_DOUBLE_BIT / TARGET_CHAR_BIT,
1642 "long double", (struct objfile *) NULL);
1643 builtin_type_complex =
1644 init_type (TYPE_CODE_FLT, TARGET_COMPLEX_BIT / TARGET_CHAR_BIT,
1646 "complex", (struct objfile *) NULL);
1647 builtin_type_double_complex =
1648 init_type (TYPE_CODE_FLT, TARGET_DOUBLE_COMPLEX_BIT / TARGET_CHAR_BIT,
1650 "double complex", (struct objfile *) NULL);
1652 add_language (&c_language_defn);
1653 add_language (&cplus_language_defn);