Update readelf's display of RELR sections to include the number of locations relocated
[binutils-gdb.git] / gdb / ada-exp.y
blobf3cef6d2a3722cb8a346edee60b37736589729a8
1 /* YACC parser for Ada expressions, for GDB.
2 Copyright (C) 1986-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 /* Parse an Ada expression from text in a string,
20 and return the result as a struct expression pointer.
21 That structure contains arithmetic operations in reverse polish,
22 with constants represented by operations that are followed by special data.
23 See expression.h for the details of the format.
24 What is important here is that it can be built up sequentially
25 during the process of parsing; the lower levels of the tree always
26 come first in the result.
28 malloc's and realloc's in this file are transformed to
29 xmalloc and xrealloc respectively by the same sed command in the
30 makefile that remaps any other malloc/realloc inserted by the parser
31 generator. Doing this with #defines and trying to control the interaction
32 with include files (<malloc.h> and <stdlib.h> for example) just became
33 too messy, particularly when such includes can be inserted at random
34 times by the parser generator. */
38 #include <ctype.h>
39 #include "expression.h"
40 #include "value.h"
41 #include "parser-defs.h"
42 #include "language.h"
43 #include "ada-lang.h"
44 #include "frame.h"
45 #include "block.h"
46 #include "ada-exp.h"
48 #define parse_type(ps) builtin_type (ps->gdbarch ())
50 /* Remap normal yacc parser interface names (yyparse, yylex, yyerror,
51 etc). */
52 #define GDB_YY_REMAP_PREFIX ada_
53 #include "yy-remap.h"
55 struct name_info {
56 struct symbol *sym;
57 struct minimal_symbol *msym;
58 const struct block *block;
59 struct stoken stoken;
62 /* The state of the parser, used internally when we are parsing the
63 expression. */
65 static struct parser_state *pstate = NULL;
67 using namespace expr;
69 /* A convenience typedef. */
70 typedef std::unique_ptr<ada_assign_operation> ada_assign_up;
72 /* Data that must be held for the duration of a parse. */
74 struct ada_parse_state
76 explicit ada_parse_state (const char *expr)
77 : m_original_expr (expr)
81 std::string find_completion_bounds ();
83 const gdb_mpz *push_integer (gdb_mpz &&val)
85 auto &result = m_int_storage.emplace_back (new gdb_mpz (std::move (val)));
86 return result.get ();
89 /* The components being constructed during this parse. */
90 std::vector<ada_component_up> components;
92 /* The associations being constructed during this parse. */
93 std::vector<ada_association_up> associations;
95 /* The stack of currently active assignment expressions. This is used
96 to implement '@', the target name symbol. */
97 std::vector<ada_assign_up> assignments;
99 /* Track currently active iterated assignment names. */
100 std::unordered_map<std::string, std::vector<ada_index_var_operation *>>
101 iterated_associations;
103 auto_obstack temp_space;
105 /* Depth of parentheses, used by the lexer. */
106 int paren_depth = 0;
108 /* When completing, we'll return a special character at the end of the
109 input, to signal the completion position to the lexer. This is
110 done because flex does not have a generally useful way to detect
111 EOF in a pattern. This variable records whether the special
112 character has been emitted. */
113 bool returned_complete = false;
115 private:
117 /* We don't have a good way to manage non-POD data in Yacc, so store
118 values here. The storage here is only valid for the duration of
119 the parse. */
120 std::vector<std::unique_ptr<gdb_mpz>> m_int_storage;
122 /* The original expression string. */
123 const char *m_original_expr;
126 /* The current Ada parser object. */
128 static ada_parse_state *ada_parser;
130 int yyparse (void);
132 static int yylex (void);
134 static void yyerror (const char *);
136 static void write_int (struct parser_state *, LONGEST, struct type *);
138 static void write_object_renaming (struct parser_state *,
139 const struct block *, const char *, int,
140 const char *, int);
142 static struct type* write_var_or_type (struct parser_state *,
143 const struct block *, struct stoken);
144 static struct type *write_var_or_type_completion (struct parser_state *,
145 const struct block *,
146 struct stoken);
148 static void write_name_assoc (struct parser_state *, struct stoken);
150 static const struct block *block_lookup (const struct block *, const char *);
152 static void write_ambiguous_var (struct parser_state *,
153 const struct block *, const char *, int);
155 static struct type *type_for_char (struct parser_state *, ULONGEST);
157 static struct type *type_system_address (struct parser_state *);
159 /* Handle Ada type resolution for OP. DEPROCEDURE_P and CONTEXT_TYPE
160 are passed to the resolve method, if called. */
161 static operation_up
162 resolve (operation_up &&op, bool deprocedure_p, struct type *context_type)
164 operation_up result = std::move (op);
165 ada_resolvable *res = dynamic_cast<ada_resolvable *> (result.get ());
166 if (res != nullptr)
167 return res->replace (std::move (result),
168 pstate->expout.get (),
169 deprocedure_p,
170 pstate->parse_completion,
171 pstate->block_tracker,
172 context_type);
173 return result;
176 /* Like parser_state::pop, but handles Ada type resolution.
177 DEPROCEDURE_P and CONTEXT_TYPE are passed to the resolve method, if
178 called. */
179 static operation_up
180 ada_pop (bool deprocedure_p = true, struct type *context_type = nullptr)
182 /* Of course it's ok to call parser_state::pop here... */
183 return resolve (pstate->pop (), deprocedure_p, context_type);
186 /* Like parser_state::wrap, but use ada_pop to pop the value. */
187 template<typename T>
188 void
189 ada_wrap ()
191 operation_up arg = ada_pop ();
192 pstate->push_new<T> (std::move (arg));
195 /* Create and push an address-of operation, as appropriate for Ada.
196 If TYPE is not NULL, the resulting operation will be wrapped in a
197 cast to TYPE. */
198 static void
199 ada_addrof (struct type *type = nullptr)
201 operation_up arg = ada_pop (false);
202 operation_up addr = make_operation<unop_addr_operation> (std::move (arg));
203 operation_up wrapped
204 = make_operation<ada_wrapped_operation> (std::move (addr));
205 if (type != nullptr)
206 wrapped = make_operation<unop_cast_operation> (std::move (wrapped), type);
207 pstate->push (std::move (wrapped));
210 /* Handle operator overloading. Either returns a function all
211 operation wrapping the arguments, or it returns null, leaving the
212 caller to construct the appropriate operation. If RHS is null, a
213 unary operator is assumed. */
214 static operation_up
215 maybe_overload (enum exp_opcode op, operation_up &lhs, operation_up &rhs)
217 struct value *args[2];
219 int nargs = 1;
220 args[0] = lhs->evaluate (nullptr, pstate->expout.get (),
221 EVAL_AVOID_SIDE_EFFECTS);
222 if (rhs == nullptr)
223 args[1] = nullptr;
224 else
226 args[1] = rhs->evaluate (nullptr, pstate->expout.get (),
227 EVAL_AVOID_SIDE_EFFECTS);
228 ++nargs;
231 block_symbol fn = ada_find_operator_symbol (op, pstate->parse_completion,
232 nargs, args);
233 if (fn.symbol == nullptr)
234 return {};
236 if (symbol_read_needs_frame (fn.symbol))
237 pstate->block_tracker->update (fn.block, INNERMOST_BLOCK_FOR_SYMBOLS);
238 operation_up callee = make_operation<ada_var_value_operation> (fn);
240 std::vector<operation_up> argvec;
241 argvec.push_back (std::move (lhs));
242 if (rhs != nullptr)
243 argvec.push_back (std::move (rhs));
244 return make_operation<ada_funcall_operation> (std::move (callee),
245 std::move (argvec));
248 /* Like parser_state::wrap, but use ada_pop to pop the value, and
249 handle unary overloading. */
250 template<typename T>
251 void
252 ada_wrap_overload (enum exp_opcode op)
254 operation_up arg = ada_pop ();
255 operation_up empty;
257 operation_up call = maybe_overload (op, arg, empty);
258 if (call == nullptr)
259 call = make_operation<T> (std::move (arg));
260 pstate->push (std::move (call));
263 /* A variant of parser_state::wrap2 that uses ada_pop to pop both
264 operands, and then pushes a new Ada-wrapped operation of the
265 template type T. */
266 template<typename T>
267 void
268 ada_un_wrap2 (enum exp_opcode op)
270 operation_up rhs = ada_pop ();
271 operation_up lhs = ada_pop ();
273 operation_up wrapped = maybe_overload (op, lhs, rhs);
274 if (wrapped == nullptr)
276 wrapped = make_operation<T> (std::move (lhs), std::move (rhs));
277 wrapped = make_operation<ada_wrapped_operation> (std::move (wrapped));
279 pstate->push (std::move (wrapped));
282 /* A variant of parser_state::wrap2 that uses ada_pop to pop both
283 operands. Unlike ada_un_wrap2, ada_wrapped_operation is not
284 used. */
285 template<typename T>
286 void
287 ada_wrap2 (enum exp_opcode op)
289 operation_up rhs = ada_pop ();
290 operation_up lhs = ada_pop ();
291 operation_up call = maybe_overload (op, lhs, rhs);
292 if (call == nullptr)
293 call = make_operation<T> (std::move (lhs), std::move (rhs));
294 pstate->push (std::move (call));
297 /* A variant of parser_state::wrap2 that uses ada_pop to pop both
298 operands. OP is also passed to the constructor of the new binary
299 operation. */
300 template<typename T>
301 void
302 ada_wrap_op (enum exp_opcode op)
304 operation_up rhs = ada_pop ();
305 operation_up lhs = ada_pop ();
306 operation_up call = maybe_overload (op, lhs, rhs);
307 if (call == nullptr)
308 call = make_operation<T> (op, std::move (lhs), std::move (rhs));
309 pstate->push (std::move (call));
312 /* Pop three operands using ada_pop, then construct a new ternary
313 operation of type T and push it. */
314 template<typename T>
315 void
316 ada_wrap3 ()
318 operation_up rhs = ada_pop ();
319 operation_up mid = ada_pop ();
320 operation_up lhs = ada_pop ();
321 pstate->push_new<T> (std::move (lhs), std::move (mid), std::move (rhs));
324 /* Pop NARGS operands, then a callee operand, and use these to
325 construct and push a new Ada function call operation. */
326 static void
327 ada_funcall (int nargs)
329 /* We use the ordinary pop here, because we're going to do
330 resolution in a separate step, in order to handle array
331 indices. */
332 std::vector<operation_up> args = pstate->pop_vector (nargs);
333 /* Call parser_state::pop here, because we don't want to
334 function-convert the callee slot of a call we're already
335 constructing. */
336 operation_up callee = pstate->pop ();
338 ada_var_value_operation *vvo
339 = dynamic_cast<ada_var_value_operation *> (callee.get ());
340 int array_arity = 0;
341 struct type *callee_t = nullptr;
342 if (vvo == nullptr
343 || vvo->get_symbol ()->domain () != UNDEF_DOMAIN)
345 struct value *callee_v = callee->evaluate (nullptr,
346 pstate->expout.get (),
347 EVAL_AVOID_SIDE_EFFECTS);
348 callee_t = ada_check_typedef (callee_v->type ());
349 array_arity = ada_array_arity (callee_t);
352 for (int i = 0; i < nargs; ++i)
354 struct type *subtype = nullptr;
355 if (i < array_arity)
356 subtype = ada_index_type (callee_t, i + 1, "array type");
357 args[i] = resolve (std::move (args[i]), true, subtype);
360 std::unique_ptr<ada_funcall_operation> funcall
361 (new ada_funcall_operation (std::move (callee), std::move (args)));
362 funcall->resolve (pstate->expout.get (), true, pstate->parse_completion,
363 pstate->block_tracker, nullptr);
364 pstate->push (std::move (funcall));
367 /* Create a new ada_component_up of the indicated type and arguments,
368 and push it on the global 'components' vector. */
369 template<typename T, typename... Arg>
370 void
371 push_component (Arg... args)
373 ada_parser->components.emplace_back (new T (std::forward<Arg> (args)...));
376 /* Examine the final element of the 'components' vector, and return it
377 as a pointer to an ada_choices_component. The caller is
378 responsible for ensuring that the final element is in fact an
379 ada_choices_component. */
380 static ada_choices_component *
381 choice_component ()
383 ada_component *last = ada_parser->components.back ().get ();
384 return gdb::checked_static_cast<ada_choices_component *> (last);
387 /* Pop the most recent component from the global stack, and return
388 it. */
389 static ada_component_up
390 pop_component ()
392 ada_component_up result = std::move (ada_parser->components.back ());
393 ada_parser->components.pop_back ();
394 return result;
397 /* Pop the N most recent components from the global stack, and return
398 them in a vector. */
399 static std::vector<ada_component_up>
400 pop_components (int n)
402 std::vector<ada_component_up> result (n);
403 for (int i = 1; i <= n; ++i)
404 result[n - i] = pop_component ();
405 return result;
408 /* Create a new ada_association_up of the indicated type and
409 arguments, and push it on the global 'associations' vector. */
410 template<typename T, typename... Arg>
411 void
412 push_association (Arg... args)
414 ada_parser->associations.emplace_back (new T (std::forward<Arg> (args)...));
417 /* Pop the most recent association from the global stack, and return
418 it. */
419 static ada_association_up
420 pop_association ()
422 ada_association_up result = std::move (ada_parser->associations.back ());
423 ada_parser->associations.pop_back ();
424 return result;
427 /* Pop the N most recent associations from the global stack, and
428 return them in a vector. */
429 static std::vector<ada_association_up>
430 pop_associations (int n)
432 std::vector<ada_association_up> result (n);
433 for (int i = 1; i <= n; ++i)
434 result[n - i] = pop_association ();
435 return result;
438 /* Expression completer for attributes. */
439 struct ada_tick_completer : public expr_completion_base
441 explicit ada_tick_completer (std::string &&name)
442 : m_name (std::move (name))
446 bool complete (struct expression *exp,
447 completion_tracker &tracker) override;
449 private:
451 std::string m_name;
454 /* Make a new ada_tick_completer and wrap it in a unique pointer. */
455 static std::unique_ptr<expr_completion_base>
456 make_tick_completer (struct stoken tok)
458 return (std::unique_ptr<expr_completion_base>
459 (new ada_tick_completer (std::string (tok.ptr, tok.length))));
464 %union
466 LONGEST lval;
467 struct {
468 const gdb_mpz *val;
469 struct type *type;
470 } typed_val;
471 struct {
472 LONGEST val;
473 struct type *type;
474 } typed_char;
475 struct {
476 gdb_byte val[16];
477 struct type *type;
478 } typed_val_float;
479 struct type *tval;
480 struct stoken sval;
481 const struct block *bval;
482 struct internalvar *ivar;
485 %type <lval> positional_list component_groups component_associations
486 %type <lval> aggregate_component_list
487 %type <tval> var_or_type type_prefix opt_type_prefix
489 %token <typed_val> INT NULL_PTR
490 %token <typed_char> CHARLIT
491 %token <typed_val_float> FLOAT
492 %token TRUEKEYWORD FALSEKEYWORD
493 %token WITH DELTA
494 %token COLONCOLON
495 %token <sval> STRING NAME DOT_ID TICK_COMPLETE DOT_COMPLETE NAME_COMPLETE
496 %type <bval> block
497 %type <lval> arglist tick_arglist
499 /* Special type cases, put in to allow the parser to distinguish different
500 legal basetypes. */
501 %token <sval> DOLLAR_VARIABLE
503 %nonassoc ASSIGN
504 %left _AND_ OR XOR THEN ELSE
505 %left '=' NOTEQUAL '<' '>' LEQ GEQ IN DOTDOT
506 %left '@'
507 %left '+' '-' '&'
508 %left UNARY
509 %left '*' '/' MOD REM
510 %right STARSTAR ABS NOT
512 /* Artificial token to give NAME => ... and NAME | priority over reducing
513 NAME to <primary> and to give <primary>' priority over reducing <primary>
514 to <simple_exp>. */
515 %nonassoc VAR
517 %nonassoc ARROW '|'
519 %right TICK_ACCESS TICK_ADDRESS TICK_FIRST TICK_LAST TICK_LENGTH
520 %right TICK_MAX TICK_MIN TICK_MODULUS
521 %right TICK_POS TICK_RANGE TICK_SIZE TICK_TAG TICK_VAL
522 %right TICK_COMPLETE TICK_ENUM_REP TICK_ENUM_VAL
523 /* The following are right-associative only so that reductions at this
524 precedence have lower precedence than '.' and '('. The syntax still
525 forces a.b.c, e.g., to be LEFT-associated. */
526 %right '.' '(' '[' DOT_ID DOT_COMPLETE
528 %token NEW OTHERS FOR
533 start : exp1
536 /* Expressions, including the sequencing operator. */
537 exp1 : exp
538 | exp1 ';' exp
539 { ada_wrap2<comma_operation> (BINOP_COMMA); }
540 | primary ASSIGN
542 ada_parser->assignments.emplace_back
543 (new ada_assign_operation (ada_pop (), nullptr));
545 exp /* Extension for convenience */
547 ada_assign_up assign
548 = std::move (ada_parser->assignments.back ());
549 ada_parser->assignments.pop_back ();
550 value *lhs_val = (assign->eval_for_resolution
551 (pstate->expout.get ()));
553 operation_up rhs = pstate->pop ();
554 rhs = resolve (std::move (rhs), true,
555 lhs_val->type ());
557 assign->set_rhs (std::move (rhs));
558 pstate->push (std::move (assign));
562 /* Expressions, not including the sequencing operator. */
564 primary : primary DOT_ID
566 if (strcmp ($2.ptr, "all") == 0)
567 ada_wrap<ada_unop_ind_operation> ();
568 else
570 operation_up arg = ada_pop ();
571 pstate->push_new<ada_structop_operation>
572 (std::move (arg), copy_name ($2));
577 primary : primary DOT_COMPLETE
579 /* This is done even for ".all", because
580 that might be a prefix. */
581 operation_up arg = ada_pop ();
582 ada_structop_operation *str_op
583 = (new ada_structop_operation
584 (std::move (arg), copy_name ($2)));
585 str_op->set_prefix (ada_parser->find_completion_bounds ());
586 pstate->push (operation_up (str_op));
587 pstate->mark_struct_expression (str_op);
591 primary : primary '(' arglist ')'
592 { ada_funcall ($3); }
593 | var_or_type '(' arglist ')'
595 if ($1 != NULL)
597 if ($3 != 1)
598 error (_("Invalid conversion"));
599 operation_up arg = ada_pop ();
600 pstate->push_new<unop_cast_operation>
601 (std::move (arg), $1);
603 else
604 ada_funcall ($3);
608 primary : var_or_type '\'' '(' exp ')'
610 if ($1 == NULL)
611 error (_("Type required for qualification"));
612 operation_up arg = ada_pop (true,
613 check_typedef ($1));
614 pstate->push_new<ada_qual_operation>
615 (std::move (arg), $1);
619 primary :
620 primary '(' simple_exp DOTDOT simple_exp ')'
621 { ada_wrap3<ada_ternop_slice_operation> (); }
622 | var_or_type '(' simple_exp DOTDOT simple_exp ')'
623 { if ($1 == NULL)
624 ada_wrap3<ada_ternop_slice_operation> ();
625 else
626 error (_("Cannot slice a type"));
630 primary : '(' exp1 ')' { }
633 /* The following rule causes a conflict with the type conversion
634 var_or_type (exp)
635 To get around it, we give '(' higher priority and add bridge rules for
636 var_or_type (exp, exp, ...)
637 var_or_type (exp .. exp)
638 We also have the action for var_or_type(exp) generate a function call
639 when the first symbol does not denote a type. */
641 primary : var_or_type %prec VAR
642 { if ($1 != NULL)
643 pstate->push_new<type_operation> ($1);
647 primary : DOLLAR_VARIABLE /* Various GDB extensions */
648 { pstate->push_dollar ($1); }
651 primary : aggregate
653 pstate->push_new<ada_aggregate_operation>
654 (pop_component ());
658 primary : '@'
660 if (ada_parser->assignments.empty ())
661 error (_("the target name symbol ('@') may only "
662 "appear in an assignment context"));
663 ada_assign_operation *current
664 = ada_parser->assignments.back ().get ();
665 pstate->push_new<ada_target_operation> (current);
669 simple_exp : primary
672 simple_exp : '-' simple_exp %prec UNARY
673 { ada_wrap_overload<ada_neg_operation> (UNOP_NEG); }
676 simple_exp : '+' simple_exp %prec UNARY
678 operation_up arg = ada_pop ();
679 operation_up empty;
681 /* If an overloaded operator was found, use
682 it. Otherwise, unary + has no effect and
683 the argument can be pushed instead. */
684 operation_up call = maybe_overload (UNOP_PLUS, arg,
685 empty);
686 if (call != nullptr)
687 arg = std::move (call);
688 pstate->push (std::move (arg));
692 simple_exp : NOT simple_exp %prec UNARY
694 ada_wrap_overload<unary_logical_not_operation>
695 (UNOP_LOGICAL_NOT);
699 simple_exp : ABS simple_exp %prec UNARY
700 { ada_wrap_overload<ada_abs_operation> (UNOP_ABS); }
703 arglist : { $$ = 0; }
706 arglist : exp
707 { $$ = 1; }
708 | NAME ARROW exp
709 { $$ = 1; }
710 | arglist ',' exp
711 { $$ = $1 + 1; }
712 | arglist ',' NAME ARROW exp
713 { $$ = $1 + 1; }
716 primary : '{' var_or_type '}' primary %prec '.'
717 /* GDB extension */
719 if ($2 == NULL)
720 error (_("Type required within braces in coercion"));
721 operation_up arg = ada_pop ();
722 pstate->push_new<unop_memval_operation>
723 (std::move (arg), $2);
727 /* Binary operators in order of decreasing precedence. */
729 simple_exp : simple_exp STARSTAR simple_exp
730 { ada_wrap2<ada_binop_exp_operation> (BINOP_EXP); }
733 simple_exp : simple_exp '*' simple_exp
734 { ada_wrap2<ada_binop_mul_operation> (BINOP_MUL); }
737 simple_exp : simple_exp '/' simple_exp
738 { ada_wrap2<ada_binop_div_operation> (BINOP_DIV); }
741 simple_exp : simple_exp REM simple_exp /* May need to be fixed to give correct Ada REM */
742 { ada_wrap2<ada_binop_rem_operation> (BINOP_REM); }
745 simple_exp : simple_exp MOD simple_exp
746 { ada_wrap2<ada_binop_mod_operation> (BINOP_MOD); }
749 simple_exp : simple_exp '@' simple_exp /* GDB extension */
750 { ada_wrap2<repeat_operation> (BINOP_REPEAT); }
753 simple_exp : simple_exp '+' simple_exp
754 { ada_wrap_op<ada_binop_addsub_operation> (BINOP_ADD); }
757 simple_exp : simple_exp '&' simple_exp
758 { ada_wrap2<ada_concat_operation> (BINOP_CONCAT); }
761 simple_exp : simple_exp '-' simple_exp
762 { ada_wrap_op<ada_binop_addsub_operation> (BINOP_SUB); }
765 relation : simple_exp
768 relation : simple_exp '=' simple_exp
769 { ada_wrap_op<ada_binop_equal_operation> (BINOP_EQUAL); }
772 relation : simple_exp NOTEQUAL simple_exp
773 { ada_wrap_op<ada_binop_equal_operation> (BINOP_NOTEQUAL); }
776 relation : simple_exp LEQ simple_exp
777 { ada_un_wrap2<leq_operation> (BINOP_LEQ); }
780 relation : simple_exp IN simple_exp DOTDOT simple_exp
781 { ada_wrap3<ada_ternop_range_operation> (); }
782 | simple_exp IN primary TICK_RANGE tick_arglist
784 operation_up rhs = ada_pop ();
785 operation_up lhs = ada_pop ();
786 pstate->push_new<ada_binop_in_bounds_operation>
787 (std::move (lhs), std::move (rhs), $5);
789 | simple_exp IN var_or_type %prec TICK_ACCESS
791 if ($3 == NULL)
792 error (_("Right operand of 'in' must be type"));
793 operation_up arg = ada_pop ();
794 pstate->push_new<ada_unop_range_operation>
795 (std::move (arg), $3);
797 | simple_exp NOT IN simple_exp DOTDOT simple_exp
798 { ada_wrap3<ada_ternop_range_operation> ();
799 ada_wrap<unary_logical_not_operation> (); }
800 | simple_exp NOT IN primary TICK_RANGE tick_arglist
802 operation_up rhs = ada_pop ();
803 operation_up lhs = ada_pop ();
804 pstate->push_new<ada_binop_in_bounds_operation>
805 (std::move (lhs), std::move (rhs), $6);
806 ada_wrap<unary_logical_not_operation> ();
808 | simple_exp NOT IN var_or_type %prec TICK_ACCESS
810 if ($4 == NULL)
811 error (_("Right operand of 'in' must be type"));
812 operation_up arg = ada_pop ();
813 pstate->push_new<ada_unop_range_operation>
814 (std::move (arg), $4);
815 ada_wrap<unary_logical_not_operation> ();
819 relation : simple_exp GEQ simple_exp
820 { ada_un_wrap2<geq_operation> (BINOP_GEQ); }
823 relation : simple_exp '<' simple_exp
824 { ada_un_wrap2<less_operation> (BINOP_LESS); }
827 relation : simple_exp '>' simple_exp
828 { ada_un_wrap2<gtr_operation> (BINOP_GTR); }
831 exp : relation
832 | and_exp
833 | and_then_exp
834 | or_exp
835 | or_else_exp
836 | xor_exp
839 and_exp :
840 relation _AND_ relation
841 { ada_wrap2<bitwise_and_operation>
842 (BINOP_BITWISE_AND); }
843 | and_exp _AND_ relation
844 { ada_wrap2<bitwise_and_operation>
845 (BINOP_BITWISE_AND); }
848 and_then_exp :
849 relation _AND_ THEN relation
850 { ada_wrap2<logical_and_operation>
851 (BINOP_LOGICAL_AND); }
852 | and_then_exp _AND_ THEN relation
853 { ada_wrap2<logical_and_operation>
854 (BINOP_LOGICAL_AND); }
857 or_exp :
858 relation OR relation
859 { ada_wrap2<bitwise_ior_operation>
860 (BINOP_BITWISE_IOR); }
861 | or_exp OR relation
862 { ada_wrap2<bitwise_ior_operation>
863 (BINOP_BITWISE_IOR); }
866 or_else_exp :
867 relation OR ELSE relation
868 { ada_wrap2<logical_or_operation> (BINOP_LOGICAL_OR); }
869 | or_else_exp OR ELSE relation
870 { ada_wrap2<logical_or_operation> (BINOP_LOGICAL_OR); }
873 xor_exp : relation XOR relation
874 { ada_wrap2<bitwise_xor_operation>
875 (BINOP_BITWISE_XOR); }
876 | xor_exp XOR relation
877 { ada_wrap2<bitwise_xor_operation>
878 (BINOP_BITWISE_XOR); }
881 /* Primaries can denote types (OP_TYPE). In cases such as
882 primary TICK_ADDRESS, where a type would be invalid, it will be
883 caught when evaluate_subexp in ada-lang.c tries to evaluate the
884 primary, expecting a value. Precedence rules resolve the ambiguity
885 in NAME TICK_ACCESS in favor of shifting to form a var_or_type. A
886 construct such as aType'access'access will again cause an error when
887 aType'access evaluates to a type that evaluate_subexp attempts to
888 evaluate. */
889 primary : primary TICK_ACCESS
890 { ada_addrof (); }
891 | primary TICK_ADDRESS
892 { ada_addrof (type_system_address (pstate)); }
893 | primary TICK_COMPLETE
895 pstate->mark_completion (make_tick_completer ($2));
897 | primary TICK_FIRST tick_arglist
899 operation_up arg = ada_pop ();
900 pstate->push_new<ada_unop_atr_operation>
901 (std::move (arg), OP_ATR_FIRST, $3);
903 | primary TICK_LAST tick_arglist
905 operation_up arg = ada_pop ();
906 pstate->push_new<ada_unop_atr_operation>
907 (std::move (arg), OP_ATR_LAST, $3);
909 | primary TICK_LENGTH tick_arglist
911 operation_up arg = ada_pop ();
912 pstate->push_new<ada_unop_atr_operation>
913 (std::move (arg), OP_ATR_LENGTH, $3);
915 | primary TICK_SIZE
916 { ada_wrap<ada_atr_size_operation> (); }
917 | primary TICK_TAG
918 { ada_wrap<ada_atr_tag_operation> (); }
919 | opt_type_prefix TICK_MIN '(' exp ',' exp ')'
920 { ada_wrap2<ada_binop_min_operation> (BINOP_MIN); }
921 | opt_type_prefix TICK_MAX '(' exp ',' exp ')'
922 { ada_wrap2<ada_binop_max_operation> (BINOP_MAX); }
923 | opt_type_prefix TICK_POS '(' exp ')'
924 { ada_wrap<ada_pos_operation> (); }
925 | type_prefix TICK_VAL '(' exp ')'
927 operation_up arg = ada_pop ();
928 pstate->push_new<ada_atr_val_operation>
929 ($1, std::move (arg));
931 | type_prefix TICK_ENUM_REP '(' exp ')'
933 operation_up arg = ada_pop (true, $1);
934 pstate->push_new<ada_atr_enum_rep_operation>
935 ($1, std::move (arg));
937 | type_prefix TICK_ENUM_VAL '(' exp ')'
939 operation_up arg = ada_pop (true, $1);
940 pstate->push_new<ada_atr_enum_val_operation>
941 ($1, std::move (arg));
943 | type_prefix TICK_MODULUS
945 struct type *type_arg = check_typedef ($1);
946 if (!ada_is_modular_type (type_arg))
947 error (_("'modulus must be applied to modular type"));
948 write_int (pstate, ada_modulus (type_arg),
949 type_arg->target_type ());
953 tick_arglist : %prec '('
954 { $$ = 1; }
955 | '(' INT ')'
956 { $$ = $2.val->as_integer<LONGEST> (); }
959 type_prefix :
960 var_or_type
962 if ($1 == NULL)
963 error (_("Prefix must be type"));
964 $$ = $1;
968 opt_type_prefix :
969 type_prefix
970 { $$ = $1; }
971 | /* EMPTY */
972 { $$ = parse_type (pstate)->builtin_void; }
976 primary : INT
978 pstate->push_new<long_const_operation> ($1.type, *$1.val);
979 ada_wrap<ada_wrapped_operation> ();
983 primary : CHARLIT
985 pstate->push_new<ada_char_operation> ($1.type, $1.val);
989 primary : FLOAT
991 float_data data;
992 std::copy (std::begin ($1.val), std::end ($1.val),
993 std::begin (data));
994 pstate->push_new<float_const_operation>
995 ($1.type, data);
996 ada_wrap<ada_wrapped_operation> ();
1000 primary : NULL_PTR
1002 struct type *null_ptr_type
1003 = lookup_pointer_type (parse_type (pstate)->builtin_int0);
1004 write_int (pstate, 0, null_ptr_type);
1008 primary : STRING
1010 pstate->push_new<ada_string_operation>
1011 (copy_name ($1));
1015 primary : TRUEKEYWORD
1017 write_int (pstate, 1,
1018 parse_type (pstate)->builtin_bool);
1020 | FALSEKEYWORD
1022 write_int (pstate, 0,
1023 parse_type (pstate)->builtin_bool);
1027 primary : NEW NAME
1028 { error (_("NEW not implemented.")); }
1031 var_or_type: NAME %prec VAR
1032 { $$ = write_var_or_type (pstate, NULL, $1); }
1033 | NAME_COMPLETE %prec VAR
1035 $$ = write_var_or_type_completion (pstate,
1036 NULL,
1037 $1);
1039 | block NAME %prec VAR
1040 { $$ = write_var_or_type (pstate, $1, $2); }
1041 | block NAME_COMPLETE %prec VAR
1043 $$ = write_var_or_type_completion (pstate,
1045 $2);
1047 | NAME TICK_ACCESS
1049 $$ = write_var_or_type (pstate, NULL, $1);
1050 if ($$ == NULL)
1051 ada_addrof ();
1052 else
1053 $$ = lookup_pointer_type ($$);
1055 | block NAME TICK_ACCESS
1057 $$ = write_var_or_type (pstate, $1, $2);
1058 if ($$ == NULL)
1059 ada_addrof ();
1060 else
1061 $$ = lookup_pointer_type ($$);
1065 /* GDB extension */
1066 block : NAME COLONCOLON
1067 { $$ = block_lookup (NULL, $1.ptr); }
1068 | block NAME COLONCOLON
1069 { $$ = block_lookup ($1, $2.ptr); }
1072 aggregate :
1073 '(' exp WITH DELTA aggregate_component_list ')'
1075 std::vector<ada_component_up> components
1076 = pop_components ($5);
1077 operation_up base = ada_pop ();
1079 push_component<ada_aggregate_component>
1080 (std::move (base), std::move (components));
1082 | '(' aggregate_component_list ')'
1084 std::vector<ada_component_up> components
1085 = pop_components ($2);
1087 push_component<ada_aggregate_component>
1088 (std::move (components));
1092 aggregate_component_list :
1093 component_groups { $$ = $1; }
1094 | positional_list exp
1096 push_component<ada_positional_component>
1097 ($1, ada_pop ());
1098 $$ = $1 + 1;
1100 | positional_list component_groups
1101 { $$ = $1 + $2; }
1104 positional_list :
1105 exp ','
1107 push_component<ada_positional_component>
1108 (0, ada_pop ());
1109 $$ = 1;
1111 | positional_list exp ','
1113 push_component<ada_positional_component>
1114 ($1, ada_pop ());
1115 $$ = $1 + 1;
1119 component_groups:
1120 others { $$ = 1; }
1121 | component_group { $$ = 1; }
1122 | component_group ',' component_groups
1123 { $$ = $3 + 1; }
1126 others : OTHERS ARROW exp
1128 push_component<ada_others_component> (ada_pop ());
1132 component_group :
1133 component_associations
1135 ada_choices_component *choices = choice_component ();
1136 choices->set_associations (pop_associations ($1));
1138 | FOR NAME IN
1140 std::string name = copy_name ($2);
1142 auto iter = ada_parser->iterated_associations.find (name);
1143 if (iter != ada_parser->iterated_associations.end ())
1144 error (_("Nested use of index parameter '%s'"),
1145 name.c_str ());
1147 ada_parser->iterated_associations[name] = {};
1149 component_associations
1151 std::string name = copy_name ($2);
1153 ada_choices_component *choices = choice_component ();
1154 choices->set_associations (pop_associations ($5));
1156 auto iter = ada_parser->iterated_associations.find (name);
1157 gdb_assert (iter != ada_parser->iterated_associations.end ());
1158 for (ada_index_var_operation *var : iter->second)
1159 var->set_choices (choices);
1161 ada_parser->iterated_associations.erase (name);
1163 choices->set_name (std::move (name));
1167 /* We use this somewhat obscure definition in order to handle NAME => and
1168 NAME | differently from exp => and exp |. ARROW and '|' have a precedence
1169 above that of the reduction of NAME to var_or_type. By delaying
1170 decisions until after the => or '|', we convert the ambiguity to a
1171 resolved shift/reduce conflict. */
1172 component_associations :
1173 NAME ARROW exp
1175 push_component<ada_choices_component> (ada_pop ());
1176 write_name_assoc (pstate, $1);
1177 $$ = 1;
1179 | simple_exp ARROW exp
1181 push_component<ada_choices_component> (ada_pop ());
1182 push_association<ada_name_association> (ada_pop ());
1183 $$ = 1;
1185 | simple_exp DOTDOT simple_exp ARROW exp
1187 push_component<ada_choices_component> (ada_pop ());
1188 operation_up rhs = ada_pop ();
1189 operation_up lhs = ada_pop ();
1190 push_association<ada_discrete_range_association>
1191 (std::move (lhs), std::move (rhs));
1192 $$ = 1;
1194 | NAME '|' component_associations
1196 write_name_assoc (pstate, $1);
1197 $$ = $3 + 1;
1199 | simple_exp '|' component_associations
1201 push_association<ada_name_association> (ada_pop ());
1202 $$ = $3 + 1;
1204 | simple_exp DOTDOT simple_exp '|' component_associations
1207 operation_up rhs = ada_pop ();
1208 operation_up lhs = ada_pop ();
1209 push_association<ada_discrete_range_association>
1210 (std::move (lhs), std::move (rhs));
1211 $$ = $5 + 1;
1215 /* Some extensions borrowed from C, for the benefit of those who find they
1216 can't get used to Ada notation in GDB. */
1218 primary : '*' primary %prec '.'
1219 { ada_wrap<ada_unop_ind_operation> (); }
1220 | '&' primary %prec '.'
1221 { ada_addrof (); }
1222 | primary '[' exp ']'
1224 ada_wrap2<subscript_operation> (BINOP_SUBSCRIPT);
1225 ada_wrap<ada_wrapped_operation> ();
1231 /* yylex defined in ada-lex.c: Reads one token, getting characters */
1232 /* through lexptr. */
1234 /* Remap normal flex interface names (yylex) as well as gratuitiously */
1235 /* global symbol names, so we can have multiple flex-generated parsers */
1236 /* in gdb. */
1238 /* (See note above on previous definitions for YACC.) */
1240 #define yy_create_buffer ada_yy_create_buffer
1241 #define yy_delete_buffer ada_yy_delete_buffer
1242 #define yy_init_buffer ada_yy_init_buffer
1243 #define yy_load_buffer_state ada_yy_load_buffer_state
1244 #define yy_switch_to_buffer ada_yy_switch_to_buffer
1245 #define yyrestart ada_yyrestart
1246 #define yytext ada_yytext
1248 /* The following kludge was found necessary to prevent conflicts between */
1249 /* defs.h and non-standard stdlib.h files. */
1250 #define qsort __qsort__dummy
1251 #include "ada-lex.c"
1254 ada_parse (struct parser_state *par_state)
1256 /* Setting up the parser state. */
1257 scoped_restore pstate_restore = make_scoped_restore (&pstate, par_state);
1258 gdb_assert (par_state != NULL);
1260 ada_parse_state parser (par_state->lexptr);
1261 scoped_restore parser_restore = make_scoped_restore (&ada_parser, &parser);
1263 scoped_restore restore_yydebug = make_scoped_restore (&yydebug,
1264 par_state->debug);
1266 lexer_init (yyin); /* (Re-)initialize lexer. */
1268 int result = yyparse ();
1269 if (!result)
1271 struct type *context_type = nullptr;
1272 if (par_state->void_context_p)
1273 context_type = parse_type (par_state)->builtin_void;
1274 pstate->set_operation (ada_pop (true, context_type));
1276 return result;
1279 static void
1280 yyerror (const char *msg)
1282 pstate->parse_error (msg);
1285 /* Emit expression to access an instance of SYM, in block BLOCK (if
1286 non-NULL). */
1288 static void
1289 write_var_from_sym (struct parser_state *par_state, block_symbol sym)
1291 if (symbol_read_needs_frame (sym.symbol))
1292 par_state->block_tracker->update (sym.block, INNERMOST_BLOCK_FOR_SYMBOLS);
1294 par_state->push_new<ada_var_value_operation> (sym);
1297 /* Write integer or boolean constant ARG of type TYPE. */
1299 static void
1300 write_int (struct parser_state *par_state, LONGEST arg, struct type *type)
1302 pstate->push_new<long_const_operation> (type, arg);
1303 ada_wrap<ada_wrapped_operation> ();
1306 /* Emit expression corresponding to the renamed object named
1307 designated by RENAMED_ENTITY[0 .. RENAMED_ENTITY_LEN-1] in the
1308 context of ORIG_LEFT_CONTEXT, to which is applied the operations
1309 encoded by RENAMING_EXPR. MAX_DEPTH is the maximum number of
1310 cascaded renamings to allow. If ORIG_LEFT_CONTEXT is null, it
1311 defaults to the currently selected block. ORIG_SYMBOL is the
1312 symbol that originally encoded the renaming. It is needed only
1313 because its prefix also qualifies any index variables used to index
1314 or slice an array. It should not be necessary once we go to the
1315 new encoding entirely (FIXME pnh 7/20/2007). */
1317 static void
1318 write_object_renaming (struct parser_state *par_state,
1319 const struct block *orig_left_context,
1320 const char *renamed_entity, int renamed_entity_len,
1321 const char *renaming_expr, int max_depth)
1323 char *name;
1324 enum { SIMPLE_INDEX, LOWER_BOUND, UPPER_BOUND } slice_state;
1325 struct block_symbol sym_info;
1327 if (max_depth <= 0)
1328 error (_("Could not find renamed symbol"));
1330 if (orig_left_context == NULL)
1331 orig_left_context = get_selected_block (NULL);
1333 name = obstack_strndup (&ada_parser->temp_space, renamed_entity,
1334 renamed_entity_len);
1335 ada_lookup_encoded_symbol (name, orig_left_context, SEARCH_VFT, &sym_info);
1336 if (sym_info.symbol == NULL)
1337 error (_("Could not find renamed variable: %s"), ada_decode (name).c_str ());
1338 else if (sym_info.symbol->aclass () == LOC_TYPEDEF)
1339 /* We have a renaming of an old-style renaming symbol. Don't
1340 trust the block information. */
1341 sym_info.block = orig_left_context;
1344 const char *inner_renamed_entity;
1345 int inner_renamed_entity_len;
1346 const char *inner_renaming_expr;
1348 switch (ada_parse_renaming (sym_info.symbol, &inner_renamed_entity,
1349 &inner_renamed_entity_len,
1350 &inner_renaming_expr))
1352 case ADA_NOT_RENAMING:
1353 write_var_from_sym (par_state, sym_info);
1354 break;
1355 case ADA_OBJECT_RENAMING:
1356 write_object_renaming (par_state, sym_info.block,
1357 inner_renamed_entity, inner_renamed_entity_len,
1358 inner_renaming_expr, max_depth - 1);
1359 break;
1360 default:
1361 goto BadEncoding;
1365 slice_state = SIMPLE_INDEX;
1366 while (*renaming_expr == 'X')
1368 renaming_expr += 1;
1370 switch (*renaming_expr) {
1371 case 'A':
1372 renaming_expr += 1;
1373 ada_wrap<ada_unop_ind_operation> ();
1374 break;
1375 case 'L':
1376 slice_state = LOWER_BOUND;
1377 [[fallthrough]];
1378 case 'S':
1379 renaming_expr += 1;
1380 if (isdigit (*renaming_expr))
1382 char *next;
1383 long val = strtol (renaming_expr, &next, 10);
1384 if (next == renaming_expr)
1385 goto BadEncoding;
1386 renaming_expr = next;
1387 write_int (par_state, val, parse_type (par_state)->builtin_int);
1389 else
1391 const char *end;
1392 char *index_name;
1393 struct block_symbol index_sym_info;
1395 end = strchr (renaming_expr, 'X');
1396 if (end == NULL)
1397 end = renaming_expr + strlen (renaming_expr);
1399 index_name = obstack_strndup (&ada_parser->temp_space,
1400 renaming_expr,
1401 end - renaming_expr);
1402 renaming_expr = end;
1404 ada_lookup_encoded_symbol (index_name, orig_left_context,
1405 SEARCH_VFT, &index_sym_info);
1406 if (index_sym_info.symbol == NULL)
1407 error (_("Could not find %s"), index_name);
1408 else if (index_sym_info.symbol->aclass () == LOC_TYPEDEF)
1409 /* Index is an old-style renaming symbol. */
1410 index_sym_info.block = orig_left_context;
1411 write_var_from_sym (par_state, index_sym_info);
1413 if (slice_state == SIMPLE_INDEX)
1414 ada_funcall (1);
1415 else if (slice_state == LOWER_BOUND)
1416 slice_state = UPPER_BOUND;
1417 else if (slice_state == UPPER_BOUND)
1419 ada_wrap3<ada_ternop_slice_operation> ();
1420 slice_state = SIMPLE_INDEX;
1422 break;
1424 case 'R':
1426 const char *end;
1428 renaming_expr += 1;
1430 if (slice_state != SIMPLE_INDEX)
1431 goto BadEncoding;
1432 end = strchr (renaming_expr, 'X');
1433 if (end == NULL)
1434 end = renaming_expr + strlen (renaming_expr);
1436 operation_up arg = ada_pop ();
1437 pstate->push_new<ada_structop_operation>
1438 (std::move (arg), std::string (renaming_expr,
1439 end - renaming_expr));
1440 renaming_expr = end;
1441 break;
1444 default:
1445 goto BadEncoding;
1448 if (slice_state == SIMPLE_INDEX)
1449 return;
1451 BadEncoding:
1452 error (_("Internal error in encoding of renaming declaration"));
1455 static const struct block*
1456 block_lookup (const struct block *context, const char *raw_name)
1458 const char *name;
1459 struct symtab *symtab;
1460 const struct block *result = NULL;
1462 std::string name_storage;
1463 if (raw_name[0] == '\'')
1465 raw_name += 1;
1466 name = raw_name;
1468 else
1470 name_storage = ada_encode (raw_name);
1471 name = name_storage.c_str ();
1474 std::vector<struct block_symbol> syms
1475 = ada_lookup_symbol_list (name, context, SEARCH_FUNCTION_DOMAIN);
1477 if (context == NULL
1478 && (syms.empty () || syms[0].symbol->aclass () != LOC_BLOCK))
1479 symtab = lookup_symtab (name);
1480 else
1481 symtab = NULL;
1483 if (symtab != NULL)
1484 result = symtab->compunit ()->blockvector ()->static_block ();
1485 else if (syms.empty () || syms[0].symbol->aclass () != LOC_BLOCK)
1487 if (context == NULL)
1488 error (_("No file or function \"%s\"."), raw_name);
1489 else
1490 error (_("No function \"%s\" in specified context."), raw_name);
1492 else
1494 if (syms.size () > 1)
1495 warning (_("Function name \"%s\" ambiguous here"), raw_name);
1496 result = syms[0].symbol->value_block ();
1499 return result;
1502 static struct symbol*
1503 select_possible_type_sym (const std::vector<struct block_symbol> &syms)
1505 int i;
1506 int preferred_index;
1507 struct type *preferred_type;
1509 preferred_index = -1; preferred_type = NULL;
1510 for (i = 0; i < syms.size (); i += 1)
1511 switch (syms[i].symbol->aclass ())
1513 case LOC_TYPEDEF:
1514 if (ada_prefer_type (syms[i].symbol->type (), preferred_type))
1516 preferred_index = i;
1517 preferred_type = syms[i].symbol->type ();
1519 break;
1520 case LOC_REGISTER:
1521 case LOC_ARG:
1522 case LOC_REF_ARG:
1523 case LOC_REGPARM_ADDR:
1524 case LOC_LOCAL:
1525 case LOC_COMPUTED:
1526 return NULL;
1527 default:
1528 break;
1530 if (preferred_type == NULL)
1531 return NULL;
1532 return syms[preferred_index].symbol;
1535 static struct type*
1536 find_primitive_type (struct parser_state *par_state, const char *name)
1538 struct type *type;
1539 type = language_lookup_primitive_type (par_state->language (),
1540 par_state->gdbarch (),
1541 name);
1542 if (type == NULL && strcmp ("system__address", name) == 0)
1543 type = type_system_address (par_state);
1545 if (type != NULL)
1547 /* Check to see if we have a regular definition of this
1548 type that just didn't happen to have been read yet. */
1549 struct symbol *sym;
1550 char *expanded_name =
1551 (char *) alloca (strlen (name) + sizeof ("standard__"));
1552 strcpy (expanded_name, "standard__");
1553 strcat (expanded_name, name);
1554 sym = ada_lookup_symbol (expanded_name, NULL, SEARCH_TYPE_DOMAIN).symbol;
1555 if (sym != NULL && sym->aclass () == LOC_TYPEDEF)
1556 type = sym->type ();
1559 return type;
1562 static int
1563 chop_selector (const char *name, int end)
1565 int i;
1566 for (i = end - 1; i > 0; i -= 1)
1567 if (name[i] == '.' || (name[i] == '_' && name[i+1] == '_'))
1568 return i;
1569 return -1;
1572 /* If NAME is a string beginning with a separator (either '__', or
1573 '.'), chop this separator and return the result; else, return
1574 NAME. */
1576 static const char *
1577 chop_separator (const char *name)
1579 if (*name == '.')
1580 return name + 1;
1582 if (name[0] == '_' && name[1] == '_')
1583 return name + 2;
1585 return name;
1588 /* Given that SELS is a string of the form (<sep><identifier>)*, where
1589 <sep> is '__' or '.', write the indicated sequence of
1590 STRUCTOP_STRUCT expression operators. Returns a pointer to the
1591 last operation that was pushed. */
1592 static ada_structop_operation *
1593 write_selectors (struct parser_state *par_state, const char *sels)
1595 ada_structop_operation *result = nullptr;
1596 while (*sels != '\0')
1598 const char *p = chop_separator (sels);
1599 sels = p;
1600 while (*sels != '\0' && *sels != '.'
1601 && (sels[0] != '_' || sels[1] != '_'))
1602 sels += 1;
1603 operation_up arg = ada_pop ();
1604 result = new ada_structop_operation (std::move (arg),
1605 std::string (p, sels - p));
1606 pstate->push (operation_up (result));
1608 return result;
1611 /* Write a variable access (OP_VAR_VALUE) to ambiguous encoded name
1612 NAME[0..LEN-1], in block context BLOCK, to be resolved later. Writes
1613 a temporary symbol that is valid until the next call to ada_parse.
1615 static void
1616 write_ambiguous_var (struct parser_state *par_state,
1617 const struct block *block, const char *name, int len)
1619 struct symbol *sym = new (&ada_parser->temp_space) symbol ();
1621 sym->set_domain (UNDEF_DOMAIN);
1622 sym->set_linkage_name (obstack_strndup (&ada_parser->temp_space, name, len));
1623 sym->set_language (language_ada, nullptr);
1625 block_symbol bsym { sym, block };
1626 par_state->push_new<ada_var_value_operation> (bsym);
1629 /* A convenient wrapper around ada_get_field_index that takes
1630 a non NUL-terminated FIELD_NAME0 and a FIELD_NAME_LEN instead
1631 of a NUL-terminated field name. */
1633 static int
1634 ada_nget_field_index (const struct type *type, const char *field_name0,
1635 int field_name_len, int maybe_missing)
1637 char *field_name = (char *) alloca ((field_name_len + 1) * sizeof (char));
1639 strncpy (field_name, field_name0, field_name_len);
1640 field_name[field_name_len] = '\0';
1641 return ada_get_field_index (type, field_name, maybe_missing);
1644 /* If encoded_field_name is the name of a field inside symbol SYM,
1645 then return the type of that field. Otherwise, return NULL.
1647 This function is actually recursive, so if ENCODED_FIELD_NAME
1648 doesn't match one of the fields of our symbol, then try to see
1649 if ENCODED_FIELD_NAME could not be a succession of field names
1650 (in other words, the user entered an expression of the form
1651 TYPE_NAME.FIELD1.FIELD2.FIELD3), in which case we evaluate
1652 each field name sequentially to obtain the desired field type.
1653 In case of failure, we return NULL. */
1655 static struct type *
1656 get_symbol_field_type (struct symbol *sym, const char *encoded_field_name)
1658 const char *field_name = encoded_field_name;
1659 const char *subfield_name;
1660 struct type *type = sym->type ();
1661 int fieldno;
1663 if (type == NULL || field_name == NULL)
1664 return NULL;
1665 type = check_typedef (type);
1667 while (field_name[0] != '\0')
1669 field_name = chop_separator (field_name);
1671 fieldno = ada_get_field_index (type, field_name, 1);
1672 if (fieldno >= 0)
1673 return type->field (fieldno).type ();
1675 subfield_name = field_name;
1676 while (*subfield_name != '\0' && *subfield_name != '.'
1677 && (subfield_name[0] != '_' || subfield_name[1] != '_'))
1678 subfield_name += 1;
1680 if (subfield_name[0] == '\0')
1681 return NULL;
1683 fieldno = ada_nget_field_index (type, field_name,
1684 subfield_name - field_name, 1);
1685 if (fieldno < 0)
1686 return NULL;
1688 type = type->field (fieldno).type ();
1689 field_name = subfield_name;
1692 return NULL;
1695 /* Look up NAME0 (an unencoded identifier or dotted name) in BLOCK (or
1696 expression_block_context if NULL). If it denotes a type, return
1697 that type. Otherwise, write expression code to evaluate it as an
1698 object and return NULL. In this second case, NAME0 will, in general,
1699 have the form <name>(.<selector_name>)*, where <name> is an object
1700 or renaming encoded in the debugging data. Calls error if no
1701 prefix <name> matches a name in the debugging data (i.e., matches
1702 either a complete name or, as a wild-card match, the final
1703 identifier). */
1705 static struct type*
1706 write_var_or_type (struct parser_state *par_state,
1707 const struct block *block, struct stoken name0)
1709 int depth;
1710 char *encoded_name;
1711 int name_len;
1713 std::string name_storage = ada_encode (name0.ptr);
1715 if (block == nullptr)
1717 auto iter = ada_parser->iterated_associations.find (name_storage);
1718 if (iter != ada_parser->iterated_associations.end ())
1720 auto op = std::make_unique<ada_index_var_operation> ();
1721 iter->second.push_back (op.get ());
1722 par_state->push (std::move (op));
1723 return nullptr;
1726 block = par_state->expression_context_block;
1729 name_len = name_storage.size ();
1730 encoded_name = obstack_strndup (&ada_parser->temp_space,
1731 name_storage.c_str (),
1732 name_len);
1733 for (depth = 0; depth < MAX_RENAMING_CHAIN_LENGTH; depth += 1)
1735 int tail_index;
1737 tail_index = name_len;
1738 while (tail_index > 0)
1740 struct symbol *type_sym;
1741 struct symbol *renaming_sym;
1742 const char* renaming;
1743 int renaming_len;
1744 const char* renaming_expr;
1745 int terminator = encoded_name[tail_index];
1747 encoded_name[tail_index] = '\0';
1748 /* In order to avoid double-encoding, we want to only pass
1749 the decoded form to lookup functions. */
1750 std::string decoded_name = ada_decode (encoded_name);
1751 encoded_name[tail_index] = terminator;
1753 std::vector<struct block_symbol> syms
1754 = ada_lookup_symbol_list (decoded_name.c_str (), block,
1755 SEARCH_VFT);
1757 type_sym = select_possible_type_sym (syms);
1759 if (type_sym != NULL)
1760 renaming_sym = type_sym;
1761 else if (syms.size () == 1)
1762 renaming_sym = syms[0].symbol;
1763 else
1764 renaming_sym = NULL;
1766 switch (ada_parse_renaming (renaming_sym, &renaming,
1767 &renaming_len, &renaming_expr))
1769 case ADA_NOT_RENAMING:
1770 break;
1771 case ADA_PACKAGE_RENAMING:
1772 case ADA_EXCEPTION_RENAMING:
1773 case ADA_SUBPROGRAM_RENAMING:
1775 int alloc_len = renaming_len + name_len - tail_index + 1;
1776 char *new_name
1777 = (char *) obstack_alloc (&ada_parser->temp_space,
1778 alloc_len);
1779 strncpy (new_name, renaming, renaming_len);
1780 strcpy (new_name + renaming_len, encoded_name + tail_index);
1781 encoded_name = new_name;
1782 name_len = renaming_len + name_len - tail_index;
1783 goto TryAfterRenaming;
1785 case ADA_OBJECT_RENAMING:
1786 write_object_renaming (par_state, block, renaming, renaming_len,
1787 renaming_expr, MAX_RENAMING_CHAIN_LENGTH);
1788 write_selectors (par_state, encoded_name + tail_index);
1789 return NULL;
1790 default:
1791 internal_error (_("impossible value from ada_parse_renaming"));
1794 if (type_sym != NULL)
1796 struct type *field_type;
1798 if (tail_index == name_len)
1799 return type_sym->type ();
1801 /* We have some extraneous characters after the type name.
1802 If this is an expression "TYPE_NAME.FIELD0.[...].FIELDN",
1803 then try to get the type of FIELDN. */
1804 field_type
1805 = get_symbol_field_type (type_sym, encoded_name + tail_index);
1806 if (field_type != NULL)
1807 return field_type;
1808 else
1809 error (_("Invalid attempt to select from type: \"%s\"."),
1810 name0.ptr);
1812 else if (tail_index == name_len && syms.empty ())
1814 struct type *type = find_primitive_type (par_state,
1815 encoded_name);
1817 if (type != NULL)
1818 return type;
1821 if (syms.size () == 1)
1823 write_var_from_sym (par_state, syms[0]);
1824 write_selectors (par_state, encoded_name + tail_index);
1825 return NULL;
1827 else if (syms.empty ())
1829 struct objfile *objfile = nullptr;
1830 if (block != nullptr)
1831 objfile = block->objfile ();
1833 struct bound_minimal_symbol msym
1834 = ada_lookup_simple_minsym (decoded_name.c_str (), objfile);
1835 if (msym.minsym != NULL)
1837 par_state->push_new<ada_var_msym_value_operation> (msym);
1838 /* Maybe cause error here rather than later? FIXME? */
1839 write_selectors (par_state, encoded_name + tail_index);
1840 return NULL;
1843 if (tail_index == name_len
1844 && strncmp (encoded_name, "standard__",
1845 sizeof ("standard__") - 1) == 0)
1846 error (_("No definition of \"%s\" found."), name0.ptr);
1848 tail_index = chop_selector (encoded_name, tail_index);
1850 else
1852 write_ambiguous_var (par_state, block, encoded_name,
1853 tail_index);
1854 write_selectors (par_state, encoded_name + tail_index);
1855 return NULL;
1859 if (!have_full_symbols () && !have_partial_symbols () && block == NULL)
1860 error (_("No symbol table is loaded. Use the \"file\" command."));
1861 if (block == par_state->expression_context_block)
1862 error (_("No definition of \"%s\" in current context."), name0.ptr);
1863 else
1864 error (_("No definition of \"%s\" in specified context."), name0.ptr);
1866 TryAfterRenaming: ;
1869 error (_("Could not find renamed symbol \"%s\""), name0.ptr);
1873 /* Because ada_completer_word_break_characters does not contain '.' --
1874 and it cannot easily be added, this breaks other completions -- we
1875 have to recreate the completion word-splitting here, so that we can
1876 provide a prefix that is then used when completing field names.
1877 Without this, an attempt like "complete print abc.d" will give a
1878 result like "print def" rather than "print abc.def". */
1880 std::string
1881 ada_parse_state::find_completion_bounds ()
1883 const char *end = pstate->lexptr;
1884 /* First the end of the prefix. Here we stop at the token start or
1885 at '.' or space. */
1886 for (; end > m_original_expr && end[-1] != '.' && !isspace (end[-1]); --end)
1888 /* Nothing. */
1890 /* Now find the start of the prefix. */
1891 const char *ptr = end;
1892 /* Here we allow '.'. */
1893 for (;
1894 ptr > m_original_expr && (ptr[-1] == '.'
1895 || ptr[-1] == '_'
1896 || (ptr[-1] >= 'a' && ptr[-1] <= 'z')
1897 || (ptr[-1] >= 'A' && ptr[-1] <= 'Z')
1898 || (ptr[-1] & 0xff) >= 0x80);
1899 --ptr)
1901 /* Nothing. */
1903 /* ... except, skip leading spaces. */
1904 ptr = skip_spaces (ptr);
1906 return std::string (ptr, end);
1909 /* A wrapper for write_var_or_type that is used specifically when
1910 completion is requested for the last of a sequence of
1911 identifiers. */
1913 static struct type *
1914 write_var_or_type_completion (struct parser_state *par_state,
1915 const struct block *block, struct stoken name0)
1917 int tail_index = chop_selector (name0.ptr, name0.length);
1918 /* If there's no separator, just defer to ordinary symbol
1919 completion. */
1920 if (tail_index == -1)
1921 return write_var_or_type (par_state, block, name0);
1923 std::string copy (name0.ptr, tail_index);
1924 struct type *type = write_var_or_type (par_state, block,
1925 { copy.c_str (),
1926 (int) copy.length () });
1927 /* For completion purposes, it's enough that we return a type
1928 here. */
1929 if (type != nullptr)
1930 return type;
1932 ada_structop_operation *op = write_selectors (par_state,
1933 name0.ptr + tail_index);
1934 op->set_prefix (ada_parser->find_completion_bounds ());
1935 par_state->mark_struct_expression (op);
1936 return nullptr;
1939 /* Write a left side of a component association (e.g., NAME in NAME =>
1940 exp). If NAME has the form of a selected component, write it as an
1941 ordinary expression. If it is a simple variable that unambiguously
1942 corresponds to exactly one symbol that does not denote a type or an
1943 object renaming, also write it normally as an OP_VAR_VALUE.
1944 Otherwise, write it as an OP_NAME.
1946 Unfortunately, we don't know at this point whether NAME is supposed
1947 to denote a record component name or the value of an array index.
1948 Therefore, it is not appropriate to disambiguate an ambiguous name
1949 as we normally would, nor to replace a renaming with its referent.
1950 As a result, in the (one hopes) rare case that one writes an
1951 aggregate such as (R => 42) where R renames an object or is an
1952 ambiguous name, one must write instead ((R) => 42). */
1954 static void
1955 write_name_assoc (struct parser_state *par_state, struct stoken name)
1957 if (strchr (name.ptr, '.') == NULL)
1959 std::vector<struct block_symbol> syms
1960 = ada_lookup_symbol_list (name.ptr,
1961 par_state->expression_context_block,
1962 SEARCH_VFT);
1964 if (syms.size () != 1 || syms[0].symbol->aclass () == LOC_TYPEDEF)
1965 pstate->push_new<ada_string_operation> (copy_name (name));
1966 else
1967 write_var_from_sym (par_state, syms[0]);
1969 else
1970 if (write_var_or_type (par_state, NULL, name) != NULL)
1971 error (_("Invalid use of type."));
1973 push_association<ada_name_association> (ada_pop ());
1976 static struct type *
1977 type_for_char (struct parser_state *par_state, ULONGEST value)
1979 if (value <= 0xff)
1980 return language_string_char_type (par_state->language (),
1981 par_state->gdbarch ());
1982 else if (value <= 0xffff)
1983 return language_lookup_primitive_type (par_state->language (),
1984 par_state->gdbarch (),
1985 "wide_character");
1986 return language_lookup_primitive_type (par_state->language (),
1987 par_state->gdbarch (),
1988 "wide_wide_character");
1991 static struct type *
1992 type_system_address (struct parser_state *par_state)
1994 struct type *type
1995 = language_lookup_primitive_type (par_state->language (),
1996 par_state->gdbarch (),
1997 "system__address");
1998 return type != NULL ? type : parse_type (par_state)->builtin_data_ptr;