1 /* YACC parser for Pascal expressions, for GDB.
2 Copyright (C) 2000-2018 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 3 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, see <http://www.gnu.org/licenses/>. */
19 /* This file is derived from c-exp.y */
21 /* Parse a Pascal expression from text in a string,
22 and return the result as a struct expression pointer.
23 That structure contains arithmetic operations in reverse polish,
24 with constants represented by operations that are followed by special data.
25 See expression.h for the details of the format.
26 What is important here is that it can be built up sequentially
27 during the process of parsing; the lower levels of the tree always
28 come first in the result.
30 Note that malloc's and realloc's in this file are transformed to
31 xmalloc and xrealloc respectively by the same sed command in the
32 makefile that remaps any other malloc/realloc inserted by the parser
33 generator. Doing this with #defines and trying to control the interaction
34 with include files (<malloc.h> and <stdlib.h> for example) just became
35 too messy, particularly when such includes can be inserted at random
36 times by the parser generator. */
38 /* Known bugs or limitations:
39 - pascal string operations are not supported at all.
40 - there are some problems with boolean types.
41 - Pascal type hexadecimal constants are not supported
42 because they conflict with the internal variables format.
43 Probably also lots of other problems, less well defined PM. */
48 #include "expression.h"
50 #include "parser-defs.h"
53 #include "bfd.h" /* Required by objfiles.h. */
54 #include "symfile.h" /* Required by objfiles.h. */
55 #include "objfiles.h" /* For have_full_symbols and have_partial_symbols. */
57 #include "completer.h"
59 #define parse_type(ps) builtin_type (parse_gdbarch (ps))
61 /* Remap normal yacc parser interface names (yyparse, yylex, yyerror,
63 #define GDB_YY_REMAP_PREFIX pascal_
66 /* The state of the parser, used internally when we are parsing the
69 static struct parser_state *pstate = NULL;
73 static int yylex (void);
75 void yyerror (const char *);
77 static char *uptok (const char *, int);
80 /* Although the yacc "value" of an expression is not used,
81 since the result is stored in the structure being created,
82 other node types do have values. */
101 const struct block *bval;
102 enum exp_opcode opcode;
103 struct internalvar *ivar;
110 /* YYSTYPE gets defined by %union */
111 static int parse_number (struct parser_state *,
112 const char *, int, int, YYSTYPE *);
114 static struct type *current_type;
115 static struct internalvar *intvar;
116 static int leftdiv_is_integer;
117 static void push_current_type (void);
118 static void pop_current_type (void);
119 static int search_field;
122 %type <voidval> exp exp1 type_exp start normal_start variable qualified_name
123 %type <tval> type typebase
124 /* %type <bval> block */
126 /* Fancy type parsing. */
129 %token <typed_val_int> INT
130 %token <typed_val_float> FLOAT
132 /* Both NAME and TYPENAME tokens represent symbols in the input,
133 and both convey their data as strings.
134 But a TYPENAME is a string that happens to be defined as a typedef
135 or builtin type name (such as int or char)
136 and a NAME is any other symbol.
137 Contexts where this distinction is not important can use the
138 nonterminal "name", which matches either NAME or TYPENAME. */
141 %token <sval> FIELDNAME
142 %token <voidval> COMPLETE
143 %token <ssym> NAME /* BLOCKNAME defined below to give it higher precedence. */
144 %token <tsym> TYPENAME
146 %type <ssym> name_not_typename
148 /* A NAME_OR_INT is a symbol which is not known in the symbol table,
149 but which would parse as a valid number in the current input radix.
150 E.g. "c" when input_radix==16. Depending on the parse, it will be
151 turned into a name or into a number. */
153 %token <ssym> NAME_OR_INT
155 %token STRUCT CLASS SIZEOF COLONCOLON
158 /* Special type cases, put in to allow the parser to distinguish different
161 %token <voidval> VARIABLE
166 %token <lval> TRUEKEYWORD FALSEKEYWORD
176 %left '<' '>' LEQ GEQ
177 %left LSH RSH DIV MOD
181 %right UNARY INCREMENT DECREMENT
182 %right ARROW '.' '[' '('
184 %token <ssym> BLOCKNAME
191 start : { current_type = NULL;
194 leftdiv_is_integer = 0;
205 { write_exp_elt_opcode (pstate, OP_TYPE);
206 write_exp_elt_type (pstate, $1);
207 write_exp_elt_opcode (pstate, OP_TYPE);
208 current_type = $1; } ;
210 /* Expressions, including the comma operator. */
213 { write_exp_elt_opcode (pstate, BINOP_COMMA); }
216 /* Expressions, not including the comma operator. */
217 exp : exp '^' %prec UNARY
218 { write_exp_elt_opcode (pstate, UNOP_IND);
220 current_type = TYPE_TARGET_TYPE (current_type); }
223 exp : '@' exp %prec UNARY
224 { write_exp_elt_opcode (pstate, UNOP_ADDR);
226 current_type = TYPE_POINTER_TYPE (current_type); }
229 exp : '-' exp %prec UNARY
230 { write_exp_elt_opcode (pstate, UNOP_NEG); }
233 exp : NOT exp %prec UNARY
234 { write_exp_elt_opcode (pstate, UNOP_LOGICAL_NOT); }
237 exp : INCREMENT '(' exp ')' %prec UNARY
238 { write_exp_elt_opcode (pstate, UNOP_PREINCREMENT); }
241 exp : DECREMENT '(' exp ')' %prec UNARY
242 { write_exp_elt_opcode (pstate, UNOP_PREDECREMENT); }
246 field_exp : exp '.' %prec UNARY
247 { search_field = 1; }
250 exp : field_exp FIELDNAME
251 { write_exp_elt_opcode (pstate, STRUCTOP_STRUCT);
252 write_exp_string (pstate, $2);
253 write_exp_elt_opcode (pstate, STRUCTOP_STRUCT);
257 while (TYPE_CODE (current_type)
260 TYPE_TARGET_TYPE (current_type);
261 current_type = lookup_struct_elt_type (
262 current_type, $2.ptr, 0);
269 { write_exp_elt_opcode (pstate, STRUCTOP_STRUCT);
270 write_exp_string (pstate, $2);
271 write_exp_elt_opcode (pstate, STRUCTOP_STRUCT);
275 while (TYPE_CODE (current_type)
278 TYPE_TARGET_TYPE (current_type);
279 current_type = lookup_struct_elt_type (
280 current_type, $2.ptr, 0);
284 exp : field_exp name COMPLETE
285 { mark_struct_expression (pstate);
286 write_exp_elt_opcode (pstate, STRUCTOP_STRUCT);
287 write_exp_string (pstate, $2);
288 write_exp_elt_opcode (pstate, STRUCTOP_STRUCT); }
290 exp : field_exp COMPLETE
292 mark_struct_expression (pstate);
293 write_exp_elt_opcode (pstate, STRUCTOP_STRUCT);
296 write_exp_string (pstate, s);
297 write_exp_elt_opcode (pstate, STRUCTOP_STRUCT); }
301 /* We need to save the current_type value. */
302 { const char *arrayname;
304 arrayfieldindex = is_pascal_string_type (
305 current_type, NULL, NULL,
306 NULL, NULL, &arrayname);
309 struct stoken stringsval;
312 buf = (char *) alloca (strlen (arrayname) + 1);
313 stringsval.ptr = buf;
314 stringsval.length = strlen (arrayname);
315 strcpy (buf, arrayname);
316 current_type = TYPE_FIELD_TYPE (current_type,
317 arrayfieldindex - 1);
318 write_exp_elt_opcode (pstate, STRUCTOP_STRUCT);
319 write_exp_string (pstate, stringsval);
320 write_exp_elt_opcode (pstate, STRUCTOP_STRUCT);
322 push_current_type (); }
324 { pop_current_type ();
325 write_exp_elt_opcode (pstate, BINOP_SUBSCRIPT);
327 current_type = TYPE_TARGET_TYPE (current_type); }
331 /* This is to save the value of arglist_len
332 being accumulated by an outer function call. */
333 { push_current_type ();
335 arglist ')' %prec ARROW
336 { write_exp_elt_opcode (pstate, OP_FUNCALL);
337 write_exp_elt_longcst (pstate,
338 (LONGEST) end_arglist ());
339 write_exp_elt_opcode (pstate, OP_FUNCALL);
342 current_type = TYPE_TARGET_TYPE (current_type);
349 | arglist ',' exp %prec ABOVE_COMMA
353 exp : type '(' exp ')' %prec UNARY
356 /* Allow automatic dereference of classes. */
357 if ((TYPE_CODE (current_type) == TYPE_CODE_PTR)
358 && (TYPE_CODE (TYPE_TARGET_TYPE (current_type)) == TYPE_CODE_STRUCT)
359 && (TYPE_CODE ($1) == TYPE_CODE_STRUCT))
360 write_exp_elt_opcode (pstate, UNOP_IND);
362 write_exp_elt_opcode (pstate, UNOP_CAST);
363 write_exp_elt_type (pstate, $1);
364 write_exp_elt_opcode (pstate, UNOP_CAST);
372 /* Binary operators in order of decreasing precedence. */
375 { write_exp_elt_opcode (pstate, BINOP_MUL); }
379 if (current_type && is_integral_type (current_type))
380 leftdiv_is_integer = 1;
384 if (leftdiv_is_integer && current_type
385 && is_integral_type (current_type))
387 write_exp_elt_opcode (pstate, UNOP_CAST);
388 write_exp_elt_type (pstate,
390 ->builtin_long_double);
392 = parse_type (pstate)->builtin_long_double;
393 write_exp_elt_opcode (pstate, UNOP_CAST);
394 leftdiv_is_integer = 0;
397 write_exp_elt_opcode (pstate, BINOP_DIV);
402 { write_exp_elt_opcode (pstate, BINOP_INTDIV); }
406 { write_exp_elt_opcode (pstate, BINOP_REM); }
410 { write_exp_elt_opcode (pstate, BINOP_ADD); }
414 { write_exp_elt_opcode (pstate, BINOP_SUB); }
418 { write_exp_elt_opcode (pstate, BINOP_LSH); }
422 { write_exp_elt_opcode (pstate, BINOP_RSH); }
426 { write_exp_elt_opcode (pstate, BINOP_EQUAL);
427 current_type = parse_type (pstate)->builtin_bool;
431 exp : exp NOTEQUAL exp
432 { write_exp_elt_opcode (pstate, BINOP_NOTEQUAL);
433 current_type = parse_type (pstate)->builtin_bool;
438 { write_exp_elt_opcode (pstate, BINOP_LEQ);
439 current_type = parse_type (pstate)->builtin_bool;
444 { write_exp_elt_opcode (pstate, BINOP_GEQ);
445 current_type = parse_type (pstate)->builtin_bool;
450 { write_exp_elt_opcode (pstate, BINOP_LESS);
451 current_type = parse_type (pstate)->builtin_bool;
456 { write_exp_elt_opcode (pstate, BINOP_GTR);
457 current_type = parse_type (pstate)->builtin_bool;
462 { write_exp_elt_opcode (pstate, BINOP_BITWISE_AND); }
466 { write_exp_elt_opcode (pstate, BINOP_BITWISE_XOR); }
470 { write_exp_elt_opcode (pstate, BINOP_BITWISE_IOR); }
474 { write_exp_elt_opcode (pstate, BINOP_ASSIGN); }
478 { write_exp_elt_opcode (pstate, OP_BOOL);
479 write_exp_elt_longcst (pstate, (LONGEST) $1);
480 current_type = parse_type (pstate)->builtin_bool;
481 write_exp_elt_opcode (pstate, OP_BOOL); }
485 { write_exp_elt_opcode (pstate, OP_BOOL);
486 write_exp_elt_longcst (pstate, (LONGEST) $1);
487 current_type = parse_type (pstate)->builtin_bool;
488 write_exp_elt_opcode (pstate, OP_BOOL); }
492 { write_exp_elt_opcode (pstate, OP_LONG);
493 write_exp_elt_type (pstate, $1.type);
494 current_type = $1.type;
495 write_exp_elt_longcst (pstate, (LONGEST)($1.val));
496 write_exp_elt_opcode (pstate, OP_LONG); }
501 parse_number (pstate, $1.stoken.ptr,
502 $1.stoken.length, 0, &val);
503 write_exp_elt_opcode (pstate, OP_LONG);
504 write_exp_elt_type (pstate, val.typed_val_int.type);
505 current_type = val.typed_val_int.type;
506 write_exp_elt_longcst (pstate, (LONGEST)
507 val.typed_val_int.val);
508 write_exp_elt_opcode (pstate, OP_LONG);
514 { write_exp_elt_opcode (pstate, OP_FLOAT);
515 write_exp_elt_type (pstate, $1.type);
516 current_type = $1.type;
517 write_exp_elt_floatcst (pstate, $1.val);
518 write_exp_elt_opcode (pstate, OP_FLOAT); }
525 /* Already written by write_dollar_variable.
526 Handle current_type. */
528 struct value * val, * mark;
530 mark = value_mark ();
531 val = value_of_internalvar (parse_gdbarch (pstate),
533 current_type = value_type (val);
534 value_release_to_mark (mark);
539 exp : SIZEOF '(' type ')' %prec UNARY
540 { write_exp_elt_opcode (pstate, OP_LONG);
541 write_exp_elt_type (pstate,
542 parse_type (pstate)->builtin_int);
543 current_type = parse_type (pstate)->builtin_int;
544 $3 = check_typedef ($3);
545 write_exp_elt_longcst (pstate,
546 (LONGEST) TYPE_LENGTH ($3));
547 write_exp_elt_opcode (pstate, OP_LONG); }
550 exp : SIZEOF '(' exp ')' %prec UNARY
551 { write_exp_elt_opcode (pstate, UNOP_SIZEOF);
552 current_type = parse_type (pstate)->builtin_int; }
555 { /* C strings are converted into array constants with
556 an explicit null byte added at the end. Thus
557 the array upper bound is the string length.
558 There is no such thing in C as a completely empty
560 const char *sp = $1.ptr; int count = $1.length;
564 write_exp_elt_opcode (pstate, OP_LONG);
565 write_exp_elt_type (pstate,
568 write_exp_elt_longcst (pstate,
570 write_exp_elt_opcode (pstate, OP_LONG);
572 write_exp_elt_opcode (pstate, OP_LONG);
573 write_exp_elt_type (pstate,
576 write_exp_elt_longcst (pstate, (LONGEST)'\0');
577 write_exp_elt_opcode (pstate, OP_LONG);
578 write_exp_elt_opcode (pstate, OP_ARRAY);
579 write_exp_elt_longcst (pstate, (LONGEST) 0);
580 write_exp_elt_longcst (pstate,
581 (LONGEST) ($1.length));
582 write_exp_elt_opcode (pstate, OP_ARRAY); }
588 struct value * this_val;
589 struct type * this_type;
590 write_exp_elt_opcode (pstate, OP_THIS);
591 write_exp_elt_opcode (pstate, OP_THIS);
592 /* We need type of this. */
594 = value_of_this_silent (parse_language (pstate));
596 this_type = value_type (this_val);
601 if (TYPE_CODE (this_type) == TYPE_CODE_PTR)
603 this_type = TYPE_TARGET_TYPE (this_type);
604 write_exp_elt_opcode (pstate, UNOP_IND);
608 current_type = this_type;
612 /* end of object pascal. */
616 if ($1.sym.symbol != 0)
617 $$ = SYMBOL_BLOCK_VALUE ($1.sym.symbol);
621 lookup_symtab (copy_name ($1.stoken));
623 $$ = BLOCKVECTOR_BLOCK (SYMTAB_BLOCKVECTOR (tem),
626 error (_("No file or function \"%s\"."),
627 copy_name ($1.stoken));
632 block : block COLONCOLON name
634 = lookup_symbol (copy_name ($3), $1,
635 VAR_DOMAIN, NULL).symbol;
637 if (!tem || SYMBOL_CLASS (tem) != LOC_BLOCK)
638 error (_("No function \"%s\" in specified context."),
640 $$ = SYMBOL_BLOCK_VALUE (tem); }
643 variable: block COLONCOLON name
644 { struct block_symbol sym;
646 sym = lookup_symbol (copy_name ($3), $1,
649 error (_("No symbol \"%s\" in specified context."),
652 write_exp_elt_opcode (pstate, OP_VAR_VALUE);
653 write_exp_elt_block (pstate, sym.block);
654 write_exp_elt_sym (pstate, sym.symbol);
655 write_exp_elt_opcode (pstate, OP_VAR_VALUE); }
658 qualified_name: typebase COLONCOLON name
660 struct type *type = $1;
662 if (TYPE_CODE (type) != TYPE_CODE_STRUCT
663 && TYPE_CODE (type) != TYPE_CODE_UNION)
664 error (_("`%s' is not defined as an aggregate type."),
667 write_exp_elt_opcode (pstate, OP_SCOPE);
668 write_exp_elt_type (pstate, type);
669 write_exp_string (pstate, $3);
670 write_exp_elt_opcode (pstate, OP_SCOPE);
674 variable: qualified_name
677 char *name = copy_name ($2);
679 struct bound_minimal_symbol msymbol;
682 lookup_symbol (name, (const struct block *) NULL,
683 VAR_DOMAIN, NULL).symbol;
686 write_exp_elt_opcode (pstate, OP_VAR_VALUE);
687 write_exp_elt_block (pstate, NULL);
688 write_exp_elt_sym (pstate, sym);
689 write_exp_elt_opcode (pstate, OP_VAR_VALUE);
693 msymbol = lookup_bound_minimal_symbol (name);
694 if (msymbol.minsym != NULL)
695 write_exp_msymbol (pstate, msymbol);
696 else if (!have_full_symbols ()
697 && !have_partial_symbols ())
698 error (_("No symbol table is loaded. "
699 "Use the \"file\" command."));
701 error (_("No symbol \"%s\" in current context."),
706 variable: name_not_typename
707 { struct block_symbol sym = $1.sym;
711 if (symbol_read_needs_frame (sym.symbol))
712 innermost_block.update (sym);
714 write_exp_elt_opcode (pstate, OP_VAR_VALUE);
715 write_exp_elt_block (pstate, sym.block);
716 write_exp_elt_sym (pstate, sym.symbol);
717 write_exp_elt_opcode (pstate, OP_VAR_VALUE);
718 current_type = sym.symbol->type; }
719 else if ($1.is_a_field_of_this)
721 struct value * this_val;
722 struct type * this_type;
723 /* Object pascal: it hangs off of `this'. Must
724 not inadvertently convert from a method call
726 innermost_block.update (sym);
727 write_exp_elt_opcode (pstate, OP_THIS);
728 write_exp_elt_opcode (pstate, OP_THIS);
729 write_exp_elt_opcode (pstate, STRUCTOP_PTR);
730 write_exp_string (pstate, $1.stoken);
731 write_exp_elt_opcode (pstate, STRUCTOP_PTR);
732 /* We need type of this. */
734 = value_of_this_silent (parse_language (pstate));
736 this_type = value_type (this_val);
740 current_type = lookup_struct_elt_type (
742 copy_name ($1.stoken), 0);
748 struct bound_minimal_symbol msymbol;
749 char *arg = copy_name ($1.stoken);
752 lookup_bound_minimal_symbol (arg);
753 if (msymbol.minsym != NULL)
754 write_exp_msymbol (pstate, msymbol);
755 else if (!have_full_symbols ()
756 && !have_partial_symbols ())
757 error (_("No symbol table is loaded. "
758 "Use the \"file\" command."));
760 error (_("No symbol \"%s\" in current context."),
761 copy_name ($1.stoken));
770 /* We used to try to recognize more pointer to member types here, but
771 that didn't work (shift/reduce conflicts meant that these rules never
772 got executed). The problem is that
773 int (foo::bar::baz::bizzle)
774 is a function type but
775 int (foo::bar::baz::bizzle::*)
776 is a pointer to member type. Stroustrup loses again! */
781 typebase /* Implements (approximately): (type-qualifier)* type-specifier */
783 { $$ = lookup_pointer_type ($2); }
787 { $$ = lookup_struct (copy_name ($2),
788 expression_context_block); }
790 { $$ = lookup_struct (copy_name ($2),
791 expression_context_block); }
792 /* "const" and "volatile" are curently ignored. A type qualifier
793 after the type is handled in the ptype rule. I think these could
797 name : NAME { $$ = $1.stoken; }
798 | BLOCKNAME { $$ = $1.stoken; }
799 | TYPENAME { $$ = $1.stoken; }
800 | NAME_OR_INT { $$ = $1.stoken; }
803 name_not_typename : NAME
805 /* These would be useful if name_not_typename was useful, but it is just
806 a fake for "variable", so these cause reduce/reduce conflicts because
807 the parser can't tell whether NAME_OR_INT is a name_not_typename (=variable,
808 =exp) or just an exp. If name_not_typename was ever used in an lvalue
809 context where only a name could occur, this might be useful.
816 /* Take care of parsing a number (anything that starts with a digit).
817 Set yylval and return the token type; update lexptr.
818 LEN is the number of characters in it. */
820 /*** Needs some error checking for the float case ***/
823 parse_number (struct parser_state *par_state,
824 const char *p, int len, int parsed_float, YYSTYPE *putithere)
826 /* FIXME: Shouldn't these be unsigned? We don't deal with negative values
827 here, and we do kind of silly things like cast to unsigned. */
834 int base = input_radix;
837 /* Number of "L" suffixes encountered. */
840 /* We have found a "L" or "U" suffix. */
841 int found_suffix = 0;
844 struct type *signed_type;
845 struct type *unsigned_type;
849 /* Handle suffixes: 'f' for float, 'l' for long double.
850 FIXME: This appears to be an extension -- do we want this? */
851 if (len >= 1 && tolower (p[len - 1]) == 'f')
853 putithere->typed_val_float.type
854 = parse_type (par_state)->builtin_float;
857 else if (len >= 1 && tolower (p[len - 1]) == 'l')
859 putithere->typed_val_float.type
860 = parse_type (par_state)->builtin_long_double;
863 /* Default type for floating-point literals is double. */
866 putithere->typed_val_float.type
867 = parse_type (par_state)->builtin_double;
870 if (!parse_float (p, len,
871 putithere->typed_val_float.type,
872 putithere->typed_val_float.val))
877 /* Handle base-switching prefixes 0x, 0t, 0d, 0. */
911 if (c >= 'A' && c <= 'Z')
913 if (c != 'l' && c != 'u')
915 if (c >= '0' && c <= '9')
923 if (base > 10 && c >= 'a' && c <= 'f')
927 n += i = c - 'a' + 10;
940 return ERROR; /* Char not a digit */
943 return ERROR; /* Invalid digit in this base. */
945 /* Portably test for overflow (only works for nonzero values, so make
946 a second check for zero). FIXME: Can't we just make n and prevn
947 unsigned and avoid this? */
948 if (c != 'l' && c != 'u' && (prevn >= n) && n != 0)
949 unsigned_p = 1; /* Try something unsigned. */
951 /* Portably test for unsigned overflow.
952 FIXME: This check is wrong; for example it doesn't find overflow
953 on 0x123456789 when LONGEST is 32 bits. */
954 if (c != 'l' && c != 'u' && n != 0)
956 if ((unsigned_p && (ULONGEST) prevn >= (ULONGEST) n))
957 error (_("Numeric constant too large."));
962 /* An integer constant is an int, a long, or a long long. An L
963 suffix forces it to be long; an LL suffix forces it to be long
964 long. If not forced to a larger size, it gets the first type of
965 the above that it fits in. To figure out whether it fits, we
966 shift it right and see whether anything remains. Note that we
967 can't shift sizeof (LONGEST) * HOST_CHAR_BIT bits or more in one
968 operation, because many compilers will warn about such a shift
969 (which always produces a zero result). Sometimes gdbarch_int_bit
970 or gdbarch_long_bit will be that big, sometimes not. To deal with
971 the case where it is we just always shift the value more than
972 once, with fewer bits each time. */
974 un = (ULONGEST)n >> 2;
976 && (un >> (gdbarch_int_bit (parse_gdbarch (par_state)) - 2)) == 0)
979 = ((ULONGEST)1) << (gdbarch_int_bit (parse_gdbarch (par_state)) - 1);
981 /* A large decimal (not hex or octal) constant (between INT_MAX
982 and UINT_MAX) is a long or unsigned long, according to ANSI,
983 never an unsigned int, but this code treats it as unsigned
984 int. This probably should be fixed. GCC gives a warning on
987 unsigned_type = parse_type (par_state)->builtin_unsigned_int;
988 signed_type = parse_type (par_state)->builtin_int;
991 && (un >> (gdbarch_long_bit (parse_gdbarch (par_state)) - 2)) == 0)
994 = ((ULONGEST)1) << (gdbarch_long_bit (parse_gdbarch (par_state)) - 1);
995 unsigned_type = parse_type (par_state)->builtin_unsigned_long;
996 signed_type = parse_type (par_state)->builtin_long;
1001 if (sizeof (ULONGEST) * HOST_CHAR_BIT
1002 < gdbarch_long_long_bit (parse_gdbarch (par_state)))
1003 /* A long long does not fit in a LONGEST. */
1004 shift = (sizeof (ULONGEST) * HOST_CHAR_BIT - 1);
1006 shift = (gdbarch_long_long_bit (parse_gdbarch (par_state)) - 1);
1007 high_bit = (ULONGEST) 1 << shift;
1008 unsigned_type = parse_type (par_state)->builtin_unsigned_long_long;
1009 signed_type = parse_type (par_state)->builtin_long_long;
1012 putithere->typed_val_int.val = n;
1014 /* If the high bit of the worked out type is set then this number
1015 has to be unsigned. */
1017 if (unsigned_p || (n & high_bit))
1019 putithere->typed_val_int.type = unsigned_type;
1023 putithere->typed_val_int.type = signed_type;
1032 struct type *stored;
1033 struct type_push *next;
1036 static struct type_push *tp_top = NULL;
1039 push_current_type (void)
1041 struct type_push *tpnew;
1042 tpnew = (struct type_push *) malloc (sizeof (struct type_push));
1043 tpnew->next = tp_top;
1044 tpnew->stored = current_type;
1045 current_type = NULL;
1050 pop_current_type (void)
1052 struct type_push *tp = tp_top;
1055 current_type = tp->stored;
1065 enum exp_opcode opcode;
1068 static const struct token tokentab3[] =
1070 {"shr", RSH, BINOP_END},
1071 {"shl", LSH, BINOP_END},
1072 {"and", ANDAND, BINOP_END},
1073 {"div", DIV, BINOP_END},
1074 {"not", NOT, BINOP_END},
1075 {"mod", MOD, BINOP_END},
1076 {"inc", INCREMENT, BINOP_END},
1077 {"dec", DECREMENT, BINOP_END},
1078 {"xor", XOR, BINOP_END}
1081 static const struct token tokentab2[] =
1083 {"or", OR, BINOP_END},
1084 {"<>", NOTEQUAL, BINOP_END},
1085 {"<=", LEQ, BINOP_END},
1086 {">=", GEQ, BINOP_END},
1087 {":=", ASSIGN, BINOP_END},
1088 {"::", COLONCOLON, BINOP_END} };
1090 /* Allocate uppercased var: */
1091 /* make an uppercased copy of tokstart. */
1093 uptok (const char *tokstart, int namelen)
1096 char *uptokstart = (char *)malloc(namelen+1);
1097 for (i = 0;i <= namelen;i++)
1099 if ((tokstart[i]>='a' && tokstart[i]<='z'))
1100 uptokstart[i] = tokstart[i]-('a'-'A');
1102 uptokstart[i] = tokstart[i];
1104 uptokstart[namelen]='\0';
1108 /* Read one token, getting characters through lexptr. */
1116 const char *tokstart;
1119 int explen, tempbufindex;
1120 static char *tempbuf;
1121 static int tempbufsize;
1125 prev_lexptr = lexptr;
1128 explen = strlen (lexptr);
1130 /* See if it is a special token of length 3. */
1132 for (i = 0; i < sizeof (tokentab3) / sizeof (tokentab3[0]); i++)
1133 if (strncasecmp (tokstart, tokentab3[i].oper, 3) == 0
1134 && (!isalpha (tokentab3[i].oper[0]) || explen == 3
1135 || (!isalpha (tokstart[3])
1136 && !isdigit (tokstart[3]) && tokstart[3] != '_')))
1139 yylval.opcode = tokentab3[i].opcode;
1140 return tokentab3[i].token;
1143 /* See if it is a special token of length 2. */
1145 for (i = 0; i < sizeof (tokentab2) / sizeof (tokentab2[0]); i++)
1146 if (strncasecmp (tokstart, tokentab2[i].oper, 2) == 0
1147 && (!isalpha (tokentab2[i].oper[0]) || explen == 2
1148 || (!isalpha (tokstart[2])
1149 && !isdigit (tokstart[2]) && tokstart[2] != '_')))
1152 yylval.opcode = tokentab2[i].opcode;
1153 return tokentab2[i].token;
1156 switch (c = *tokstart)
1159 if (search_field && parse_completion)
1171 /* We either have a character constant ('0' or '\177' for example)
1172 or we have a quoted symbol reference ('foo(int,int)' in object pascal
1177 c = parse_escape (parse_gdbarch (pstate), &lexptr);
1179 error (_("Empty character constant."));
1181 yylval.typed_val_int.val = c;
1182 yylval.typed_val_int.type = parse_type (pstate)->builtin_char;
1187 namelen = skip_quoted (tokstart) - tokstart;
1190 lexptr = tokstart + namelen;
1191 if (lexptr[-1] != '\'')
1192 error (_("Unmatched single quote."));
1195 uptokstart = uptok(tokstart,namelen);
1198 error (_("Invalid character constant."));
1208 if (paren_depth == 0)
1215 if (comma_terminates && paren_depth == 0)
1221 /* Might be a floating point number. */
1222 if (lexptr[1] < '0' || lexptr[1] > '9')
1224 goto symbol; /* Nope, must be a symbol. */
1227 /* FALL THRU into number case. */
1240 /* It's a number. */
1241 int got_dot = 0, got_e = 0, toktype;
1242 const char *p = tokstart;
1243 int hex = input_radix > 10;
1245 if (c == '0' && (p[1] == 'x' || p[1] == 'X'))
1250 else if (c == '0' && (p[1]=='t' || p[1]=='T'
1251 || p[1]=='d' || p[1]=='D'))
1259 /* This test includes !hex because 'e' is a valid hex digit
1260 and thus does not indicate a floating point number when
1261 the radix is hex. */
1262 if (!hex && !got_e && (*p == 'e' || *p == 'E'))
1263 got_dot = got_e = 1;
1264 /* This test does not include !hex, because a '.' always indicates
1265 a decimal floating point number regardless of the radix. */
1266 else if (!got_dot && *p == '.')
1268 else if (got_e && (p[-1] == 'e' || p[-1] == 'E')
1269 && (*p == '-' || *p == '+'))
1270 /* This is the sign of the exponent, not the end of the
1273 /* We will take any letters or digits. parse_number will
1274 complain if past the radix, or if L or U are not final. */
1275 else if ((*p < '0' || *p > '9')
1276 && ((*p < 'a' || *p > 'z')
1277 && (*p < 'A' || *p > 'Z')))
1280 toktype = parse_number (pstate, tokstart,
1281 p - tokstart, got_dot | got_e, &yylval);
1282 if (toktype == ERROR)
1284 char *err_copy = (char *) alloca (p - tokstart + 1);
1286 memcpy (err_copy, tokstart, p - tokstart);
1287 err_copy[p - tokstart] = 0;
1288 error (_("Invalid number \"%s\"."), err_copy);
1319 /* Build the gdb internal form of the input string in tempbuf,
1320 translating any standard C escape forms seen. Note that the
1321 buffer is null byte terminated *only* for the convenience of
1322 debugging gdb itself and printing the buffer contents when
1323 the buffer contains no embedded nulls. Gdb does not depend
1324 upon the buffer being null byte terminated, it uses the length
1325 string instead. This allows gdb to handle C strings (as well
1326 as strings in other languages) with embedded null bytes. */
1328 tokptr = ++tokstart;
1332 /* Grow the static temp buffer if necessary, including allocating
1333 the first one on demand. */
1334 if (tempbufindex + 1 >= tempbufsize)
1336 tempbuf = (char *) realloc (tempbuf, tempbufsize += 64);
1343 /* Do nothing, loop will terminate. */
1347 c = parse_escape (parse_gdbarch (pstate), &tokptr);
1352 tempbuf[tempbufindex++] = c;
1355 tempbuf[tempbufindex++] = *tokptr++;
1358 } while ((*tokptr != '"') && (*tokptr != '\0'));
1359 if (*tokptr++ != '"')
1361 error (_("Unterminated string in expression."));
1363 tempbuf[tempbufindex] = '\0'; /* See note above. */
1364 yylval.sval.ptr = tempbuf;
1365 yylval.sval.length = tempbufindex;
1370 if (!(c == '_' || c == '$'
1371 || (c >= 'a' && c <= 'z') || (c >= 'A' && c <= 'Z')))
1372 /* We must have come across a bad character (e.g. ';'). */
1373 error (_("Invalid character '%c' in expression."), c);
1375 /* It's a name. See how long it is. */
1377 for (c = tokstart[namelen];
1378 (c == '_' || c == '$' || (c >= '0' && c <= '9')
1379 || (c >= 'a' && c <= 'z') || (c >= 'A' && c <= 'Z') || c == '<');)
1381 /* Template parameter lists are part of the name.
1382 FIXME: This mishandles `print $a<4&&$a>3'. */
1386 int nesting_level = 1;
1387 while (tokstart[++i])
1389 if (tokstart[i] == '<')
1391 else if (tokstart[i] == '>')
1393 if (--nesting_level == 0)
1397 if (tokstart[i] == '>')
1403 /* do NOT uppercase internals because of registers !!! */
1404 c = tokstart[++namelen];
1407 uptokstart = uptok(tokstart,namelen);
1409 /* The token "if" terminates the expression and is NOT
1410 removed from the input stream. */
1411 if (namelen == 2 && uptokstart[0] == 'I' && uptokstart[1] == 'F')
1421 /* Catch specific keywords. Should be done with a data structure. */
1425 if (strcmp (uptokstart, "OBJECT") == 0)
1430 if (strcmp (uptokstart, "RECORD") == 0)
1435 if (strcmp (uptokstart, "SIZEOF") == 0)
1442 if (strcmp (uptokstart, "CLASS") == 0)
1447 if (strcmp (uptokstart, "FALSE") == 0)
1451 return FALSEKEYWORD;
1455 if (strcmp (uptokstart, "TRUE") == 0)
1461 if (strcmp (uptokstart, "SELF") == 0)
1463 /* Here we search for 'this' like
1464 inserted in FPC stabs debug info. */
1465 static const char this_name[] = "this";
1467 if (lookup_symbol (this_name, expression_context_block,
1468 VAR_DOMAIN, NULL).symbol)
1479 yylval.sval.ptr = tokstart;
1480 yylval.sval.length = namelen;
1482 if (*tokstart == '$')
1486 /* $ is the normal prefix for pascal hexadecimal values
1487 but this conflicts with the GDB use for debugger variables
1488 so in expression to enter hexadecimal values
1489 we still need to use C syntax with 0xff */
1490 write_dollar_variable (pstate, yylval.sval);
1491 tmp = (char *) alloca (namelen + 1);
1492 memcpy (tmp, tokstart, namelen);
1493 tmp[namelen] = '\0';
1494 intvar = lookup_only_internalvar (tmp + 1);
1499 /* Use token-type BLOCKNAME for symbols that happen to be defined as
1500 functions or symtabs. If this is not so, then ...
1501 Use token-type TYPENAME for symbols that happen to be defined
1502 currently as names of types; NAME for other symbols.
1503 The caller is not constrained to care about the distinction. */
1505 char *tmp = copy_name (yylval.sval);
1507 struct field_of_this_result is_a_field_of_this;
1511 is_a_field_of_this.type = NULL;
1512 if (search_field && current_type)
1513 is_a_field = (lookup_struct_elt_type (current_type, tmp, 1) != NULL);
1517 sym = lookup_symbol (tmp, expression_context_block,
1518 VAR_DOMAIN, &is_a_field_of_this).symbol;
1519 /* second chance uppercased (as Free Pascal does). */
1520 if (!sym && is_a_field_of_this.type == NULL && !is_a_field)
1522 for (i = 0; i <= namelen; i++)
1524 if ((tmp[i] >= 'a' && tmp[i] <= 'z'))
1525 tmp[i] -= ('a'-'A');
1527 if (search_field && current_type)
1528 is_a_field = (lookup_struct_elt_type (current_type, tmp, 1) != NULL);
1532 sym = lookup_symbol (tmp, expression_context_block,
1533 VAR_DOMAIN, &is_a_field_of_this).symbol;
1535 /* Third chance Capitalized (as GPC does). */
1536 if (!sym && is_a_field_of_this.type == NULL && !is_a_field)
1538 for (i = 0; i <= namelen; i++)
1542 if ((tmp[i] >= 'a' && tmp[i] <= 'z'))
1543 tmp[i] -= ('a'-'A');
1546 if ((tmp[i] >= 'A' && tmp[i] <= 'Z'))
1547 tmp[i] -= ('A'-'a');
1549 if (search_field && current_type)
1550 is_a_field = (lookup_struct_elt_type (current_type, tmp, 1) != NULL);
1554 sym = lookup_symbol (tmp, expression_context_block,
1555 VAR_DOMAIN, &is_a_field_of_this).symbol;
1558 if (is_a_field || (is_a_field_of_this.type != NULL))
1560 tempbuf = (char *) realloc (tempbuf, namelen + 1);
1561 strncpy (tempbuf, tmp, namelen);
1562 tempbuf [namelen] = 0;
1563 yylval.sval.ptr = tempbuf;
1564 yylval.sval.length = namelen;
1565 yylval.ssym.sym.symbol = NULL;
1566 yylval.ssym.sym.block = NULL;
1568 yylval.ssym.is_a_field_of_this = is_a_field_of_this.type != NULL;
1574 /* Call lookup_symtab, not lookup_partial_symtab, in case there are
1575 no psymtabs (coff, xcoff, or some future change to blow away the
1576 psymtabs once once symbols are read). */
1577 if ((sym && SYMBOL_CLASS (sym) == LOC_BLOCK)
1578 || lookup_symtab (tmp))
1580 yylval.ssym.sym.symbol = sym;
1581 yylval.ssym.sym.block = NULL;
1582 yylval.ssym.is_a_field_of_this = is_a_field_of_this.type != NULL;
1586 if (sym && SYMBOL_CLASS (sym) == LOC_TYPEDEF)
1589 /* Despite the following flaw, we need to keep this code enabled.
1590 Because we can get called from check_stub_method, if we don't
1591 handle nested types then it screws many operations in any
1592 program which uses nested types. */
1593 /* In "A::x", if x is a member function of A and there happens
1594 to be a type (nested or not, since the stabs don't make that
1595 distinction) named x, then this code incorrectly thinks we
1596 are dealing with nested types rather than a member function. */
1599 const char *namestart;
1600 struct symbol *best_sym;
1602 /* Look ahead to detect nested types. This probably should be
1603 done in the grammar, but trying seemed to introduce a lot
1604 of shift/reduce and reduce/reduce conflicts. It's possible
1605 that it could be done, though. Or perhaps a non-grammar, but
1606 less ad hoc, approach would work well. */
1608 /* Since we do not currently have any way of distinguishing
1609 a nested type from a non-nested one (the stabs don't tell
1610 us whether a type is nested), we just ignore the
1617 /* Skip whitespace. */
1618 while (*p == ' ' || *p == '\t' || *p == '\n')
1620 if (*p == ':' && p[1] == ':')
1622 /* Skip the `::'. */
1624 /* Skip whitespace. */
1625 while (*p == ' ' || *p == '\t' || *p == '\n')
1628 while (*p == '_' || *p == '$' || (*p >= '0' && *p <= '9')
1629 || (*p >= 'a' && *p <= 'z')
1630 || (*p >= 'A' && *p <= 'Z'))
1634 struct symbol *cur_sym;
1635 /* As big as the whole rest of the expression, which is
1636 at least big enough. */
1638 = (char *) alloca (strlen (tmp) + strlen (namestart)
1643 memcpy (tmp1, tmp, strlen (tmp));
1644 tmp1 += strlen (tmp);
1645 memcpy (tmp1, "::", 2);
1647 memcpy (tmp1, namestart, p - namestart);
1648 tmp1[p - namestart] = '\0';
1649 cur_sym = lookup_symbol (ncopy, expression_context_block,
1650 VAR_DOMAIN, NULL).symbol;
1653 if (SYMBOL_CLASS (cur_sym) == LOC_TYPEDEF)
1671 yylval.tsym.type = SYMBOL_TYPE (best_sym);
1673 yylval.tsym.type = SYMBOL_TYPE (sym);
1679 = language_lookup_primitive_type (parse_language (pstate),
1680 parse_gdbarch (pstate), tmp);
1681 if (yylval.tsym.type != NULL)
1687 /* Input names that aren't symbols but ARE valid hex numbers,
1688 when the input radix permits them, can be names or numbers
1689 depending on the parse. Note we support radixes > 16 here. */
1691 && ((tokstart[0] >= 'a' && tokstart[0] < 'a' + input_radix - 10)
1692 || (tokstart[0] >= 'A' && tokstart[0] < 'A' + input_radix - 10)))
1694 YYSTYPE newlval; /* Its value is ignored. */
1695 hextype = parse_number (pstate, tokstart, namelen, 0, &newlval);
1698 yylval.ssym.sym.symbol = sym;
1699 yylval.ssym.sym.block = NULL;
1700 yylval.ssym.is_a_field_of_this = is_a_field_of_this.type != NULL;
1707 /* Any other kind of symbol. */
1708 yylval.ssym.sym.symbol = sym;
1709 yylval.ssym.sym.block = NULL;
1715 pascal_parse (struct parser_state *par_state)
1717 /* Setting up the parser state. */
1718 scoped_restore pstate_restore = make_scoped_restore (&pstate);
1719 gdb_assert (par_state != NULL);
1726 yyerror (const char *msg)
1729 lexptr = prev_lexptr;
1731 error (_("A %s in expression, near `%s'."), (msg ? msg : "error"), lexptr);