RISC-V: Don't report warnings when linking different privileged spec objects.
[binutils-gdb.git] / gdb / p-exp.y
blob938d3cf20240cb46e493c954e3558dbf5f170312
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 <ctype.h>
47 #include "expression.h"
48 #include "value.h"
49 #include "parser-defs.h"
50 #include "language.h"
51 #include "p-lang.h"
52 #include "block.h"
53 #include "expop.h"
55 #define parse_type(ps) builtin_type (ps->gdbarch ())
57 /* Remap normal yacc parser interface names (yyparse, yylex, yyerror,
58 etc). */
59 #define GDB_YY_REMAP_PREFIX pascal_
60 #include "yy-remap.h"
62 /* The state of the parser, used internally when we are parsing the
63 expression. */
65 static struct parser_state *pstate = NULL;
67 /* Depth of parentheses. */
68 static int paren_depth;
70 int yyparse (void);
72 static int yylex (void);
74 static void yyerror (const char *);
76 static char *uptok (const char *, int);
78 static const char *pascal_skip_string (const char *str);
80 using namespace expr;
83 /* Although the yacc "value" of an expression is not used,
84 since the result is stored in the structure being created,
85 other node types do have values. */
87 %union
89 LONGEST lval;
90 struct {
91 LONGEST val;
92 struct type *type;
93 } typed_val_int;
94 struct {
95 gdb_byte val[16];
96 struct type *type;
97 } typed_val_float;
98 struct symbol *sym;
99 struct type *tval;
100 struct stoken sval;
101 struct ttype tsym;
102 struct symtoken ssym;
103 int voidval;
104 const struct block *bval;
105 enum exp_opcode opcode;
106 struct internalvar *ivar;
108 struct type **tvec;
109 int *ivec;
113 /* YYSTYPE gets defined by %union */
114 static int parse_number (struct parser_state *,
115 const char *, int, int, YYSTYPE *);
117 static struct type *current_type;
118 static int leftdiv_is_integer;
119 static void push_current_type (void);
120 static void pop_current_type (void);
121 static int search_field;
124 %type <voidval> exp exp1 type_exp start normal_start variable qualified_name
125 %type <tval> type typebase
126 /* %type <bval> block */
128 /* Fancy type parsing. */
129 %type <tval> ptype
131 %token <typed_val_int> INT
132 %token <typed_val_float> FLOAT
134 /* Both NAME and TYPENAME tokens represent symbols in the input,
135 and both convey their data as strings.
136 But a TYPENAME is a string that happens to be defined as a typedef
137 or builtin type name (such as int or char)
138 and a NAME is any other symbol.
139 Contexts where this distinction is not important can use the
140 nonterminal "name", which matches either NAME or TYPENAME. */
142 %token <sval> STRING
143 %token <sval> FIELDNAME
144 %token <voidval> COMPLETE
145 %token <ssym> NAME /* BLOCKNAME defined below to give it higher precedence. */
146 %token <tsym> TYPENAME
147 %type <sval> name
148 %type <ssym> name_not_typename
150 /* A NAME_OR_INT is a symbol which is not known in the symbol table,
151 but which would parse as a valid number in the current input radix.
152 E.g. "c" when input_radix==16. Depending on the parse, it will be
153 turned into a name or into a number. */
155 %token <ssym> NAME_OR_INT
157 %token STRUCT CLASS SIZEOF COLONCOLON
158 %token ERROR
160 /* Special type cases, put in to allow the parser to distinguish different
161 legal basetypes. */
163 %token <sval> DOLLAR_VARIABLE
166 /* Object pascal */
167 %token THIS
168 %token <lval> TRUEKEYWORD FALSEKEYWORD
170 %left ','
171 %left ABOVE_COMMA
172 %right ASSIGN
173 %left NOT
174 %left OR
175 %left XOR
176 %left ANDAND
177 %left '=' NOTEQUAL
178 %left '<' '>' LEQ GEQ
179 %left LSH RSH DIV MOD
180 %left '@'
181 %left '+' '-'
182 %left '*' '/'
183 %right UNARY INCREMENT DECREMENT
184 %right ARROW '.' '[' '('
185 %left '^'
186 %token <ssym> BLOCKNAME
187 %type <bval> block
188 %left COLONCOLON
193 start : { current_type = NULL;
194 search_field = 0;
195 leftdiv_is_integer = 0;
197 normal_start {}
200 normal_start :
201 exp1
202 | type_exp
205 type_exp: type
207 pstate->push_new<type_operation> ($1);
208 current_type = $1; } ;
210 /* Expressions, including the comma operator. */
211 exp1 : exp
212 | exp1 ',' exp
213 { pstate->wrap2<comma_operation> (); }
216 /* Expressions, not including the comma operator. */
217 exp : exp '^' %prec UNARY
218 { pstate->wrap<unop_ind_operation> ();
219 if (current_type)
220 current_type = current_type->target_type (); }
223 exp : '@' exp %prec UNARY
224 { pstate->wrap<unop_addr_operation> ();
225 if (current_type)
226 current_type = TYPE_POINTER_TYPE (current_type); }
229 exp : '-' exp %prec UNARY
230 { pstate->wrap<unary_neg_operation> (); }
233 exp : NOT exp %prec UNARY
234 { pstate->wrap<unary_logical_not_operation> (); }
237 exp : INCREMENT '(' exp ')' %prec UNARY
238 { pstate->wrap<preinc_operation> (); }
241 exp : DECREMENT '(' exp ')' %prec UNARY
242 { pstate->wrap<predec_operation> (); }
246 field_exp : exp '.' %prec UNARY
247 { search_field = 1; }
250 exp : field_exp FIELDNAME
252 pstate->push_new<structop_operation>
253 (pstate->pop (), copy_name ($2));
254 search_field = 0;
255 if (current_type)
257 while (current_type->code ()
258 == TYPE_CODE_PTR)
259 current_type =
260 current_type->target_type ();
261 current_type = lookup_struct_elt_type (
262 current_type, $2.ptr, 0);
268 exp : field_exp name
270 pstate->push_new<structop_operation>
271 (pstate->pop (), copy_name ($2));
272 search_field = 0;
273 if (current_type)
275 while (current_type->code ()
276 == TYPE_CODE_PTR)
277 current_type =
278 current_type->target_type ();
279 current_type = lookup_struct_elt_type (
280 current_type, $2.ptr, 0);
284 exp : field_exp name COMPLETE
286 structop_base_operation *op
287 = new structop_ptr_operation (pstate->pop (),
288 copy_name ($2));
289 pstate->mark_struct_expression (op);
290 pstate->push (operation_up (op));
293 exp : field_exp COMPLETE
295 structop_base_operation *op
296 = new structop_ptr_operation (pstate->pop (), "");
297 pstate->mark_struct_expression (op);
298 pstate->push (operation_up (op));
302 exp : exp '['
303 /* We need to save the current_type value. */
304 { const char *arrayname;
305 int arrayfieldindex
306 = pascal_is_string_type (current_type, NULL, NULL,
307 NULL, NULL, &arrayname);
308 if (arrayfieldindex)
310 current_type
311 = (current_type
312 ->field (arrayfieldindex - 1).type ());
313 pstate->push_new<structop_operation>
314 (pstate->pop (), arrayname);
316 push_current_type (); }
317 exp1 ']'
318 { pop_current_type ();
319 pstate->wrap2<subscript_operation> ();
320 if (current_type)
321 current_type = current_type->target_type (); }
324 exp : exp '('
325 /* This is to save the value of arglist_len
326 being accumulated by an outer function call. */
327 { push_current_type ();
328 pstate->start_arglist (); }
329 arglist ')' %prec ARROW
331 std::vector<operation_up> args
332 = pstate->pop_vector (pstate->end_arglist ());
333 pstate->push_new<funcall_operation>
334 (pstate->pop (), std::move (args));
335 pop_current_type ();
336 if (current_type)
337 current_type = current_type->target_type ();
341 arglist :
342 | exp
343 { pstate->arglist_len = 1; }
344 | arglist ',' exp %prec ABOVE_COMMA
345 { pstate->arglist_len++; }
348 exp : type '(' exp ')' %prec UNARY
349 { if (current_type)
351 /* Allow automatic dereference of classes. */
352 if ((current_type->code () == TYPE_CODE_PTR)
353 && (current_type->target_type ()->code () == TYPE_CODE_STRUCT)
354 && (($1)->code () == TYPE_CODE_STRUCT))
355 pstate->wrap<unop_ind_operation> ();
357 pstate->push_new<unop_cast_operation>
358 (pstate->pop (), $1);
359 current_type = $1; }
362 exp : '(' exp1 ')'
366 /* Binary operators in order of decreasing precedence. */
368 exp : exp '*' exp
369 { pstate->wrap2<mul_operation> (); }
372 exp : exp '/' {
373 if (current_type && is_integral_type (current_type))
374 leftdiv_is_integer = 1;
378 if (leftdiv_is_integer && current_type
379 && is_integral_type (current_type))
381 pstate->push_new<unop_cast_operation>
382 (pstate->pop (),
383 parse_type (pstate)->builtin_long_double);
384 current_type
385 = parse_type (pstate)->builtin_long_double;
386 leftdiv_is_integer = 0;
389 pstate->wrap2<div_operation> ();
393 exp : exp DIV exp
394 { pstate->wrap2<intdiv_operation> (); }
397 exp : exp MOD exp
398 { pstate->wrap2<rem_operation> (); }
401 exp : exp '+' exp
402 { pstate->wrap2<add_operation> (); }
405 exp : exp '-' exp
406 { pstate->wrap2<sub_operation> (); }
409 exp : exp LSH exp
410 { pstate->wrap2<lsh_operation> (); }
413 exp : exp RSH exp
414 { pstate->wrap2<rsh_operation> (); }
417 exp : exp '=' exp
419 pstate->wrap2<equal_operation> ();
420 current_type = parse_type (pstate)->builtin_bool;
424 exp : exp NOTEQUAL exp
426 pstate->wrap2<notequal_operation> ();
427 current_type = parse_type (pstate)->builtin_bool;
431 exp : exp LEQ exp
433 pstate->wrap2<leq_operation> ();
434 current_type = parse_type (pstate)->builtin_bool;
438 exp : exp GEQ exp
440 pstate->wrap2<geq_operation> ();
441 current_type = parse_type (pstate)->builtin_bool;
445 exp : exp '<' exp
447 pstate->wrap2<less_operation> ();
448 current_type = parse_type (pstate)->builtin_bool;
452 exp : exp '>' exp
454 pstate->wrap2<gtr_operation> ();
455 current_type = parse_type (pstate)->builtin_bool;
459 exp : exp ANDAND exp
460 { pstate->wrap2<bitwise_and_operation> (); }
463 exp : exp XOR exp
464 { pstate->wrap2<bitwise_xor_operation> (); }
467 exp : exp OR exp
468 { pstate->wrap2<bitwise_ior_operation> (); }
471 exp : exp ASSIGN exp
472 { pstate->wrap2<assign_operation> (); }
475 exp : TRUEKEYWORD
477 pstate->push_new<bool_operation> ($1);
478 current_type = parse_type (pstate)->builtin_bool;
482 exp : FALSEKEYWORD
484 pstate->push_new<bool_operation> ($1);
485 current_type = parse_type (pstate)->builtin_bool;
489 exp : INT
491 pstate->push_new<long_const_operation>
492 ($1.type, $1.val);
493 current_type = $1.type;
497 exp : NAME_OR_INT
498 { YYSTYPE val;
499 parse_number (pstate, $1.stoken.ptr,
500 $1.stoken.length, 0, &val);
501 pstate->push_new<long_const_operation>
502 (val.typed_val_int.type,
503 val.typed_val_int.val);
504 current_type = val.typed_val_int.type;
509 exp : FLOAT
511 float_data data;
512 std::copy (std::begin ($1.val), std::end ($1.val),
513 std::begin (data));
514 pstate->push_new<float_const_operation> ($1.type, data);
518 exp : variable
521 exp : DOLLAR_VARIABLE
523 pstate->push_dollar ($1);
525 /* $ is the normal prefix for pascal
526 hexadecimal values but this conflicts
527 with the GDB use for debugger variables
528 so in expression to enter hexadecimal
529 values we still need to use C syntax with
530 0xff */
531 std::string tmp ($1.ptr, $1.length);
532 /* Handle current_type. */
533 struct internalvar *intvar
534 = lookup_only_internalvar (tmp.c_str () + 1);
535 if (intvar != nullptr)
537 scoped_value_mark mark;
539 value *val
540 = value_of_internalvar (pstate->gdbarch (),
541 intvar);
542 current_type = val->type ();
547 exp : SIZEOF '(' type ')' %prec UNARY
549 current_type = parse_type (pstate)->builtin_int;
550 $3 = check_typedef ($3);
551 pstate->push_new<long_const_operation>
552 (parse_type (pstate)->builtin_int,
553 $3->length ()); }
556 exp : SIZEOF '(' exp ')' %prec UNARY
557 { pstate->wrap<unop_sizeof_operation> ();
558 current_type = parse_type (pstate)->builtin_int; }
560 exp : STRING
561 { /* C strings are converted into array constants with
562 an explicit null byte added at the end. Thus
563 the array upper bound is the string length.
564 There is no such thing in C as a completely empty
565 string. */
566 const char *sp = $1.ptr; int count = $1.length;
568 std::vector<operation_up> args (count + 1);
569 for (int i = 0; i < count; ++i)
570 args[i] = (make_operation<long_const_operation>
571 (parse_type (pstate)->builtin_char,
572 *sp++));
573 args[count] = (make_operation<long_const_operation>
574 (parse_type (pstate)->builtin_char,
575 '\0'));
576 pstate->push_new<array_operation>
577 (0, $1.length, std::move (args));
581 /* Object pascal */
582 exp : THIS
584 struct value * this_val;
585 struct type * this_type;
586 pstate->push_new<op_this_operation> ();
587 /* We need type of this. */
588 this_val
589 = value_of_this_silent (pstate->language ());
590 if (this_val)
591 this_type = this_val->type ();
592 else
593 this_type = NULL;
594 if (this_type)
596 if (this_type->code () == TYPE_CODE_PTR)
598 this_type = this_type->target_type ();
599 pstate->wrap<unop_ind_operation> ();
603 current_type = this_type;
607 /* end of object pascal. */
609 block : BLOCKNAME
611 if ($1.sym.symbol != 0)
612 $$ = $1.sym.symbol->value_block ();
613 else
615 std::string copy = copy_name ($1.stoken);
616 struct symtab *tem =
617 lookup_symtab (current_program_space, copy.c_str ());
618 if (tem)
619 $$ = (tem->compunit ()->blockvector ()
620 ->static_block ());
621 else
622 error (_("No file or function \"%s\"."),
623 copy.c_str ());
628 block : block COLONCOLON name
630 std::string copy = copy_name ($3);
631 struct symbol *tem
632 = lookup_symbol (copy.c_str (), $1,
633 SEARCH_FUNCTION_DOMAIN,
634 nullptr).symbol;
636 if (tem == nullptr)
637 error (_("No function \"%s\" in specified context."),
638 copy.c_str ());
639 $$ = tem->value_block (); }
642 variable: block COLONCOLON name
643 { struct block_symbol sym;
645 std::string copy = copy_name ($3);
646 sym = lookup_symbol (copy.c_str (), $1,
647 SEARCH_VFT, NULL);
648 if (sym.symbol == 0)
649 error (_("No symbol \"%s\" in specified context."),
650 copy.c_str ());
652 pstate->push_new<var_value_operation> (sym);
656 qualified_name: typebase COLONCOLON name
658 struct type *type = $1;
660 if (type->code () != TYPE_CODE_STRUCT
661 && type->code () != TYPE_CODE_UNION)
662 error (_("`%s' is not defined as an aggregate type."),
663 type->name ());
665 pstate->push_new<scope_operation>
666 (type, copy_name ($3));
670 variable: qualified_name
671 | COLONCOLON name
673 std::string name = copy_name ($2);
675 struct block_symbol sym
676 = lookup_symbol (name.c_str (), nullptr,
677 SEARCH_VFT, nullptr);
678 pstate->push_symbol (name.c_str (), sym);
682 variable: name_not_typename
683 { struct block_symbol sym = $1.sym;
685 if (sym.symbol)
687 if (symbol_read_needs_frame (sym.symbol))
688 pstate->block_tracker->update (sym);
690 pstate->push_new<var_value_operation> (sym);
691 current_type = sym.symbol->type (); }
692 else if ($1.is_a_field_of_this)
694 struct value * this_val;
695 struct type * this_type;
696 /* Object pascal: it hangs off of `this'. Must
697 not inadvertently convert from a method call
698 to data ref. */
699 pstate->block_tracker->update (sym);
700 operation_up thisop
701 = make_operation<op_this_operation> ();
702 pstate->push_new<structop_operation>
703 (std::move (thisop), copy_name ($1.stoken));
704 /* We need type of this. */
705 this_val
706 = value_of_this_silent (pstate->language ());
707 if (this_val)
708 this_type = this_val->type ();
709 else
710 this_type = NULL;
711 if (this_type)
712 current_type = lookup_struct_elt_type (
713 this_type,
714 copy_name ($1.stoken).c_str (), 0);
715 else
716 current_type = NULL;
718 else
720 std::string arg = copy_name ($1.stoken);
722 bound_minimal_symbol msymbol
723 = lookup_minimal_symbol (current_program_space, arg.c_str ());
724 if (msymbol.minsym != NULL)
725 pstate->push_new<var_msym_value_operation>
726 (msymbol);
727 else if (!have_full_symbols (current_program_space)
728 && !have_partial_symbols (current_program_space))
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 /* Skip over a Pascal string. STR must point to the opening single quote
1046 character. This function returns a pointer to the character after the
1047 closing single quote character.
1049 This function does not support embedded, escaped single quotes, which
1050 is done by placing two consecutive single quotes into a string.
1051 Support for this would be easy to add, but this function is only used
1052 from the Python expression parser, and if we did skip over escaped
1053 quotes then the rest of the expression parser wouldn't handle them
1054 correctly. */
1055 static const char *
1056 pascal_skip_string (const char *str)
1058 gdb_assert (*str == '\'');
1061 ++str;
1062 while (*str != '\0' && *str != '\'');
1064 return str;
1067 /* Read one token, getting characters through lexptr. */
1069 static int
1070 yylex (void)
1072 int c;
1073 int namelen;
1074 const char *tokstart;
1075 char *uptokstart;
1076 const char *tokptr;
1077 int explen, tempbufindex;
1078 static char *tempbuf;
1079 static int tempbufsize;
1081 retry:
1083 pstate->prev_lexptr = pstate->lexptr;
1085 tokstart = pstate->lexptr;
1086 explen = strlen (pstate->lexptr);
1088 /* See if it is a special token of length 3. */
1089 if (explen > 2)
1090 for (const auto &token : tokentab3)
1091 if (strncasecmp (tokstart, token.oper, 3) == 0
1092 && (!isalpha (token.oper[0]) || explen == 3
1093 || (!isalpha (tokstart[3])
1094 && !isdigit (tokstart[3]) && tokstart[3] != '_')))
1096 pstate->lexptr += 3;
1097 yylval.opcode = token.opcode;
1098 return token.token;
1101 /* See if it is a special token of length 2. */
1102 if (explen > 1)
1103 for (const auto &token : tokentab2)
1104 if (strncasecmp (tokstart, token.oper, 2) == 0
1105 && (!isalpha (token.oper[0]) || explen == 2
1106 || (!isalpha (tokstart[2])
1107 && !isdigit (tokstart[2]) && tokstart[2] != '_')))
1109 pstate->lexptr += 2;
1110 yylval.opcode = token.opcode;
1111 return token.token;
1114 switch (c = *tokstart)
1116 case 0:
1117 if (search_field && pstate->parse_completion)
1118 return COMPLETE;
1119 else
1120 return 0;
1122 case ' ':
1123 case '\t':
1124 case '\n':
1125 pstate->lexptr++;
1126 goto retry;
1128 case '\'':
1129 /* We either have a character constant ('0' or '\177' for example)
1130 or we have a quoted symbol reference ('foo(int,int)' in object pascal
1131 for example). */
1132 pstate->lexptr++;
1133 c = *pstate->lexptr++;
1134 if (c == '\\')
1135 c = parse_escape (pstate->gdbarch (), &pstate->lexptr);
1136 else if (c == '\'')
1137 error (_("Empty character constant."));
1139 yylval.typed_val_int.val = c;
1140 yylval.typed_val_int.type = parse_type (pstate)->builtin_char;
1142 c = *pstate->lexptr++;
1143 if (c != '\'')
1145 namelen = pascal_skip_string (tokstart) - tokstart;
1146 if (namelen > 2)
1148 pstate->lexptr = tokstart + namelen;
1149 if (pstate->lexptr[-1] != '\'')
1150 error (_("Unmatched single quote."));
1151 namelen -= 2;
1152 tokstart++;
1153 uptokstart = uptok(tokstart,namelen);
1154 goto tryname;
1156 error (_("Invalid character constant."));
1158 return INT;
1160 case '(':
1161 paren_depth++;
1162 pstate->lexptr++;
1163 return c;
1165 case ')':
1166 if (paren_depth == 0)
1167 return 0;
1168 paren_depth--;
1169 pstate->lexptr++;
1170 return c;
1172 case ',':
1173 if (pstate->comma_terminates && paren_depth == 0)
1174 return 0;
1175 pstate->lexptr++;
1176 return c;
1178 case '.':
1179 /* Might be a floating point number. */
1180 if (pstate->lexptr[1] < '0' || pstate->lexptr[1] > '9')
1182 goto symbol; /* Nope, must be a symbol. */
1185 [[fallthrough]];
1187 case '0':
1188 case '1':
1189 case '2':
1190 case '3':
1191 case '4':
1192 case '5':
1193 case '6':
1194 case '7':
1195 case '8':
1196 case '9':
1198 /* It's a number. */
1199 int got_dot = 0, got_e = 0, toktype;
1200 const char *p = tokstart;
1201 int hex = input_radix > 10;
1203 if (c == '0' && (p[1] == 'x' || p[1] == 'X'))
1205 p += 2;
1206 hex = 1;
1208 else if (c == '0' && (p[1]=='t' || p[1]=='T'
1209 || p[1]=='d' || p[1]=='D'))
1211 p += 2;
1212 hex = 0;
1215 for (;; ++p)
1217 /* This test includes !hex because 'e' is a valid hex digit
1218 and thus does not indicate a floating point number when
1219 the radix is hex. */
1220 if (!hex && !got_e && (*p == 'e' || *p == 'E'))
1221 got_dot = got_e = 1;
1222 /* This test does not include !hex, because a '.' always indicates
1223 a decimal floating point number regardless of the radix. */
1224 else if (!got_dot && *p == '.')
1225 got_dot = 1;
1226 else if (got_e && (p[-1] == 'e' || p[-1] == 'E')
1227 && (*p == '-' || *p == '+'))
1228 /* This is the sign of the exponent, not the end of the
1229 number. */
1230 continue;
1231 /* We will take any letters or digits. parse_number will
1232 complain if past the radix, or if L or U are not final. */
1233 else if ((*p < '0' || *p > '9')
1234 && ((*p < 'a' || *p > 'z')
1235 && (*p < 'A' || *p > 'Z')))
1236 break;
1238 toktype = parse_number (pstate, tokstart,
1239 p - tokstart, got_dot | got_e, &yylval);
1240 if (toktype == ERROR)
1241 error (_("Invalid number \"%.*s\"."), (int) (p - tokstart),
1242 tokstart);
1243 pstate->lexptr = p;
1244 return toktype;
1247 case '+':
1248 case '-':
1249 case '*':
1250 case '/':
1251 case '|':
1252 case '&':
1253 case '^':
1254 case '~':
1255 case '!':
1256 case '@':
1257 case '<':
1258 case '>':
1259 case '[':
1260 case ']':
1261 case '?':
1262 case ':':
1263 case '=':
1264 case '{':
1265 case '}':
1266 symbol:
1267 pstate->lexptr++;
1268 return c;
1270 case '"':
1272 /* Build the gdb internal form of the input string in tempbuf,
1273 translating any standard C escape forms seen. Note that the
1274 buffer is null byte terminated *only* for the convenience of
1275 debugging gdb itself and printing the buffer contents when
1276 the buffer contains no embedded nulls. Gdb does not depend
1277 upon the buffer being null byte terminated, it uses the length
1278 string instead. This allows gdb to handle C strings (as well
1279 as strings in other languages) with embedded null bytes. */
1281 tokptr = ++tokstart;
1282 tempbufindex = 0;
1284 do {
1285 /* Grow the static temp buffer if necessary, including allocating
1286 the first one on demand. */
1287 if (tempbufindex + 1 >= tempbufsize)
1289 tempbuf = (char *) realloc (tempbuf, tempbufsize += 64);
1292 switch (*tokptr)
1294 case '\0':
1295 case '"':
1296 /* Do nothing, loop will terminate. */
1297 break;
1298 case '\\':
1299 ++tokptr;
1300 c = parse_escape (pstate->gdbarch (), &tokptr);
1301 if (c == -1)
1303 continue;
1305 tempbuf[tempbufindex++] = c;
1306 break;
1307 default:
1308 tempbuf[tempbufindex++] = *tokptr++;
1309 break;
1311 } while ((*tokptr != '"') && (*tokptr != '\0'));
1312 if (*tokptr++ != '"')
1314 error (_("Unterminated string in expression."));
1316 tempbuf[tempbufindex] = '\0'; /* See note above. */
1317 yylval.sval.ptr = tempbuf;
1318 yylval.sval.length = tempbufindex;
1319 pstate->lexptr = tokptr;
1320 return (STRING);
1323 if (!(c == '_' || c == '$'
1324 || (c >= 'a' && c <= 'z') || (c >= 'A' && c <= 'Z')))
1325 /* We must have come across a bad character (e.g. ';'). */
1326 error (_("Invalid character '%c' in expression."), c);
1328 /* It's a name. See how long it is. */
1329 namelen = 0;
1330 for (c = tokstart[namelen];
1331 (c == '_' || c == '$' || (c >= '0' && c <= '9')
1332 || (c >= 'a' && c <= 'z') || (c >= 'A' && c <= 'Z') || c == '<');)
1334 /* Template parameter lists are part of the name.
1335 FIXME: This mishandles `print $a<4&&$a>3'. */
1336 if (c == '<')
1338 int i = namelen;
1339 int nesting_level = 1;
1340 while (tokstart[++i])
1342 if (tokstart[i] == '<')
1343 nesting_level++;
1344 else if (tokstart[i] == '>')
1346 if (--nesting_level == 0)
1347 break;
1350 if (tokstart[i] == '>')
1351 namelen = i;
1352 else
1353 break;
1356 /* do NOT uppercase internals because of registers !!! */
1357 c = tokstart[++namelen];
1360 uptokstart = uptok(tokstart,namelen);
1362 /* The token "if" terminates the expression and is NOT
1363 removed from the input stream. */
1364 if (namelen == 2 && uptokstart[0] == 'I' && uptokstart[1] == 'F')
1366 free (uptokstart);
1367 return 0;
1370 pstate->lexptr += namelen;
1372 tryname:
1374 /* Catch specific keywords. Should be done with a data structure. */
1375 switch (namelen)
1377 case 6:
1378 if (strcmp (uptokstart, "OBJECT") == 0)
1380 free (uptokstart);
1381 return CLASS;
1383 if (strcmp (uptokstart, "RECORD") == 0)
1385 free (uptokstart);
1386 return STRUCT;
1388 if (strcmp (uptokstart, "SIZEOF") == 0)
1390 free (uptokstart);
1391 return SIZEOF;
1393 break;
1394 case 5:
1395 if (strcmp (uptokstart, "CLASS") == 0)
1397 free (uptokstart);
1398 return CLASS;
1400 if (strcmp (uptokstart, "FALSE") == 0)
1402 yylval.lval = 0;
1403 free (uptokstart);
1404 return FALSEKEYWORD;
1406 break;
1407 case 4:
1408 if (strcmp (uptokstart, "TRUE") == 0)
1410 yylval.lval = 1;
1411 free (uptokstart);
1412 return TRUEKEYWORD;
1414 if (strcmp (uptokstart, "SELF") == 0)
1416 /* Here we search for 'this' like
1417 inserted in FPC stabs debug info. */
1418 static const char this_name[] = "this";
1420 if (lookup_symbol (this_name, pstate->expression_context_block,
1421 SEARCH_VFT, NULL).symbol)
1423 free (uptokstart);
1424 return THIS;
1427 break;
1428 default:
1429 break;
1432 yylval.sval.ptr = tokstart;
1433 yylval.sval.length = namelen;
1435 if (*tokstart == '$')
1437 free (uptokstart);
1438 return DOLLAR_VARIABLE;
1441 /* Use token-type BLOCKNAME for symbols that happen to be defined as
1442 functions or symtabs. If this is not so, then ...
1443 Use token-type TYPENAME for symbols that happen to be defined
1444 currently as names of types; NAME for other symbols.
1445 The caller is not constrained to care about the distinction. */
1447 std::string tmp = copy_name (yylval.sval);
1448 struct symbol *sym;
1449 struct field_of_this_result is_a_field_of_this;
1450 int is_a_field = 0;
1451 int hextype;
1453 is_a_field_of_this.type = NULL;
1454 if (search_field && current_type)
1455 is_a_field = (lookup_struct_elt_type (current_type,
1456 tmp.c_str (), 1) != NULL);
1457 if (is_a_field)
1458 sym = NULL;
1459 else
1460 sym = lookup_symbol (tmp.c_str (), pstate->expression_context_block,
1461 SEARCH_VFT, &is_a_field_of_this).symbol;
1462 /* second chance uppercased (as Free Pascal does). */
1463 if (!sym && is_a_field_of_this.type == NULL && !is_a_field)
1465 for (int i = 0; i <= namelen; i++)
1467 if ((tmp[i] >= 'a' && tmp[i] <= 'z'))
1468 tmp[i] -= ('a'-'A');
1470 if (search_field && current_type)
1471 is_a_field = (lookup_struct_elt_type (current_type,
1472 tmp.c_str (), 1) != NULL);
1473 if (is_a_field)
1474 sym = NULL;
1475 else
1476 sym = lookup_symbol (tmp.c_str (), pstate->expression_context_block,
1477 SEARCH_VFT, &is_a_field_of_this).symbol;
1479 /* Third chance Capitalized (as GPC does). */
1480 if (!sym && is_a_field_of_this.type == NULL && !is_a_field)
1482 for (int i = 0; i <= namelen; i++)
1484 if (i == 0)
1486 if ((tmp[i] >= 'a' && tmp[i] <= 'z'))
1487 tmp[i] -= ('a'-'A');
1489 else
1490 if ((tmp[i] >= 'A' && tmp[i] <= 'Z'))
1491 tmp[i] -= ('A'-'a');
1493 if (search_field && current_type)
1494 is_a_field = (lookup_struct_elt_type (current_type,
1495 tmp.c_str (), 1) != NULL);
1496 if (is_a_field)
1497 sym = NULL;
1498 else
1499 sym = lookup_symbol (tmp.c_str (), pstate->expression_context_block,
1500 SEARCH_VFT, &is_a_field_of_this).symbol;
1503 if (is_a_field || (is_a_field_of_this.type != NULL))
1505 tempbuf = (char *) realloc (tempbuf, namelen + 1);
1506 strncpy (tempbuf, tmp.c_str (), namelen);
1507 tempbuf [namelen] = 0;
1508 yylval.sval.ptr = tempbuf;
1509 yylval.sval.length = namelen;
1510 yylval.ssym.sym.symbol = NULL;
1511 yylval.ssym.sym.block = NULL;
1512 free (uptokstart);
1513 yylval.ssym.is_a_field_of_this = is_a_field_of_this.type != NULL;
1514 if (is_a_field)
1515 return FIELDNAME;
1516 else
1517 return NAME;
1519 /* Call lookup_symtab, not lookup_partial_symtab, in case there are
1520 no psymtabs (coff, xcoff, or some future change to blow away the
1521 psymtabs once once symbols are read). */
1522 if ((sym && sym->aclass () == LOC_BLOCK)
1523 || lookup_symtab (current_program_space, tmp.c_str ()))
1525 yylval.ssym.sym.symbol = sym;
1526 yylval.ssym.sym.block = NULL;
1527 yylval.ssym.is_a_field_of_this = is_a_field_of_this.type != NULL;
1528 free (uptokstart);
1529 return BLOCKNAME;
1531 if (sym && sym->aclass () == LOC_TYPEDEF)
1533 #if 1
1534 /* Despite the following flaw, we need to keep this code enabled.
1535 Because we can get called from check_stub_method, if we don't
1536 handle nested types then it screws many operations in any
1537 program which uses nested types. */
1538 /* In "A::x", if x is a member function of A and there happens
1539 to be a type (nested or not, since the stabs don't make that
1540 distinction) named x, then this code incorrectly thinks we
1541 are dealing with nested types rather than a member function. */
1543 const char *p;
1544 const char *namestart;
1545 struct symbol *best_sym;
1547 /* Look ahead to detect nested types. This probably should be
1548 done in the grammar, but trying seemed to introduce a lot
1549 of shift/reduce and reduce/reduce conflicts. It's possible
1550 that it could be done, though. Or perhaps a non-grammar, but
1551 less ad hoc, approach would work well. */
1553 /* Since we do not currently have any way of distinguishing
1554 a nested type from a non-nested one (the stabs don't tell
1555 us whether a type is nested), we just ignore the
1556 containing type. */
1558 p = pstate->lexptr;
1559 best_sym = sym;
1560 while (1)
1562 /* Skip whitespace. */
1563 while (*p == ' ' || *p == '\t' || *p == '\n')
1564 ++p;
1565 if (*p == ':' && p[1] == ':')
1567 /* Skip the `::'. */
1568 p += 2;
1569 /* Skip whitespace. */
1570 while (*p == ' ' || *p == '\t' || *p == '\n')
1571 ++p;
1572 namestart = p;
1573 while (*p == '_' || *p == '$' || (*p >= '0' && *p <= '9')
1574 || (*p >= 'a' && *p <= 'z')
1575 || (*p >= 'A' && *p <= 'Z'))
1576 ++p;
1577 if (p != namestart)
1579 struct symbol *cur_sym;
1580 /* As big as the whole rest of the expression, which is
1581 at least big enough. */
1582 char *ncopy
1583 = (char *) alloca (tmp.size () + strlen (namestart)
1584 + 3);
1585 char *tmp1;
1587 tmp1 = ncopy;
1588 memcpy (tmp1, tmp.c_str (), tmp.size ());
1589 tmp1 += tmp.size ();
1590 memcpy (tmp1, "::", 2);
1591 tmp1 += 2;
1592 memcpy (tmp1, namestart, p - namestart);
1593 tmp1[p - namestart] = '\0';
1594 cur_sym
1595 = lookup_symbol (ncopy,
1596 pstate->expression_context_block,
1597 SEARCH_VFT, NULL).symbol;
1598 if (cur_sym)
1600 if (cur_sym->aclass () == LOC_TYPEDEF)
1602 best_sym = cur_sym;
1603 pstate->lexptr = p;
1605 else
1606 break;
1608 else
1609 break;
1611 else
1612 break;
1614 else
1615 break;
1618 yylval.tsym.type = best_sym->type ();
1619 #else /* not 0 */
1620 yylval.tsym.type = sym->type ();
1621 #endif /* not 0 */
1622 free (uptokstart);
1623 return TYPENAME;
1625 yylval.tsym.type
1626 = language_lookup_primitive_type (pstate->language (),
1627 pstate->gdbarch (), tmp.c_str ());
1628 if (yylval.tsym.type != NULL)
1630 free (uptokstart);
1631 return TYPENAME;
1634 /* Input names that aren't symbols but ARE valid hex numbers,
1635 when the input radix permits them, can be names or numbers
1636 depending on the parse. Note we support radixes > 16 here. */
1637 if (!sym
1638 && ((tokstart[0] >= 'a' && tokstart[0] < 'a' + input_radix - 10)
1639 || (tokstart[0] >= 'A' && tokstart[0] < 'A' + input_radix - 10)))
1641 YYSTYPE newlval; /* Its value is ignored. */
1642 hextype = parse_number (pstate, tokstart, namelen, 0, &newlval);
1643 if (hextype == INT)
1645 yylval.ssym.sym.symbol = sym;
1646 yylval.ssym.sym.block = NULL;
1647 yylval.ssym.is_a_field_of_this = is_a_field_of_this.type != NULL;
1648 free (uptokstart);
1649 return NAME_OR_INT;
1653 free(uptokstart);
1654 /* Any other kind of symbol. */
1655 yylval.ssym.sym.symbol = sym;
1656 yylval.ssym.sym.block = NULL;
1657 return NAME;
1661 /* See language.h. */
1664 pascal_language::parser (struct parser_state *par_state) const
1666 /* Setting up the parser state. */
1667 scoped_restore pstate_restore = make_scoped_restore (&pstate);
1668 gdb_assert (par_state != NULL);
1669 pstate = par_state;
1670 paren_depth = 0;
1672 int result = yyparse ();
1673 if (!result)
1674 pstate->set_operation (pstate->pop ());
1675 return result;
1678 static void
1679 yyerror (const char *msg)
1681 pstate->parse_error (msg);