1 /* YACC parser for Pascal expressions, for GDB.
2 Copyright (C) 2000, 2006, 2007, 2008 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., 51 Franklin Street, Fifth Floor,
19 Boston, MA 02110-1301, USA. */
21 /* This file is derived from c-exp.y */
23 /* Parse a Pascal expression from text in a string,
24 and return the result as a struct expression pointer.
25 That structure contains arithmetic operations in reverse polish,
26 with constants represented by operations that are followed by special data.
27 See expression.h for the details of the format.
28 What is important here is that it can be built up sequentially
29 during the process of parsing; the lower levels of the tree always
30 come first in the result.
32 Note that malloc's and realloc's in this file are transformed to
33 xmalloc and xrealloc respectively by the same sed command in the
34 makefile that remaps any other malloc/realloc inserted by the parser
35 generator. Doing this with #defines and trying to control the interaction
36 with include files (<malloc.h> and <stdlib.h> for example) just became
37 too messy, particularly when such includes can be inserted at random
38 times by the parser generator. */
40 /* Known bugs or limitations:
41 - pascal string operations are not supported at all.
42 - there are some problems with boolean types.
43 - Pascal type hexadecimal constants are not supported
44 because they conflict with the internal variables format.
45 Probably also lots of other problems, less well defined PM */
49 #include "gdb_string.h"
51 #include "expression.h"
53 #include "parser-defs.h"
56 #include "bfd.h" /* Required by objfiles.h. */
57 #include "symfile.h" /* Required by objfiles.h. */
58 #include "objfiles.h" /* For have_full_symbols and have_partial_symbols */
61 #define parse_type builtin_type (parse_gdbarch)
63 /* Remap normal yacc parser interface names (yyparse, yylex, yyerror, etc),
64 as well as gratuitiously global symbol names, so we can have multiple
65 yacc generated parsers in gdb. Note that these are only the variables
66 produced by yacc. If other parser generators (bison, byacc, etc) produce
67 additional global names that conflict at link time, then those parser
68 generators need to be fixed instead of adding those names to this list. */
70 #define yymaxdepth pascal_maxdepth
71 #define yyparse pascal_parse
72 #define yylex pascal_lex
73 #define yyerror pascal_error
74 #define yylval pascal_lval
75 #define yychar pascal_char
76 #define yydebug pascal_debug
77 #define yypact pascal_pact
78 #define yyr1 pascal_r1
79 #define yyr2 pascal_r2
80 #define yydef pascal_def
81 #define yychk pascal_chk
82 #define yypgo pascal_pgo
83 #define yyact pascal_act
84 #define yyexca pascal_exca
85 #define yyerrflag pascal_errflag
86 #define yynerrs pascal_nerrs
87 #define yyps pascal_ps
88 #define yypv pascal_pv
90 #define yy_yys pascal_yys
91 #define yystate pascal_state
92 #define yytmp pascal_tmp
94 #define yy_yyv pascal_yyv
95 #define yyval pascal_val
96 #define yylloc pascal_lloc
97 #define yyreds pascal_reds /* With YYDEBUG defined */
98 #define yytoks pascal_toks /* With YYDEBUG defined */
99 #define yyname pascal_name /* With YYDEBUG defined */
100 #define yyrule pascal_rule /* With YYDEBUG defined */
101 #define yylhs pascal_yylhs
102 #define yylen pascal_yylen
103 #define yydefred pascal_yydefred
104 #define yydgoto pascal_yydgoto
105 #define yysindex pascal_yysindex
106 #define yyrindex pascal_yyrindex
107 #define yygindex pascal_yygindex
108 #define yytable pascal_yytable
109 #define yycheck pascal_yycheck
112 #define YYDEBUG 1 /* Default to yydebug support */
115 #define YYFPRINTF parser_fprintf
119 static int yylex (void);
124 static char * uptok (char *, int);
127 /* Although the yacc "value" of an expression is not used,
128 since the result is stored in the structure being created,
129 other node types do have values. */
146 struct symtoken ssym;
149 enum exp_opcode opcode;
150 struct internalvar *ivar;
157 /* YYSTYPE gets defined by %union */
159 parse_number (char *, int, int, YYSTYPE *);
161 static struct type *current_type;
162 static int leftdiv_is_integer;
163 static void push_current_type (void);
164 static void pop_current_type (void);
165 static int search_field;
168 %type <voidval> exp exp1 type_exp start normal_start variable qualified_name
169 %type <tval> type typebase
170 /* %type <bval> block */
172 /* Fancy type parsing. */
175 %token <typed_val_int> INT
176 %token <typed_val_float> FLOAT
178 /* Both NAME and TYPENAME tokens represent symbols in the input,
179 and both convey their data as strings.
180 But a TYPENAME is a string that happens to be defined as a typedef
181 or builtin type name (such as int or char)
182 and a NAME is any other symbol.
183 Contexts where this distinction is not important can use the
184 nonterminal "name", which matches either NAME or TYPENAME. */
187 %token <sval> FIELDNAME
188 %token <ssym> NAME /* BLOCKNAME defined below to give it higher precedence. */
189 %token <tsym> TYPENAME
191 %type <ssym> name_not_typename
193 /* A NAME_OR_INT is a symbol which is not known in the symbol table,
194 but which would parse as a valid number in the current input radix.
195 E.g. "c" when input_radix==16. Depending on the parse, it will be
196 turned into a name or into a number. */
198 %token <ssym> NAME_OR_INT
200 %token STRUCT CLASS SIZEOF COLONCOLON
203 /* Special type cases, put in to allow the parser to distinguish different
206 %token <voidval> VARIABLE
211 %token <lval> TRUEKEYWORD FALSEKEYWORD
221 %left '<' '>' LEQ GEQ
222 %left LSH RSH DIV MOD
226 %right UNARY INCREMENT DECREMENT
227 %right ARROW '.' '[' '('
229 %token <ssym> BLOCKNAME
236 start : { current_type = NULL;
238 leftdiv_is_integer = 0;
249 { write_exp_elt_opcode(OP_TYPE);
250 write_exp_elt_type($1);
251 write_exp_elt_opcode(OP_TYPE);
252 current_type = $1; } ;
254 /* Expressions, including the comma operator. */
257 { write_exp_elt_opcode (BINOP_COMMA); }
260 /* Expressions, not including the comma operator. */
261 exp : exp '^' %prec UNARY
262 { write_exp_elt_opcode (UNOP_IND);
264 current_type = TYPE_TARGET_TYPE (current_type); }
267 exp : '@' exp %prec UNARY
268 { write_exp_elt_opcode (UNOP_ADDR);
270 current_type = TYPE_POINTER_TYPE (current_type); }
273 exp : '-' exp %prec UNARY
274 { write_exp_elt_opcode (UNOP_NEG); }
277 exp : NOT exp %prec UNARY
278 { write_exp_elt_opcode (UNOP_LOGICAL_NOT); }
281 exp : INCREMENT '(' exp ')' %prec UNARY
282 { write_exp_elt_opcode (UNOP_PREINCREMENT); }
285 exp : DECREMENT '(' exp ')' %prec UNARY
286 { write_exp_elt_opcode (UNOP_PREDECREMENT); }
289 exp : exp '.' { search_field = 1; }
292 { write_exp_elt_opcode (STRUCTOP_STRUCT);
293 write_exp_string ($4);
294 write_exp_elt_opcode (STRUCTOP_STRUCT);
297 { while (TYPE_CODE (current_type) == TYPE_CODE_PTR)
298 current_type = TYPE_TARGET_TYPE (current_type);
299 current_type = lookup_struct_elt_type (
300 current_type, $4.ptr, 0); };
303 /* We need to save the current_type value */
306 arrayfieldindex = is_pascal_string_type (
307 current_type, NULL, NULL,
308 NULL, NULL, &arrayname);
311 struct stoken stringsval;
312 stringsval.ptr = alloca (strlen (arrayname) + 1);
313 stringsval.length = strlen (arrayname);
314 strcpy (stringsval.ptr, arrayname);
315 current_type = TYPE_FIELD_TYPE (current_type,
316 arrayfieldindex - 1);
317 write_exp_elt_opcode (STRUCTOP_STRUCT);
318 write_exp_string (stringsval);
319 write_exp_elt_opcode (STRUCTOP_STRUCT);
321 push_current_type (); }
323 { pop_current_type ();
324 write_exp_elt_opcode (BINOP_SUBSCRIPT);
326 current_type = TYPE_TARGET_TYPE (current_type); }
330 /* This is to save the value of arglist_len
331 being accumulated by an outer function call. */
332 { push_current_type ();
334 arglist ')' %prec ARROW
335 { write_exp_elt_opcode (OP_FUNCALL);
336 write_exp_elt_longcst ((LONGEST) end_arglist ());
337 write_exp_elt_opcode (OP_FUNCALL);
340 current_type = TYPE_TARGET_TYPE (current_type);
347 | arglist ',' exp %prec ABOVE_COMMA
351 exp : type '(' exp ')' %prec UNARY
354 /* Allow automatic dereference of classes. */
355 if ((TYPE_CODE (current_type) == TYPE_CODE_PTR)
356 && (TYPE_CODE (TYPE_TARGET_TYPE (current_type)) == TYPE_CODE_CLASS)
357 && (TYPE_CODE ($1) == TYPE_CODE_CLASS))
358 write_exp_elt_opcode (UNOP_IND);
360 write_exp_elt_opcode (UNOP_CAST);
361 write_exp_elt_type ($1);
362 write_exp_elt_opcode (UNOP_CAST);
370 /* Binary operators in order of decreasing precedence. */
373 { write_exp_elt_opcode (BINOP_MUL); }
377 if (current_type && is_integral_type (current_type))
378 leftdiv_is_integer = 1;
382 if (leftdiv_is_integer && current_type
383 && is_integral_type (current_type))
385 write_exp_elt_opcode (UNOP_CAST);
386 write_exp_elt_type (parse_type->builtin_long_double);
387 current_type = parse_type->builtin_long_double;
388 write_exp_elt_opcode (UNOP_CAST);
389 leftdiv_is_integer = 0;
392 write_exp_elt_opcode (BINOP_DIV);
397 { write_exp_elt_opcode (BINOP_INTDIV); }
401 { write_exp_elt_opcode (BINOP_REM); }
405 { write_exp_elt_opcode (BINOP_ADD); }
409 { write_exp_elt_opcode (BINOP_SUB); }
413 { write_exp_elt_opcode (BINOP_LSH); }
417 { write_exp_elt_opcode (BINOP_RSH); }
421 { write_exp_elt_opcode (BINOP_EQUAL);
422 current_type = parse_type->builtin_bool;
426 exp : exp NOTEQUAL exp
427 { write_exp_elt_opcode (BINOP_NOTEQUAL);
428 current_type = parse_type->builtin_bool;
433 { write_exp_elt_opcode (BINOP_LEQ);
434 current_type = parse_type->builtin_bool;
439 { write_exp_elt_opcode (BINOP_GEQ);
440 current_type = parse_type->builtin_bool;
445 { write_exp_elt_opcode (BINOP_LESS);
446 current_type = parse_type->builtin_bool;
451 { write_exp_elt_opcode (BINOP_GTR);
452 current_type = parse_type->builtin_bool;
457 { write_exp_elt_opcode (BINOP_BITWISE_AND); }
461 { write_exp_elt_opcode (BINOP_BITWISE_XOR); }
465 { write_exp_elt_opcode (BINOP_BITWISE_IOR); }
469 { write_exp_elt_opcode (BINOP_ASSIGN); }
473 { write_exp_elt_opcode (OP_BOOL);
474 write_exp_elt_longcst ((LONGEST) $1);
475 current_type = parse_type->builtin_bool;
476 write_exp_elt_opcode (OP_BOOL); }
480 { write_exp_elt_opcode (OP_BOOL);
481 write_exp_elt_longcst ((LONGEST) $1);
482 current_type = parse_type->builtin_bool;
483 write_exp_elt_opcode (OP_BOOL); }
487 { write_exp_elt_opcode (OP_LONG);
488 write_exp_elt_type ($1.type);
489 current_type = $1.type;
490 write_exp_elt_longcst ((LONGEST)($1.val));
491 write_exp_elt_opcode (OP_LONG); }
496 parse_number ($1.stoken.ptr, $1.stoken.length, 0, &val);
497 write_exp_elt_opcode (OP_LONG);
498 write_exp_elt_type (val.typed_val_int.type);
499 current_type = val.typed_val_int.type;
500 write_exp_elt_longcst ((LONGEST)val.typed_val_int.val);
501 write_exp_elt_opcode (OP_LONG);
507 { write_exp_elt_opcode (OP_DOUBLE);
508 write_exp_elt_type ($1.type);
509 current_type = $1.type;
510 write_exp_elt_dblcst ($1.dval);
511 write_exp_elt_opcode (OP_DOUBLE); }
518 /* Already written by write_dollar_variable. */
521 exp : SIZEOF '(' type ')' %prec UNARY
522 { write_exp_elt_opcode (OP_LONG);
523 write_exp_elt_type (parse_type->builtin_int);
525 write_exp_elt_longcst ((LONGEST) TYPE_LENGTH ($3));
526 write_exp_elt_opcode (OP_LONG); }
530 { /* C strings are converted into array constants with
531 an explicit null byte added at the end. Thus
532 the array upper bound is the string length.
533 There is no such thing in C as a completely empty
535 char *sp = $1.ptr; int count = $1.length;
538 write_exp_elt_opcode (OP_LONG);
539 write_exp_elt_type (parse_type->builtin_char);
540 write_exp_elt_longcst ((LONGEST)(*sp++));
541 write_exp_elt_opcode (OP_LONG);
543 write_exp_elt_opcode (OP_LONG);
544 write_exp_elt_type (parse_type->builtin_char);
545 write_exp_elt_longcst ((LONGEST)'\0');
546 write_exp_elt_opcode (OP_LONG);
547 write_exp_elt_opcode (OP_ARRAY);
548 write_exp_elt_longcst ((LONGEST) 0);
549 write_exp_elt_longcst ((LONGEST) ($1.length));
550 write_exp_elt_opcode (OP_ARRAY); }
556 struct value * this_val;
557 struct type * this_type;
558 write_exp_elt_opcode (OP_THIS);
559 write_exp_elt_opcode (OP_THIS);
560 /* we need type of this */
561 this_val = value_of_this (0);
563 this_type = value_type (this_val);
568 if (TYPE_CODE (this_type) == TYPE_CODE_PTR)
570 this_type = TYPE_TARGET_TYPE (this_type);
571 write_exp_elt_opcode (UNOP_IND);
575 current_type = this_type;
579 /* end of object pascal. */
584 $$ = SYMBOL_BLOCK_VALUE ($1.sym);
588 lookup_symtab (copy_name ($1.stoken));
590 $$ = BLOCKVECTOR_BLOCK (BLOCKVECTOR (tem), STATIC_BLOCK);
592 error ("No file or function \"%s\".",
593 copy_name ($1.stoken));
598 block : block COLONCOLON name
600 = lookup_symbol (copy_name ($3), $1,
601 VAR_DOMAIN, (int *) NULL);
602 if (!tem || SYMBOL_CLASS (tem) != LOC_BLOCK)
603 error ("No function \"%s\" in specified context.",
605 $$ = SYMBOL_BLOCK_VALUE (tem); }
608 variable: block COLONCOLON name
609 { struct symbol *sym;
610 sym = lookup_symbol (copy_name ($3), $1,
611 VAR_DOMAIN, (int *) NULL);
613 error ("No symbol \"%s\" in specified context.",
616 write_exp_elt_opcode (OP_VAR_VALUE);
617 /* block_found is set by lookup_symbol. */
618 write_exp_elt_block (block_found);
619 write_exp_elt_sym (sym);
620 write_exp_elt_opcode (OP_VAR_VALUE); }
623 qualified_name: typebase COLONCOLON name
625 struct type *type = $1;
626 if (TYPE_CODE (type) != TYPE_CODE_STRUCT
627 && TYPE_CODE (type) != TYPE_CODE_UNION)
628 error ("`%s' is not defined as an aggregate type.",
631 write_exp_elt_opcode (OP_SCOPE);
632 write_exp_elt_type (type);
633 write_exp_string ($3);
634 write_exp_elt_opcode (OP_SCOPE);
638 variable: qualified_name
641 char *name = copy_name ($2);
643 struct minimal_symbol *msymbol;
646 lookup_symbol (name, (const struct block *) NULL,
647 VAR_DOMAIN, (int *) NULL);
650 write_exp_elt_opcode (OP_VAR_VALUE);
651 write_exp_elt_block (NULL);
652 write_exp_elt_sym (sym);
653 write_exp_elt_opcode (OP_VAR_VALUE);
657 msymbol = lookup_minimal_symbol (name, NULL, NULL);
659 write_exp_msymbol (msymbol);
660 else if (!have_full_symbols () && !have_partial_symbols ())
661 error ("No symbol table is loaded. Use the \"file\" command.");
663 error ("No symbol \"%s\" in current context.", name);
667 variable: name_not_typename
668 { struct symbol *sym = $1.sym;
672 if (symbol_read_needs_frame (sym))
674 if (innermost_block == 0
675 || contained_in (block_found,
677 innermost_block = block_found;
680 write_exp_elt_opcode (OP_VAR_VALUE);
681 /* We want to use the selected frame, not
682 another more inner frame which happens to
683 be in the same block. */
684 write_exp_elt_block (NULL);
685 write_exp_elt_sym (sym);
686 write_exp_elt_opcode (OP_VAR_VALUE);
687 current_type = sym->type; }
688 else if ($1.is_a_field_of_this)
690 struct value * this_val;
691 struct type * this_type;
692 /* Object pascal: it hangs off of `this'. Must
693 not inadvertently convert from a method call
695 if (innermost_block == 0
696 || contained_in (block_found,
698 innermost_block = block_found;
699 write_exp_elt_opcode (OP_THIS);
700 write_exp_elt_opcode (OP_THIS);
701 write_exp_elt_opcode (STRUCTOP_PTR);
702 write_exp_string ($1.stoken);
703 write_exp_elt_opcode (STRUCTOP_PTR);
704 /* we need type of this */
705 this_val = value_of_this (0);
707 this_type = value_type (this_val);
711 current_type = lookup_struct_elt_type (
713 copy_name ($1.stoken), 0);
719 struct minimal_symbol *msymbol;
720 char *arg = copy_name ($1.stoken);
723 lookup_minimal_symbol (arg, NULL, NULL);
725 write_exp_msymbol (msymbol);
726 else if (!have_full_symbols () && !have_partial_symbols ())
727 error ("No symbol table is loaded. Use the \"file\" command.");
729 error ("No symbol \"%s\" in current context.",
730 copy_name ($1.stoken));
739 /* We used to try to recognize more pointer to member types here, but
740 that didn't work (shift/reduce conflicts meant that these rules never
741 got executed). The problem is that
742 int (foo::bar::baz::bizzle)
743 is a function type but
744 int (foo::bar::baz::bizzle::*)
745 is a pointer to member type. Stroustrup loses again! */
750 typebase /* Implements (approximately): (type-qualifier)* type-specifier */
752 { $$ = lookup_pointer_type ($2); }
756 { $$ = lookup_struct (copy_name ($2),
757 expression_context_block); }
759 { $$ = lookup_struct (copy_name ($2),
760 expression_context_block); }
761 /* "const" and "volatile" are curently ignored. A type qualifier
762 after the type is handled in the ptype rule. I think these could
766 name : NAME { $$ = $1.stoken; }
767 | BLOCKNAME { $$ = $1.stoken; }
768 | TYPENAME { $$ = $1.stoken; }
769 | NAME_OR_INT { $$ = $1.stoken; }
772 name_not_typename : NAME
774 /* These would be useful if name_not_typename was useful, but it is just
775 a fake for "variable", so these cause reduce/reduce conflicts because
776 the parser can't tell whether NAME_OR_INT is a name_not_typename (=variable,
777 =exp) or just an exp. If name_not_typename was ever used in an lvalue
778 context where only a name could occur, this might be useful.
785 /* Take care of parsing a number (anything that starts with a digit).
786 Set yylval and return the token type; update lexptr.
787 LEN is the number of characters in it. */
789 /*** Needs some error checking for the float case ***/
792 parse_number (p, len, parsed_float, putithere)
798 /* FIXME: Shouldn't these be unsigned? We don't deal with negative values
799 here, and we do kind of silly things like cast to unsigned. */
806 int base = input_radix;
809 /* Number of "L" suffixes encountered. */
812 /* We have found a "L" or "U" suffix. */
813 int found_suffix = 0;
816 struct type *signed_type;
817 struct type *unsigned_type;
821 /* It's a float since it contains a point or an exponent. */
823 int num = 0; /* number of tokens scanned by scanf */
824 char saved_char = p[len];
826 p[len] = 0; /* null-terminate the token */
827 num = sscanf (p, "%" DOUBLEST_SCAN_FORMAT "%c",
828 &putithere->typed_val_float.dval, &c);
829 p[len] = saved_char; /* restore the input stream */
830 if (num != 1) /* check scanf found ONLY a float ... */
832 /* See if it has `f' or `l' suffix (float or long double). */
834 c = tolower (p[len - 1]);
837 putithere->typed_val_float.type = parse_type->builtin_float;
839 putithere->typed_val_float.type = parse_type->builtin_long_double;
840 else if (isdigit (c) || c == '.')
841 putithere->typed_val_float.type = parse_type->builtin_double;
848 /* Handle base-switching prefixes 0x, 0t, 0d, 0 */
882 if (c >= 'A' && c <= 'Z')
884 if (c != 'l' && c != 'u')
886 if (c >= '0' && c <= '9')
894 if (base > 10 && c >= 'a' && c <= 'f')
898 n += i = c - 'a' + 10;
911 return ERROR; /* Char not a digit */
914 return ERROR; /* Invalid digit in this base */
916 /* Portably test for overflow (only works for nonzero values, so make
917 a second check for zero). FIXME: Can't we just make n and prevn
918 unsigned and avoid this? */
919 if (c != 'l' && c != 'u' && (prevn >= n) && n != 0)
920 unsigned_p = 1; /* Try something unsigned */
922 /* Portably test for unsigned overflow.
923 FIXME: This check is wrong; for example it doesn't find overflow
924 on 0x123456789 when LONGEST is 32 bits. */
925 if (c != 'l' && c != 'u' && n != 0)
927 if ((unsigned_p && (ULONGEST) prevn >= (ULONGEST) n))
928 error ("Numeric constant too large.");
933 /* An integer constant is an int, a long, or a long long. An L
934 suffix forces it to be long; an LL suffix forces it to be long
935 long. If not forced to a larger size, it gets the first type of
936 the above that it fits in. To figure out whether it fits, we
937 shift it right and see whether anything remains. Note that we
938 can't shift sizeof (LONGEST) * HOST_CHAR_BIT bits or more in one
939 operation, because many compilers will warn about such a shift
940 (which always produces a zero result). Sometimes gdbarch_int_bit
941 or gdbarch_long_bit will be that big, sometimes not. To deal with
942 the case where it is we just always shift the value more than
943 once, with fewer bits each time. */
945 un = (ULONGEST)n >> 2;
947 && (un >> (gdbarch_int_bit (parse_gdbarch) - 2)) == 0)
949 high_bit = ((ULONGEST)1) << (gdbarch_int_bit (parse_gdbarch) - 1);
951 /* A large decimal (not hex or octal) constant (between INT_MAX
952 and UINT_MAX) is a long or unsigned long, according to ANSI,
953 never an unsigned int, but this code treats it as unsigned
954 int. This probably should be fixed. GCC gives a warning on
957 unsigned_type = parse_type->builtin_unsigned_int;
958 signed_type = parse_type->builtin_int;
961 && (un >> (gdbarch_long_bit (parse_gdbarch) - 2)) == 0)
963 high_bit = ((ULONGEST)1) << (gdbarch_long_bit (parse_gdbarch) - 1);
964 unsigned_type = parse_type->builtin_unsigned_long;
965 signed_type = parse_type->builtin_long;
970 if (sizeof (ULONGEST) * HOST_CHAR_BIT
971 < gdbarch_long_long_bit (parse_gdbarch))
972 /* A long long does not fit in a LONGEST. */
973 shift = (sizeof (ULONGEST) * HOST_CHAR_BIT - 1);
975 shift = (gdbarch_long_long_bit (parse_gdbarch) - 1);
976 high_bit = (ULONGEST) 1 << shift;
977 unsigned_type = parse_type->builtin_unsigned_long_long;
978 signed_type = parse_type->builtin_long_long;
981 putithere->typed_val_int.val = n;
983 /* If the high bit of the worked out type is set then this number
984 has to be unsigned. */
986 if (unsigned_p || (n & high_bit))
988 putithere->typed_val_int.type = unsigned_type;
992 putithere->typed_val_int.type = signed_type;
1001 struct type *stored;
1002 struct type_push *next;
1005 static struct type_push *tp_top = NULL;
1008 push_current_type (void)
1010 struct type_push *tpnew;
1011 tpnew = (struct type_push *) malloc (sizeof (struct type_push));
1012 tpnew->next = tp_top;
1013 tpnew->stored = current_type;
1014 current_type = NULL;
1019 pop_current_type (void)
1021 struct type_push *tp = tp_top;
1024 current_type = tp->stored;
1034 enum exp_opcode opcode;
1037 static const struct token tokentab3[] =
1039 {"shr", RSH, BINOP_END},
1040 {"shl", LSH, BINOP_END},
1041 {"and", ANDAND, BINOP_END},
1042 {"div", DIV, BINOP_END},
1043 {"not", NOT, BINOP_END},
1044 {"mod", MOD, BINOP_END},
1045 {"inc", INCREMENT, BINOP_END},
1046 {"dec", DECREMENT, BINOP_END},
1047 {"xor", XOR, BINOP_END}
1050 static const struct token tokentab2[] =
1052 {"or", OR, BINOP_END},
1053 {"<>", NOTEQUAL, BINOP_END},
1054 {"<=", LEQ, BINOP_END},
1055 {">=", GEQ, BINOP_END},
1056 {":=", ASSIGN, BINOP_END},
1057 {"::", COLONCOLON, BINOP_END} };
1059 /* Allocate uppercased var */
1060 /* make an uppercased copy of tokstart */
1061 static char * uptok (tokstart, namelen)
1066 char *uptokstart = (char *)malloc(namelen+1);
1067 for (i = 0;i <= namelen;i++)
1069 if ((tokstart[i]>='a' && tokstart[i]<='z'))
1070 uptokstart[i] = tokstart[i]-('a'-'A');
1072 uptokstart[i] = tokstart[i];
1074 uptokstart[namelen]='\0';
1077 /* Read one token, getting characters through lexptr. */
1090 int explen, tempbufindex;
1091 static char *tempbuf;
1092 static int tempbufsize;
1096 prev_lexptr = lexptr;
1099 explen = strlen (lexptr);
1100 /* See if it is a special token of length 3. */
1102 for (i = 0; i < sizeof (tokentab3) / sizeof (tokentab3[0]); i++)
1103 if (strncasecmp (tokstart, tokentab3[i].operator, 3) == 0
1104 && (!isalpha (tokentab3[i].operator[0]) || explen == 3
1105 || (!isalpha (tokstart[3]) && !isdigit (tokstart[3]) && tokstart[3] != '_')))
1108 yylval.opcode = tokentab3[i].opcode;
1109 return tokentab3[i].token;
1112 /* See if it is a special token of length 2. */
1114 for (i = 0; i < sizeof (tokentab2) / sizeof (tokentab2[0]); i++)
1115 if (strncasecmp (tokstart, tokentab2[i].operator, 2) == 0
1116 && (!isalpha (tokentab2[i].operator[0]) || explen == 2
1117 || (!isalpha (tokstart[2]) && !isdigit (tokstart[2]) && tokstart[2] != '_')))
1120 yylval.opcode = tokentab2[i].opcode;
1121 return tokentab2[i].token;
1124 switch (c = *tokstart)
1136 /* We either have a character constant ('0' or '\177' for example)
1137 or we have a quoted symbol reference ('foo(int,int)' in object pascal
1142 c = parse_escape (&lexptr);
1144 error ("Empty character constant.");
1146 yylval.typed_val_int.val = c;
1147 yylval.typed_val_int.type = parse_type->builtin_char;
1152 namelen = skip_quoted (tokstart) - tokstart;
1155 lexptr = tokstart + namelen;
1156 if (lexptr[-1] != '\'')
1157 error ("Unmatched single quote.");
1160 uptokstart = uptok(tokstart,namelen);
1163 error ("Invalid character constant.");
1173 if (paren_depth == 0)
1180 if (comma_terminates && paren_depth == 0)
1186 /* Might be a floating point number. */
1187 if (lexptr[1] < '0' || lexptr[1] > '9')
1188 goto symbol; /* Nope, must be a symbol. */
1189 /* FALL THRU into number case. */
1202 /* It's a number. */
1203 int got_dot = 0, got_e = 0, toktype;
1205 int hex = input_radix > 10;
1207 if (c == '0' && (p[1] == 'x' || p[1] == 'X'))
1212 else if (c == '0' && (p[1]=='t' || p[1]=='T' || p[1]=='d' || p[1]=='D'))
1220 /* This test includes !hex because 'e' is a valid hex digit
1221 and thus does not indicate a floating point number when
1222 the radix is hex. */
1223 if (!hex && !got_e && (*p == 'e' || *p == 'E'))
1224 got_dot = got_e = 1;
1225 /* This test does not include !hex, because a '.' always indicates
1226 a decimal floating point number regardless of the radix. */
1227 else if (!got_dot && *p == '.')
1229 else if (got_e && (p[-1] == 'e' || p[-1] == 'E')
1230 && (*p == '-' || *p == '+'))
1231 /* This is the sign of the exponent, not the end of the
1234 /* We will take any letters or digits. parse_number will
1235 complain if past the radix, or if L or U are not final. */
1236 else if ((*p < '0' || *p > '9')
1237 && ((*p < 'a' || *p > 'z')
1238 && (*p < 'A' || *p > 'Z')))
1241 toktype = parse_number (tokstart, p - tokstart, got_dot|got_e, &yylval);
1242 if (toktype == ERROR)
1244 char *err_copy = (char *) alloca (p - tokstart + 1);
1246 memcpy (err_copy, tokstart, p - tokstart);
1247 err_copy[p - tokstart] = 0;
1248 error ("Invalid number \"%s\".", err_copy);
1279 /* Build the gdb internal form of the input string in tempbuf,
1280 translating any standard C escape forms seen. Note that the
1281 buffer is null byte terminated *only* for the convenience of
1282 debugging gdb itself and printing the buffer contents when
1283 the buffer contains no embedded nulls. Gdb does not depend
1284 upon the buffer being null byte terminated, it uses the length
1285 string instead. This allows gdb to handle C strings (as well
1286 as strings in other languages) with embedded null bytes */
1288 tokptr = ++tokstart;
1292 /* Grow the static temp buffer if necessary, including allocating
1293 the first one on demand. */
1294 if (tempbufindex + 1 >= tempbufsize)
1296 tempbuf = (char *) realloc (tempbuf, tempbufsize += 64);
1303 /* Do nothing, loop will terminate. */
1307 c = parse_escape (&tokptr);
1312 tempbuf[tempbufindex++] = c;
1315 tempbuf[tempbufindex++] = *tokptr++;
1318 } while ((*tokptr != '"') && (*tokptr != '\0'));
1319 if (*tokptr++ != '"')
1321 error ("Unterminated string in expression.");
1323 tempbuf[tempbufindex] = '\0'; /* See note above */
1324 yylval.sval.ptr = tempbuf;
1325 yylval.sval.length = tempbufindex;
1330 if (!(c == '_' || c == '$'
1331 || (c >= 'a' && c <= 'z') || (c >= 'A' && c <= 'Z')))
1332 /* We must have come across a bad character (e.g. ';'). */
1333 error ("Invalid character '%c' in expression.", c);
1335 /* It's a name. See how long it is. */
1337 for (c = tokstart[namelen];
1338 (c == '_' || c == '$' || (c >= '0' && c <= '9')
1339 || (c >= 'a' && c <= 'z') || (c >= 'A' && c <= 'Z') || c == '<');)
1341 /* Template parameter lists are part of the name.
1342 FIXME: This mishandles `print $a<4&&$a>3'. */
1346 int nesting_level = 1;
1347 while (tokstart[++i])
1349 if (tokstart[i] == '<')
1351 else if (tokstart[i] == '>')
1353 if (--nesting_level == 0)
1357 if (tokstart[i] == '>')
1363 /* do NOT uppercase internals because of registers !!! */
1364 c = tokstart[++namelen];
1367 uptokstart = uptok(tokstart,namelen);
1369 /* The token "if" terminates the expression and is NOT
1370 removed from the input stream. */
1371 if (namelen == 2 && uptokstart[0] == 'I' && uptokstart[1] == 'F')
1381 /* Catch specific keywords. Should be done with a data structure. */
1385 if (strcmp (uptokstart, "OBJECT") == 0)
1390 if (strcmp (uptokstart, "RECORD") == 0)
1395 if (strcmp (uptokstart, "SIZEOF") == 0)
1402 if (strcmp (uptokstart, "CLASS") == 0)
1407 if (strcmp (uptokstart, "FALSE") == 0)
1411 return FALSEKEYWORD;
1415 if (strcmp (uptokstart, "TRUE") == 0)
1421 if (strcmp (uptokstart, "SELF") == 0)
1423 /* here we search for 'this' like
1424 inserted in FPC stabs debug info */
1425 static const char this_name[] = "this";
1427 if (lookup_symbol (this_name, expression_context_block,
1428 VAR_DOMAIN, (int *) NULL))
1439 yylval.sval.ptr = tokstart;
1440 yylval.sval.length = namelen;
1442 if (*tokstart == '$')
1444 /* $ is the normal prefix for pascal hexadecimal values
1445 but this conflicts with the GDB use for debugger variables
1446 so in expression to enter hexadecimal values
1447 we still need to use C syntax with 0xff */
1448 write_dollar_variable (yylval.sval);
1453 /* Use token-type BLOCKNAME for symbols that happen to be defined as
1454 functions or symtabs. If this is not so, then ...
1455 Use token-type TYPENAME for symbols that happen to be defined
1456 currently as names of types; NAME for other symbols.
1457 The caller is not constrained to care about the distinction. */
1459 char *tmp = copy_name (yylval.sval);
1461 int is_a_field_of_this = 0;
1466 if (search_field && current_type)
1467 is_a_field = (lookup_struct_elt_type (current_type, tmp, 1) != NULL);
1471 sym = lookup_symbol (tmp, expression_context_block,
1472 VAR_DOMAIN, &is_a_field_of_this);
1473 /* second chance uppercased (as Free Pascal does). */
1474 if (!sym && !is_a_field_of_this && !is_a_field)
1476 for (i = 0; i <= namelen; i++)
1478 if ((tmp[i] >= 'a' && tmp[i] <= 'z'))
1479 tmp[i] -= ('a'-'A');
1481 if (search_field && current_type)
1482 is_a_field = (lookup_struct_elt_type (current_type, tmp, 1) != NULL);
1486 sym = lookup_symbol (tmp, expression_context_block,
1487 VAR_DOMAIN, &is_a_field_of_this);
1488 if (sym || is_a_field_of_this || is_a_field)
1489 for (i = 0; i <= namelen; i++)
1491 if ((tokstart[i] >= 'a' && tokstart[i] <= 'z'))
1492 tokstart[i] -= ('a'-'A');
1495 /* Third chance Capitalized (as GPC does). */
1496 if (!sym && !is_a_field_of_this && !is_a_field)
1498 for (i = 0; i <= namelen; i++)
1502 if ((tmp[i] >= 'a' && tmp[i] <= 'z'))
1503 tmp[i] -= ('a'-'A');
1506 if ((tmp[i] >= 'A' && tmp[i] <= 'Z'))
1507 tmp[i] -= ('A'-'a');
1509 if (search_field && current_type)
1510 is_a_field = (lookup_struct_elt_type (current_type, tmp, 1) != NULL);
1514 sym = lookup_symbol (tmp, expression_context_block,
1515 VAR_DOMAIN, &is_a_field_of_this);
1516 if (sym || is_a_field_of_this || is_a_field)
1517 for (i = 0; i <= namelen; i++)
1521 if ((tokstart[i] >= 'a' && tokstart[i] <= 'z'))
1522 tokstart[i] -= ('a'-'A');
1525 if ((tokstart[i] >= 'A' && tokstart[i] <= 'Z'))
1526 tokstart[i] -= ('A'-'a');
1532 tempbuf = (char *) realloc (tempbuf, namelen + 1);
1533 strncpy (tempbuf, tokstart, namelen); tempbuf [namelen] = 0;
1534 yylval.sval.ptr = tempbuf;
1535 yylval.sval.length = namelen;
1539 /* Call lookup_symtab, not lookup_partial_symtab, in case there are
1540 no psymtabs (coff, xcoff, or some future change to blow away the
1541 psymtabs once once symbols are read). */
1542 if ((sym && SYMBOL_CLASS (sym) == LOC_BLOCK)
1543 || lookup_symtab (tmp))
1545 yylval.ssym.sym = sym;
1546 yylval.ssym.is_a_field_of_this = is_a_field_of_this;
1550 if (sym && SYMBOL_CLASS (sym) == LOC_TYPEDEF)
1553 /* Despite the following flaw, we need to keep this code enabled.
1554 Because we can get called from check_stub_method, if we don't
1555 handle nested types then it screws many operations in any
1556 program which uses nested types. */
1557 /* In "A::x", if x is a member function of A and there happens
1558 to be a type (nested or not, since the stabs don't make that
1559 distinction) named x, then this code incorrectly thinks we
1560 are dealing with nested types rather than a member function. */
1564 struct symbol *best_sym;
1566 /* Look ahead to detect nested types. This probably should be
1567 done in the grammar, but trying seemed to introduce a lot
1568 of shift/reduce and reduce/reduce conflicts. It's possible
1569 that it could be done, though. Or perhaps a non-grammar, but
1570 less ad hoc, approach would work well. */
1572 /* Since we do not currently have any way of distinguishing
1573 a nested type from a non-nested one (the stabs don't tell
1574 us whether a type is nested), we just ignore the
1581 /* Skip whitespace. */
1582 while (*p == ' ' || *p == '\t' || *p == '\n')
1584 if (*p == ':' && p[1] == ':')
1586 /* Skip the `::'. */
1588 /* Skip whitespace. */
1589 while (*p == ' ' || *p == '\t' || *p == '\n')
1592 while (*p == '_' || *p == '$' || (*p >= '0' && *p <= '9')
1593 || (*p >= 'a' && *p <= 'z')
1594 || (*p >= 'A' && *p <= 'Z'))
1598 struct symbol *cur_sym;
1599 /* As big as the whole rest of the expression, which is
1600 at least big enough. */
1601 char *ncopy = alloca (strlen (tmp)+strlen (namestart)+3);
1605 memcpy (tmp1, tmp, strlen (tmp));
1606 tmp1 += strlen (tmp);
1607 memcpy (tmp1, "::", 2);
1609 memcpy (tmp1, namestart, p - namestart);
1610 tmp1[p - namestart] = '\0';
1611 cur_sym = lookup_symbol (ncopy, expression_context_block,
1612 VAR_DOMAIN, (int *) NULL);
1615 if (SYMBOL_CLASS (cur_sym) == LOC_TYPEDEF)
1633 yylval.tsym.type = SYMBOL_TYPE (best_sym);
1635 yylval.tsym.type = SYMBOL_TYPE (sym);
1641 = language_lookup_primitive_type_by_name (parse_language,
1642 parse_gdbarch, tmp);
1643 if (yylval.tsym.type != NULL)
1649 /* Input names that aren't symbols but ARE valid hex numbers,
1650 when the input radix permits them, can be names or numbers
1651 depending on the parse. Note we support radixes > 16 here. */
1653 && ((tokstart[0] >= 'a' && tokstart[0] < 'a' + input_radix - 10)
1654 || (tokstart[0] >= 'A' && tokstart[0] < 'A' + input_radix - 10)))
1656 YYSTYPE newlval; /* Its value is ignored. */
1657 hextype = parse_number (tokstart, namelen, 0, &newlval);
1660 yylval.ssym.sym = sym;
1661 yylval.ssym.is_a_field_of_this = is_a_field_of_this;
1668 /* Any other kind of symbol */
1669 yylval.ssym.sym = sym;
1670 yylval.ssym.is_a_field_of_this = is_a_field_of_this;
1680 lexptr = prev_lexptr;
1682 error ("A %s in expression, near `%s'.", (msg ? msg : "error"), lexptr);