Regenerate AArch64 opcodes files
[binutils-gdb.git] / gdb / p-exp.y
blobea7eb8c8d7e1d517701b52eba6c18547a31c9b73
1 /* YACC parser for Pascal expressions, for GDB.
2 Copyright (C) 2000-2024 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. */
46 #include "defs.h"
47 #include <ctype.h>
48 #include "expression.h"
49 #include "value.h"
50 #include "parser-defs.h"
51 #include "language.h"
52 #include "p-lang.h"
53 #include "block.h"
54 #include "expop.h"
56 #define parse_type(ps) builtin_type (ps->gdbarch ())
58 /* Remap normal yacc parser interface names (yyparse, yylex, yyerror,
59 etc). */
60 #define GDB_YY_REMAP_PREFIX pascal_
61 #include "yy-remap.h"
63 /* The state of the parser, used internally when we are parsing the
64 expression. */
66 static struct parser_state *pstate = NULL;
68 /* Depth of parentheses. */
69 static int paren_depth;
71 int yyparse (void);
73 static int yylex (void);
75 static void yyerror (const char *);
77 static char *uptok (const char *, int);
79 using namespace expr;
82 /* Although the yacc "value" of an expression is not used,
83 since the result is stored in the structure being created,
84 other node types do have values. */
86 %union
88 LONGEST lval;
89 struct {
90 LONGEST val;
91 struct type *type;
92 } typed_val_int;
93 struct {
94 gdb_byte val[16];
95 struct type *type;
96 } typed_val_float;
97 struct symbol *sym;
98 struct type *tval;
99 struct stoken sval;
100 struct ttype tsym;
101 struct symtoken ssym;
102 int voidval;
103 const struct block *bval;
104 enum exp_opcode opcode;
105 struct internalvar *ivar;
107 struct type **tvec;
108 int *ivec;
112 /* YYSTYPE gets defined by %union */
113 static int parse_number (struct parser_state *,
114 const char *, int, int, YYSTYPE *);
116 static struct type *current_type;
117 static int leftdiv_is_integer;
118 static void push_current_type (void);
119 static void pop_current_type (void);
120 static int search_field;
123 %type <voidval> exp exp1 type_exp start normal_start variable qualified_name
124 %type <tval> type typebase
125 /* %type <bval> block */
127 /* Fancy type parsing. */
128 %type <tval> ptype
130 %token <typed_val_int> INT
131 %token <typed_val_float> FLOAT
133 /* Both NAME and TYPENAME tokens represent symbols in the input,
134 and both convey their data as strings.
135 But a TYPENAME is a string that happens to be defined as a typedef
136 or builtin type name (such as int or char)
137 and a NAME is any other symbol.
138 Contexts where this distinction is not important can use the
139 nonterminal "name", which matches either NAME or TYPENAME. */
141 %token <sval> STRING
142 %token <sval> FIELDNAME
143 %token <voidval> COMPLETE
144 %token <ssym> NAME /* BLOCKNAME defined below to give it higher precedence. */
145 %token <tsym> TYPENAME
146 %type <sval> name
147 %type <ssym> name_not_typename
149 /* A NAME_OR_INT is a symbol which is not known in the symbol table,
150 but which would parse as a valid number in the current input radix.
151 E.g. "c" when input_radix==16. Depending on the parse, it will be
152 turned into a name or into a number. */
154 %token <ssym> NAME_OR_INT
156 %token STRUCT CLASS SIZEOF COLONCOLON
157 %token ERROR
159 /* Special type cases, put in to allow the parser to distinguish different
160 legal basetypes. */
162 %token <sval> DOLLAR_VARIABLE
165 /* Object pascal */
166 %token THIS
167 %token <lval> TRUEKEYWORD FALSEKEYWORD
169 %left ','
170 %left ABOVE_COMMA
171 %right ASSIGN
172 %left NOT
173 %left OR
174 %left XOR
175 %left ANDAND
176 %left '=' NOTEQUAL
177 %left '<' '>' LEQ GEQ
178 %left LSH RSH DIV MOD
179 %left '@'
180 %left '+' '-'
181 %left '*' '/'
182 %right UNARY INCREMENT DECREMENT
183 %right ARROW '.' '[' '('
184 %left '^'
185 %token <ssym> BLOCKNAME
186 %type <bval> block
187 %left COLONCOLON
192 start : { current_type = NULL;
193 search_field = 0;
194 leftdiv_is_integer = 0;
196 normal_start {}
199 normal_start :
200 exp1
201 | type_exp
204 type_exp: type
206 pstate->push_new<type_operation> ($1);
207 current_type = $1; } ;
209 /* Expressions, including the comma operator. */
210 exp1 : exp
211 | exp1 ',' exp
212 { pstate->wrap2<comma_operation> (); }
215 /* Expressions, not including the comma operator. */
216 exp : exp '^' %prec UNARY
217 { pstate->wrap<unop_ind_operation> ();
218 if (current_type)
219 current_type = current_type->target_type (); }
222 exp : '@' exp %prec UNARY
223 { pstate->wrap<unop_addr_operation> ();
224 if (current_type)
225 current_type = TYPE_POINTER_TYPE (current_type); }
228 exp : '-' exp %prec UNARY
229 { pstate->wrap<unary_neg_operation> (); }
232 exp : NOT exp %prec UNARY
233 { pstate->wrap<unary_logical_not_operation> (); }
236 exp : INCREMENT '(' exp ')' %prec UNARY
237 { pstate->wrap<preinc_operation> (); }
240 exp : DECREMENT '(' exp ')' %prec UNARY
241 { pstate->wrap<predec_operation> (); }
245 field_exp : exp '.' %prec UNARY
246 { search_field = 1; }
249 exp : field_exp FIELDNAME
251 pstate->push_new<structop_operation>
252 (pstate->pop (), copy_name ($2));
253 search_field = 0;
254 if (current_type)
256 while (current_type->code ()
257 == TYPE_CODE_PTR)
258 current_type =
259 current_type->target_type ();
260 current_type = lookup_struct_elt_type (
261 current_type, $2.ptr, 0);
267 exp : field_exp name
269 pstate->push_new<structop_operation>
270 (pstate->pop (), copy_name ($2));
271 search_field = 0;
272 if (current_type)
274 while (current_type->code ()
275 == TYPE_CODE_PTR)
276 current_type =
277 current_type->target_type ();
278 current_type = lookup_struct_elt_type (
279 current_type, $2.ptr, 0);
283 exp : field_exp name COMPLETE
285 structop_base_operation *op
286 = new structop_ptr_operation (pstate->pop (),
287 copy_name ($2));
288 pstate->mark_struct_expression (op);
289 pstate->push (operation_up (op));
292 exp : field_exp COMPLETE
294 structop_base_operation *op
295 = new structop_ptr_operation (pstate->pop (), "");
296 pstate->mark_struct_expression (op);
297 pstate->push (operation_up (op));
301 exp : exp '['
302 /* We need to save the current_type value. */
303 { const char *arrayname;
304 int arrayfieldindex
305 = pascal_is_string_type (current_type, NULL, NULL,
306 NULL, NULL, &arrayname);
307 if (arrayfieldindex)
309 current_type
310 = (current_type
311 ->field (arrayfieldindex - 1).type ());
312 pstate->push_new<structop_operation>
313 (pstate->pop (), arrayname);
315 push_current_type (); }
316 exp1 ']'
317 { pop_current_type ();
318 pstate->wrap2<subscript_operation> ();
319 if (current_type)
320 current_type = current_type->target_type (); }
323 exp : exp '('
324 /* This is to save the value of arglist_len
325 being accumulated by an outer function call. */
326 { push_current_type ();
327 pstate->start_arglist (); }
328 arglist ')' %prec ARROW
330 std::vector<operation_up> args
331 = pstate->pop_vector (pstate->end_arglist ());
332 pstate->push_new<funcall_operation>
333 (pstate->pop (), std::move (args));
334 pop_current_type ();
335 if (current_type)
336 current_type = current_type->target_type ();
340 arglist :
341 | exp
342 { pstate->arglist_len = 1; }
343 | arglist ',' exp %prec ABOVE_COMMA
344 { pstate->arglist_len++; }
347 exp : type '(' exp ')' %prec UNARY
348 { if (current_type)
350 /* Allow automatic dereference of classes. */
351 if ((current_type->code () == TYPE_CODE_PTR)
352 && (current_type->target_type ()->code () == TYPE_CODE_STRUCT)
353 && (($1)->code () == TYPE_CODE_STRUCT))
354 pstate->wrap<unop_ind_operation> ();
356 pstate->push_new<unop_cast_operation>
357 (pstate->pop (), $1);
358 current_type = $1; }
361 exp : '(' exp1 ')'
365 /* Binary operators in order of decreasing precedence. */
367 exp : exp '*' exp
368 { pstate->wrap2<mul_operation> (); }
371 exp : exp '/' {
372 if (current_type && is_integral_type (current_type))
373 leftdiv_is_integer = 1;
377 if (leftdiv_is_integer && current_type
378 && is_integral_type (current_type))
380 pstate->push_new<unop_cast_operation>
381 (pstate->pop (),
382 parse_type (pstate)->builtin_long_double);
383 current_type
384 = parse_type (pstate)->builtin_long_double;
385 leftdiv_is_integer = 0;
388 pstate->wrap2<div_operation> ();
392 exp : exp DIV exp
393 { pstate->wrap2<intdiv_operation> (); }
396 exp : exp MOD exp
397 { pstate->wrap2<rem_operation> (); }
400 exp : exp '+' exp
401 { pstate->wrap2<add_operation> (); }
404 exp : exp '-' exp
405 { pstate->wrap2<sub_operation> (); }
408 exp : exp LSH exp
409 { pstate->wrap2<lsh_operation> (); }
412 exp : exp RSH exp
413 { pstate->wrap2<rsh_operation> (); }
416 exp : exp '=' exp
418 pstate->wrap2<equal_operation> ();
419 current_type = parse_type (pstate)->builtin_bool;
423 exp : exp NOTEQUAL exp
425 pstate->wrap2<notequal_operation> ();
426 current_type = parse_type (pstate)->builtin_bool;
430 exp : exp LEQ exp
432 pstate->wrap2<leq_operation> ();
433 current_type = parse_type (pstate)->builtin_bool;
437 exp : exp GEQ exp
439 pstate->wrap2<geq_operation> ();
440 current_type = parse_type (pstate)->builtin_bool;
444 exp : exp '<' exp
446 pstate->wrap2<less_operation> ();
447 current_type = parse_type (pstate)->builtin_bool;
451 exp : exp '>' exp
453 pstate->wrap2<gtr_operation> ();
454 current_type = parse_type (pstate)->builtin_bool;
458 exp : exp ANDAND exp
459 { pstate->wrap2<bitwise_and_operation> (); }
462 exp : exp XOR exp
463 { pstate->wrap2<bitwise_xor_operation> (); }
466 exp : exp OR exp
467 { pstate->wrap2<bitwise_ior_operation> (); }
470 exp : exp ASSIGN exp
471 { pstate->wrap2<assign_operation> (); }
474 exp : TRUEKEYWORD
476 pstate->push_new<bool_operation> ($1);
477 current_type = parse_type (pstate)->builtin_bool;
481 exp : FALSEKEYWORD
483 pstate->push_new<bool_operation> ($1);
484 current_type = parse_type (pstate)->builtin_bool;
488 exp : INT
490 pstate->push_new<long_const_operation>
491 ($1.type, $1.val);
492 current_type = $1.type;
496 exp : NAME_OR_INT
497 { YYSTYPE val;
498 parse_number (pstate, $1.stoken.ptr,
499 $1.stoken.length, 0, &val);
500 pstate->push_new<long_const_operation>
501 (val.typed_val_int.type,
502 val.typed_val_int.val);
503 current_type = val.typed_val_int.type;
508 exp : FLOAT
510 float_data data;
511 std::copy (std::begin ($1.val), std::end ($1.val),
512 std::begin (data));
513 pstate->push_new<float_const_operation> ($1.type, data);
517 exp : variable
520 exp : DOLLAR_VARIABLE
522 pstate->push_dollar ($1);
524 /* $ is the normal prefix for pascal
525 hexadecimal values but this conflicts
526 with the GDB use for debugger variables
527 so in expression to enter hexadecimal
528 values we still need to use C syntax with
529 0xff */
530 std::string tmp ($1.ptr, $1.length);
531 /* Handle current_type. */
532 struct internalvar *intvar
533 = lookup_only_internalvar (tmp.c_str () + 1);
534 if (intvar != nullptr)
536 scoped_value_mark mark;
538 value *val
539 = value_of_internalvar (pstate->gdbarch (),
540 intvar);
541 current_type = val->type ();
546 exp : SIZEOF '(' type ')' %prec UNARY
548 current_type = parse_type (pstate)->builtin_int;
549 $3 = check_typedef ($3);
550 pstate->push_new<long_const_operation>
551 (parse_type (pstate)->builtin_int,
552 $3->length ()); }
555 exp : SIZEOF '(' exp ')' %prec UNARY
556 { pstate->wrap<unop_sizeof_operation> ();
557 current_type = parse_type (pstate)->builtin_int; }
559 exp : STRING
560 { /* C strings are converted into array constants with
561 an explicit null byte added at the end. Thus
562 the array upper bound is the string length.
563 There is no such thing in C as a completely empty
564 string. */
565 const char *sp = $1.ptr; int count = $1.length;
567 std::vector<operation_up> args (count + 1);
568 for (int i = 0; i < count; ++i)
569 args[i] = (make_operation<long_const_operation>
570 (parse_type (pstate)->builtin_char,
571 *sp++));
572 args[count] = (make_operation<long_const_operation>
573 (parse_type (pstate)->builtin_char,
574 '\0'));
575 pstate->push_new<array_operation>
576 (0, $1.length, std::move (args));
580 /* Object pascal */
581 exp : THIS
583 struct value * this_val;
584 struct type * this_type;
585 pstate->push_new<op_this_operation> ();
586 /* We need type of this. */
587 this_val
588 = value_of_this_silent (pstate->language ());
589 if (this_val)
590 this_type = this_val->type ();
591 else
592 this_type = NULL;
593 if (this_type)
595 if (this_type->code () == TYPE_CODE_PTR)
597 this_type = this_type->target_type ();
598 pstate->wrap<unop_ind_operation> ();
602 current_type = this_type;
606 /* end of object pascal. */
608 block : BLOCKNAME
610 if ($1.sym.symbol != 0)
611 $$ = $1.sym.symbol->value_block ();
612 else
614 std::string copy = copy_name ($1.stoken);
615 struct symtab *tem =
616 lookup_symtab (copy.c_str ());
617 if (tem)
618 $$ = (tem->compunit ()->blockvector ()
619 ->static_block ());
620 else
621 error (_("No file or function \"%s\"."),
622 copy.c_str ());
627 block : block COLONCOLON name
629 std::string copy = copy_name ($3);
630 struct symbol *tem
631 = lookup_symbol (copy.c_str (), $1,
632 SEARCH_FUNCTION_DOMAIN,
633 nullptr).symbol;
635 if (tem == nullptr)
636 error (_("No function \"%s\" in specified context."),
637 copy.c_str ());
638 $$ = tem->value_block (); }
641 variable: block COLONCOLON name
642 { struct block_symbol sym;
644 std::string copy = copy_name ($3);
645 sym = lookup_symbol (copy.c_str (), $1,
646 SEARCH_VFT, NULL);
647 if (sym.symbol == 0)
648 error (_("No symbol \"%s\" in specified context."),
649 copy.c_str ());
651 pstate->push_new<var_value_operation> (sym);
655 qualified_name: typebase COLONCOLON name
657 struct type *type = $1;
659 if (type->code () != TYPE_CODE_STRUCT
660 && type->code () != TYPE_CODE_UNION)
661 error (_("`%s' is not defined as an aggregate type."),
662 type->name ());
664 pstate->push_new<scope_operation>
665 (type, copy_name ($3));
669 variable: qualified_name
670 | COLONCOLON name
672 std::string name = copy_name ($2);
674 struct block_symbol sym
675 = lookup_symbol (name.c_str (), nullptr,
676 SEARCH_VFT, nullptr);
677 pstate->push_symbol (name.c_str (), sym);
681 variable: name_not_typename
682 { struct block_symbol sym = $1.sym;
684 if (sym.symbol)
686 if (symbol_read_needs_frame (sym.symbol))
687 pstate->block_tracker->update (sym);
689 pstate->push_new<var_value_operation> (sym);
690 current_type = sym.symbol->type (); }
691 else if ($1.is_a_field_of_this)
693 struct value * this_val;
694 struct type * this_type;
695 /* Object pascal: it hangs off of `this'. Must
696 not inadvertently convert from a method call
697 to data ref. */
698 pstate->block_tracker->update (sym);
699 operation_up thisop
700 = make_operation<op_this_operation> ();
701 pstate->push_new<structop_operation>
702 (std::move (thisop), copy_name ($1.stoken));
703 /* We need type of this. */
704 this_val
705 = value_of_this_silent (pstate->language ());
706 if (this_val)
707 this_type = this_val->type ();
708 else
709 this_type = NULL;
710 if (this_type)
711 current_type = lookup_struct_elt_type (
712 this_type,
713 copy_name ($1.stoken).c_str (), 0);
714 else
715 current_type = NULL;
717 else
719 struct bound_minimal_symbol msymbol;
720 std::string arg = copy_name ($1.stoken);
722 msymbol =
723 lookup_bound_minimal_symbol (arg.c_str ());
724 if (msymbol.minsym != NULL)
725 pstate->push_new<var_msym_value_operation>
726 (msymbol);
727 else if (!have_full_symbols ()
728 && !have_partial_symbols ())
729 error (_("No symbol table is loaded. "
730 "Use the \"file\" command."));
731 else
732 error (_("No symbol \"%s\" in current context."),
733 arg.c_str ());
739 ptype : typebase
742 /* We used to try to recognize more pointer to member types here, but
743 that didn't work (shift/reduce conflicts meant that these rules never
744 got executed). The problem is that
745 int (foo::bar::baz::bizzle)
746 is a function type but
747 int (foo::bar::baz::bizzle::*)
748 is a pointer to member type. Stroustrup loses again! */
750 type : ptype
753 typebase /* Implements (approximately): (type-qualifier)* type-specifier */
754 : '^' typebase
755 { $$ = lookup_pointer_type ($2); }
756 | TYPENAME
757 { $$ = $1.type; }
758 | STRUCT name
759 { $$
760 = lookup_struct (copy_name ($2).c_str (),
761 pstate->expression_context_block);
763 | CLASS name
764 { $$
765 = lookup_struct (copy_name ($2).c_str (),
766 pstate->expression_context_block);
768 /* "const" and "volatile" are curently ignored. A type qualifier
769 after the type is handled in the ptype rule. I think these could
770 be too. */
773 name : NAME { $$ = $1.stoken; }
774 | BLOCKNAME { $$ = $1.stoken; }
775 | TYPENAME { $$ = $1.stoken; }
776 | NAME_OR_INT { $$ = $1.stoken; }
779 name_not_typename : NAME
780 | BLOCKNAME
781 /* These would be useful if name_not_typename was useful, but it is just
782 a fake for "variable", so these cause reduce/reduce conflicts because
783 the parser can't tell whether NAME_OR_INT is a name_not_typename (=variable,
784 =exp) or just an exp. If name_not_typename was ever used in an lvalue
785 context where only a name could occur, this might be useful.
786 | NAME_OR_INT
792 /* Take care of parsing a number (anything that starts with a digit).
793 Set yylval and return the token type; update lexptr.
794 LEN is the number of characters in it. */
796 /*** Needs some error checking for the float case ***/
798 static int
799 parse_number (struct parser_state *par_state,
800 const char *p, int len, int parsed_float, YYSTYPE *putithere)
802 ULONGEST n = 0;
803 ULONGEST prevn = 0;
805 int i = 0;
806 int c;
807 int base = input_radix;
808 int unsigned_p = 0;
810 /* Number of "L" suffixes encountered. */
811 int long_p = 0;
813 /* We have found a "L" or "U" suffix. */
814 int found_suffix = 0;
816 if (parsed_float)
818 /* Handle suffixes: 'f' for float, 'l' for long double.
819 FIXME: This appears to be an extension -- do we want this? */
820 if (len >= 1 && tolower (p[len - 1]) == 'f')
822 putithere->typed_val_float.type
823 = parse_type (par_state)->builtin_float;
824 len--;
826 else if (len >= 1 && tolower (p[len - 1]) == 'l')
828 putithere->typed_val_float.type
829 = parse_type (par_state)->builtin_long_double;
830 len--;
832 /* Default type for floating-point literals is double. */
833 else
835 putithere->typed_val_float.type
836 = parse_type (par_state)->builtin_double;
839 if (!parse_float (p, len,
840 putithere->typed_val_float.type,
841 putithere->typed_val_float.val))
842 return ERROR;
843 return FLOAT;
846 /* Handle base-switching prefixes 0x, 0t, 0d, 0. */
847 if (p[0] == '0' && len > 1)
848 switch (p[1])
850 case 'x':
851 case 'X':
852 if (len >= 3)
854 p += 2;
855 base = 16;
856 len -= 2;
858 break;
860 case 't':
861 case 'T':
862 case 'd':
863 case 'D':
864 if (len >= 3)
866 p += 2;
867 base = 10;
868 len -= 2;
870 break;
872 default:
873 base = 8;
874 break;
877 while (len-- > 0)
879 c = *p++;
880 if (c >= 'A' && c <= 'Z')
881 c += 'a' - 'A';
882 if (c != 'l' && c != 'u')
883 n *= base;
884 if (c >= '0' && c <= '9')
886 if (found_suffix)
887 return ERROR;
888 n += i = c - '0';
890 else
892 if (base > 10 && c >= 'a' && c <= 'f')
894 if (found_suffix)
895 return ERROR;
896 n += i = c - 'a' + 10;
898 else if (c == 'l')
900 ++long_p;
901 found_suffix = 1;
903 else if (c == 'u')
905 unsigned_p = 1;
906 found_suffix = 1;
908 else
909 return ERROR; /* Char not a digit */
911 if (i >= base)
912 return ERROR; /* Invalid digit in this base. */
914 if (c != 'l' && c != 'u')
916 /* Test for overflow. */
917 if (prevn == 0 && n == 0)
919 else if (prevn >= n)
920 error (_("Numeric constant too large."));
922 prevn = n;
925 /* An integer constant is an int, a long, or a long long. An L
926 suffix forces it to be long; an LL suffix forces it to be long
927 long. If not forced to a larger size, it gets the first type of
928 the above that it fits in. To figure out whether it fits, we
929 shift it right and see whether anything remains. Note that we
930 can't shift sizeof (LONGEST) * HOST_CHAR_BIT bits or more in one
931 operation, because many compilers will warn about such a shift
932 (which always produces a zero result). Sometimes gdbarch_int_bit
933 or gdbarch_long_bit will be that big, sometimes not. To deal with
934 the case where it is we just always shift the value more than
935 once, with fewer bits each time. */
937 int int_bits = gdbarch_int_bit (par_state->gdbarch ());
938 int long_bits = gdbarch_long_bit (par_state->gdbarch ());
939 int long_long_bits = gdbarch_long_long_bit (par_state->gdbarch ());
940 bool have_signed = !unsigned_p;
941 bool have_int = long_p == 0;
942 bool have_long = long_p <= 1;
943 if (have_int && have_signed && fits_in_type (1, n, int_bits, true))
944 putithere->typed_val_int.type = parse_type (par_state)->builtin_int;
945 else if (have_int && fits_in_type (1, n, int_bits, false))
946 putithere->typed_val_int.type
947 = parse_type (par_state)->builtin_unsigned_int;
948 else if (have_long && have_signed && fits_in_type (1, n, long_bits, true))
949 putithere->typed_val_int.type = parse_type (par_state)->builtin_long;
950 else if (have_long && fits_in_type (1, n, long_bits, false))
951 putithere->typed_val_int.type
952 = parse_type (par_state)->builtin_unsigned_long;
953 else if (have_signed && fits_in_type (1, n, long_long_bits, true))
954 putithere->typed_val_int.type
955 = parse_type (par_state)->builtin_long_long;
956 else if (fits_in_type (1, n, long_long_bits, false))
957 putithere->typed_val_int.type
958 = parse_type (par_state)->builtin_unsigned_long_long;
959 else
960 error (_("Numeric constant too large."));
961 putithere->typed_val_int.val = n;
963 return INT;
967 struct type_push
969 struct type *stored;
970 struct type_push *next;
973 static struct type_push *tp_top = NULL;
975 static void
976 push_current_type (void)
978 struct type_push *tpnew;
979 tpnew = (struct type_push *) malloc (sizeof (struct type_push));
980 tpnew->next = tp_top;
981 tpnew->stored = current_type;
982 current_type = NULL;
983 tp_top = tpnew;
986 static void
987 pop_current_type (void)
989 struct type_push *tp = tp_top;
990 if (tp)
992 current_type = tp->stored;
993 tp_top = tp->next;
994 free (tp);
998 struct p_token
1000 const char *oper;
1001 int token;
1002 enum exp_opcode opcode;
1005 static const struct p_token tokentab3[] =
1007 {"shr", RSH, OP_NULL},
1008 {"shl", LSH, OP_NULL},
1009 {"and", ANDAND, OP_NULL},
1010 {"div", DIV, OP_NULL},
1011 {"not", NOT, OP_NULL},
1012 {"mod", MOD, OP_NULL},
1013 {"inc", INCREMENT, OP_NULL},
1014 {"dec", DECREMENT, OP_NULL},
1015 {"xor", XOR, OP_NULL}
1018 static const struct p_token tokentab2[] =
1020 {"or", OR, OP_NULL},
1021 {"<>", NOTEQUAL, OP_NULL},
1022 {"<=", LEQ, OP_NULL},
1023 {">=", GEQ, OP_NULL},
1024 {":=", ASSIGN, OP_NULL},
1025 {"::", COLONCOLON, OP_NULL} };
1027 /* Allocate uppercased var: */
1028 /* make an uppercased copy of tokstart. */
1029 static char *
1030 uptok (const char *tokstart, int namelen)
1032 int i;
1033 char *uptokstart = (char *)malloc(namelen+1);
1034 for (i = 0;i <= namelen;i++)
1036 if ((tokstart[i]>='a' && tokstart[i]<='z'))
1037 uptokstart[i] = tokstart[i]-('a'-'A');
1038 else
1039 uptokstart[i] = tokstart[i];
1041 uptokstart[namelen]='\0';
1042 return uptokstart;
1045 /* Read one token, getting characters through lexptr. */
1047 static int
1048 yylex (void)
1050 int c;
1051 int namelen;
1052 const char *tokstart;
1053 char *uptokstart;
1054 const char *tokptr;
1055 int explen, tempbufindex;
1056 static char *tempbuf;
1057 static int tempbufsize;
1059 retry:
1061 pstate->prev_lexptr = pstate->lexptr;
1063 tokstart = pstate->lexptr;
1064 explen = strlen (pstate->lexptr);
1066 /* See if it is a special token of length 3. */
1067 if (explen > 2)
1068 for (const auto &token : tokentab3)
1069 if (strncasecmp (tokstart, token.oper, 3) == 0
1070 && (!isalpha (token.oper[0]) || explen == 3
1071 || (!isalpha (tokstart[3])
1072 && !isdigit (tokstart[3]) && tokstart[3] != '_')))
1074 pstate->lexptr += 3;
1075 yylval.opcode = token.opcode;
1076 return token.token;
1079 /* See if it is a special token of length 2. */
1080 if (explen > 1)
1081 for (const auto &token : tokentab2)
1082 if (strncasecmp (tokstart, token.oper, 2) == 0
1083 && (!isalpha (token.oper[0]) || explen == 2
1084 || (!isalpha (tokstart[2])
1085 && !isdigit (tokstart[2]) && tokstart[2] != '_')))
1087 pstate->lexptr += 2;
1088 yylval.opcode = token.opcode;
1089 return token.token;
1092 switch (c = *tokstart)
1094 case 0:
1095 if (search_field && pstate->parse_completion)
1096 return COMPLETE;
1097 else
1098 return 0;
1100 case ' ':
1101 case '\t':
1102 case '\n':
1103 pstate->lexptr++;
1104 goto retry;
1106 case '\'':
1107 /* We either have a character constant ('0' or '\177' for example)
1108 or we have a quoted symbol reference ('foo(int,int)' in object pascal
1109 for example). */
1110 pstate->lexptr++;
1111 c = *pstate->lexptr++;
1112 if (c == '\\')
1113 c = parse_escape (pstate->gdbarch (), &pstate->lexptr);
1114 else if (c == '\'')
1115 error (_("Empty character constant."));
1117 yylval.typed_val_int.val = c;
1118 yylval.typed_val_int.type = parse_type (pstate)->builtin_char;
1120 c = *pstate->lexptr++;
1121 if (c != '\'')
1123 namelen = skip_quoted (tokstart) - tokstart;
1124 if (namelen > 2)
1126 pstate->lexptr = tokstart + namelen;
1127 if (pstate->lexptr[-1] != '\'')
1128 error (_("Unmatched single quote."));
1129 namelen -= 2;
1130 tokstart++;
1131 uptokstart = uptok(tokstart,namelen);
1132 goto tryname;
1134 error (_("Invalid character constant."));
1136 return INT;
1138 case '(':
1139 paren_depth++;
1140 pstate->lexptr++;
1141 return c;
1143 case ')':
1144 if (paren_depth == 0)
1145 return 0;
1146 paren_depth--;
1147 pstate->lexptr++;
1148 return c;
1150 case ',':
1151 if (pstate->comma_terminates && paren_depth == 0)
1152 return 0;
1153 pstate->lexptr++;
1154 return c;
1156 case '.':
1157 /* Might be a floating point number. */
1158 if (pstate->lexptr[1] < '0' || pstate->lexptr[1] > '9')
1160 goto symbol; /* Nope, must be a symbol. */
1163 [[fallthrough]];
1165 case '0':
1166 case '1':
1167 case '2':
1168 case '3':
1169 case '4':
1170 case '5':
1171 case '6':
1172 case '7':
1173 case '8':
1174 case '9':
1176 /* It's a number. */
1177 int got_dot = 0, got_e = 0, toktype;
1178 const char *p = tokstart;
1179 int hex = input_radix > 10;
1181 if (c == '0' && (p[1] == 'x' || p[1] == 'X'))
1183 p += 2;
1184 hex = 1;
1186 else if (c == '0' && (p[1]=='t' || p[1]=='T'
1187 || p[1]=='d' || p[1]=='D'))
1189 p += 2;
1190 hex = 0;
1193 for (;; ++p)
1195 /* This test includes !hex because 'e' is a valid hex digit
1196 and thus does not indicate a floating point number when
1197 the radix is hex. */
1198 if (!hex && !got_e && (*p == 'e' || *p == 'E'))
1199 got_dot = got_e = 1;
1200 /* This test does not include !hex, because a '.' always indicates
1201 a decimal floating point number regardless of the radix. */
1202 else if (!got_dot && *p == '.')
1203 got_dot = 1;
1204 else if (got_e && (p[-1] == 'e' || p[-1] == 'E')
1205 && (*p == '-' || *p == '+'))
1206 /* This is the sign of the exponent, not the end of the
1207 number. */
1208 continue;
1209 /* We will take any letters or digits. parse_number will
1210 complain if past the radix, or if L or U are not final. */
1211 else if ((*p < '0' || *p > '9')
1212 && ((*p < 'a' || *p > 'z')
1213 && (*p < 'A' || *p > 'Z')))
1214 break;
1216 toktype = parse_number (pstate, tokstart,
1217 p - tokstart, got_dot | got_e, &yylval);
1218 if (toktype == ERROR)
1220 char *err_copy = (char *) alloca (p - tokstart + 1);
1222 memcpy (err_copy, tokstart, p - tokstart);
1223 err_copy[p - tokstart] = 0;
1224 error (_("Invalid number \"%s\"."), err_copy);
1226 pstate->lexptr = p;
1227 return toktype;
1230 case '+':
1231 case '-':
1232 case '*':
1233 case '/':
1234 case '|':
1235 case '&':
1236 case '^':
1237 case '~':
1238 case '!':
1239 case '@':
1240 case '<':
1241 case '>':
1242 case '[':
1243 case ']':
1244 case '?':
1245 case ':':
1246 case '=':
1247 case '{':
1248 case '}':
1249 symbol:
1250 pstate->lexptr++;
1251 return c;
1253 case '"':
1255 /* Build the gdb internal form of the input string in tempbuf,
1256 translating any standard C escape forms seen. Note that the
1257 buffer is null byte terminated *only* for the convenience of
1258 debugging gdb itself and printing the buffer contents when
1259 the buffer contains no embedded nulls. Gdb does not depend
1260 upon the buffer being null byte terminated, it uses the length
1261 string instead. This allows gdb to handle C strings (as well
1262 as strings in other languages) with embedded null bytes. */
1264 tokptr = ++tokstart;
1265 tempbufindex = 0;
1267 do {
1268 /* Grow the static temp buffer if necessary, including allocating
1269 the first one on demand. */
1270 if (tempbufindex + 1 >= tempbufsize)
1272 tempbuf = (char *) realloc (tempbuf, tempbufsize += 64);
1275 switch (*tokptr)
1277 case '\0':
1278 case '"':
1279 /* Do nothing, loop will terminate. */
1280 break;
1281 case '\\':
1282 ++tokptr;
1283 c = parse_escape (pstate->gdbarch (), &tokptr);
1284 if (c == -1)
1286 continue;
1288 tempbuf[tempbufindex++] = c;
1289 break;
1290 default:
1291 tempbuf[tempbufindex++] = *tokptr++;
1292 break;
1294 } while ((*tokptr != '"') && (*tokptr != '\0'));
1295 if (*tokptr++ != '"')
1297 error (_("Unterminated string in expression."));
1299 tempbuf[tempbufindex] = '\0'; /* See note above. */
1300 yylval.sval.ptr = tempbuf;
1301 yylval.sval.length = tempbufindex;
1302 pstate->lexptr = tokptr;
1303 return (STRING);
1306 if (!(c == '_' || c == '$'
1307 || (c >= 'a' && c <= 'z') || (c >= 'A' && c <= 'Z')))
1308 /* We must have come across a bad character (e.g. ';'). */
1309 error (_("Invalid character '%c' in expression."), c);
1311 /* It's a name. See how long it is. */
1312 namelen = 0;
1313 for (c = tokstart[namelen];
1314 (c == '_' || c == '$' || (c >= '0' && c <= '9')
1315 || (c >= 'a' && c <= 'z') || (c >= 'A' && c <= 'Z') || c == '<');)
1317 /* Template parameter lists are part of the name.
1318 FIXME: This mishandles `print $a<4&&$a>3'. */
1319 if (c == '<')
1321 int i = namelen;
1322 int nesting_level = 1;
1323 while (tokstart[++i])
1325 if (tokstart[i] == '<')
1326 nesting_level++;
1327 else if (tokstart[i] == '>')
1329 if (--nesting_level == 0)
1330 break;
1333 if (tokstart[i] == '>')
1334 namelen = i;
1335 else
1336 break;
1339 /* do NOT uppercase internals because of registers !!! */
1340 c = tokstart[++namelen];
1343 uptokstart = uptok(tokstart,namelen);
1345 /* The token "if" terminates the expression and is NOT
1346 removed from the input stream. */
1347 if (namelen == 2 && uptokstart[0] == 'I' && uptokstart[1] == 'F')
1349 free (uptokstart);
1350 return 0;
1353 pstate->lexptr += namelen;
1355 tryname:
1357 /* Catch specific keywords. Should be done with a data structure. */
1358 switch (namelen)
1360 case 6:
1361 if (strcmp (uptokstart, "OBJECT") == 0)
1363 free (uptokstart);
1364 return CLASS;
1366 if (strcmp (uptokstart, "RECORD") == 0)
1368 free (uptokstart);
1369 return STRUCT;
1371 if (strcmp (uptokstart, "SIZEOF") == 0)
1373 free (uptokstart);
1374 return SIZEOF;
1376 break;
1377 case 5:
1378 if (strcmp (uptokstart, "CLASS") == 0)
1380 free (uptokstart);
1381 return CLASS;
1383 if (strcmp (uptokstart, "FALSE") == 0)
1385 yylval.lval = 0;
1386 free (uptokstart);
1387 return FALSEKEYWORD;
1389 break;
1390 case 4:
1391 if (strcmp (uptokstart, "TRUE") == 0)
1393 yylval.lval = 1;
1394 free (uptokstart);
1395 return TRUEKEYWORD;
1397 if (strcmp (uptokstart, "SELF") == 0)
1399 /* Here we search for 'this' like
1400 inserted in FPC stabs debug info. */
1401 static const char this_name[] = "this";
1403 if (lookup_symbol (this_name, pstate->expression_context_block,
1404 SEARCH_VFT, NULL).symbol)
1406 free (uptokstart);
1407 return THIS;
1410 break;
1411 default:
1412 break;
1415 yylval.sval.ptr = tokstart;
1416 yylval.sval.length = namelen;
1418 if (*tokstart == '$')
1420 free (uptokstart);
1421 return DOLLAR_VARIABLE;
1424 /* Use token-type BLOCKNAME for symbols that happen to be defined as
1425 functions or symtabs. If this is not so, then ...
1426 Use token-type TYPENAME for symbols that happen to be defined
1427 currently as names of types; NAME for other symbols.
1428 The caller is not constrained to care about the distinction. */
1430 std::string tmp = copy_name (yylval.sval);
1431 struct symbol *sym;
1432 struct field_of_this_result is_a_field_of_this;
1433 int is_a_field = 0;
1434 int hextype;
1436 is_a_field_of_this.type = NULL;
1437 if (search_field && current_type)
1438 is_a_field = (lookup_struct_elt_type (current_type,
1439 tmp.c_str (), 1) != NULL);
1440 if (is_a_field)
1441 sym = NULL;
1442 else
1443 sym = lookup_symbol (tmp.c_str (), pstate->expression_context_block,
1444 SEARCH_VFT, &is_a_field_of_this).symbol;
1445 /* second chance uppercased (as Free Pascal does). */
1446 if (!sym && is_a_field_of_this.type == NULL && !is_a_field)
1448 for (int i = 0; i <= namelen; i++)
1450 if ((tmp[i] >= 'a' && tmp[i] <= 'z'))
1451 tmp[i] -= ('a'-'A');
1453 if (search_field && current_type)
1454 is_a_field = (lookup_struct_elt_type (current_type,
1455 tmp.c_str (), 1) != NULL);
1456 if (is_a_field)
1457 sym = NULL;
1458 else
1459 sym = lookup_symbol (tmp.c_str (), pstate->expression_context_block,
1460 SEARCH_VFT, &is_a_field_of_this).symbol;
1462 /* Third chance Capitalized (as GPC does). */
1463 if (!sym && is_a_field_of_this.type == NULL && !is_a_field)
1465 for (int i = 0; i <= namelen; i++)
1467 if (i == 0)
1469 if ((tmp[i] >= 'a' && tmp[i] <= 'z'))
1470 tmp[i] -= ('a'-'A');
1472 else
1473 if ((tmp[i] >= 'A' && tmp[i] <= 'Z'))
1474 tmp[i] -= ('A'-'a');
1476 if (search_field && current_type)
1477 is_a_field = (lookup_struct_elt_type (current_type,
1478 tmp.c_str (), 1) != NULL);
1479 if (is_a_field)
1480 sym = NULL;
1481 else
1482 sym = lookup_symbol (tmp.c_str (), pstate->expression_context_block,
1483 SEARCH_VFT, &is_a_field_of_this).symbol;
1486 if (is_a_field || (is_a_field_of_this.type != NULL))
1488 tempbuf = (char *) realloc (tempbuf, namelen + 1);
1489 strncpy (tempbuf, tmp.c_str (), namelen);
1490 tempbuf [namelen] = 0;
1491 yylval.sval.ptr = tempbuf;
1492 yylval.sval.length = namelen;
1493 yylval.ssym.sym.symbol = NULL;
1494 yylval.ssym.sym.block = NULL;
1495 free (uptokstart);
1496 yylval.ssym.is_a_field_of_this = is_a_field_of_this.type != NULL;
1497 if (is_a_field)
1498 return FIELDNAME;
1499 else
1500 return NAME;
1502 /* Call lookup_symtab, not lookup_partial_symtab, in case there are
1503 no psymtabs (coff, xcoff, or some future change to blow away the
1504 psymtabs once once symbols are read). */
1505 if ((sym && sym->aclass () == LOC_BLOCK)
1506 || lookup_symtab (tmp.c_str ()))
1508 yylval.ssym.sym.symbol = sym;
1509 yylval.ssym.sym.block = NULL;
1510 yylval.ssym.is_a_field_of_this = is_a_field_of_this.type != NULL;
1511 free (uptokstart);
1512 return BLOCKNAME;
1514 if (sym && sym->aclass () == LOC_TYPEDEF)
1516 #if 1
1517 /* Despite the following flaw, we need to keep this code enabled.
1518 Because we can get called from check_stub_method, if we don't
1519 handle nested types then it screws many operations in any
1520 program which uses nested types. */
1521 /* In "A::x", if x is a member function of A and there happens
1522 to be a type (nested or not, since the stabs don't make that
1523 distinction) named x, then this code incorrectly thinks we
1524 are dealing with nested types rather than a member function. */
1526 const char *p;
1527 const char *namestart;
1528 struct symbol *best_sym;
1530 /* Look ahead to detect nested types. This probably should be
1531 done in the grammar, but trying seemed to introduce a lot
1532 of shift/reduce and reduce/reduce conflicts. It's possible
1533 that it could be done, though. Or perhaps a non-grammar, but
1534 less ad hoc, approach would work well. */
1536 /* Since we do not currently have any way of distinguishing
1537 a nested type from a non-nested one (the stabs don't tell
1538 us whether a type is nested), we just ignore the
1539 containing type. */
1541 p = pstate->lexptr;
1542 best_sym = sym;
1543 while (1)
1545 /* Skip whitespace. */
1546 while (*p == ' ' || *p == '\t' || *p == '\n')
1547 ++p;
1548 if (*p == ':' && p[1] == ':')
1550 /* Skip the `::'. */
1551 p += 2;
1552 /* Skip whitespace. */
1553 while (*p == ' ' || *p == '\t' || *p == '\n')
1554 ++p;
1555 namestart = p;
1556 while (*p == '_' || *p == '$' || (*p >= '0' && *p <= '9')
1557 || (*p >= 'a' && *p <= 'z')
1558 || (*p >= 'A' && *p <= 'Z'))
1559 ++p;
1560 if (p != namestart)
1562 struct symbol *cur_sym;
1563 /* As big as the whole rest of the expression, which is
1564 at least big enough. */
1565 char *ncopy
1566 = (char *) alloca (tmp.size () + strlen (namestart)
1567 + 3);
1568 char *tmp1;
1570 tmp1 = ncopy;
1571 memcpy (tmp1, tmp.c_str (), tmp.size ());
1572 tmp1 += tmp.size ();
1573 memcpy (tmp1, "::", 2);
1574 tmp1 += 2;
1575 memcpy (tmp1, namestart, p - namestart);
1576 tmp1[p - namestart] = '\0';
1577 cur_sym
1578 = lookup_symbol (ncopy,
1579 pstate->expression_context_block,
1580 SEARCH_VFT, NULL).symbol;
1581 if (cur_sym)
1583 if (cur_sym->aclass () == LOC_TYPEDEF)
1585 best_sym = cur_sym;
1586 pstate->lexptr = p;
1588 else
1589 break;
1591 else
1592 break;
1594 else
1595 break;
1597 else
1598 break;
1601 yylval.tsym.type = best_sym->type ();
1602 #else /* not 0 */
1603 yylval.tsym.type = sym->type ();
1604 #endif /* not 0 */
1605 free (uptokstart);
1606 return TYPENAME;
1608 yylval.tsym.type
1609 = language_lookup_primitive_type (pstate->language (),
1610 pstate->gdbarch (), tmp.c_str ());
1611 if (yylval.tsym.type != NULL)
1613 free (uptokstart);
1614 return TYPENAME;
1617 /* Input names that aren't symbols but ARE valid hex numbers,
1618 when the input radix permits them, can be names or numbers
1619 depending on the parse. Note we support radixes > 16 here. */
1620 if (!sym
1621 && ((tokstart[0] >= 'a' && tokstart[0] < 'a' + input_radix - 10)
1622 || (tokstart[0] >= 'A' && tokstart[0] < 'A' + input_radix - 10)))
1624 YYSTYPE newlval; /* Its value is ignored. */
1625 hextype = parse_number (pstate, tokstart, namelen, 0, &newlval);
1626 if (hextype == INT)
1628 yylval.ssym.sym.symbol = sym;
1629 yylval.ssym.sym.block = NULL;
1630 yylval.ssym.is_a_field_of_this = is_a_field_of_this.type != NULL;
1631 free (uptokstart);
1632 return NAME_OR_INT;
1636 free(uptokstart);
1637 /* Any other kind of symbol. */
1638 yylval.ssym.sym.symbol = sym;
1639 yylval.ssym.sym.block = NULL;
1640 return NAME;
1644 /* See language.h. */
1647 pascal_language::parser (struct parser_state *par_state) const
1649 /* Setting up the parser state. */
1650 scoped_restore pstate_restore = make_scoped_restore (&pstate);
1651 gdb_assert (par_state != NULL);
1652 pstate = par_state;
1653 paren_depth = 0;
1655 int result = yyparse ();
1656 if (!result)
1657 pstate->set_operation (pstate->pop ());
1658 return result;
1661 static void
1662 yyerror (const char *msg)
1664 pstate->parse_error (msg);