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. */
45 #include "expression.h"
46 #include "parser-defs.h"
53 /* These MUST be included in any grammar file!!!! Please choose unique names!
54 Note that this are a combined list of variables that can be produced
55 by any one of bison, byacc, or yacc. */
56 #define yymaxdepth c_maxdepth
57 #define yyparse c_parse
59 #define yyerror c_error
62 #define yydebug c_debug
71 #define yyerrflag c_errflag
72 #define yynerrs c_nerrs
77 #define yystate c_state
83 #define yyss c_yyss /* byacc */
84 #define yyssp c_yysp /* byacc */
85 #define yyvs c_yyvs /* byacc */
86 #define yyvsp c_yyvsp /* byacc */
89 yyparse PARAMS ((void));
92 yylex PARAMS ((void));
95 yyerror PARAMS ((char *));
97 /* #define YYDEBUG 1 */
101 /* Although the yacc "value" of an expression is not used,
102 since the result is stored in the structure being created,
103 other node types do have values. */
108 unsigned LONGEST ulval;
118 struct symtoken ssym;
121 enum exp_opcode opcode;
122 struct internalvar *ivar;
129 /* YYSTYPE gets defined by %union */
131 parse_number PARAMS ((char *, int, int, YYSTYPE *));
134 %type <voidval> exp exp1 type_exp start variable qualified_name
135 %type <tval> type typebase
136 %type <tvec> nonempty_typelist
137 /* %type <bval> block */
139 /* Fancy type parsing. */
140 %type <voidval> func_mod direct_abs_decl abs_decl
142 %type <lval> array_mod
144 %token <typed_val> INT
147 /* Both NAME and TYPENAME tokens represent symbols in the input,
148 and both convey their data as strings.
149 But a TYPENAME is a string that happens to be defined as a typedef
150 or builtin type name (such as int or char)
151 and a NAME is any other symbol.
152 Contexts where this distinction is not important can use the
153 nonterminal "name", which matches either NAME or TYPENAME. */
156 %token <ssym> NAME /* BLOCKNAME defined below to give it higher precedence. */
157 %token <tsym> TYPENAME
159 %type <ssym> name_not_typename
160 %type <tsym> typename
162 /* A NAME_OR_INT is a symbol which is not known in the symbol table,
163 but which would parse as a valid number in the current input radix.
164 E.g. "c" when input_radix==16. Depending on the parse, it will be
165 turned into a name or into a number. */
167 %token <ssym> NAME_OR_INT
169 %token STRUCT CLASS UNION ENUM SIZEOF UNSIGNED COLONCOLON
173 /* Special type cases, put in to allow the parser to distinguish different
175 %token SIGNED_KEYWORD LONG SHORT INT_KEYWORD CONST_KEYWORD VOLATILE_KEYWORD
176 %token <lval> LAST REGNAME
178 %token <ivar> VARIABLE
180 %token <opcode> ASSIGN_MODIFY
187 %right '=' ASSIGN_MODIFY
195 %left '<' '>' LEQ GEQ
200 %right UNARY INCREMENT DECREMENT
201 %right ARROW '.' '[' '('
202 %token <ssym> BLOCKNAME
214 { write_exp_elt_opcode(OP_TYPE);
215 write_exp_elt_type($1);
216 write_exp_elt_opcode(OP_TYPE);}
219 /* Expressions, including the comma operator. */
222 { write_exp_elt_opcode (BINOP_COMMA); }
225 /* Expressions, not including the comma operator. */
226 exp : '*' exp %prec UNARY
227 { write_exp_elt_opcode (UNOP_IND); }
229 exp : '&' exp %prec UNARY
230 { write_exp_elt_opcode (UNOP_ADDR); }
232 exp : '-' exp %prec UNARY
233 { write_exp_elt_opcode (UNOP_NEG); }
236 exp : '!' exp %prec UNARY
237 { write_exp_elt_opcode (UNOP_LOGICAL_NOT); }
240 exp : '~' exp %prec UNARY
241 { write_exp_elt_opcode (UNOP_COMPLEMENT); }
244 exp : INCREMENT exp %prec UNARY
245 { write_exp_elt_opcode (UNOP_PREINCREMENT); }
248 exp : DECREMENT exp %prec UNARY
249 { write_exp_elt_opcode (UNOP_PREDECREMENT); }
252 exp : exp INCREMENT %prec UNARY
253 { write_exp_elt_opcode (UNOP_POSTINCREMENT); }
256 exp : exp DECREMENT %prec UNARY
257 { write_exp_elt_opcode (UNOP_POSTDECREMENT); }
260 exp : SIZEOF exp %prec UNARY
261 { write_exp_elt_opcode (UNOP_SIZEOF); }
265 { write_exp_elt_opcode (STRUCTOP_PTR);
266 write_exp_string ($3);
267 write_exp_elt_opcode (STRUCTOP_PTR); }
270 exp : exp ARROW qualified_name
271 { /* exp->type::name becomes exp->*(&type::name) */
272 /* Note: this doesn't work if name is a
273 static member! FIXME */
274 write_exp_elt_opcode (UNOP_ADDR);
275 write_exp_elt_opcode (STRUCTOP_MPTR); }
277 exp : exp ARROW '*' exp
278 { write_exp_elt_opcode (STRUCTOP_MPTR); }
282 { write_exp_elt_opcode (STRUCTOP_STRUCT);
283 write_exp_string ($3);
284 write_exp_elt_opcode (STRUCTOP_STRUCT); }
287 exp : exp '.' qualified_name
288 { /* exp.type::name becomes exp.*(&type::name) */
289 /* Note: this doesn't work if name is a
290 static member! FIXME */
291 write_exp_elt_opcode (UNOP_ADDR);
292 write_exp_elt_opcode (STRUCTOP_MEMBER); }
295 exp : exp '.' '*' exp
296 { write_exp_elt_opcode (STRUCTOP_MEMBER); }
299 exp : exp '[' exp1 ']'
300 { write_exp_elt_opcode (BINOP_SUBSCRIPT); }
304 /* This is to save the value of arglist_len
305 being accumulated by an outer function call. */
306 { start_arglist (); }
307 arglist ')' %prec ARROW
308 { write_exp_elt_opcode (OP_FUNCALL);
309 write_exp_elt_longcst ((LONGEST) end_arglist ());
310 write_exp_elt_opcode (OP_FUNCALL); }
320 arglist : arglist ',' exp %prec ABOVE_COMMA
324 exp : '{' type '}' exp %prec UNARY
325 { write_exp_elt_opcode (UNOP_MEMVAL);
326 write_exp_elt_type ($2);
327 write_exp_elt_opcode (UNOP_MEMVAL); }
330 exp : '(' type ')' exp %prec UNARY
331 { write_exp_elt_opcode (UNOP_CAST);
332 write_exp_elt_type ($2);
333 write_exp_elt_opcode (UNOP_CAST); }
340 /* Binary operators in order of decreasing precedence. */
343 { write_exp_elt_opcode (BINOP_REPEAT); }
347 { write_exp_elt_opcode (BINOP_MUL); }
351 { write_exp_elt_opcode (BINOP_DIV); }
355 { write_exp_elt_opcode (BINOP_REM); }
359 { write_exp_elt_opcode (BINOP_ADD); }
363 { write_exp_elt_opcode (BINOP_SUB); }
367 { write_exp_elt_opcode (BINOP_LSH); }
371 { write_exp_elt_opcode (BINOP_RSH); }
375 { write_exp_elt_opcode (BINOP_EQUAL); }
378 exp : exp NOTEQUAL exp
379 { write_exp_elt_opcode (BINOP_NOTEQUAL); }
383 { write_exp_elt_opcode (BINOP_LEQ); }
387 { write_exp_elt_opcode (BINOP_GEQ); }
391 { write_exp_elt_opcode (BINOP_LESS); }
395 { write_exp_elt_opcode (BINOP_GTR); }
399 { write_exp_elt_opcode (BINOP_BITWISE_AND); }
403 { write_exp_elt_opcode (BINOP_BITWISE_XOR); }
407 { write_exp_elt_opcode (BINOP_BITWISE_IOR); }
411 { write_exp_elt_opcode (BINOP_LOGICAL_AND); }
415 { write_exp_elt_opcode (BINOP_LOGICAL_OR); }
418 exp : exp '?' exp ':' exp %prec '?'
419 { write_exp_elt_opcode (TERNOP_COND); }
423 { write_exp_elt_opcode (BINOP_ASSIGN); }
426 exp : exp ASSIGN_MODIFY exp
427 { write_exp_elt_opcode (BINOP_ASSIGN_MODIFY);
428 write_exp_elt_opcode ($2);
429 write_exp_elt_opcode (BINOP_ASSIGN_MODIFY); }
433 { write_exp_elt_opcode (OP_LONG);
434 write_exp_elt_type ($1.type);
435 write_exp_elt_longcst ((LONGEST)($1.val));
436 write_exp_elt_opcode (OP_LONG); }
441 parse_number ($1.stoken.ptr, $1.stoken.length, 0, &val);
442 write_exp_elt_opcode (OP_LONG);
443 write_exp_elt_type (val.typed_val.type);
444 write_exp_elt_longcst ((LONGEST)val.typed_val.val);
445 write_exp_elt_opcode (OP_LONG);
451 { write_exp_elt_opcode (OP_DOUBLE);
452 write_exp_elt_type (builtin_type_double);
453 write_exp_elt_dblcst ($1);
454 write_exp_elt_opcode (OP_DOUBLE); }
461 { write_exp_elt_opcode (OP_LAST);
462 write_exp_elt_longcst ((LONGEST) $1);
463 write_exp_elt_opcode (OP_LAST); }
467 { write_exp_elt_opcode (OP_REGISTER);
468 write_exp_elt_longcst ((LONGEST) $1);
469 write_exp_elt_opcode (OP_REGISTER); }
473 { write_exp_elt_opcode (OP_INTERNALVAR);
474 write_exp_elt_intern ($1);
475 write_exp_elt_opcode (OP_INTERNALVAR); }
478 exp : SIZEOF '(' type ')' %prec UNARY
479 { write_exp_elt_opcode (OP_LONG);
480 write_exp_elt_type (builtin_type_int);
481 write_exp_elt_longcst ((LONGEST) TYPE_LENGTH ($3));
482 write_exp_elt_opcode (OP_LONG); }
486 { write_exp_elt_opcode (OP_STRING);
487 write_exp_string ($1);
488 write_exp_elt_opcode (OP_STRING); }
493 { write_exp_elt_opcode (OP_THIS);
494 write_exp_elt_opcode (OP_THIS); }
502 $$ = SYMBOL_BLOCK_VALUE ($1.sym);
506 lookup_symtab (copy_name ($1.stoken));
508 $$ = BLOCKVECTOR_BLOCK
509 (BLOCKVECTOR (tem), STATIC_BLOCK);
511 error ("No file or function \"%s\".",
512 copy_name ($1.stoken));
517 block : block COLONCOLON name
519 = lookup_symbol (copy_name ($3), $1,
520 VAR_NAMESPACE, 0, NULL);
521 if (!tem || SYMBOL_CLASS (tem) != LOC_BLOCK)
522 error ("No function \"%s\" in specified context.",
524 $$ = SYMBOL_BLOCK_VALUE (tem); }
527 variable: block COLONCOLON name
528 { struct symbol *sym;
529 sym = lookup_symbol (copy_name ($3), $1,
530 VAR_NAMESPACE, 0, NULL);
532 error ("No symbol \"%s\" in specified context.",
535 write_exp_elt_opcode (OP_VAR_VALUE);
536 write_exp_elt_sym (sym);
537 write_exp_elt_opcode (OP_VAR_VALUE); }
540 qualified_name: typebase COLONCOLON name
542 struct type *type = $1;
543 if (TYPE_CODE (type) != TYPE_CODE_STRUCT
544 && TYPE_CODE (type) != TYPE_CODE_UNION)
545 error ("`%s' is not defined as an aggregate type.",
548 write_exp_elt_opcode (OP_SCOPE);
549 write_exp_elt_type (type);
550 write_exp_string ($3);
551 write_exp_elt_opcode (OP_SCOPE);
553 | typebase COLONCOLON '~' name
555 struct type *type = $1;
556 struct stoken tmp_token;
557 if (TYPE_CODE (type) != TYPE_CODE_STRUCT
558 && TYPE_CODE (type) != TYPE_CODE_UNION)
559 error ("`%s' is not defined as an aggregate type.",
562 if (strcmp (type_name_no_tag (type), $4.ptr))
563 error ("invalid destructor `%s::~%s'",
564 type_name_no_tag (type), $4.ptr);
566 tmp_token.ptr = (char*) alloca ($4.length + 2);
567 tmp_token.length = $4.length + 1;
568 tmp_token.ptr[0] = '~';
569 memcpy (tmp_token.ptr+1, $4.ptr, $4.length);
570 tmp_token.ptr[tmp_token.length] = 0;
571 write_exp_elt_opcode (OP_SCOPE);
572 write_exp_elt_type (type);
573 write_exp_string (tmp_token);
574 write_exp_elt_opcode (OP_SCOPE);
578 variable: qualified_name
581 char *name = copy_name ($2);
583 struct minimal_symbol *msymbol;
586 lookup_symbol (name, 0, VAR_NAMESPACE, 0, NULL);
589 write_exp_elt_opcode (OP_VAR_VALUE);
590 write_exp_elt_sym (sym);
591 write_exp_elt_opcode (OP_VAR_VALUE);
595 msymbol = lookup_minimal_symbol (name,
596 (struct objfile *) NULL);
599 write_exp_elt_opcode (OP_LONG);
600 write_exp_elt_type (builtin_type_int);
601 write_exp_elt_longcst ((LONGEST) msymbol -> address);
602 write_exp_elt_opcode (OP_LONG);
603 write_exp_elt_opcode (UNOP_MEMVAL);
604 if (msymbol -> type == mst_data ||
605 msymbol -> type == mst_bss)
606 write_exp_elt_type (builtin_type_int);
607 else if (msymbol -> type == mst_text)
608 write_exp_elt_type (lookup_function_type (builtin_type_int));
610 write_exp_elt_type (builtin_type_char);
611 write_exp_elt_opcode (UNOP_MEMVAL);
614 if (!have_full_symbols () && !have_partial_symbols ())
615 error ("No symbol table is loaded. Use the \"file\" command.");
617 error ("No symbol \"%s\" in current context.", name);
621 variable: name_not_typename
622 { struct symbol *sym = $1.sym;
626 switch (SYMBOL_CLASS (sym))
634 if (innermost_block == 0 ||
635 contained_in (block_found,
637 innermost_block = block_found;
644 case LOC_CONST_BYTES:
646 /* In this case the expression can
647 be evaluated regardless of what
648 frame we are in, so there is no
649 need to check for the
650 innermost_block. These cases are
651 listed so that gcc -Wall will
652 report types that may not have
657 write_exp_elt_opcode (OP_VAR_VALUE);
658 write_exp_elt_sym (sym);
659 write_exp_elt_opcode (OP_VAR_VALUE);
661 else if ($1.is_a_field_of_this)
663 /* C++: it hangs off of `this'. Must
664 not inadvertently convert from a method call
666 if (innermost_block == 0 ||
667 contained_in (block_found, innermost_block))
668 innermost_block = block_found;
669 write_exp_elt_opcode (OP_THIS);
670 write_exp_elt_opcode (OP_THIS);
671 write_exp_elt_opcode (STRUCTOP_PTR);
672 write_exp_string ($1.stoken);
673 write_exp_elt_opcode (STRUCTOP_PTR);
677 struct minimal_symbol *msymbol;
678 register char *arg = copy_name ($1.stoken);
680 msymbol = lookup_minimal_symbol (arg,
681 (struct objfile *) NULL);
684 write_exp_elt_opcode (OP_LONG);
685 write_exp_elt_type (builtin_type_int);
686 write_exp_elt_longcst ((LONGEST) msymbol -> address);
687 write_exp_elt_opcode (OP_LONG);
688 write_exp_elt_opcode (UNOP_MEMVAL);
689 if (msymbol -> type == mst_data ||
690 msymbol -> type == mst_bss)
691 write_exp_elt_type (builtin_type_int);
692 else if (msymbol -> type == mst_text)
693 write_exp_elt_type (lookup_function_type (builtin_type_int));
695 write_exp_elt_type (builtin_type_char);
696 write_exp_elt_opcode (UNOP_MEMVAL);
698 else if (!have_full_symbols () && !have_partial_symbols ())
699 error ("No symbol table is loaded. Use the \"file\" command.");
701 error ("No symbol \"%s\" in current context.",
702 copy_name ($1.stoken));
711 /* This is where the interesting stuff happens. */
714 struct type *follow_type = $1;
723 follow_type = lookup_pointer_type (follow_type);
726 follow_type = lookup_reference_type (follow_type);
729 array_size = pop_type_int ();
730 if (array_size != -1)
731 follow_type = create_array_type (follow_type,
734 follow_type = lookup_pointer_type (follow_type);
737 follow_type = lookup_function_type (follow_type);
745 { push_type (tp_pointer); $$ = 0; }
747 { push_type (tp_pointer); $$ = $2; }
749 { push_type (tp_reference); $$ = 0; }
751 { push_type (tp_reference); $$ = $2; }
755 direct_abs_decl: '(' abs_decl ')'
757 | direct_abs_decl array_mod
760 push_type (tp_array);
765 push_type (tp_array);
768 | direct_abs_decl func_mod
769 { push_type (tp_function); }
771 { push_type (tp_function); }
782 | '(' nonempty_typelist ')'
783 { free ((PTR)$2); $$ = 0; }
787 | typebase COLONCOLON '*'
788 { $$ = lookup_member_type (builtin_type_int, $1); }
789 | type '(' typebase COLONCOLON '*' ')'
790 { $$ = lookup_member_type ($1, $3); }
791 | type '(' typebase COLONCOLON '*' ')' '(' ')'
792 { $$ = lookup_member_type
793 (lookup_function_type ($1), $3); }
794 | type '(' typebase COLONCOLON '*' ')' '(' nonempty_typelist ')'
795 { $$ = lookup_member_type
796 (lookup_function_type ($1), $3);
800 typebase /* Implements (approximately): (type-qualifier)* type-specifier */
804 { $$ = builtin_type_int; }
806 { $$ = builtin_type_long; }
808 { $$ = builtin_type_short; }
810 { $$ = builtin_type_long; }
811 | UNSIGNED LONG INT_KEYWORD
812 { $$ = builtin_type_unsigned_long; }
814 { $$ = builtin_type_long_long; }
815 | LONG LONG INT_KEYWORD
816 { $$ = builtin_type_long_long; }
818 { $$ = builtin_type_unsigned_long_long; }
819 | UNSIGNED LONG LONG INT_KEYWORD
820 { $$ = builtin_type_unsigned_long_long; }
822 { $$ = builtin_type_short; }
823 | UNSIGNED SHORT INT_KEYWORD
824 { $$ = builtin_type_unsigned_short; }
826 { $$ = lookup_struct (copy_name ($2),
827 expression_context_block); }
829 { $$ = lookup_struct (copy_name ($2),
830 expression_context_block); }
832 { $$ = lookup_union (copy_name ($2),
833 expression_context_block); }
835 { $$ = lookup_enum (copy_name ($2),
836 expression_context_block); }
838 { $$ = lookup_unsigned_typename (TYPE_NAME($2.type)); }
840 { $$ = builtin_type_unsigned_int; }
841 | SIGNED_KEYWORD typename
842 { $$ = lookup_signed_typename (TYPE_NAME($2.type)); }
844 { $$ = builtin_type_int; }
845 | TEMPLATE name '<' type '>'
846 { $$ = lookup_template_type(copy_name($2), $4,
847 expression_context_block);
849 /* "const" and "volatile" are curently ignored. */
850 | CONST_KEYWORD typebase { $$ = $2; }
851 | VOLATILE_KEYWORD typebase { $$ = $2; }
857 $$.stoken.ptr = "int";
858 $$.stoken.length = 3;
859 $$.type = builtin_type_int;
863 $$.stoken.ptr = "long";
864 $$.stoken.length = 4;
865 $$.type = builtin_type_long;
869 $$.stoken.ptr = "short";
870 $$.stoken.length = 5;
871 $$.type = builtin_type_short;
877 { $$ = (struct type **) malloc (sizeof (struct type *) * 2);
878 $<ivec>$[0] = 1; /* Number of types in vector */
881 | nonempty_typelist ',' type
882 { int len = sizeof (struct type *) * (++($<ivec>1[0]) + 1);
883 $$ = (struct type **) realloc ((char *) $1, len);
884 $$[$<ivec>$[0]] = $3;
888 name : NAME { $$ = $1.stoken; }
889 | BLOCKNAME { $$ = $1.stoken; }
890 | TYPENAME { $$ = $1.stoken; }
891 | NAME_OR_INT { $$ = $1.stoken; }
894 name_not_typename : NAME
896 /* These would be useful if name_not_typename was useful, but it is just
897 a fake for "variable", so these cause reduce/reduce conflicts because
898 the parser can't tell whether NAME_OR_INT is a name_not_typename (=variable,
899 =exp) or just an exp. If name_not_typename was ever used in an lvalue
900 context where only a name could occur, this might be useful.
907 /* Take care of parsing a number (anything that starts with a digit).
908 Set yylval and return the token type; update lexptr.
909 LEN is the number of characters in it. */
911 /*** Needs some error checking for the float case ***/
914 parse_number (p, len, parsed_float, putithere)
920 register LONGEST n = 0;
921 register LONGEST prevn = 0;
924 register int base = input_radix;
928 struct type *signed_type;
929 struct type *unsigned_type;
933 /* It's a float since it contains a point or an exponent. */
934 putithere->dval = atof (p);
938 /* Handle base-switching prefixes 0x, 0t, 0d, 0 */
972 if (c >= 'A' && c <= 'Z')
974 if (c != 'l' && c != 'u')
976 if (c >= '0' && c <= '9')
980 if (base > 10 && c >= 'a' && c <= 'f')
981 n += i = c - 'a' + 10;
982 else if (len == 0 && c == 'l')
984 else if (len == 0 && c == 'u')
987 return ERROR; /* Char not a digit */
990 return ERROR; /* Invalid digit in this base */
992 /* Portably test for overflow (only works for nonzero values, so make
993 a second check for zero). */
994 if((prevn >= n) && n != 0)
995 unsigned_p=1; /* Try something unsigned */
996 /* If range checking enabled, portably test for unsigned overflow. */
997 if(RANGE_CHECK && n!=0)
999 if((unsigned_p && (unsigned)prevn >= (unsigned)n))
1000 range_error("Overflow on numeric constant.");
1005 /* If the number is too big to be an int, or it's got an l suffix
1006 then it's a long. Work out if this has to be a long by
1007 shifting right and and seeing if anything remains, and the
1008 target int size is different to the target long size. */
1010 if ((TARGET_INT_BIT != TARGET_LONG_BIT && (n >> TARGET_INT_BIT)) || long_p)
1012 high_bit = ((LONGEST)1) << (TARGET_LONG_BIT-1);
1013 unsigned_type = builtin_type_unsigned_long;
1014 signed_type = builtin_type_long;
1018 high_bit = ((LONGEST)1) << (TARGET_INT_BIT-1);
1019 unsigned_type = builtin_type_unsigned_int;
1020 signed_type = builtin_type_int;
1023 putithere->typed_val.val = n;
1025 /* If the high bit of the worked out type is set then this number
1026 has to be unsigned. */
1028 if (unsigned_p || (n & high_bit))
1030 putithere->typed_val.type = unsigned_type;
1034 putithere->typed_val.type = signed_type;
1044 enum exp_opcode opcode;
1047 const static struct token tokentab3[] =
1049 {">>=", ASSIGN_MODIFY, BINOP_RSH},
1050 {"<<=", ASSIGN_MODIFY, BINOP_LSH}
1053 const static struct token tokentab2[] =
1055 {"+=", ASSIGN_MODIFY, BINOP_ADD},
1056 {"-=", ASSIGN_MODIFY, BINOP_SUB},
1057 {"*=", ASSIGN_MODIFY, BINOP_MUL},
1058 {"/=", ASSIGN_MODIFY, BINOP_DIV},
1059 {"%=", ASSIGN_MODIFY, BINOP_REM},
1060 {"|=", ASSIGN_MODIFY, BINOP_BITWISE_IOR},
1061 {"&=", ASSIGN_MODIFY, BINOP_BITWISE_AND},
1062 {"^=", ASSIGN_MODIFY, BINOP_BITWISE_XOR},
1063 {"++", INCREMENT, BINOP_END},
1064 {"--", DECREMENT, BINOP_END},
1065 {"->", ARROW, BINOP_END},
1066 {"&&", ANDAND, BINOP_END},
1067 {"||", OROR, BINOP_END},
1068 {"::", COLONCOLON, BINOP_END},
1069 {"<<", LSH, BINOP_END},
1070 {">>", RSH, BINOP_END},
1071 {"==", EQUAL, BINOP_END},
1072 {"!=", NOTEQUAL, BINOP_END},
1073 {"<=", LEQ, BINOP_END},
1074 {">=", GEQ, BINOP_END}
1077 /* Read one token, getting characters through lexptr. */
1083 register int namelen;
1084 register unsigned i;
1085 register char *tokstart;
1090 /* See if it is a special token of length 3. */
1091 for (i = 0; i < sizeof tokentab3 / sizeof tokentab3[0]; i++)
1092 if (!strncmp (tokstart, tokentab3[i].operator, 3))
1095 yylval.opcode = tokentab3[i].opcode;
1096 return tokentab3[i].token;
1099 /* See if it is a special token of length 2. */
1100 for (i = 0; i < sizeof tokentab2 / sizeof tokentab2[0]; i++)
1101 if (!strncmp (tokstart, tokentab2[i].operator, 2))
1104 yylval.opcode = tokentab2[i].opcode;
1105 return tokentab2[i].token;
1108 switch (c = *tokstart)
1120 /* We either have a character constant ('0' or '\177' for example)
1121 or we have a quoted symbol reference ('foo(int,int)' in C++
1126 c = parse_escape (&lexptr);
1128 yylval.typed_val.val = c;
1129 yylval.typed_val.type = builtin_type_char;
1134 namelen = skip_quoted (tokstart) - tokstart;
1137 lexptr = tokstart + namelen;
1142 error ("Invalid character constant.");
1152 if (paren_depth == 0)
1159 if (comma_terminates && paren_depth == 0)
1165 /* Might be a floating point number. */
1166 if (lexptr[1] < '0' || lexptr[1] > '9')
1167 goto symbol; /* Nope, must be a symbol. */
1168 /* FALL THRU into number case. */
1181 /* It's a number. */
1182 int got_dot = 0, got_e = 0, toktype;
1183 register char *p = tokstart;
1184 int hex = input_radix > 10;
1186 if (c == '0' && (p[1] == 'x' || p[1] == 'X'))
1191 else if (c == '0' && (p[1]=='t' || p[1]=='T' || p[1]=='d' || p[1]=='D'))
1199 if (!hex && !got_e && (*p == 'e' || *p == 'E'))
1200 got_dot = got_e = 1;
1201 else if (!hex && !got_dot && *p == '.')
1203 else if (got_e && (p[-1] == 'e' || p[-1] == 'E')
1204 && (*p == '-' || *p == '+'))
1205 /* This is the sign of the exponent, not the end of the
1208 /* We will take any letters or digits. parse_number will
1209 complain if past the radix, or if L or U are not final. */
1210 else if ((*p < '0' || *p > '9')
1211 && ((*p < 'a' || *p > 'z')
1212 && (*p < 'A' || *p > 'Z')))
1215 toktype = parse_number (tokstart, p - tokstart, got_dot|got_e, &yylval);
1216 if (toktype == ERROR)
1218 char *err_copy = (char *) alloca (p - tokstart + 1);
1220 memcpy (err_copy, tokstart, p - tokstart);
1221 err_copy[p - tokstart] = 0;
1222 error ("Invalid number \"%s\".", err_copy);
1253 for (namelen = 1; (c = tokstart[namelen]) != '"'; namelen++)
1256 c = tokstart[++namelen];
1257 if (c >= '0' && c <= '9')
1259 c = tokstart[++namelen];
1260 if (c >= '0' && c <= '9')
1261 c = tokstart[++namelen];
1264 yylval.sval.ptr = tokstart + 1;
1265 yylval.sval.length = namelen - 1;
1266 lexptr += namelen + 1;
1270 if (!(c == '_' || c == '$'
1271 || (c >= 'a' && c <= 'z') || (c >= 'A' && c <= 'Z')))
1272 /* We must have come across a bad character (e.g. ';'). */
1273 error ("Invalid character '%c' in expression.", c);
1275 /* It's a name. See how long it is. */
1277 for (c = tokstart[namelen];
1278 (c == '_' || c == '$' || (c >= '0' && c <= '9')
1279 || (c >= 'a' && c <= 'z') || (c >= 'A' && c <= 'Z'));
1280 c = tokstart[++namelen])
1283 /* The token "if" terminates the expression and is NOT
1284 removed from the input stream. */
1285 if (namelen == 2 && tokstart[0] == 'i' && tokstart[1] == 'f')
1292 /* Handle the tokens $digits; also $ (short for $0) and $$ (short for $$1)
1293 and $$digits (equivalent to $<-digits> if you could type that).
1294 Make token type LAST, and put the number (the digits) in yylval. */
1297 if (*tokstart == '$')
1299 register int negate = 0;
1301 /* Double dollar means negate the number and add -1 as well.
1302 Thus $$ alone means -1. */
1303 if (namelen >= 2 && tokstart[1] == '$')
1310 /* Just dollars (one or two) */
1311 yylval.lval = - negate;
1314 /* Is the rest of the token digits? */
1315 for (; c < namelen; c++)
1316 if (!(tokstart[c] >= '0' && tokstart[c] <= '9'))
1320 yylval.lval = atoi (tokstart + 1 + negate);
1322 yylval.lval = - yylval.lval;
1327 /* Handle tokens that refer to machine registers:
1328 $ followed by a register name. */
1330 if (*tokstart == '$') {
1331 for (c = 0; c < NUM_REGS; c++)
1332 if (namelen - 1 == strlen (reg_names[c])
1333 && !strncmp (tokstart + 1, reg_names[c], namelen - 1))
1338 for (c = 0; c < num_std_regs; c++)
1339 if (namelen - 1 == strlen (std_regs[c].name)
1340 && !strncmp (tokstart + 1, std_regs[c].name, namelen - 1))
1342 yylval.lval = std_regs[c].regnum;
1346 /* Catch specific keywords. Should be done with a data structure. */
1350 if (!strncmp (tokstart, "unsigned", 8))
1352 if (current_language->la_language == language_cplus
1353 && !strncmp (tokstart, "template", 8))
1355 if (!strncmp (tokstart, "volatile", 8))
1356 return VOLATILE_KEYWORD;
1359 if (!strncmp (tokstart, "struct", 6))
1361 if (!strncmp (tokstart, "signed", 6))
1362 return SIGNED_KEYWORD;
1363 if (!strncmp (tokstart, "sizeof", 6))
1367 if (current_language->la_language == language_cplus
1368 && !strncmp (tokstart, "class", 5))
1370 if (!strncmp (tokstart, "union", 5))
1372 if (!strncmp (tokstart, "short", 5))
1374 if (!strncmp (tokstart, "const", 5))
1375 return CONST_KEYWORD;
1378 if (!strncmp (tokstart, "enum", 4))
1380 if (!strncmp (tokstart, "long", 4))
1382 if (current_language->la_language == language_cplus
1383 && !strncmp (tokstart, "this", 4))
1385 static const char this_name[] =
1386 { CPLUS_MARKER, 't', 'h', 'i', 's', '\0' };
1388 if (lookup_symbol (this_name, expression_context_block,
1389 VAR_NAMESPACE, 0, NULL))
1394 if (!strncmp (tokstart, "int", 3))
1401 yylval.sval.ptr = tokstart;
1402 yylval.sval.length = namelen;
1404 /* Any other names starting in $ are debugger internal variables. */
1406 if (*tokstart == '$')
1408 yylval.ivar = lookup_internalvar (copy_name (yylval.sval) + 1);
1412 /* Use token-type BLOCKNAME for symbols that happen to be defined as
1413 functions or symtabs. If this is not so, then ...
1414 Use token-type TYPENAME for symbols that happen to be defined
1415 currently as names of types; NAME for other symbols.
1416 The caller is not constrained to care about the distinction. */
1418 char *tmp = copy_name (yylval.sval);
1420 int is_a_field_of_this = 0;
1423 sym = lookup_symbol (tmp, expression_context_block,
1425 current_language->la_language == language_cplus
1426 ? &is_a_field_of_this : NULL,
1428 if ((sym && SYMBOL_CLASS (sym) == LOC_BLOCK) ||
1429 lookup_partial_symtab (tmp))
1431 yylval.ssym.sym = sym;
1432 yylval.ssym.is_a_field_of_this = is_a_field_of_this;
1435 if (sym && SYMBOL_CLASS (sym) == LOC_TYPEDEF)
1437 yylval.tsym.type = SYMBOL_TYPE (sym);
1440 if ((yylval.tsym.type = lookup_primitive_typename (tmp)) != 0)
1443 /* Input names that aren't symbols but ARE valid hex numbers,
1444 when the input radix permits them, can be names or numbers
1445 depending on the parse. Note we support radixes > 16 here. */
1447 ((tokstart[0] >= 'a' && tokstart[0] < 'a' + input_radix - 10) ||
1448 (tokstart[0] >= 'A' && tokstart[0] < 'A' + input_radix - 10)))
1450 YYSTYPE newlval; /* Its value is ignored. */
1451 hextype = parse_number (tokstart, namelen, 0, &newlval);
1454 yylval.ssym.sym = sym;
1455 yylval.ssym.is_a_field_of_this = is_a_field_of_this;
1460 /* Any other kind of symbol */
1461 yylval.ssym.sym = sym;
1462 yylval.ssym.is_a_field_of_this = is_a_field_of_this;
1471 error (msg ? msg : "Invalid syntax in expression.");
1474 /* Table mapping opcodes into strings for printing operators
1475 and precedences of the operators. */
1477 const static struct op_print c_op_print_tab[] =
1479 {",", BINOP_COMMA, PREC_COMMA, 0},
1480 {"=", BINOP_ASSIGN, PREC_ASSIGN, 1},
1481 {"||", BINOP_LOGICAL_OR, PREC_LOGICAL_OR, 0},
1482 {"&&", BINOP_LOGICAL_AND, PREC_LOGICAL_AND, 0},
1483 {"|", BINOP_BITWISE_IOR, PREC_BITWISE_IOR, 0},
1484 {"^", BINOP_BITWISE_XOR, PREC_BITWISE_XOR, 0},
1485 {"&", BINOP_BITWISE_AND, PREC_BITWISE_AND, 0},
1486 {"==", BINOP_EQUAL, PREC_EQUAL, 0},
1487 {"!=", BINOP_NOTEQUAL, PREC_EQUAL, 0},
1488 {"<=", BINOP_LEQ, PREC_ORDER, 0},
1489 {">=", BINOP_GEQ, PREC_ORDER, 0},
1490 {">", BINOP_GTR, PREC_ORDER, 0},
1491 {"<", BINOP_LESS, PREC_ORDER, 0},
1492 {">>", BINOP_RSH, PREC_SHIFT, 0},
1493 {"<<", BINOP_LSH, PREC_SHIFT, 0},
1494 {"+", BINOP_ADD, PREC_ADD, 0},
1495 {"-", BINOP_SUB, PREC_ADD, 0},
1496 {"*", BINOP_MUL, PREC_MUL, 0},
1497 {"/", BINOP_DIV, PREC_MUL, 0},
1498 {"%", BINOP_REM, PREC_MUL, 0},
1499 {"@", BINOP_REPEAT, PREC_REPEAT, 0},
1500 {"-", UNOP_NEG, PREC_PREFIX, 0},
1501 {"!", UNOP_LOGICAL_NOT, PREC_PREFIX, 0},
1502 {"~", UNOP_COMPLEMENT, PREC_PREFIX, 0},
1503 {"*", UNOP_IND, PREC_PREFIX, 0},
1504 {"&", UNOP_ADDR, PREC_PREFIX, 0},
1505 {"sizeof ", UNOP_SIZEOF, PREC_PREFIX, 0},
1506 {"++", UNOP_PREINCREMENT, PREC_PREFIX, 0},
1507 {"--", UNOP_PREDECREMENT, PREC_PREFIX, 0},
1509 {"::", BINOP_SCOPE, PREC_PREFIX, 0},
1513 /* These variables point to the objects
1514 representing the predefined C data types. */
1516 struct type *builtin_type_void;
1517 struct type *builtin_type_char;
1518 struct type *builtin_type_short;
1519 struct type *builtin_type_int;
1520 struct type *builtin_type_long;
1521 struct type *builtin_type_long_long;
1522 struct type *builtin_type_signed_char;
1523 struct type *builtin_type_unsigned_char;
1524 struct type *builtin_type_unsigned_short;
1525 struct type *builtin_type_unsigned_int;
1526 struct type *builtin_type_unsigned_long;
1527 struct type *builtin_type_unsigned_long_long;
1528 struct type *builtin_type_float;
1529 struct type *builtin_type_double;
1530 struct type *builtin_type_long_double;
1531 struct type *builtin_type_complex;
1532 struct type *builtin_type_double_complex;
1534 struct type ** const (c_builtin_types[]) =
1538 &builtin_type_short,
1540 &builtin_type_float,
1541 &builtin_type_double,
1543 &builtin_type_long_long,
1544 &builtin_type_signed_char,
1545 &builtin_type_unsigned_char,
1546 &builtin_type_unsigned_short,
1547 &builtin_type_unsigned_int,
1548 &builtin_type_unsigned_long,
1549 &builtin_type_unsigned_long_long,
1550 &builtin_type_long_double,
1551 &builtin_type_complex,
1552 &builtin_type_double_complex,
1556 const struct language_defn c_language_defn = {
1557 "c", /* Language name */
1564 &BUILTIN_TYPE_LONGEST, /* longest signed integral type */
1565 &BUILTIN_TYPE_UNSIGNED_LONGEST,/* longest unsigned integral type */
1566 &builtin_type_double, /* longest floating point type */ /*FIXME*/
1567 "0x%x", "0x%", "x", /* Hex format, prefix, suffix */
1568 "0%o", "0%", "o", /* Octal format, prefix, suffix */
1569 c_op_print_tab, /* expression operators for printing */
1573 const struct language_defn cplus_language_defn = {
1574 "c++", /* Language name */
1581 &BUILTIN_TYPE_LONGEST, /* longest signed integral type */
1582 &BUILTIN_TYPE_UNSIGNED_LONGEST,/* longest unsigned integral type */
1583 &builtin_type_double, /* longest floating point type */ /*FIXME*/
1584 "0x%x", "0x%", "x", /* Hex format, prefix, suffix */
1585 "0%o", "0%", "o", /* Octal format, prefix, suffix */
1586 c_op_print_tab, /* expression operators for printing */
1591 _initialize_c_exp ()
1594 init_type (TYPE_CODE_VOID, 1,
1596 "void", (struct objfile *) NULL);
1598 init_type (TYPE_CODE_INT, TARGET_CHAR_BIT / TARGET_CHAR_BIT,
1600 "char", (struct objfile *) NULL);
1601 builtin_type_signed_char =
1602 init_type (TYPE_CODE_INT, TARGET_CHAR_BIT / TARGET_CHAR_BIT,
1604 "signed char", (struct objfile *) NULL);
1605 builtin_type_unsigned_char =
1606 init_type (TYPE_CODE_INT, TARGET_CHAR_BIT / TARGET_CHAR_BIT,
1608 "unsigned char", (struct objfile *) NULL);
1609 builtin_type_short =
1610 init_type (TYPE_CODE_INT, TARGET_SHORT_BIT / TARGET_CHAR_BIT,
1612 "short", (struct objfile *) NULL);
1613 builtin_type_unsigned_short =
1614 init_type (TYPE_CODE_INT, TARGET_SHORT_BIT / TARGET_CHAR_BIT,
1616 "unsigned short", (struct objfile *) NULL);
1618 init_type (TYPE_CODE_INT, TARGET_INT_BIT / TARGET_CHAR_BIT,
1620 "int", (struct objfile *) NULL);
1621 builtin_type_unsigned_int =
1622 init_type (TYPE_CODE_INT, TARGET_INT_BIT / TARGET_CHAR_BIT,
1624 "unsigned int", (struct objfile *) NULL);
1626 init_type (TYPE_CODE_INT, TARGET_LONG_BIT / TARGET_CHAR_BIT,
1628 "long", (struct objfile *) NULL);
1629 builtin_type_unsigned_long =
1630 init_type (TYPE_CODE_INT, TARGET_LONG_BIT / TARGET_CHAR_BIT,
1632 "unsigned long", (struct objfile *) NULL);
1633 builtin_type_long_long =
1634 init_type (TYPE_CODE_INT, TARGET_LONG_LONG_BIT / TARGET_CHAR_BIT,
1636 "long long", (struct objfile *) NULL);
1637 builtin_type_unsigned_long_long =
1638 init_type (TYPE_CODE_INT, TARGET_LONG_LONG_BIT / TARGET_CHAR_BIT,
1640 "unsigned long long", (struct objfile *) NULL);
1641 builtin_type_float =
1642 init_type (TYPE_CODE_FLT, TARGET_FLOAT_BIT / TARGET_CHAR_BIT,
1644 "float", (struct objfile *) NULL);
1645 builtin_type_double =
1646 init_type (TYPE_CODE_FLT, TARGET_DOUBLE_BIT / TARGET_CHAR_BIT,
1648 "double", (struct objfile *) NULL);
1649 builtin_type_long_double =
1650 init_type (TYPE_CODE_FLT, TARGET_LONG_DOUBLE_BIT / TARGET_CHAR_BIT,
1652 "long double", (struct objfile *) NULL);
1653 builtin_type_complex =
1654 init_type (TYPE_CODE_FLT, TARGET_COMPLEX_BIT / TARGET_CHAR_BIT,
1656 "complex", (struct objfile *) NULL);
1657 builtin_type_double_complex =
1658 init_type (TYPE_CODE_FLT, TARGET_DOUBLE_COMPLEX_BIT / TARGET_CHAR_BIT,
1660 "double complex", (struct objfile *) NULL);
1662 add_language (&c_language_defn);
1663 add_language (&cplus_language_defn);