xref: /netbsd-src/external/gpl3/gdb.old/dist/gdb/ada-exp.y (revision 8b657b0747480f8989760d71343d6dd33f8d4cf9)
1 /* YACC parser for Ada expressions, for GDB.
2    Copyright (C) 1986-2023 Free Software Foundation, Inc.
3 
4    This file is part of GDB.
5 
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.
10 
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.
15 
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/>.  */
18 
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.
27 
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.  */
35 
36 %{
37 
38 #include "defs.h"
39 #include <ctype.h>
40 #include "expression.h"
41 #include "value.h"
42 #include "parser-defs.h"
43 #include "language.h"
44 #include "ada-lang.h"
45 #include "bfd.h" /* Required by objfiles.h.  */
46 #include "symfile.h" /* Required by objfiles.h.  */
47 #include "objfiles.h" /* For have_full_symbols and have_partial_symbols */
48 #include "frame.h"
49 #include "block.h"
50 #include "ada-exp.h"
51 
52 #define parse_type(ps) builtin_type (ps->gdbarch ())
53 
54 /* Remap normal yacc parser interface names (yyparse, yylex, yyerror,
55    etc).  */
56 #define GDB_YY_REMAP_PREFIX ada_
57 #include "yy-remap.h"
58 
59 struct name_info {
60   struct symbol *sym;
61   struct minimal_symbol *msym;
62   const struct block *block;
63   struct stoken stoken;
64 };
65 
66 /* The state of the parser, used internally when we are parsing the
67    expression.  */
68 
69 static struct parser_state *pstate = NULL;
70 
71 /* The original expression string.  */
72 static const char *original_expr;
73 
74 int yyparse (void);
75 
76 static int yylex (void);
77 
78 static void yyerror (const char *);
79 
80 static void write_int (struct parser_state *, LONGEST, struct type *);
81 
82 static void write_object_renaming (struct parser_state *,
83 				   const struct block *, const char *, int,
84 				   const char *, int);
85 
86 static struct type* write_var_or_type (struct parser_state *,
87 				       const struct block *, struct stoken);
88 static struct type *write_var_or_type_completion (struct parser_state *,
89 						  const struct block *,
90 						  struct stoken);
91 
92 static void write_name_assoc (struct parser_state *, struct stoken);
93 
94 static const struct block *block_lookup (const struct block *, const char *);
95 
96 static void write_ambiguous_var (struct parser_state *,
97 				 const struct block *, const char *, int);
98 
99 static struct type *type_int (struct parser_state *);
100 
101 static struct type *type_long (struct parser_state *);
102 
103 static struct type *type_long_long (struct parser_state *);
104 
105 static struct type *type_long_double (struct parser_state *);
106 
107 static struct type *type_for_char (struct parser_state *, ULONGEST);
108 
109 static struct type *type_boolean (struct parser_state *);
110 
111 static struct type *type_system_address (struct parser_state *);
112 
113 static std::string find_completion_bounds (struct parser_state *);
114 
115 using namespace expr;
116 
117 /* Handle Ada type resolution for OP.  DEPROCEDURE_P and CONTEXT_TYPE
118    are passed to the resolve method, if called.  */
119 static operation_up
120 resolve (operation_up &&op, bool deprocedure_p, struct type *context_type)
121 {
122   operation_up result = std::move (op);
123   ada_resolvable *res = dynamic_cast<ada_resolvable *> (result.get ());
124   if (res != nullptr)
125     return res->replace (std::move (result),
126 			 pstate->expout.get (),
127 			 deprocedure_p,
128 			 pstate->parse_completion,
129 			 pstate->block_tracker,
130 			 context_type);
131   return result;
132 }
133 
134 /* Like parser_state::pop, but handles Ada type resolution.
135    DEPROCEDURE_P and CONTEXT_TYPE are passed to the resolve method, if
136    called.  */
137 static operation_up
138 ada_pop (bool deprocedure_p = true, struct type *context_type = nullptr)
139 {
140   /* Of course it's ok to call parser_state::pop here... */
141   return resolve (pstate->pop (), deprocedure_p, context_type);
142 }
143 
144 /* Like parser_state::wrap, but use ada_pop to pop the value.  */
145 template<typename T>
146 void
147 ada_wrap ()
148 {
149   operation_up arg = ada_pop ();
150   pstate->push_new<T> (std::move (arg));
151 }
152 
153 /* Create and push an address-of operation, as appropriate for Ada.
154    If TYPE is not NULL, the resulting operation will be wrapped in a
155    cast to TYPE.  */
156 static void
157 ada_addrof (struct type *type = nullptr)
158 {
159   operation_up arg = ada_pop (false);
160   operation_up addr = make_operation<unop_addr_operation> (std::move (arg));
161   operation_up wrapped
162     = make_operation<ada_wrapped_operation> (std::move (addr));
163   if (type != nullptr)
164     wrapped = make_operation<unop_cast_operation> (std::move (wrapped), type);
165   pstate->push (std::move (wrapped));
166 }
167 
168 /* Handle operator overloading.  Either returns a function all
169    operation wrapping the arguments, or it returns null, leaving the
170    caller to construct the appropriate operation.  If RHS is null, a
171    unary operator is assumed.  */
172 static operation_up
173 maybe_overload (enum exp_opcode op, operation_up &lhs, operation_up &rhs)
174 {
175   struct value *args[2];
176 
177   int nargs = 1;
178   args[0] = lhs->evaluate (nullptr, pstate->expout.get (),
179 			   EVAL_AVOID_SIDE_EFFECTS);
180   if (rhs == nullptr)
181     args[1] = nullptr;
182   else
183     {
184       args[1] = rhs->evaluate (nullptr, pstate->expout.get (),
185 			       EVAL_AVOID_SIDE_EFFECTS);
186       ++nargs;
187     }
188 
189   block_symbol fn = ada_find_operator_symbol (op, pstate->parse_completion,
190 					      nargs, args);
191   if (fn.symbol == nullptr)
192     return {};
193 
194   if (symbol_read_needs_frame (fn.symbol))
195     pstate->block_tracker->update (fn.block, INNERMOST_BLOCK_FOR_SYMBOLS);
196   operation_up callee = make_operation<ada_var_value_operation> (fn);
197 
198   std::vector<operation_up> argvec;
199   argvec.push_back (std::move (lhs));
200   if (rhs != nullptr)
201     argvec.push_back (std::move (rhs));
202   return make_operation<ada_funcall_operation> (std::move (callee),
203 						std::move (argvec));
204 }
205 
206 /* Like parser_state::wrap, but use ada_pop to pop the value, and
207    handle unary overloading.  */
208 template<typename T>
209 void
210 ada_wrap_overload (enum exp_opcode op)
211 {
212   operation_up arg = ada_pop ();
213   operation_up empty;
214 
215   operation_up call = maybe_overload (op, arg, empty);
216   if (call == nullptr)
217     call = make_operation<T> (std::move (arg));
218   pstate->push (std::move (call));
219 }
220 
221 /* A variant of parser_state::wrap2 that uses ada_pop to pop both
222    operands, and then pushes a new Ada-wrapped operation of the
223    template type T.  */
224 template<typename T>
225 void
226 ada_un_wrap2 (enum exp_opcode op)
227 {
228   operation_up rhs = ada_pop ();
229   operation_up lhs = ada_pop ();
230 
231   operation_up wrapped = maybe_overload (op, lhs, rhs);
232   if (wrapped == nullptr)
233     {
234       wrapped = make_operation<T> (std::move (lhs), std::move (rhs));
235       wrapped = make_operation<ada_wrapped_operation> (std::move (wrapped));
236     }
237   pstate->push (std::move (wrapped));
238 }
239 
240 /* A variant of parser_state::wrap2 that uses ada_pop to pop both
241    operands.  Unlike ada_un_wrap2, ada_wrapped_operation is not
242    used.  */
243 template<typename T>
244 void
245 ada_wrap2 (enum exp_opcode op)
246 {
247   operation_up rhs = ada_pop ();
248   operation_up lhs = ada_pop ();
249   operation_up call = maybe_overload (op, lhs, rhs);
250   if (call == nullptr)
251     call = make_operation<T> (std::move (lhs), std::move (rhs));
252   pstate->push (std::move (call));
253 }
254 
255 /* A variant of parser_state::wrap2 that uses ada_pop to pop both
256    operands.  OP is also passed to the constructor of the new binary
257    operation.  */
258 template<typename T>
259 void
260 ada_wrap_op (enum exp_opcode op)
261 {
262   operation_up rhs = ada_pop ();
263   operation_up lhs = ada_pop ();
264   operation_up call = maybe_overload (op, lhs, rhs);
265   if (call == nullptr)
266     call = make_operation<T> (op, std::move (lhs), std::move (rhs));
267   pstate->push (std::move (call));
268 }
269 
270 /* Pop three operands using ada_pop, then construct a new ternary
271    operation of type T and push it.  */
272 template<typename T>
273 void
274 ada_wrap3 ()
275 {
276   operation_up rhs = ada_pop ();
277   operation_up mid = ada_pop ();
278   operation_up lhs = ada_pop ();
279   pstate->push_new<T> (std::move (lhs), std::move (mid), std::move (rhs));
280 }
281 
282 /* Pop NARGS operands, then a callee operand, and use these to
283    construct and push a new Ada function call operation.  */
284 static void
285 ada_funcall (int nargs)
286 {
287   /* We use the ordinary pop here, because we're going to do
288      resolution in a separate step, in order to handle array
289      indices.  */
290   std::vector<operation_up> args = pstate->pop_vector (nargs);
291   /* Call parser_state::pop here, because we don't want to
292      function-convert the callee slot of a call we're already
293      constructing.  */
294   operation_up callee = pstate->pop ();
295 
296   ada_var_value_operation *vvo
297     = dynamic_cast<ada_var_value_operation *> (callee.get ());
298   int array_arity = 0;
299   struct type *callee_t = nullptr;
300   if (vvo == nullptr
301       || vvo->get_symbol ()->domain () != UNDEF_DOMAIN)
302     {
303       struct value *callee_v = callee->evaluate (nullptr,
304 						 pstate->expout.get (),
305 						 EVAL_AVOID_SIDE_EFFECTS);
306       callee_t = ada_check_typedef (value_type (callee_v));
307       array_arity = ada_array_arity (callee_t);
308     }
309 
310   for (int i = 0; i < nargs; ++i)
311     {
312       struct type *subtype = nullptr;
313       if (i < array_arity)
314 	subtype = ada_index_type (callee_t, i + 1, "array type");
315       args[i] = resolve (std::move (args[i]), true, subtype);
316     }
317 
318   std::unique_ptr<ada_funcall_operation> funcall
319     (new ada_funcall_operation (std::move (callee), std::move (args)));
320   funcall->resolve (pstate->expout.get (), true, pstate->parse_completion,
321 		    pstate->block_tracker, nullptr);
322   pstate->push (std::move (funcall));
323 }
324 
325 /* The components being constructed during this parse.  */
326 static std::vector<ada_component_up> components;
327 
328 /* Create a new ada_component_up of the indicated type and arguments,
329    and push it on the global 'components' vector.  */
330 template<typename T, typename... Arg>
331 void
332 push_component (Arg... args)
333 {
334   components.emplace_back (new T (std::forward<Arg> (args)...));
335 }
336 
337 /* Examine the final element of the 'components' vector, and return it
338    as a pointer to an ada_choices_component.  The caller is
339    responsible for ensuring that the final element is in fact an
340    ada_choices_component.  */
341 static ada_choices_component *
342 choice_component ()
343 {
344   ada_component *last = components.back ().get ();
345   return gdb::checked_static_cast<ada_choices_component *> (last);
346 }
347 
348 /* Pop the most recent component from the global stack, and return
349    it.  */
350 static ada_component_up
351 pop_component ()
352 {
353   ada_component_up result = std::move (components.back ());
354   components.pop_back ();
355   return result;
356 }
357 
358 /* Pop the N most recent components from the global stack, and return
359    them in a vector.  */
360 static std::vector<ada_component_up>
361 pop_components (int n)
362 {
363   std::vector<ada_component_up> result (n);
364   for (int i = 1; i <= n; ++i)
365     result[n - i] = pop_component ();
366   return result;
367 }
368 
369 /* The associations being constructed during this parse.  */
370 static std::vector<ada_association_up> associations;
371 
372 /* Create a new ada_association_up of the indicated type and
373    arguments, and push it on the global 'associations' vector.  */
374 template<typename T, typename... Arg>
375 void
376 push_association (Arg... args)
377 {
378   associations.emplace_back (new T (std::forward<Arg> (args)...));
379 }
380 
381 /* Pop the most recent association from the global stack, and return
382    it.  */
383 static ada_association_up
384 pop_association ()
385 {
386   ada_association_up result = std::move (associations.back ());
387   associations.pop_back ();
388   return result;
389 }
390 
391 /* Pop the N most recent associations from the global stack, and
392    return them in a vector.  */
393 static std::vector<ada_association_up>
394 pop_associations (int n)
395 {
396   std::vector<ada_association_up> result (n);
397   for (int i = 1; i <= n; ++i)
398     result[n - i] = pop_association ();
399   return result;
400 }
401 
402 /* Expression completer for attributes.  */
403 struct ada_tick_completer : public expr_completion_base
404 {
405   explicit ada_tick_completer (std::string &&name)
406     : m_name (std::move (name))
407   {
408   }
409 
410   bool complete (struct expression *exp,
411 		 completion_tracker &tracker) override;
412 
413 private:
414 
415   std::string m_name;
416 };
417 
418 /* Make a new ada_tick_completer and wrap it in a unique pointer.  */
419 static std::unique_ptr<expr_completion_base>
420 make_tick_completer (struct stoken tok)
421 {
422   return (std::unique_ptr<expr_completion_base>
423 	  (new ada_tick_completer (std::string (tok.ptr, tok.length))));
424 }
425 
426 %}
427 
428 %union
429   {
430     LONGEST lval;
431     struct {
432       LONGEST val;
433       struct type *type;
434     } typed_val;
435     struct {
436       gdb_byte val[16];
437       struct type *type;
438     } typed_val_float;
439     struct type *tval;
440     struct stoken sval;
441     const struct block *bval;
442     struct internalvar *ivar;
443   }
444 
445 %type <lval> positional_list component_groups component_associations
446 %type <lval> aggregate_component_list
447 %type <tval> var_or_type type_prefix opt_type_prefix
448 
449 %token <typed_val> INT NULL_PTR CHARLIT
450 %token <typed_val_float> FLOAT
451 %token TRUEKEYWORD FALSEKEYWORD
452 %token COLONCOLON
453 %token <sval> STRING NAME DOT_ID TICK_COMPLETE DOT_COMPLETE NAME_COMPLETE
454 %type <bval> block
455 %type <lval> arglist tick_arglist
456 
457 /* Special type cases, put in to allow the parser to distinguish different
458    legal basetypes.  */
459 %token <sval> DOLLAR_VARIABLE
460 
461 %nonassoc ASSIGN
462 %left _AND_ OR XOR THEN ELSE
463 %left '=' NOTEQUAL '<' '>' LEQ GEQ IN DOTDOT
464 %left '@'
465 %left '+' '-' '&'
466 %left UNARY
467 %left '*' '/' MOD REM
468 %right STARSTAR ABS NOT
469 
470 /* Artificial token to give NAME => ... and NAME | priority over reducing
471    NAME to <primary> and to give <primary>' priority over reducing <primary>
472    to <simple_exp>. */
473 %nonassoc VAR
474 
475 %nonassoc ARROW '|'
476 
477 %right TICK_ACCESS TICK_ADDRESS TICK_FIRST TICK_LAST TICK_LENGTH
478 %right TICK_MAX TICK_MIN TICK_MODULUS
479 %right TICK_POS TICK_RANGE TICK_SIZE TICK_TAG TICK_VAL
480 %right TICK_COMPLETE
481  /* The following are right-associative only so that reductions at this
482     precedence have lower precedence than '.' and '('.  The syntax still
483     forces a.b.c, e.g., to be LEFT-associated.  */
484 %right '.' '(' '[' DOT_ID DOT_COMPLETE
485 
486 %token NEW OTHERS
487 
488 
489 %%
490 
491 start   :	exp1
492 	;
493 
494 /* Expressions, including the sequencing operator.  */
495 exp1	:	exp
496 	|	exp1 ';' exp
497 			{ ada_wrap2<comma_operation> (BINOP_COMMA); }
498 	| 	primary ASSIGN exp   /* Extension for convenience */
499 			{
500 			  operation_up rhs = pstate->pop ();
501 			  operation_up lhs = ada_pop ();
502 			  value *lhs_val
503 			    = lhs->evaluate (nullptr, pstate->expout.get (),
504 					     EVAL_AVOID_SIDE_EFFECTS);
505 			  rhs = resolve (std::move (rhs), true,
506 					 value_type (lhs_val));
507 			  pstate->push_new<ada_assign_operation>
508 			    (std::move (lhs), std::move (rhs));
509 			}
510 	;
511 
512 /* Expressions, not including the sequencing operator.  */
513 
514 primary :	primary DOT_ID
515 			{
516 			  if (strcmp ($2.ptr, "all") == 0)
517 			    ada_wrap<ada_unop_ind_operation> ();
518 			  else
519 			    {
520 			      operation_up arg = ada_pop ();
521 			      pstate->push_new<ada_structop_operation>
522 				(std::move (arg), copy_name ($2));
523 			    }
524 			}
525 	;
526 
527 primary :	primary DOT_COMPLETE
528 			{
529 			  /* This is done even for ".all", because
530 			     that might be a prefix.  */
531 			  operation_up arg = ada_pop ();
532 			  ada_structop_operation *str_op
533 			    = (new ada_structop_operation
534 			       (std::move (arg), copy_name ($2)));
535 			  str_op->set_prefix (find_completion_bounds (pstate));
536 			  pstate->push (operation_up (str_op));
537 			  pstate->mark_struct_expression (str_op);
538 			}
539 	;
540 
541 primary :	primary '(' arglist ')'
542 			{ ada_funcall ($3); }
543 	|	var_or_type '(' arglist ')'
544 			{
545 			  if ($1 != NULL)
546 			    {
547 			      if ($3 != 1)
548 				error (_("Invalid conversion"));
549 			      operation_up arg = ada_pop ();
550 			      pstate->push_new<unop_cast_operation>
551 				(std::move (arg), $1);
552 			    }
553 			  else
554 			    ada_funcall ($3);
555 			}
556 	;
557 
558 primary :	var_or_type '\'' '(' exp ')'
559 			{
560 			  if ($1 == NULL)
561 			    error (_("Type required for qualification"));
562 			  operation_up arg = ada_pop (true,
563 						      check_typedef ($1));
564 			  pstate->push_new<ada_qual_operation>
565 			    (std::move (arg), $1);
566 			}
567 	;
568 
569 primary :
570 		primary '(' simple_exp DOTDOT simple_exp ')'
571 			{ ada_wrap3<ada_ternop_slice_operation> (); }
572 	|	var_or_type '(' simple_exp DOTDOT simple_exp ')'
573 			{ if ($1 == NULL)
574 			    ada_wrap3<ada_ternop_slice_operation> ();
575 			  else
576 			    error (_("Cannot slice a type"));
577 			}
578 	;
579 
580 primary :	'(' exp1 ')'	{ }
581 	;
582 
583 /* The following rule causes a conflict with the type conversion
584        var_or_type (exp)
585    To get around it, we give '(' higher priority and add bridge rules for
586        var_or_type (exp, exp, ...)
587        var_or_type (exp .. exp)
588    We also have the action for  var_or_type(exp) generate a function call
589    when the first symbol does not denote a type. */
590 
591 primary :	var_or_type	%prec VAR
592 			{ if ($1 != NULL)
593 			    pstate->push_new<type_operation> ($1);
594 			}
595 	;
596 
597 primary :	DOLLAR_VARIABLE /* Various GDB extensions */
598 			{ pstate->push_dollar ($1); }
599 	;
600 
601 primary :     	aggregate
602 			{
603 			  pstate->push_new<ada_aggregate_operation>
604 			    (pop_component ());
605 			}
606 	;
607 
608 simple_exp : 	primary
609 	;
610 
611 simple_exp :	'-' simple_exp    %prec UNARY
612 			{ ada_wrap_overload<ada_neg_operation> (UNOP_NEG); }
613 	;
614 
615 simple_exp :	'+' simple_exp    %prec UNARY
616 			{
617 			  operation_up arg = ada_pop ();
618 			  operation_up empty;
619 
620 			  /* If an overloaded operator was found, use
621 			     it.  Otherwise, unary + has no effect and
622 			     the argument can be pushed instead.  */
623 			  operation_up call = maybe_overload (UNOP_PLUS, arg,
624 							      empty);
625 			  if (call != nullptr)
626 			    arg = std::move (call);
627 			  pstate->push (std::move (arg));
628 			}
629 	;
630 
631 simple_exp :	NOT simple_exp    %prec UNARY
632 			{
633 			  ada_wrap_overload<unary_logical_not_operation>
634 			    (UNOP_LOGICAL_NOT);
635 			}
636 	;
637 
638 simple_exp :    ABS simple_exp	   %prec UNARY
639 			{ ada_wrap_overload<ada_abs_operation> (UNOP_ABS); }
640 	;
641 
642 arglist	:		{ $$ = 0; }
643 	;
644 
645 arglist	:	exp
646 			{ $$ = 1; }
647 	|	NAME ARROW exp
648 			{ $$ = 1; }
649 	|	arglist ',' exp
650 			{ $$ = $1 + 1; }
651 	|	arglist ',' NAME ARROW exp
652 			{ $$ = $1 + 1; }
653 	;
654 
655 primary :	'{' var_or_type '}' primary  %prec '.'
656 		/* GDB extension */
657 			{
658 			  if ($2 == NULL)
659 			    error (_("Type required within braces in coercion"));
660 			  operation_up arg = ada_pop ();
661 			  pstate->push_new<unop_memval_operation>
662 			    (std::move (arg), $2);
663 			}
664 	;
665 
666 /* Binary operators in order of decreasing precedence.  */
667 
668 simple_exp 	: 	simple_exp STARSTAR simple_exp
669 			{ ada_wrap2<ada_binop_exp_operation> (BINOP_EXP); }
670 	;
671 
672 simple_exp	:	simple_exp '*' simple_exp
673 			{ ada_wrap2<ada_binop_mul_operation> (BINOP_MUL); }
674 	;
675 
676 simple_exp	:	simple_exp '/' simple_exp
677 			{ ada_wrap2<ada_binop_div_operation> (BINOP_DIV); }
678 	;
679 
680 simple_exp	:	simple_exp REM simple_exp /* May need to be fixed to give correct Ada REM */
681 			{ ada_wrap2<ada_binop_rem_operation> (BINOP_REM); }
682 	;
683 
684 simple_exp	:	simple_exp MOD simple_exp
685 			{ ada_wrap2<ada_binop_mod_operation> (BINOP_MOD); }
686 	;
687 
688 simple_exp	:	simple_exp '@' simple_exp	/* GDB extension */
689 			{ ada_wrap2<repeat_operation> (BINOP_REPEAT); }
690 	;
691 
692 simple_exp	:	simple_exp '+' simple_exp
693 			{ ada_wrap_op<ada_binop_addsub_operation> (BINOP_ADD); }
694 	;
695 
696 simple_exp	:	simple_exp '&' simple_exp
697 			{ ada_wrap2<ada_concat_operation> (BINOP_CONCAT); }
698 	;
699 
700 simple_exp	:	simple_exp '-' simple_exp
701 			{ ada_wrap_op<ada_binop_addsub_operation> (BINOP_SUB); }
702 	;
703 
704 relation :	simple_exp
705 	;
706 
707 relation :	simple_exp '=' simple_exp
708 			{ ada_wrap_op<ada_binop_equal_operation> (BINOP_EQUAL); }
709 	;
710 
711 relation :	simple_exp NOTEQUAL simple_exp
712 			{ ada_wrap_op<ada_binop_equal_operation> (BINOP_NOTEQUAL); }
713 	;
714 
715 relation :	simple_exp LEQ simple_exp
716 			{ ada_un_wrap2<leq_operation> (BINOP_LEQ); }
717 	;
718 
719 relation :	simple_exp IN simple_exp DOTDOT simple_exp
720 			{ ada_wrap3<ada_ternop_range_operation> (); }
721 	|       simple_exp IN primary TICK_RANGE tick_arglist
722 			{
723 			  operation_up rhs = ada_pop ();
724 			  operation_up lhs = ada_pop ();
725 			  pstate->push_new<ada_binop_in_bounds_operation>
726 			    (std::move (lhs), std::move (rhs), $5);
727 			}
728  	|	simple_exp IN var_or_type	%prec TICK_ACCESS
729 			{
730 			  if ($3 == NULL)
731 			    error (_("Right operand of 'in' must be type"));
732 			  operation_up arg = ada_pop ();
733 			  pstate->push_new<ada_unop_range_operation>
734 			    (std::move (arg), $3);
735 			}
736 	|	simple_exp NOT IN simple_exp DOTDOT simple_exp
737 			{ ada_wrap3<ada_ternop_range_operation> ();
738 			  ada_wrap<unary_logical_not_operation> (); }
739 	|       simple_exp NOT IN primary TICK_RANGE tick_arglist
740 			{
741 			  operation_up rhs = ada_pop ();
742 			  operation_up lhs = ada_pop ();
743 			  pstate->push_new<ada_binop_in_bounds_operation>
744 			    (std::move (lhs), std::move (rhs), $6);
745 			  ada_wrap<unary_logical_not_operation> ();
746 			}
747  	|	simple_exp NOT IN var_or_type	%prec TICK_ACCESS
748 			{
749 			  if ($4 == NULL)
750 			    error (_("Right operand of 'in' must be type"));
751 			  operation_up arg = ada_pop ();
752 			  pstate->push_new<ada_unop_range_operation>
753 			    (std::move (arg), $4);
754 			  ada_wrap<unary_logical_not_operation> ();
755 			}
756 	;
757 
758 relation :	simple_exp GEQ simple_exp
759 			{ ada_un_wrap2<geq_operation> (BINOP_GEQ); }
760 	;
761 
762 relation :	simple_exp '<' simple_exp
763 			{ ada_un_wrap2<less_operation> (BINOP_LESS); }
764 	;
765 
766 relation :	simple_exp '>' simple_exp
767 			{ ada_un_wrap2<gtr_operation> (BINOP_GTR); }
768 	;
769 
770 exp	:	relation
771 	|	and_exp
772 	|	and_then_exp
773 	|	or_exp
774 	|	or_else_exp
775 	|	xor_exp
776 	;
777 
778 and_exp :
779 		relation _AND_ relation
780 			{ ada_wrap2<ada_bitwise_and_operation>
781 			    (BINOP_BITWISE_AND); }
782 	|	and_exp _AND_ relation
783 			{ ada_wrap2<ada_bitwise_and_operation>
784 			    (BINOP_BITWISE_AND); }
785 	;
786 
787 and_then_exp :
788 	       relation _AND_ THEN relation
789 			{ ada_wrap2<logical_and_operation>
790 			    (BINOP_LOGICAL_AND); }
791 	|	and_then_exp _AND_ THEN relation
792 			{ ada_wrap2<logical_and_operation>
793 			    (BINOP_LOGICAL_AND); }
794 	;
795 
796 or_exp :
797 		relation OR relation
798 			{ ada_wrap2<ada_bitwise_ior_operation>
799 			    (BINOP_BITWISE_IOR); }
800 	|	or_exp OR relation
801 			{ ada_wrap2<ada_bitwise_ior_operation>
802 			    (BINOP_BITWISE_IOR); }
803 	;
804 
805 or_else_exp :
806 	       relation OR ELSE relation
807 			{ ada_wrap2<logical_or_operation> (BINOP_LOGICAL_OR); }
808 	|      or_else_exp OR ELSE relation
809 			{ ada_wrap2<logical_or_operation> (BINOP_LOGICAL_OR); }
810 	;
811 
812 xor_exp :       relation XOR relation
813 			{ ada_wrap2<ada_bitwise_xor_operation>
814 			    (BINOP_BITWISE_XOR); }
815 	|	xor_exp XOR relation
816 			{ ada_wrap2<ada_bitwise_xor_operation>
817 			    (BINOP_BITWISE_XOR); }
818 	;
819 
820 /* Primaries can denote types (OP_TYPE).  In cases such as
821    primary TICK_ADDRESS, where a type would be invalid, it will be
822    caught when evaluate_subexp in ada-lang.c tries to evaluate the
823    primary, expecting a value.  Precedence rules resolve the ambiguity
824    in NAME TICK_ACCESS in favor of shifting to form a var_or_type.  A
825    construct such as aType'access'access will again cause an error when
826    aType'access evaluates to a type that evaluate_subexp attempts to
827    evaluate. */
828 primary :	primary TICK_ACCESS
829 			{ ada_addrof (); }
830 	|	primary TICK_ADDRESS
831 			{ ada_addrof (type_system_address (pstate)); }
832 	|	primary TICK_COMPLETE
833 			{
834 			  pstate->mark_completion (make_tick_completer ($2));
835 			}
836 	|	primary TICK_FIRST tick_arglist
837 			{
838 			  operation_up arg = ada_pop ();
839 			  pstate->push_new<ada_unop_atr_operation>
840 			    (std::move (arg), OP_ATR_FIRST, $3);
841 			}
842 	|	primary TICK_LAST tick_arglist
843 			{
844 			  operation_up arg = ada_pop ();
845 			  pstate->push_new<ada_unop_atr_operation>
846 			    (std::move (arg), OP_ATR_LAST, $3);
847 			}
848 	| 	primary TICK_LENGTH tick_arglist
849 			{
850 			  operation_up arg = ada_pop ();
851 			  pstate->push_new<ada_unop_atr_operation>
852 			    (std::move (arg), OP_ATR_LENGTH, $3);
853 			}
854 	|       primary TICK_SIZE
855 			{ ada_wrap<ada_atr_size_operation> (); }
856 	|	primary TICK_TAG
857 			{ ada_wrap<ada_atr_tag_operation> (); }
858 	|       opt_type_prefix TICK_MIN '(' exp ',' exp ')'
859 			{ ada_wrap2<ada_binop_min_operation> (BINOP_MIN); }
860 	|       opt_type_prefix TICK_MAX '(' exp ',' exp ')'
861 			{ ada_wrap2<ada_binop_max_operation> (BINOP_MAX); }
862 	| 	opt_type_prefix TICK_POS '(' exp ')'
863 			{ ada_wrap<ada_pos_operation> (); }
864 	|	type_prefix TICK_VAL '(' exp ')'
865 			{
866 			  operation_up arg = ada_pop ();
867 			  pstate->push_new<ada_atr_val_operation>
868 			    ($1, std::move (arg));
869 			}
870 	|	type_prefix TICK_MODULUS
871 			{
872 			  struct type *type_arg = check_typedef ($1);
873 			  if (!ada_is_modular_type (type_arg))
874 			    error (_("'modulus must be applied to modular type"));
875 			  write_int (pstate, ada_modulus (type_arg),
876 				     type_arg->target_type ());
877 			}
878 	;
879 
880 tick_arglist :			%prec '('
881 			{ $$ = 1; }
882 	| 	'(' INT ')'
883 			{ $$ = $2.val; }
884 	;
885 
886 type_prefix :
887 		var_or_type
888 			{
889 			  if ($1 == NULL)
890 			    error (_("Prefix must be type"));
891 			  $$ = $1;
892 			}
893 	;
894 
895 opt_type_prefix :
896 		type_prefix
897 			{ $$ = $1; }
898 	| 	/* EMPTY */
899 			{ $$ = parse_type (pstate)->builtin_void; }
900 	;
901 
902 
903 primary	:	INT
904 			{ write_int (pstate, (LONGEST) $1.val, $1.type); }
905 	;
906 
907 primary	:	CHARLIT
908 			{
909 			  pstate->push_new<ada_char_operation> ($1.type, $1.val);
910 			}
911 	;
912 
913 primary	:	FLOAT
914 			{
915 			  float_data data;
916 			  std::copy (std::begin ($1.val), std::end ($1.val),
917 				     std::begin (data));
918 			  pstate->push_new<float_const_operation>
919 			    ($1.type, data);
920 			  ada_wrap<ada_wrapped_operation> ();
921 			}
922 	;
923 
924 primary	:	NULL_PTR
925 			{
926 			  struct type *null_ptr_type
927 			    = lookup_pointer_type (parse_type (pstate)->builtin_int0);
928 			  write_int (pstate, 0, null_ptr_type);
929 			}
930 	;
931 
932 primary	:	STRING
933 			{
934 			  pstate->push_new<ada_string_operation>
935 			    (copy_name ($1));
936 			}
937 	;
938 
939 primary :	TRUEKEYWORD
940 			{ write_int (pstate, 1, type_boolean (pstate)); }
941 	|	FALSEKEYWORD
942 			{ write_int (pstate, 0, type_boolean (pstate)); }
943 	;
944 
945 primary	: 	NEW NAME
946 			{ error (_("NEW not implemented.")); }
947 	;
948 
949 var_or_type:	NAME   	    %prec VAR
950 				{ $$ = write_var_or_type (pstate, NULL, $1); }
951 	|	NAME_COMPLETE %prec VAR
952 				{
953 				  $$ = write_var_or_type_completion (pstate,
954 								     NULL,
955 								     $1);
956 				}
957 	|	block NAME  %prec VAR
958 				{ $$ = write_var_or_type (pstate, $1, $2); }
959 	|	block NAME_COMPLETE  %prec VAR
960 				{
961 				  $$ = write_var_or_type_completion (pstate,
962 								     $1,
963 								     $2);
964 				}
965 	|       NAME TICK_ACCESS
966 			{
967 			  $$ = write_var_or_type (pstate, NULL, $1);
968 			  if ($$ == NULL)
969 			    ada_addrof ();
970 			  else
971 			    $$ = lookup_pointer_type ($$);
972 			}
973 	|	block NAME TICK_ACCESS
974 			{
975 			  $$ = write_var_or_type (pstate, $1, $2);
976 			  if ($$ == NULL)
977 			    ada_addrof ();
978 			  else
979 			    $$ = lookup_pointer_type ($$);
980 			}
981 	;
982 
983 /* GDB extension */
984 block   :       NAME COLONCOLON
985 			{ $$ = block_lookup (NULL, $1.ptr); }
986 	|	block NAME COLONCOLON
987 			{ $$ = block_lookup ($1, $2.ptr); }
988 	;
989 
990 aggregate :
991 		'(' aggregate_component_list ')'
992 			{
993 			  std::vector<ada_component_up> components
994 			    = pop_components ($2);
995 
996 			  push_component<ada_aggregate_component>
997 			    (std::move (components));
998 			}
999 	;
1000 
1001 aggregate_component_list :
1002 		component_groups	 { $$ = $1; }
1003 	|	positional_list exp
1004 			{
1005 			  push_component<ada_positional_component>
1006 			    ($1, ada_pop ());
1007 			  $$ = $1 + 1;
1008 			}
1009 	|	positional_list component_groups
1010 					 { $$ = $1 + $2; }
1011 	;
1012 
1013 positional_list :
1014 		exp ','
1015 			{
1016 			  push_component<ada_positional_component>
1017 			    (0, ada_pop ());
1018 			  $$ = 1;
1019 			}
1020 	|	positional_list exp ','
1021 			{
1022 			  push_component<ada_positional_component>
1023 			    ($1, ada_pop ());
1024 			  $$ = $1 + 1;
1025 			}
1026 	;
1027 
1028 component_groups:
1029 		others			 { $$ = 1; }
1030 	|	component_group		 { $$ = 1; }
1031 	|	component_group ',' component_groups
1032 					 { $$ = $3 + 1; }
1033 	;
1034 
1035 others 	:	OTHERS ARROW exp
1036 			{
1037 			  push_component<ada_others_component> (ada_pop ());
1038 			}
1039 	;
1040 
1041 component_group :
1042 		component_associations
1043 			{
1044 			  ada_choices_component *choices = choice_component ();
1045 			  choices->set_associations (pop_associations ($1));
1046 			}
1047 	;
1048 
1049 /* We use this somewhat obscure definition in order to handle NAME => and
1050    NAME | differently from exp => and exp |.  ARROW and '|' have a precedence
1051    above that of the reduction of NAME to var_or_type.  By delaying
1052    decisions until after the => or '|', we convert the ambiguity to a
1053    resolved shift/reduce conflict. */
1054 component_associations :
1055 		NAME ARROW exp
1056 			{
1057 			  push_component<ada_choices_component> (ada_pop ());
1058 			  write_name_assoc (pstate, $1);
1059 			  $$ = 1;
1060 			}
1061 	|	simple_exp ARROW exp
1062 			{
1063 			  push_component<ada_choices_component> (ada_pop ());
1064 			  push_association<ada_name_association> (ada_pop ());
1065 			  $$ = 1;
1066 			}
1067 	|	simple_exp DOTDOT simple_exp ARROW exp
1068 			{
1069 			  push_component<ada_choices_component> (ada_pop ());
1070 			  operation_up rhs = ada_pop ();
1071 			  operation_up lhs = ada_pop ();
1072 			  push_association<ada_discrete_range_association>
1073 			    (std::move (lhs), std::move (rhs));
1074 			  $$ = 1;
1075 			}
1076 	|	NAME '|' component_associations
1077 			{
1078 			  write_name_assoc (pstate, $1);
1079 			  $$ = $3 + 1;
1080 			}
1081 	|	simple_exp '|' component_associations
1082 			{
1083 			  push_association<ada_name_association> (ada_pop ());
1084 			  $$ = $3 + 1;
1085 			}
1086 	|	simple_exp DOTDOT simple_exp '|' component_associations
1087 
1088 			{
1089 			  operation_up rhs = ada_pop ();
1090 			  operation_up lhs = ada_pop ();
1091 			  push_association<ada_discrete_range_association>
1092 			    (std::move (lhs), std::move (rhs));
1093 			  $$ = $5 + 1;
1094 			}
1095 	;
1096 
1097 /* Some extensions borrowed from C, for the benefit of those who find they
1098    can't get used to Ada notation in GDB.  */
1099 
1100 primary	:	'*' primary		%prec '.'
1101 			{ ada_wrap<ada_unop_ind_operation> (); }
1102 	|	'&' primary		%prec '.'
1103 			{ ada_addrof (); }
1104 	|	primary '[' exp ']'
1105 			{
1106 			  ada_wrap2<subscript_operation> (BINOP_SUBSCRIPT);
1107 			  ada_wrap<ada_wrapped_operation> ();
1108 			}
1109 	;
1110 
1111 %%
1112 
1113 /* yylex defined in ada-lex.c: Reads one token, getting characters */
1114 /* through lexptr.  */
1115 
1116 /* Remap normal flex interface names (yylex) as well as gratuitiously */
1117 /* global symbol names, so we can have multiple flex-generated parsers */
1118 /* in gdb.  */
1119 
1120 /* (See note above on previous definitions for YACC.) */
1121 
1122 #define yy_create_buffer ada_yy_create_buffer
1123 #define yy_delete_buffer ada_yy_delete_buffer
1124 #define yy_init_buffer ada_yy_init_buffer
1125 #define yy_load_buffer_state ada_yy_load_buffer_state
1126 #define yy_switch_to_buffer ada_yy_switch_to_buffer
1127 #define yyrestart ada_yyrestart
1128 #define yytext ada_yytext
1129 
1130 static struct obstack temp_parse_space;
1131 
1132 /* The following kludge was found necessary to prevent conflicts between */
1133 /* defs.h and non-standard stdlib.h files.  */
1134 #define qsort __qsort__dummy
1135 #include "ada-lex.c"
1136 
1137 int
1138 ada_parse (struct parser_state *par_state)
1139 {
1140   /* Setting up the parser state.  */
1141   scoped_restore pstate_restore = make_scoped_restore (&pstate);
1142   gdb_assert (par_state != NULL);
1143   pstate = par_state;
1144   original_expr = par_state->lexptr;
1145 
1146   scoped_restore restore_yydebug = make_scoped_restore (&yydebug,
1147 							parser_debug);
1148 
1149   lexer_init (yyin);		/* (Re-)initialize lexer.  */
1150   obstack_free (&temp_parse_space, NULL);
1151   obstack_init (&temp_parse_space);
1152   components.clear ();
1153   associations.clear ();
1154 
1155   int result = yyparse ();
1156   if (!result)
1157     {
1158       struct type *context_type = nullptr;
1159       if (par_state->void_context_p)
1160 	context_type = parse_type (par_state)->builtin_void;
1161       pstate->set_operation (ada_pop (true, context_type));
1162     }
1163   return result;
1164 }
1165 
1166 static void
1167 yyerror (const char *msg)
1168 {
1169   error (_("Error in expression, near `%s'."), pstate->lexptr);
1170 }
1171 
1172 /* Emit expression to access an instance of SYM, in block BLOCK (if
1173    non-NULL).  */
1174 
1175 static void
1176 write_var_from_sym (struct parser_state *par_state, block_symbol sym)
1177 {
1178   if (symbol_read_needs_frame (sym.symbol))
1179     par_state->block_tracker->update (sym.block, INNERMOST_BLOCK_FOR_SYMBOLS);
1180 
1181   par_state->push_new<ada_var_value_operation> (sym);
1182 }
1183 
1184 /* Write integer or boolean constant ARG of type TYPE.  */
1185 
1186 static void
1187 write_int (struct parser_state *par_state, LONGEST arg, struct type *type)
1188 {
1189   pstate->push_new<long_const_operation> (type, arg);
1190   ada_wrap<ada_wrapped_operation> ();
1191 }
1192 
1193 /* Emit expression corresponding to the renamed object named
1194    designated by RENAMED_ENTITY[0 .. RENAMED_ENTITY_LEN-1] in the
1195    context of ORIG_LEFT_CONTEXT, to which is applied the operations
1196    encoded by RENAMING_EXPR.  MAX_DEPTH is the maximum number of
1197    cascaded renamings to allow.  If ORIG_LEFT_CONTEXT is null, it
1198    defaults to the currently selected block. ORIG_SYMBOL is the
1199    symbol that originally encoded the renaming.  It is needed only
1200    because its prefix also qualifies any index variables used to index
1201    or slice an array.  It should not be necessary once we go to the
1202    new encoding entirely (FIXME pnh 7/20/2007).  */
1203 
1204 static void
1205 write_object_renaming (struct parser_state *par_state,
1206 		       const struct block *orig_left_context,
1207 		       const char *renamed_entity, int renamed_entity_len,
1208 		       const char *renaming_expr, int max_depth)
1209 {
1210   char *name;
1211   enum { SIMPLE_INDEX, LOWER_BOUND, UPPER_BOUND } slice_state;
1212   struct block_symbol sym_info;
1213 
1214   if (max_depth <= 0)
1215     error (_("Could not find renamed symbol"));
1216 
1217   if (orig_left_context == NULL)
1218     orig_left_context = get_selected_block (NULL);
1219 
1220   name = obstack_strndup (&temp_parse_space, renamed_entity,
1221 			  renamed_entity_len);
1222   ada_lookup_encoded_symbol (name, orig_left_context, VAR_DOMAIN, &sym_info);
1223   if (sym_info.symbol == NULL)
1224     error (_("Could not find renamed variable: %s"), ada_decode (name).c_str ());
1225   else if (sym_info.symbol->aclass () == LOC_TYPEDEF)
1226     /* We have a renaming of an old-style renaming symbol.  Don't
1227        trust the block information.  */
1228     sym_info.block = orig_left_context;
1229 
1230   {
1231     const char *inner_renamed_entity;
1232     int inner_renamed_entity_len;
1233     const char *inner_renaming_expr;
1234 
1235     switch (ada_parse_renaming (sym_info.symbol, &inner_renamed_entity,
1236 				&inner_renamed_entity_len,
1237 				&inner_renaming_expr))
1238       {
1239       case ADA_NOT_RENAMING:
1240 	write_var_from_sym (par_state, sym_info);
1241 	break;
1242       case ADA_OBJECT_RENAMING:
1243 	write_object_renaming (par_state, sym_info.block,
1244 			       inner_renamed_entity, inner_renamed_entity_len,
1245 			       inner_renaming_expr, max_depth - 1);
1246 	break;
1247       default:
1248 	goto BadEncoding;
1249       }
1250   }
1251 
1252   slice_state = SIMPLE_INDEX;
1253   while (*renaming_expr == 'X')
1254     {
1255       renaming_expr += 1;
1256 
1257       switch (*renaming_expr) {
1258       case 'A':
1259 	renaming_expr += 1;
1260 	ada_wrap<ada_unop_ind_operation> ();
1261 	break;
1262       case 'L':
1263 	slice_state = LOWER_BOUND;
1264 	/* FALLTHROUGH */
1265       case 'S':
1266 	renaming_expr += 1;
1267 	if (isdigit (*renaming_expr))
1268 	  {
1269 	    char *next;
1270 	    long val = strtol (renaming_expr, &next, 10);
1271 	    if (next == renaming_expr)
1272 	      goto BadEncoding;
1273 	    renaming_expr = next;
1274 	    write_int (par_state, val, type_int (par_state));
1275 	  }
1276 	else
1277 	  {
1278 	    const char *end;
1279 	    char *index_name;
1280 	    struct block_symbol index_sym_info;
1281 
1282 	    end = strchr (renaming_expr, 'X');
1283 	    if (end == NULL)
1284 	      end = renaming_expr + strlen (renaming_expr);
1285 
1286 	    index_name = obstack_strndup (&temp_parse_space, renaming_expr,
1287 					  end - renaming_expr);
1288 	    renaming_expr = end;
1289 
1290 	    ada_lookup_encoded_symbol (index_name, orig_left_context,
1291 				       VAR_DOMAIN, &index_sym_info);
1292 	    if (index_sym_info.symbol == NULL)
1293 	      error (_("Could not find %s"), index_name);
1294 	    else if (index_sym_info.symbol->aclass () == LOC_TYPEDEF)
1295 	      /* Index is an old-style renaming symbol.  */
1296 	      index_sym_info.block = orig_left_context;
1297 	    write_var_from_sym (par_state, index_sym_info);
1298 	  }
1299 	if (slice_state == SIMPLE_INDEX)
1300 	  ada_funcall (1);
1301 	else if (slice_state == LOWER_BOUND)
1302 	  slice_state = UPPER_BOUND;
1303 	else if (slice_state == UPPER_BOUND)
1304 	  {
1305 	    ada_wrap3<ada_ternop_slice_operation> ();
1306 	    slice_state = SIMPLE_INDEX;
1307 	  }
1308 	break;
1309 
1310       case 'R':
1311 	{
1312 	  const char *end;
1313 
1314 	  renaming_expr += 1;
1315 
1316 	  if (slice_state != SIMPLE_INDEX)
1317 	    goto BadEncoding;
1318 	  end = strchr (renaming_expr, 'X');
1319 	  if (end == NULL)
1320 	    end = renaming_expr + strlen (renaming_expr);
1321 
1322 	  operation_up arg = ada_pop ();
1323 	  pstate->push_new<ada_structop_operation>
1324 	    (std::move (arg), std::string (renaming_expr,
1325 					   end - renaming_expr));
1326 	  renaming_expr = end;
1327 	  break;
1328 	}
1329 
1330       default:
1331 	goto BadEncoding;
1332       }
1333     }
1334   if (slice_state == SIMPLE_INDEX)
1335     return;
1336 
1337  BadEncoding:
1338   error (_("Internal error in encoding of renaming declaration"));
1339 }
1340 
1341 static const struct block*
1342 block_lookup (const struct block *context, const char *raw_name)
1343 {
1344   const char *name;
1345   struct symtab *symtab;
1346   const struct block *result = NULL;
1347 
1348   std::string name_storage;
1349   if (raw_name[0] == '\'')
1350     {
1351       raw_name += 1;
1352       name = raw_name;
1353     }
1354   else
1355     {
1356       name_storage = ada_encode (raw_name);
1357       name = name_storage.c_str ();
1358     }
1359 
1360   std::vector<struct block_symbol> syms
1361     = ada_lookup_symbol_list (name, context, VAR_DOMAIN);
1362 
1363   if (context == NULL
1364       && (syms.empty () || syms[0].symbol->aclass () != LOC_BLOCK))
1365     symtab = lookup_symtab (name);
1366   else
1367     symtab = NULL;
1368 
1369   if (symtab != NULL)
1370     result = symtab->compunit ()->blockvector ()->static_block ();
1371   else if (syms.empty () || syms[0].symbol->aclass () != LOC_BLOCK)
1372     {
1373       if (context == NULL)
1374 	error (_("No file or function \"%s\"."), raw_name);
1375       else
1376 	error (_("No function \"%s\" in specified context."), raw_name);
1377     }
1378   else
1379     {
1380       if (syms.size () > 1)
1381 	warning (_("Function name \"%s\" ambiguous here"), raw_name);
1382       result = syms[0].symbol->value_block ();
1383     }
1384 
1385   return result;
1386 }
1387 
1388 static struct symbol*
1389 select_possible_type_sym (const std::vector<struct block_symbol> &syms)
1390 {
1391   int i;
1392   int preferred_index;
1393   struct type *preferred_type;
1394 
1395   preferred_index = -1; preferred_type = NULL;
1396   for (i = 0; i < syms.size (); i += 1)
1397     switch (syms[i].symbol->aclass ())
1398       {
1399       case LOC_TYPEDEF:
1400 	if (ada_prefer_type (syms[i].symbol->type (), preferred_type))
1401 	  {
1402 	    preferred_index = i;
1403 	    preferred_type = syms[i].symbol->type ();
1404 	  }
1405 	break;
1406       case LOC_REGISTER:
1407       case LOC_ARG:
1408       case LOC_REF_ARG:
1409       case LOC_REGPARM_ADDR:
1410       case LOC_LOCAL:
1411       case LOC_COMPUTED:
1412 	return NULL;
1413       default:
1414 	break;
1415       }
1416   if (preferred_type == NULL)
1417     return NULL;
1418   return syms[preferred_index].symbol;
1419 }
1420 
1421 static struct type*
1422 find_primitive_type (struct parser_state *par_state, const char *name)
1423 {
1424   struct type *type;
1425   type = language_lookup_primitive_type (par_state->language (),
1426 					 par_state->gdbarch (),
1427 					 name);
1428   if (type == NULL && strcmp ("system__address", name) == 0)
1429     type = type_system_address (par_state);
1430 
1431   if (type != NULL)
1432     {
1433       /* Check to see if we have a regular definition of this
1434 	 type that just didn't happen to have been read yet.  */
1435       struct symbol *sym;
1436       char *expanded_name =
1437 	(char *) alloca (strlen (name) + sizeof ("standard__"));
1438       strcpy (expanded_name, "standard__");
1439       strcat (expanded_name, name);
1440       sym = ada_lookup_symbol (expanded_name, NULL, VAR_DOMAIN).symbol;
1441       if (sym != NULL && sym->aclass () == LOC_TYPEDEF)
1442 	type = sym->type ();
1443     }
1444 
1445   return type;
1446 }
1447 
1448 static int
1449 chop_selector (const char *name, int end)
1450 {
1451   int i;
1452   for (i = end - 1; i > 0; i -= 1)
1453     if (name[i] == '.' || (name[i] == '_' && name[i+1] == '_'))
1454       return i;
1455   return -1;
1456 }
1457 
1458 /* If NAME is a string beginning with a separator (either '__', or
1459    '.'), chop this separator and return the result; else, return
1460    NAME.  */
1461 
1462 static const char *
1463 chop_separator (const char *name)
1464 {
1465   if (*name == '.')
1466    return name + 1;
1467 
1468   if (name[0] == '_' && name[1] == '_')
1469     return name + 2;
1470 
1471   return name;
1472 }
1473 
1474 /* Given that SELS is a string of the form (<sep><identifier>)*, where
1475    <sep> is '__' or '.', write the indicated sequence of
1476    STRUCTOP_STRUCT expression operators.  Returns a pointer to the
1477    last operation that was pushed.  */
1478 static ada_structop_operation *
1479 write_selectors (struct parser_state *par_state, const char *sels)
1480 {
1481   ada_structop_operation *result = nullptr;
1482   while (*sels != '\0')
1483     {
1484       const char *p = chop_separator (sels);
1485       sels = p;
1486       while (*sels != '\0' && *sels != '.'
1487 	     && (sels[0] != '_' || sels[1] != '_'))
1488 	sels += 1;
1489       operation_up arg = ada_pop ();
1490       result = new ada_structop_operation (std::move (arg),
1491 					   std::string (p, sels - p));
1492       pstate->push (operation_up (result));
1493     }
1494   return result;
1495 }
1496 
1497 /* Write a variable access (OP_VAR_VALUE) to ambiguous encoded name
1498    NAME[0..LEN-1], in block context BLOCK, to be resolved later.  Writes
1499    a temporary symbol that is valid until the next call to ada_parse.
1500    */
1501 static void
1502 write_ambiguous_var (struct parser_state *par_state,
1503 		     const struct block *block, const char *name, int len)
1504 {
1505   struct symbol *sym = new (&temp_parse_space) symbol ();
1506 
1507   sym->set_domain (UNDEF_DOMAIN);
1508   sym->set_linkage_name (obstack_strndup (&temp_parse_space, name, len));
1509   sym->set_language (language_ada, nullptr);
1510 
1511   block_symbol bsym { sym, block };
1512   par_state->push_new<ada_var_value_operation> (bsym);
1513 }
1514 
1515 /* A convenient wrapper around ada_get_field_index that takes
1516    a non NUL-terminated FIELD_NAME0 and a FIELD_NAME_LEN instead
1517    of a NUL-terminated field name.  */
1518 
1519 static int
1520 ada_nget_field_index (const struct type *type, const char *field_name0,
1521 		      int field_name_len, int maybe_missing)
1522 {
1523   char *field_name = (char *) alloca ((field_name_len + 1) * sizeof (char));
1524 
1525   strncpy (field_name, field_name0, field_name_len);
1526   field_name[field_name_len] = '\0';
1527   return ada_get_field_index (type, field_name, maybe_missing);
1528 }
1529 
1530 /* If encoded_field_name is the name of a field inside symbol SYM,
1531    then return the type of that field.  Otherwise, return NULL.
1532 
1533    This function is actually recursive, so if ENCODED_FIELD_NAME
1534    doesn't match one of the fields of our symbol, then try to see
1535    if ENCODED_FIELD_NAME could not be a succession of field names
1536    (in other words, the user entered an expression of the form
1537    TYPE_NAME.FIELD1.FIELD2.FIELD3), in which case we evaluate
1538    each field name sequentially to obtain the desired field type.
1539    In case of failure, we return NULL.  */
1540 
1541 static struct type *
1542 get_symbol_field_type (struct symbol *sym, const char *encoded_field_name)
1543 {
1544   const char *field_name = encoded_field_name;
1545   const char *subfield_name;
1546   struct type *type = sym->type ();
1547   int fieldno;
1548 
1549   if (type == NULL || field_name == NULL)
1550     return NULL;
1551   type = check_typedef (type);
1552 
1553   while (field_name[0] != '\0')
1554     {
1555       field_name = chop_separator (field_name);
1556 
1557       fieldno = ada_get_field_index (type, field_name, 1);
1558       if (fieldno >= 0)
1559 	return type->field (fieldno).type ();
1560 
1561       subfield_name = field_name;
1562       while (*subfield_name != '\0' && *subfield_name != '.'
1563 	     && (subfield_name[0] != '_' || subfield_name[1] != '_'))
1564 	subfield_name += 1;
1565 
1566       if (subfield_name[0] == '\0')
1567 	return NULL;
1568 
1569       fieldno = ada_nget_field_index (type, field_name,
1570 				      subfield_name - field_name, 1);
1571       if (fieldno < 0)
1572 	return NULL;
1573 
1574       type = type->field (fieldno).type ();
1575       field_name = subfield_name;
1576     }
1577 
1578   return NULL;
1579 }
1580 
1581 /* Look up NAME0 (an unencoded identifier or dotted name) in BLOCK (or
1582    expression_block_context if NULL).  If it denotes a type, return
1583    that type.  Otherwise, write expression code to evaluate it as an
1584    object and return NULL. In this second case, NAME0 will, in general,
1585    have the form <name>(.<selector_name>)*, where <name> is an object
1586    or renaming encoded in the debugging data.  Calls error if no
1587    prefix <name> matches a name in the debugging data (i.e., matches
1588    either a complete name or, as a wild-card match, the final
1589    identifier).  */
1590 
1591 static struct type*
1592 write_var_or_type (struct parser_state *par_state,
1593 		   const struct block *block, struct stoken name0)
1594 {
1595   int depth;
1596   char *encoded_name;
1597   int name_len;
1598 
1599   if (block == NULL)
1600     block = par_state->expression_context_block;
1601 
1602   std::string name_storage = ada_encode (name0.ptr);
1603   name_len = name_storage.size ();
1604   encoded_name = obstack_strndup (&temp_parse_space, name_storage.c_str (),
1605 				  name_len);
1606   for (depth = 0; depth < MAX_RENAMING_CHAIN_LENGTH; depth += 1)
1607     {
1608       int tail_index;
1609 
1610       tail_index = name_len;
1611       while (tail_index > 0)
1612 	{
1613 	  struct symbol *type_sym;
1614 	  struct symbol *renaming_sym;
1615 	  const char* renaming;
1616 	  int renaming_len;
1617 	  const char* renaming_expr;
1618 	  int terminator = encoded_name[tail_index];
1619 
1620 	  encoded_name[tail_index] = '\0';
1621 	  /* In order to avoid double-encoding, we want to only pass
1622 	     the decoded form to lookup functions.  */
1623 	  std::string decoded_name = ada_decode (encoded_name);
1624 	  encoded_name[tail_index] = terminator;
1625 
1626 	  std::vector<struct block_symbol> syms
1627 	    = ada_lookup_symbol_list (decoded_name.c_str (), block, VAR_DOMAIN);
1628 
1629 	  type_sym = select_possible_type_sym (syms);
1630 
1631 	  if (type_sym != NULL)
1632 	    renaming_sym = type_sym;
1633 	  else if (syms.size () == 1)
1634 	    renaming_sym = syms[0].symbol;
1635 	  else
1636 	    renaming_sym = NULL;
1637 
1638 	  switch (ada_parse_renaming (renaming_sym, &renaming,
1639 				      &renaming_len, &renaming_expr))
1640 	    {
1641 	    case ADA_NOT_RENAMING:
1642 	      break;
1643 	    case ADA_PACKAGE_RENAMING:
1644 	    case ADA_EXCEPTION_RENAMING:
1645 	    case ADA_SUBPROGRAM_RENAMING:
1646 	      {
1647 		int alloc_len = renaming_len + name_len - tail_index + 1;
1648 		char *new_name
1649 		  = (char *) obstack_alloc (&temp_parse_space, alloc_len);
1650 		strncpy (new_name, renaming, renaming_len);
1651 		strcpy (new_name + renaming_len, encoded_name + tail_index);
1652 		encoded_name = new_name;
1653 		name_len = renaming_len + name_len - tail_index;
1654 		goto TryAfterRenaming;
1655 	      }
1656 	    case ADA_OBJECT_RENAMING:
1657 	      write_object_renaming (par_state, block, renaming, renaming_len,
1658 				     renaming_expr, MAX_RENAMING_CHAIN_LENGTH);
1659 	      write_selectors (par_state, encoded_name + tail_index);
1660 	      return NULL;
1661 	    default:
1662 	      internal_error (_("impossible value from ada_parse_renaming"));
1663 	    }
1664 
1665 	  if (type_sym != NULL)
1666 	    {
1667 	      struct type *field_type;
1668 
1669 	      if (tail_index == name_len)
1670 		return type_sym->type ();
1671 
1672 	      /* We have some extraneous characters after the type name.
1673 		 If this is an expression "TYPE_NAME.FIELD0.[...].FIELDN",
1674 		 then try to get the type of FIELDN.  */
1675 	      field_type
1676 		= get_symbol_field_type (type_sym, encoded_name + tail_index);
1677 	      if (field_type != NULL)
1678 		return field_type;
1679 	      else
1680 		error (_("Invalid attempt to select from type: \"%s\"."),
1681 		       name0.ptr);
1682 	    }
1683 	  else if (tail_index == name_len && syms.empty ())
1684 	    {
1685 	      struct type *type = find_primitive_type (par_state,
1686 						       encoded_name);
1687 
1688 	      if (type != NULL)
1689 		return type;
1690 	    }
1691 
1692 	  if (syms.size () == 1)
1693 	    {
1694 	      write_var_from_sym (par_state, syms[0]);
1695 	      write_selectors (par_state, encoded_name + tail_index);
1696 	      return NULL;
1697 	    }
1698 	  else if (syms.empty ())
1699 	    {
1700 	      struct objfile *objfile = nullptr;
1701 	      if (block != nullptr)
1702 		objfile = block_objfile (block);
1703 
1704 	      struct bound_minimal_symbol msym
1705 		= ada_lookup_simple_minsym (decoded_name.c_str (), objfile);
1706 	      if (msym.minsym != NULL)
1707 		{
1708 		  par_state->push_new<ada_var_msym_value_operation> (msym);
1709 		  /* Maybe cause error here rather than later? FIXME? */
1710 		  write_selectors (par_state, encoded_name + tail_index);
1711 		  return NULL;
1712 		}
1713 
1714 	      if (tail_index == name_len
1715 		  && strncmp (encoded_name, "standard__",
1716 			      sizeof ("standard__") - 1) == 0)
1717 		error (_("No definition of \"%s\" found."), name0.ptr);
1718 
1719 	      tail_index = chop_selector (encoded_name, tail_index);
1720 	    }
1721 	  else
1722 	    {
1723 	      write_ambiguous_var (par_state, block, encoded_name,
1724 				   tail_index);
1725 	      write_selectors (par_state, encoded_name + tail_index);
1726 	      return NULL;
1727 	    }
1728 	}
1729 
1730       if (!have_full_symbols () && !have_partial_symbols () && block == NULL)
1731 	error (_("No symbol table is loaded.  Use the \"file\" command."));
1732       if (block == par_state->expression_context_block)
1733 	error (_("No definition of \"%s\" in current context."), name0.ptr);
1734       else
1735 	error (_("No definition of \"%s\" in specified context."), name0.ptr);
1736 
1737     TryAfterRenaming: ;
1738     }
1739 
1740   error (_("Could not find renamed symbol \"%s\""), name0.ptr);
1741 
1742 }
1743 
1744 /* Because ada_completer_word_break_characters does not contain '.' --
1745    and it cannot easily be added, this breaks other completions -- we
1746    have to recreate the completion word-splitting here, so that we can
1747    provide a prefix that is then used when completing field names.
1748    Without this, an attempt like "complete print abc.d" will give a
1749    result like "print def" rather than "print abc.def".  */
1750 
1751 static std::string
1752 find_completion_bounds (struct parser_state *par_state)
1753 {
1754   const char *end = pstate->lexptr;
1755   /* First the end of the prefix.  Here we stop at the token start or
1756      at '.' or space.  */
1757   for (; end > original_expr && end[-1] != '.' && !isspace (end[-1]); --end)
1758     {
1759       /* Nothing.  */
1760     }
1761   /* Now find the start of the prefix.  */
1762   const char *ptr = end;
1763   /* Here we allow '.'.  */
1764   for (;
1765        ptr > original_expr && (ptr[-1] == '.'
1766 			       || ptr[-1] == '_'
1767 			       || (ptr[-1] >= 'a' && ptr[-1] <= 'z')
1768 			       || (ptr[-1] >= 'A' && ptr[-1] <= 'Z')
1769 			       || (ptr[-1] & 0xff) >= 0x80);
1770        --ptr)
1771     {
1772       /* Nothing.  */
1773     }
1774   /* ... except, skip leading spaces.  */
1775   ptr = skip_spaces (ptr);
1776 
1777   return std::string (ptr, end);
1778 }
1779 
1780 /* A wrapper for write_var_or_type that is used specifically when
1781    completion is requested for the last of a sequence of
1782    identifiers.  */
1783 
1784 static struct type *
1785 write_var_or_type_completion (struct parser_state *par_state,
1786 			      const struct block *block, struct stoken name0)
1787 {
1788   int tail_index = chop_selector (name0.ptr, name0.length);
1789   /* If there's no separator, just defer to ordinary symbol
1790      completion.  */
1791   if (tail_index == -1)
1792     return write_var_or_type (par_state, block, name0);
1793 
1794   std::string copy (name0.ptr, tail_index);
1795   struct type *type = write_var_or_type (par_state, block,
1796 					 { copy.c_str (),
1797 					   (int) copy.length () });
1798   /* For completion purposes, it's enough that we return a type
1799      here.  */
1800   if (type != nullptr)
1801     return type;
1802 
1803   ada_structop_operation *op = write_selectors (par_state,
1804 						name0.ptr + tail_index);
1805   op->set_prefix (find_completion_bounds (par_state));
1806   par_state->mark_struct_expression (op);
1807   return nullptr;
1808 }
1809 
1810 /* Write a left side of a component association (e.g., NAME in NAME =>
1811    exp).  If NAME has the form of a selected component, write it as an
1812    ordinary expression.  If it is a simple variable that unambiguously
1813    corresponds to exactly one symbol that does not denote a type or an
1814    object renaming, also write it normally as an OP_VAR_VALUE.
1815    Otherwise, write it as an OP_NAME.
1816 
1817    Unfortunately, we don't know at this point whether NAME is supposed
1818    to denote a record component name or the value of an array index.
1819    Therefore, it is not appropriate to disambiguate an ambiguous name
1820    as we normally would, nor to replace a renaming with its referent.
1821    As a result, in the (one hopes) rare case that one writes an
1822    aggregate such as (R => 42) where R renames an object or is an
1823    ambiguous name, one must write instead ((R) => 42). */
1824 
1825 static void
1826 write_name_assoc (struct parser_state *par_state, struct stoken name)
1827 {
1828   if (strchr (name.ptr, '.') == NULL)
1829     {
1830       std::vector<struct block_symbol> syms
1831 	= ada_lookup_symbol_list (name.ptr,
1832 				  par_state->expression_context_block,
1833 				  VAR_DOMAIN);
1834 
1835       if (syms.size () != 1 || syms[0].symbol->aclass () == LOC_TYPEDEF)
1836 	pstate->push_new<ada_string_operation> (copy_name (name));
1837       else
1838 	write_var_from_sym (par_state, syms[0]);
1839     }
1840   else
1841     if (write_var_or_type (par_state, NULL, name) != NULL)
1842       error (_("Invalid use of type."));
1843 
1844   push_association<ada_name_association> (ada_pop ());
1845 }
1846 
1847 static struct type *
1848 type_int (struct parser_state *par_state)
1849 {
1850   return parse_type (par_state)->builtin_int;
1851 }
1852 
1853 static struct type *
1854 type_long (struct parser_state *par_state)
1855 {
1856   return parse_type (par_state)->builtin_long;
1857 }
1858 
1859 static struct type *
1860 type_long_long (struct parser_state *par_state)
1861 {
1862   return parse_type (par_state)->builtin_long_long;
1863 }
1864 
1865 static struct type *
1866 type_long_double (struct parser_state *par_state)
1867 {
1868   return parse_type (par_state)->builtin_long_double;
1869 }
1870 
1871 static struct type *
1872 type_for_char (struct parser_state *par_state, ULONGEST value)
1873 {
1874   if (value <= 0xff)
1875     return language_string_char_type (par_state->language (),
1876 				      par_state->gdbarch ());
1877   else if (value <= 0xffff)
1878     return language_lookup_primitive_type (par_state->language (),
1879 					   par_state->gdbarch (),
1880 					   "wide_character");
1881   return language_lookup_primitive_type (par_state->language (),
1882 					 par_state->gdbarch (),
1883 					 "wide_wide_character");
1884 }
1885 
1886 static struct type *
1887 type_boolean (struct parser_state *par_state)
1888 {
1889   return parse_type (par_state)->builtin_bool;
1890 }
1891 
1892 static struct type *
1893 type_system_address (struct parser_state *par_state)
1894 {
1895   struct type *type
1896     = language_lookup_primitive_type (par_state->language (),
1897 				      par_state->gdbarch (),
1898 				      "system__address");
1899   return  type != NULL ? type : parse_type (par_state)->builtin_data_ptr;
1900 }
1901 
1902 void _initialize_ada_exp ();
1903 void
1904 _initialize_ada_exp ()
1905 {
1906   obstack_init (&temp_parse_space);
1907 }
1908