1 /* YACC parser for Pascal expressions, for GDB.
2 Copyright (C) 2000-2014 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. */
49 #include "expression.h"
51 #include "parser-defs.h"
54 #include "bfd.h" /* Required by objfiles.h. */
55 #include "symfile.h" /* Required by objfiles.h. */
56 #include "objfiles.h" /* For have_full_symbols and have_partial_symbols. */
58 #include "completer.h"
60 #define parse_type builtin_type (parse_gdbarch)
62 /* Remap normal yacc parser interface names (yyparse, yylex, yyerror, etc),
63 as well as gratuitiously global symbol names, so we can have multiple
64 yacc generated parsers in gdb. Note that these are only the variables
65 produced by yacc. If other parser generators (bison, byacc, etc) produce
66 additional global names that conflict at link time, then those parser
67 generators need to be fixed instead of adding those names to this list. */
69 #define yymaxdepth pascal_maxdepth
70 #define yyparse pascal_parse
71 #define yylex pascal_lex
72 #define yyerror pascal_error
73 #define yylval pascal_lval
74 #define yychar pascal_char
75 #define yydebug pascal_debug
76 #define yypact pascal_pact
77 #define yyr1 pascal_r1
78 #define yyr2 pascal_r2
79 #define yydef pascal_def
80 #define yychk pascal_chk
81 #define yypgo pascal_pgo
82 #define yyact pascal_act
83 #define yyexca pascal_exca
84 #define yyerrflag pascal_errflag
85 #define yynerrs pascal_nerrs
86 #define yyps pascal_ps
87 #define yypv pascal_pv
89 #define yy_yys pascal_yys
90 #define yystate pascal_state
91 #define yytmp pascal_tmp
93 #define yy_yyv pascal_yyv
94 #define yyval pascal_val
95 #define yylloc pascal_lloc
96 #define yyreds pascal_reds /* With YYDEBUG defined */
97 #define yytoks pascal_toks /* With YYDEBUG defined */
98 #define yyname pascal_name /* With YYDEBUG defined */
99 #define yyrule pascal_rule /* With YYDEBUG defined */
100 #define yylhs pascal_yylhs
101 #define yylen pascal_yylen
102 #define yydefred pascal_yydefred
103 #define yydgoto pascal_yydgoto
104 #define yysindex pascal_yysindex
105 #define yyrindex pascal_yyrindex
106 #define yygindex pascal_yygindex
107 #define yytable pascal_yytable
108 #define yycheck pascal_yycheck
109 #define yyss pascal_yyss
110 #define yysslim pascal_yysslim
111 #define yyssp pascal_yyssp
112 #define yystacksize pascal_yystacksize
113 #define yyvs pascal_yyvs
114 #define yyvsp pascal_yyvsp
117 #define YYDEBUG 1 /* Default to yydebug support */
120 #define YYFPRINTF parser_fprintf
124 static int yylex (void);
126 void yyerror (char *);
128 static char *uptok (const char *, int);
131 /* Although the yacc "value" of an expression is not used,
132 since the result is stored in the structure being created,
133 other node types do have values. */
150 struct symtoken ssym;
153 enum exp_opcode opcode;
154 struct internalvar *ivar;
161 /* YYSTYPE gets defined by %union */
162 static int parse_number (const char *, int, int, YYSTYPE *);
164 static struct type *current_type;
165 static struct internalvar *intvar;
166 static int leftdiv_is_integer;
167 static void push_current_type (void);
168 static void pop_current_type (void);
169 static int search_field;
172 %type <voidval> exp exp1 type_exp start normal_start variable qualified_name
173 %type <tval> type typebase
174 /* %type <bval> block */
176 /* Fancy type parsing. */
179 %token <typed_val_int> INT
180 %token <typed_val_float> FLOAT
182 /* Both NAME and TYPENAME tokens represent symbols in the input,
183 and both convey their data as strings.
184 But a TYPENAME is a string that happens to be defined as a typedef
185 or builtin type name (such as int or char)
186 and a NAME is any other symbol.
187 Contexts where this distinction is not important can use the
188 nonterminal "name", which matches either NAME or TYPENAME. */
191 %token <sval> FIELDNAME
192 %token <voidval> COMPLETE
193 %token <ssym> NAME /* BLOCKNAME defined below to give it higher precedence. */
194 %token <tsym> TYPENAME
196 %type <ssym> name_not_typename
198 /* A NAME_OR_INT is a symbol which is not known in the symbol table,
199 but which would parse as a valid number in the current input radix.
200 E.g. "c" when input_radix==16. Depending on the parse, it will be
201 turned into a name or into a number. */
203 %token <ssym> NAME_OR_INT
205 %token STRUCT CLASS SIZEOF COLONCOLON
208 /* Special type cases, put in to allow the parser to distinguish different
211 %token <voidval> VARIABLE
216 %token <lval> TRUEKEYWORD FALSEKEYWORD
226 %left '<' '>' LEQ GEQ
227 %left LSH RSH DIV MOD
231 %right UNARY INCREMENT DECREMENT
232 %right ARROW '.' '[' '('
234 %token <ssym> BLOCKNAME
241 start : { current_type = NULL;
244 leftdiv_is_integer = 0;
255 { write_exp_elt_opcode(OP_TYPE);
256 write_exp_elt_type($1);
257 write_exp_elt_opcode(OP_TYPE);
258 current_type = $1; } ;
260 /* Expressions, including the comma operator. */
263 { write_exp_elt_opcode (BINOP_COMMA); }
266 /* Expressions, not including the comma operator. */
267 exp : exp '^' %prec UNARY
268 { write_exp_elt_opcode (UNOP_IND);
270 current_type = TYPE_TARGET_TYPE (current_type); }
273 exp : '@' exp %prec UNARY
274 { write_exp_elt_opcode (UNOP_ADDR);
276 current_type = TYPE_POINTER_TYPE (current_type); }
279 exp : '-' exp %prec UNARY
280 { write_exp_elt_opcode (UNOP_NEG); }
283 exp : NOT exp %prec UNARY
284 { write_exp_elt_opcode (UNOP_LOGICAL_NOT); }
287 exp : INCREMENT '(' exp ')' %prec UNARY
288 { write_exp_elt_opcode (UNOP_PREINCREMENT); }
291 exp : DECREMENT '(' exp ')' %prec UNARY
292 { write_exp_elt_opcode (UNOP_PREDECREMENT); }
296 field_exp : exp '.' %prec UNARY
297 { search_field = 1; }
300 exp : field_exp FIELDNAME
301 { write_exp_elt_opcode (STRUCTOP_STRUCT);
302 write_exp_string ($2);
303 write_exp_elt_opcode (STRUCTOP_STRUCT);
307 while (TYPE_CODE (current_type)
310 TYPE_TARGET_TYPE (current_type);
311 current_type = lookup_struct_elt_type (
312 current_type, $2.ptr, 0);
319 { write_exp_elt_opcode (STRUCTOP_STRUCT);
320 write_exp_string ($2);
321 write_exp_elt_opcode (STRUCTOP_STRUCT);
325 while (TYPE_CODE (current_type)
328 TYPE_TARGET_TYPE (current_type);
329 current_type = lookup_struct_elt_type (
330 current_type, $2.ptr, 0);
334 exp : field_exp name COMPLETE
335 { mark_struct_expression ();
336 write_exp_elt_opcode (STRUCTOP_STRUCT);
337 write_exp_string ($2);
338 write_exp_elt_opcode (STRUCTOP_STRUCT); }
340 exp : field_exp COMPLETE
342 mark_struct_expression ();
343 write_exp_elt_opcode (STRUCTOP_STRUCT);
346 write_exp_string (s);
347 write_exp_elt_opcode (STRUCTOP_STRUCT); }
351 /* We need to save the current_type value. */
352 { const char *arrayname;
354 arrayfieldindex = is_pascal_string_type (
355 current_type, NULL, NULL,
356 NULL, NULL, &arrayname);
359 struct stoken stringsval;
362 buf = alloca (strlen (arrayname) + 1);
363 stringsval.ptr = buf;
364 stringsval.length = strlen (arrayname);
365 strcpy (buf, arrayname);
366 current_type = TYPE_FIELD_TYPE (current_type,
367 arrayfieldindex - 1);
368 write_exp_elt_opcode (STRUCTOP_STRUCT);
369 write_exp_string (stringsval);
370 write_exp_elt_opcode (STRUCTOP_STRUCT);
372 push_current_type (); }
374 { pop_current_type ();
375 write_exp_elt_opcode (BINOP_SUBSCRIPT);
377 current_type = TYPE_TARGET_TYPE (current_type); }
381 /* This is to save the value of arglist_len
382 being accumulated by an outer function call. */
383 { push_current_type ();
385 arglist ')' %prec ARROW
386 { write_exp_elt_opcode (OP_FUNCALL);
387 write_exp_elt_longcst ((LONGEST) end_arglist ());
388 write_exp_elt_opcode (OP_FUNCALL);
391 current_type = TYPE_TARGET_TYPE (current_type);
398 | arglist ',' exp %prec ABOVE_COMMA
402 exp : type '(' exp ')' %prec UNARY
405 /* Allow automatic dereference of classes. */
406 if ((TYPE_CODE (current_type) == TYPE_CODE_PTR)
407 && (TYPE_CODE (TYPE_TARGET_TYPE (current_type)) == TYPE_CODE_CLASS)
408 && (TYPE_CODE ($1) == TYPE_CODE_CLASS))
409 write_exp_elt_opcode (UNOP_IND);
411 write_exp_elt_opcode (UNOP_CAST);
412 write_exp_elt_type ($1);
413 write_exp_elt_opcode (UNOP_CAST);
421 /* Binary operators in order of decreasing precedence. */
424 { write_exp_elt_opcode (BINOP_MUL); }
428 if (current_type && is_integral_type (current_type))
429 leftdiv_is_integer = 1;
433 if (leftdiv_is_integer && current_type
434 && is_integral_type (current_type))
436 write_exp_elt_opcode (UNOP_CAST);
437 write_exp_elt_type (parse_type->builtin_long_double);
438 current_type = parse_type->builtin_long_double;
439 write_exp_elt_opcode (UNOP_CAST);
440 leftdiv_is_integer = 0;
443 write_exp_elt_opcode (BINOP_DIV);
448 { write_exp_elt_opcode (BINOP_INTDIV); }
452 { write_exp_elt_opcode (BINOP_REM); }
456 { write_exp_elt_opcode (BINOP_ADD); }
460 { write_exp_elt_opcode (BINOP_SUB); }
464 { write_exp_elt_opcode (BINOP_LSH); }
468 { write_exp_elt_opcode (BINOP_RSH); }
472 { write_exp_elt_opcode (BINOP_EQUAL);
473 current_type = parse_type->builtin_bool;
477 exp : exp NOTEQUAL exp
478 { write_exp_elt_opcode (BINOP_NOTEQUAL);
479 current_type = parse_type->builtin_bool;
484 { write_exp_elt_opcode (BINOP_LEQ);
485 current_type = parse_type->builtin_bool;
490 { write_exp_elt_opcode (BINOP_GEQ);
491 current_type = parse_type->builtin_bool;
496 { write_exp_elt_opcode (BINOP_LESS);
497 current_type = parse_type->builtin_bool;
502 { write_exp_elt_opcode (BINOP_GTR);
503 current_type = parse_type->builtin_bool;
508 { write_exp_elt_opcode (BINOP_BITWISE_AND); }
512 { write_exp_elt_opcode (BINOP_BITWISE_XOR); }
516 { write_exp_elt_opcode (BINOP_BITWISE_IOR); }
520 { write_exp_elt_opcode (BINOP_ASSIGN); }
524 { write_exp_elt_opcode (OP_BOOL);
525 write_exp_elt_longcst ((LONGEST) $1);
526 current_type = parse_type->builtin_bool;
527 write_exp_elt_opcode (OP_BOOL); }
531 { write_exp_elt_opcode (OP_BOOL);
532 write_exp_elt_longcst ((LONGEST) $1);
533 current_type = parse_type->builtin_bool;
534 write_exp_elt_opcode (OP_BOOL); }
538 { write_exp_elt_opcode (OP_LONG);
539 write_exp_elt_type ($1.type);
540 current_type = $1.type;
541 write_exp_elt_longcst ((LONGEST)($1.val));
542 write_exp_elt_opcode (OP_LONG); }
547 parse_number ($1.stoken.ptr,
548 $1.stoken.length, 0, &val);
549 write_exp_elt_opcode (OP_LONG);
550 write_exp_elt_type (val.typed_val_int.type);
551 current_type = val.typed_val_int.type;
552 write_exp_elt_longcst ((LONGEST)
553 val.typed_val_int.val);
554 write_exp_elt_opcode (OP_LONG);
560 { write_exp_elt_opcode (OP_DOUBLE);
561 write_exp_elt_type ($1.type);
562 current_type = $1.type;
563 write_exp_elt_dblcst ($1.dval);
564 write_exp_elt_opcode (OP_DOUBLE); }
571 /* Already written by write_dollar_variable.
572 Handle current_type. */
574 struct value * val, * mark;
576 mark = value_mark ();
577 val = value_of_internalvar (parse_gdbarch,
579 current_type = value_type (val);
580 value_release_to_mark (mark);
585 exp : SIZEOF '(' type ')' %prec UNARY
586 { write_exp_elt_opcode (OP_LONG);
587 write_exp_elt_type (parse_type->builtin_int);
588 current_type = parse_type->builtin_int;
590 write_exp_elt_longcst ((LONGEST) TYPE_LENGTH ($3));
591 write_exp_elt_opcode (OP_LONG); }
594 exp : SIZEOF '(' exp ')' %prec UNARY
595 { write_exp_elt_opcode (UNOP_SIZEOF);
596 current_type = parse_type->builtin_int; }
599 { /* C strings are converted into array constants with
600 an explicit null byte added at the end. Thus
601 the array upper bound is the string length.
602 There is no such thing in C as a completely empty
604 const char *sp = $1.ptr; int count = $1.length;
608 write_exp_elt_opcode (OP_LONG);
609 write_exp_elt_type (parse_type->builtin_char);
610 write_exp_elt_longcst ((LONGEST)(*sp++));
611 write_exp_elt_opcode (OP_LONG);
613 write_exp_elt_opcode (OP_LONG);
614 write_exp_elt_type (parse_type->builtin_char);
615 write_exp_elt_longcst ((LONGEST)'\0');
616 write_exp_elt_opcode (OP_LONG);
617 write_exp_elt_opcode (OP_ARRAY);
618 write_exp_elt_longcst ((LONGEST) 0);
619 write_exp_elt_longcst ((LONGEST) ($1.length));
620 write_exp_elt_opcode (OP_ARRAY); }
626 struct value * this_val;
627 struct type * this_type;
628 write_exp_elt_opcode (OP_THIS);
629 write_exp_elt_opcode (OP_THIS);
630 /* We need type of this. */
631 this_val = value_of_this_silent (parse_language);
633 this_type = value_type (this_val);
638 if (TYPE_CODE (this_type) == TYPE_CODE_PTR)
640 this_type = TYPE_TARGET_TYPE (this_type);
641 write_exp_elt_opcode (UNOP_IND);
645 current_type = this_type;
649 /* end of object pascal. */
654 $$ = SYMBOL_BLOCK_VALUE ($1.sym);
658 lookup_symtab (copy_name ($1.stoken));
660 $$ = BLOCKVECTOR_BLOCK (BLOCKVECTOR (tem),
663 error (_("No file or function \"%s\"."),
664 copy_name ($1.stoken));
669 block : block COLONCOLON name
671 = lookup_symbol (copy_name ($3), $1,
673 if (!tem || SYMBOL_CLASS (tem) != LOC_BLOCK)
674 error (_("No function \"%s\" in specified context."),
676 $$ = SYMBOL_BLOCK_VALUE (tem); }
679 variable: block COLONCOLON name
680 { struct symbol *sym;
681 sym = lookup_symbol (copy_name ($3), $1,
684 error (_("No symbol \"%s\" in specified context."),
687 write_exp_elt_opcode (OP_VAR_VALUE);
688 /* block_found is set by lookup_symbol. */
689 write_exp_elt_block (block_found);
690 write_exp_elt_sym (sym);
691 write_exp_elt_opcode (OP_VAR_VALUE); }
694 qualified_name: typebase COLONCOLON name
696 struct type *type = $1;
697 if (TYPE_CODE (type) != TYPE_CODE_STRUCT
698 && TYPE_CODE (type) != TYPE_CODE_UNION)
699 error (_("`%s' is not defined as an aggregate type."),
702 write_exp_elt_opcode (OP_SCOPE);
703 write_exp_elt_type (type);
704 write_exp_string ($3);
705 write_exp_elt_opcode (OP_SCOPE);
709 variable: qualified_name
712 char *name = copy_name ($2);
714 struct bound_minimal_symbol msymbol;
717 lookup_symbol (name, (const struct block *) NULL,
721 write_exp_elt_opcode (OP_VAR_VALUE);
722 write_exp_elt_block (NULL);
723 write_exp_elt_sym (sym);
724 write_exp_elt_opcode (OP_VAR_VALUE);
728 msymbol = lookup_bound_minimal_symbol (name);
729 if (msymbol.minsym != NULL)
730 write_exp_msymbol (msymbol);
731 else if (!have_full_symbols ()
732 && !have_partial_symbols ())
733 error (_("No symbol table is loaded. "
734 "Use the \"file\" command."));
736 error (_("No symbol \"%s\" in current context."),
741 variable: name_not_typename
742 { struct symbol *sym = $1.sym;
746 if (symbol_read_needs_frame (sym))
748 if (innermost_block == 0
749 || contained_in (block_found,
751 innermost_block = block_found;
754 write_exp_elt_opcode (OP_VAR_VALUE);
755 /* We want to use the selected frame, not
756 another more inner frame which happens to
757 be in the same block. */
758 write_exp_elt_block (NULL);
759 write_exp_elt_sym (sym);
760 write_exp_elt_opcode (OP_VAR_VALUE);
761 current_type = sym->type; }
762 else if ($1.is_a_field_of_this)
764 struct value * this_val;
765 struct type * this_type;
766 /* Object pascal: it hangs off of `this'. Must
767 not inadvertently convert from a method call
769 if (innermost_block == 0
770 || contained_in (block_found,
772 innermost_block = block_found;
773 write_exp_elt_opcode (OP_THIS);
774 write_exp_elt_opcode (OP_THIS);
775 write_exp_elt_opcode (STRUCTOP_PTR);
776 write_exp_string ($1.stoken);
777 write_exp_elt_opcode (STRUCTOP_PTR);
778 /* We need type of this. */
779 this_val = value_of_this_silent (parse_language);
781 this_type = value_type (this_val);
785 current_type = lookup_struct_elt_type (
787 copy_name ($1.stoken), 0);
793 struct bound_minimal_symbol msymbol;
794 char *arg = copy_name ($1.stoken);
797 lookup_bound_minimal_symbol (arg);
798 if (msymbol.minsym != NULL)
799 write_exp_msymbol (msymbol);
800 else if (!have_full_symbols ()
801 && !have_partial_symbols ())
802 error (_("No symbol table is loaded. "
803 "Use the \"file\" command."));
805 error (_("No symbol \"%s\" in current context."),
806 copy_name ($1.stoken));
815 /* We used to try to recognize more pointer to member types here, but
816 that didn't work (shift/reduce conflicts meant that these rules never
817 got executed). The problem is that
818 int (foo::bar::baz::bizzle)
819 is a function type but
820 int (foo::bar::baz::bizzle::*)
821 is a pointer to member type. Stroustrup loses again! */
826 typebase /* Implements (approximately): (type-qualifier)* type-specifier */
828 { $$ = lookup_pointer_type ($2); }
832 { $$ = lookup_struct (copy_name ($2),
833 expression_context_block); }
835 { $$ = lookup_struct (copy_name ($2),
836 expression_context_block); }
837 /* "const" and "volatile" are curently ignored. A type qualifier
838 after the type is handled in the ptype rule. I think these could
842 name : NAME { $$ = $1.stoken; }
843 | BLOCKNAME { $$ = $1.stoken; }
844 | TYPENAME { $$ = $1.stoken; }
845 | NAME_OR_INT { $$ = $1.stoken; }
848 name_not_typename : NAME
850 /* These would be useful if name_not_typename was useful, but it is just
851 a fake for "variable", so these cause reduce/reduce conflicts because
852 the parser can't tell whether NAME_OR_INT is a name_not_typename (=variable,
853 =exp) or just an exp. If name_not_typename was ever used in an lvalue
854 context where only a name could occur, this might be useful.
861 /* Take care of parsing a number (anything that starts with a digit).
862 Set yylval and return the token type; update lexptr.
863 LEN is the number of characters in it. */
865 /*** Needs some error checking for the float case ***/
868 parse_number (const char *p, int len, int parsed_float, YYSTYPE *putithere)
870 /* FIXME: Shouldn't these be unsigned? We don't deal with negative values
871 here, and we do kind of silly things like cast to unsigned. */
878 int base = input_radix;
881 /* Number of "L" suffixes encountered. */
884 /* We have found a "L" or "U" suffix. */
885 int found_suffix = 0;
888 struct type *signed_type;
889 struct type *unsigned_type;
893 if (! parse_c_float (parse_gdbarch, p, len,
894 &putithere->typed_val_float.dval,
895 &putithere->typed_val_float.type))
900 /* Handle base-switching prefixes 0x, 0t, 0d, 0. */
934 if (c >= 'A' && c <= 'Z')
936 if (c != 'l' && c != 'u')
938 if (c >= '0' && c <= '9')
946 if (base > 10 && c >= 'a' && c <= 'f')
950 n += i = c - 'a' + 10;
963 return ERROR; /* Char not a digit */
966 return ERROR; /* Invalid digit in this base. */
968 /* Portably test for overflow (only works for nonzero values, so make
969 a second check for zero). FIXME: Can't we just make n and prevn
970 unsigned and avoid this? */
971 if (c != 'l' && c != 'u' && (prevn >= n) && n != 0)
972 unsigned_p = 1; /* Try something unsigned. */
974 /* Portably test for unsigned overflow.
975 FIXME: This check is wrong; for example it doesn't find overflow
976 on 0x123456789 when LONGEST is 32 bits. */
977 if (c != 'l' && c != 'u' && n != 0)
979 if ((unsigned_p && (ULONGEST) prevn >= (ULONGEST) n))
980 error (_("Numeric constant too large."));
985 /* An integer constant is an int, a long, or a long long. An L
986 suffix forces it to be long; an LL suffix forces it to be long
987 long. If not forced to a larger size, it gets the first type of
988 the above that it fits in. To figure out whether it fits, we
989 shift it right and see whether anything remains. Note that we
990 can't shift sizeof (LONGEST) * HOST_CHAR_BIT bits or more in one
991 operation, because many compilers will warn about such a shift
992 (which always produces a zero result). Sometimes gdbarch_int_bit
993 or gdbarch_long_bit will be that big, sometimes not. To deal with
994 the case where it is we just always shift the value more than
995 once, with fewer bits each time. */
997 un = (ULONGEST)n >> 2;
999 && (un >> (gdbarch_int_bit (parse_gdbarch) - 2)) == 0)
1001 high_bit = ((ULONGEST)1) << (gdbarch_int_bit (parse_gdbarch) - 1);
1003 /* A large decimal (not hex or octal) constant (between INT_MAX
1004 and UINT_MAX) is a long or unsigned long, according to ANSI,
1005 never an unsigned int, but this code treats it as unsigned
1006 int. This probably should be fixed. GCC gives a warning on
1009 unsigned_type = parse_type->builtin_unsigned_int;
1010 signed_type = parse_type->builtin_int;
1012 else if (long_p <= 1
1013 && (un >> (gdbarch_long_bit (parse_gdbarch) - 2)) == 0)
1015 high_bit = ((ULONGEST)1) << (gdbarch_long_bit (parse_gdbarch) - 1);
1016 unsigned_type = parse_type->builtin_unsigned_long;
1017 signed_type = parse_type->builtin_long;
1022 if (sizeof (ULONGEST) * HOST_CHAR_BIT
1023 < gdbarch_long_long_bit (parse_gdbarch))
1024 /* A long long does not fit in a LONGEST. */
1025 shift = (sizeof (ULONGEST) * HOST_CHAR_BIT - 1);
1027 shift = (gdbarch_long_long_bit (parse_gdbarch) - 1);
1028 high_bit = (ULONGEST) 1 << shift;
1029 unsigned_type = parse_type->builtin_unsigned_long_long;
1030 signed_type = parse_type->builtin_long_long;
1033 putithere->typed_val_int.val = n;
1035 /* If the high bit of the worked out type is set then this number
1036 has to be unsigned. */
1038 if (unsigned_p || (n & high_bit))
1040 putithere->typed_val_int.type = unsigned_type;
1044 putithere->typed_val_int.type = signed_type;
1053 struct type *stored;
1054 struct type_push *next;
1057 static struct type_push *tp_top = NULL;
1060 push_current_type (void)
1062 struct type_push *tpnew;
1063 tpnew = (struct type_push *) malloc (sizeof (struct type_push));
1064 tpnew->next = tp_top;
1065 tpnew->stored = current_type;
1066 current_type = NULL;
1071 pop_current_type (void)
1073 struct type_push *tp = tp_top;
1076 current_type = tp->stored;
1086 enum exp_opcode opcode;
1089 static const struct token tokentab3[] =
1091 {"shr", RSH, BINOP_END},
1092 {"shl", LSH, BINOP_END},
1093 {"and", ANDAND, BINOP_END},
1094 {"div", DIV, BINOP_END},
1095 {"not", NOT, BINOP_END},
1096 {"mod", MOD, BINOP_END},
1097 {"inc", INCREMENT, BINOP_END},
1098 {"dec", DECREMENT, BINOP_END},
1099 {"xor", XOR, BINOP_END}
1102 static const struct token tokentab2[] =
1104 {"or", OR, BINOP_END},
1105 {"<>", NOTEQUAL, BINOP_END},
1106 {"<=", LEQ, BINOP_END},
1107 {">=", GEQ, BINOP_END},
1108 {":=", ASSIGN, BINOP_END},
1109 {"::", COLONCOLON, BINOP_END} };
1111 /* Allocate uppercased var: */
1112 /* make an uppercased copy of tokstart. */
1114 uptok (const char *tokstart, int namelen)
1117 char *uptokstart = (char *)malloc(namelen+1);
1118 for (i = 0;i <= namelen;i++)
1120 if ((tokstart[i]>='a' && tokstart[i]<='z'))
1121 uptokstart[i] = tokstart[i]-('a'-'A');
1123 uptokstart[i] = tokstart[i];
1125 uptokstart[namelen]='\0';
1129 /* Read one token, getting characters through lexptr. */
1137 const char *tokstart;
1140 int explen, tempbufindex;
1141 static char *tempbuf;
1142 static int tempbufsize;
1146 prev_lexptr = lexptr;
1149 explen = strlen (lexptr);
1151 /* See if it is a special token of length 3. */
1153 for (i = 0; i < sizeof (tokentab3) / sizeof (tokentab3[0]); i++)
1154 if (strncasecmp (tokstart, tokentab3[i].operator, 3) == 0
1155 && (!isalpha (tokentab3[i].operator[0]) || explen == 3
1156 || (!isalpha (tokstart[3])
1157 && !isdigit (tokstart[3]) && tokstart[3] != '_')))
1160 yylval.opcode = tokentab3[i].opcode;
1161 return tokentab3[i].token;
1164 /* See if it is a special token of length 2. */
1166 for (i = 0; i < sizeof (tokentab2) / sizeof (tokentab2[0]); i++)
1167 if (strncasecmp (tokstart, tokentab2[i].operator, 2) == 0
1168 && (!isalpha (tokentab2[i].operator[0]) || explen == 2
1169 || (!isalpha (tokstart[2])
1170 && !isdigit (tokstart[2]) && tokstart[2] != '_')))
1173 yylval.opcode = tokentab2[i].opcode;
1174 return tokentab2[i].token;
1177 switch (c = *tokstart)
1180 if (search_field && parse_completion)
1192 /* We either have a character constant ('0' or '\177' for example)
1193 or we have a quoted symbol reference ('foo(int,int)' in object pascal
1198 c = parse_escape (parse_gdbarch, &lexptr);
1200 error (_("Empty character constant."));
1202 yylval.typed_val_int.val = c;
1203 yylval.typed_val_int.type = parse_type->builtin_char;
1208 namelen = skip_quoted (tokstart) - tokstart;
1211 lexptr = tokstart + namelen;
1212 if (lexptr[-1] != '\'')
1213 error (_("Unmatched single quote."));
1216 uptokstart = uptok(tokstart,namelen);
1219 error (_("Invalid character constant."));
1229 if (paren_depth == 0)
1236 if (comma_terminates && paren_depth == 0)
1242 /* Might be a floating point number. */
1243 if (lexptr[1] < '0' || lexptr[1] > '9')
1245 goto symbol; /* Nope, must be a symbol. */
1248 /* FALL THRU into number case. */
1261 /* It's a number. */
1262 int got_dot = 0, got_e = 0, toktype;
1263 const char *p = tokstart;
1264 int hex = input_radix > 10;
1266 if (c == '0' && (p[1] == 'x' || p[1] == 'X'))
1271 else if (c == '0' && (p[1]=='t' || p[1]=='T'
1272 || p[1]=='d' || p[1]=='D'))
1280 /* This test includes !hex because 'e' is a valid hex digit
1281 and thus does not indicate a floating point number when
1282 the radix is hex. */
1283 if (!hex && !got_e && (*p == 'e' || *p == 'E'))
1284 got_dot = got_e = 1;
1285 /* This test does not include !hex, because a '.' always indicates
1286 a decimal floating point number regardless of the radix. */
1287 else if (!got_dot && *p == '.')
1289 else if (got_e && (p[-1] == 'e' || p[-1] == 'E')
1290 && (*p == '-' || *p == '+'))
1291 /* This is the sign of the exponent, not the end of the
1294 /* We will take any letters or digits. parse_number will
1295 complain if past the radix, or if L or U are not final. */
1296 else if ((*p < '0' || *p > '9')
1297 && ((*p < 'a' || *p > 'z')
1298 && (*p < 'A' || *p > 'Z')))
1301 toktype = parse_number (tokstart,
1302 p - tokstart, got_dot | got_e, &yylval);
1303 if (toktype == ERROR)
1305 char *err_copy = (char *) alloca (p - tokstart + 1);
1307 memcpy (err_copy, tokstart, p - tokstart);
1308 err_copy[p - tokstart] = 0;
1309 error (_("Invalid number \"%s\"."), err_copy);
1340 /* Build the gdb internal form of the input string in tempbuf,
1341 translating any standard C escape forms seen. Note that the
1342 buffer is null byte terminated *only* for the convenience of
1343 debugging gdb itself and printing the buffer contents when
1344 the buffer contains no embedded nulls. Gdb does not depend
1345 upon the buffer being null byte terminated, it uses the length
1346 string instead. This allows gdb to handle C strings (as well
1347 as strings in other languages) with embedded null bytes. */
1349 tokptr = ++tokstart;
1353 /* Grow the static temp buffer if necessary, including allocating
1354 the first one on demand. */
1355 if (tempbufindex + 1 >= tempbufsize)
1357 tempbuf = (char *) realloc (tempbuf, tempbufsize += 64);
1364 /* Do nothing, loop will terminate. */
1368 c = parse_escape (parse_gdbarch, &tokptr);
1373 tempbuf[tempbufindex++] = c;
1376 tempbuf[tempbufindex++] = *tokptr++;
1379 } while ((*tokptr != '"') && (*tokptr != '\0'));
1380 if (*tokptr++ != '"')
1382 error (_("Unterminated string in expression."));
1384 tempbuf[tempbufindex] = '\0'; /* See note above. */
1385 yylval.sval.ptr = tempbuf;
1386 yylval.sval.length = tempbufindex;
1391 if (!(c == '_' || c == '$'
1392 || (c >= 'a' && c <= 'z') || (c >= 'A' && c <= 'Z')))
1393 /* We must have come across a bad character (e.g. ';'). */
1394 error (_("Invalid character '%c' in expression."), c);
1396 /* It's a name. See how long it is. */
1398 for (c = tokstart[namelen];
1399 (c == '_' || c == '$' || (c >= '0' && c <= '9')
1400 || (c >= 'a' && c <= 'z') || (c >= 'A' && c <= 'Z') || c == '<');)
1402 /* Template parameter lists are part of the name.
1403 FIXME: This mishandles `print $a<4&&$a>3'. */
1407 int nesting_level = 1;
1408 while (tokstart[++i])
1410 if (tokstart[i] == '<')
1412 else if (tokstart[i] == '>')
1414 if (--nesting_level == 0)
1418 if (tokstart[i] == '>')
1424 /* do NOT uppercase internals because of registers !!! */
1425 c = tokstart[++namelen];
1428 uptokstart = uptok(tokstart,namelen);
1430 /* The token "if" terminates the expression and is NOT
1431 removed from the input stream. */
1432 if (namelen == 2 && uptokstart[0] == 'I' && uptokstart[1] == 'F')
1442 /* Catch specific keywords. Should be done with a data structure. */
1446 if (strcmp (uptokstart, "OBJECT") == 0)
1451 if (strcmp (uptokstart, "RECORD") == 0)
1456 if (strcmp (uptokstart, "SIZEOF") == 0)
1463 if (strcmp (uptokstart, "CLASS") == 0)
1468 if (strcmp (uptokstart, "FALSE") == 0)
1472 return FALSEKEYWORD;
1476 if (strcmp (uptokstart, "TRUE") == 0)
1482 if (strcmp (uptokstart, "SELF") == 0)
1484 /* Here we search for 'this' like
1485 inserted in FPC stabs debug info. */
1486 static const char this_name[] = "this";
1488 if (lookup_symbol (this_name, expression_context_block,
1500 yylval.sval.ptr = tokstart;
1501 yylval.sval.length = namelen;
1503 if (*tokstart == '$')
1507 /* $ is the normal prefix for pascal hexadecimal values
1508 but this conflicts with the GDB use for debugger variables
1509 so in expression to enter hexadecimal values
1510 we still need to use C syntax with 0xff */
1511 write_dollar_variable (yylval.sval);
1512 tmp = alloca (namelen + 1);
1513 memcpy (tmp, tokstart, namelen);
1514 tmp[namelen] = '\0';
1515 intvar = lookup_only_internalvar (tmp + 1);
1520 /* Use token-type BLOCKNAME for symbols that happen to be defined as
1521 functions or symtabs. If this is not so, then ...
1522 Use token-type TYPENAME for symbols that happen to be defined
1523 currently as names of types; NAME for other symbols.
1524 The caller is not constrained to care about the distinction. */
1526 char *tmp = copy_name (yylval.sval);
1528 struct field_of_this_result is_a_field_of_this;
1533 if (search_field && current_type)
1534 is_a_field = (lookup_struct_elt_type (current_type, tmp, 1) != NULL);
1538 sym = lookup_symbol (tmp, expression_context_block,
1539 VAR_DOMAIN, &is_a_field_of_this);
1540 /* second chance uppercased (as Free Pascal does). */
1541 if (!sym && is_a_field_of_this.type == NULL && !is_a_field)
1543 for (i = 0; i <= namelen; i++)
1545 if ((tmp[i] >= 'a' && tmp[i] <= 'z'))
1546 tmp[i] -= ('a'-'A');
1548 if (search_field && current_type)
1549 is_a_field = (lookup_struct_elt_type (current_type, tmp, 1) != NULL);
1553 sym = lookup_symbol (tmp, expression_context_block,
1554 VAR_DOMAIN, &is_a_field_of_this);
1556 /* Third chance Capitalized (as GPC does). */
1557 if (!sym && is_a_field_of_this.type == NULL && !is_a_field)
1559 for (i = 0; i <= namelen; i++)
1563 if ((tmp[i] >= 'a' && tmp[i] <= 'z'))
1564 tmp[i] -= ('a'-'A');
1567 if ((tmp[i] >= 'A' && tmp[i] <= 'Z'))
1568 tmp[i] -= ('A'-'a');
1570 if (search_field && current_type)
1571 is_a_field = (lookup_struct_elt_type (current_type, tmp, 1) != NULL);
1575 sym = lookup_symbol (tmp, expression_context_block,
1576 VAR_DOMAIN, &is_a_field_of_this);
1581 tempbuf = (char *) realloc (tempbuf, namelen + 1);
1582 strncpy (tempbuf, tmp, namelen);
1583 tempbuf [namelen] = 0;
1584 yylval.sval.ptr = tempbuf;
1585 yylval.sval.length = namelen;
1589 /* Call lookup_symtab, not lookup_partial_symtab, in case there are
1590 no psymtabs (coff, xcoff, or some future change to blow away the
1591 psymtabs once once symbols are read). */
1592 if ((sym && SYMBOL_CLASS (sym) == LOC_BLOCK)
1593 || lookup_symtab (tmp))
1595 yylval.ssym.sym = sym;
1596 yylval.ssym.is_a_field_of_this = is_a_field_of_this.type != NULL;
1600 if (sym && SYMBOL_CLASS (sym) == LOC_TYPEDEF)
1603 /* Despite the following flaw, we need to keep this code enabled.
1604 Because we can get called from check_stub_method, if we don't
1605 handle nested types then it screws many operations in any
1606 program which uses nested types. */
1607 /* In "A::x", if x is a member function of A and there happens
1608 to be a type (nested or not, since the stabs don't make that
1609 distinction) named x, then this code incorrectly thinks we
1610 are dealing with nested types rather than a member function. */
1613 const char *namestart;
1614 struct symbol *best_sym;
1616 /* Look ahead to detect nested types. This probably should be
1617 done in the grammar, but trying seemed to introduce a lot
1618 of shift/reduce and reduce/reduce conflicts. It's possible
1619 that it could be done, though. Or perhaps a non-grammar, but
1620 less ad hoc, approach would work well. */
1622 /* Since we do not currently have any way of distinguishing
1623 a nested type from a non-nested one (the stabs don't tell
1624 us whether a type is nested), we just ignore the
1631 /* Skip whitespace. */
1632 while (*p == ' ' || *p == '\t' || *p == '\n')
1634 if (*p == ':' && p[1] == ':')
1636 /* Skip the `::'. */
1638 /* Skip whitespace. */
1639 while (*p == ' ' || *p == '\t' || *p == '\n')
1642 while (*p == '_' || *p == '$' || (*p >= '0' && *p <= '9')
1643 || (*p >= 'a' && *p <= 'z')
1644 || (*p >= 'A' && *p <= 'Z'))
1648 struct symbol *cur_sym;
1649 /* As big as the whole rest of the expression, which is
1650 at least big enough. */
1651 char *ncopy = alloca (strlen (tmp)+strlen (namestart)+3);
1655 memcpy (tmp1, tmp, strlen (tmp));
1656 tmp1 += strlen (tmp);
1657 memcpy (tmp1, "::", 2);
1659 memcpy (tmp1, namestart, p - namestart);
1660 tmp1[p - namestart] = '\0';
1661 cur_sym = lookup_symbol (ncopy, expression_context_block,
1665 if (SYMBOL_CLASS (cur_sym) == LOC_TYPEDEF)
1683 yylval.tsym.type = SYMBOL_TYPE (best_sym);
1685 yylval.tsym.type = SYMBOL_TYPE (sym);
1691 = language_lookup_primitive_type_by_name (parse_language,
1692 parse_gdbarch, tmp);
1693 if (yylval.tsym.type != NULL)
1699 /* Input names that aren't symbols but ARE valid hex numbers,
1700 when the input radix permits them, can be names or numbers
1701 depending on the parse. Note we support radixes > 16 here. */
1703 && ((tokstart[0] >= 'a' && tokstart[0] < 'a' + input_radix - 10)
1704 || (tokstart[0] >= 'A' && tokstart[0] < 'A' + input_radix - 10)))
1706 YYSTYPE newlval; /* Its value is ignored. */
1707 hextype = parse_number (tokstart, namelen, 0, &newlval);
1710 yylval.ssym.sym = sym;
1711 yylval.ssym.is_a_field_of_this = is_a_field_of_this.type != NULL;
1718 /* Any other kind of symbol. */
1719 yylval.ssym.sym = sym;
1720 yylval.ssym.is_a_field_of_this = is_a_field_of_this.type != NULL;
1729 lexptr = prev_lexptr;
1731 error (_("A %s in expression, near `%s'."), (msg ? msg : "error"), lexptr);