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. */
39 #include <unordered_map>
40 #include "expression.h"
42 #include "parser-defs.h"
49 #define parse_type(ps) builtin_type (ps->gdbarch ())
51 /* Remap normal yacc parser interface names (yyparse, yylex, yyerror,
53 #define GDB_YY_REMAP_PREFIX ada_
58 struct minimal_symbol
*msym
;
59 const struct block
*block
;
63 /* The state of the parser, used internally when we are parsing the
66 static struct parser_state
*pstate
= NULL
;
70 /* A convenience typedef. */
71 typedef std
::unique_ptr
<ada_assign_operation
> ada_assign_up
;
73 /* Data that must be held for the duration of a parse. */
75 struct ada_parse_state
77 explicit ada_parse_state
(const char *expr
)
78 : m_original_expr
(expr
)
82 std
::string find_completion_bounds
();
84 const gdb_mpz
*push_integer
(gdb_mpz
&&val
)
86 auto
&result
= m_int_storage.emplace_back
(new gdb_mpz
(std
::move
(val
)));
90 /* The components being constructed during this parse. */
91 std
::vector
<ada_component_up
> components
;
93 /* The associations being constructed during this parse. */
94 std
::vector
<ada_association_up
> associations
;
96 /* The stack of currently active assignment expressions. This is used
97 to implement '@', the target name symbol. */
98 std
::vector
<ada_assign_up
> assignments
;
100 /* Track currently active iterated assignment names. */
101 std
::unordered_map
<std
::string, std
::vector
<ada_index_var_operation
*>>
102 iterated_associations
;
104 auto_obstack temp_space
;
106 /* Depth of parentheses, used by the lexer. */
109 /* When completing, we'll return a special character at the end of the
110 input, to signal the completion position to the lexer. This is
111 done because flex does not have a generally useful way to detect
112 EOF in a pattern. This variable records whether the special
113 character has been emitted. */
114 bool returned_complete
= false
;
118 /* We don't have a good way to manage non-POD data in Yacc, so store
119 values here. The storage here is only valid for the duration of
121 std
::vector
<std
::unique_ptr
<gdb_mpz
>> m_int_storage
;
123 /* The original expression string. */
124 const char *m_original_expr
;
127 /* The current Ada parser object. */
129 static ada_parse_state
*ada_parser
;
133 static int yylex (void);
135 static void yyerror (const char *);
137 static void write_int
(struct parser_state
*, LONGEST
, struct type
*);
139 static void write_object_renaming
(struct parser_state
*,
140 const struct block
*, const char *, int,
143 static struct type
* write_var_or_type
(struct parser_state
*,
144 const struct block
*, struct stoken
);
145 static struct type
*write_var_or_type_completion
(struct parser_state
*,
146 const struct block
*,
149 static void write_name_assoc
(struct parser_state
*, struct stoken
);
151 static const struct block
*block_lookup
(const struct block
*, const char *);
153 static void write_ambiguous_var
(struct parser_state
*,
154 const struct block
*, const char *, int);
156 static struct type
*type_for_char
(struct parser_state
*, ULONGEST
);
158 static struct type
*type_system_address
(struct parser_state
*);
160 /* Handle Ada type resolution for OP. DEPROCEDURE_P and CONTEXT_TYPE
161 are passed to the resolve method, if called. */
163 resolve
(operation_up
&&op
, bool deprocedure_p
, struct type
*context_type
)
165 operation_up result
= std
::move
(op
);
166 ada_resolvable
*res
= dynamic_cast
<ada_resolvable
*> (result.get
());
168 return res
->replace
(std
::move
(result
),
169 pstate
->expout.get
(),
171 pstate
->parse_completion
,
172 pstate
->block_tracker
,
177 /* Like parser_state::pop, but handles Ada type resolution.
178 DEPROCEDURE_P and CONTEXT_TYPE are passed to the resolve method, if
181 ada_pop
(bool deprocedure_p
= true
, struct type
*context_type
= nullptr
)
183 /* Of course it's ok to call parser_state::pop here... */
184 return resolve
(pstate
->pop
(), deprocedure_p
, context_type
);
187 /* Like parser_state::wrap, but use ada_pop to pop the value. */
192 operation_up arg
= ada_pop
();
193 pstate
->push_new
<T
> (std
::move
(arg
));
196 /* Create and push an address-of operation, as appropriate for Ada.
197 If TYPE is not NULL, the resulting operation will be wrapped in a
200 ada_addrof
(struct type
*type
= nullptr
)
202 operation_up arg
= ada_pop
(false
);
203 operation_up addr
= make_operation
<unop_addr_operation
> (std
::move
(arg
));
205 = make_operation
<ada_wrapped_operation
> (std
::move
(addr
));
207 wrapped
= make_operation
<unop_cast_operation
> (std
::move
(wrapped
), type
);
208 pstate
->push
(std
::move
(wrapped
));
211 /* Handle operator overloading. Either returns a function all
212 operation wrapping the arguments, or it returns null, leaving the
213 caller to construct the appropriate operation. If RHS is null, a
214 unary operator is assumed. */
216 maybe_overload
(enum exp_opcode op
, operation_up
&lhs
, operation_up
&rhs
)
218 struct value
*args
[2];
221 args
[0] = lhs
->evaluate
(nullptr
, pstate
->expout.get
(),
222 EVAL_AVOID_SIDE_EFFECTS
);
227 args
[1] = rhs
->evaluate
(nullptr
, pstate
->expout.get
(),
228 EVAL_AVOID_SIDE_EFFECTS
);
232 block_symbol fn
= ada_find_operator_symbol
(op
, pstate
->parse_completion
,
234 if
(fn.symbol
== nullptr
)
237 if
(symbol_read_needs_frame
(fn.symbol
))
238 pstate
->block_tracker
->update
(fn.block
, INNERMOST_BLOCK_FOR_SYMBOLS
);
239 operation_up callee
= make_operation
<ada_var_value_operation
> (fn
);
241 std
::vector
<operation_up
> argvec
;
242 argvec.push_back
(std
::move
(lhs
));
244 argvec.push_back
(std
::move
(rhs
));
245 return make_operation
<ada_funcall_operation
> (std
::move
(callee
),
249 /* Like parser_state::wrap, but use ada_pop to pop the value, and
250 handle unary overloading. */
253 ada_wrap_overload
(enum exp_opcode op
)
255 operation_up arg
= ada_pop
();
258 operation_up call
= maybe_overload
(op
, arg
, empty
);
260 call
= make_operation
<T
> (std
::move
(arg
));
261 pstate
->push
(std
::move
(call
));
264 /* A variant of parser_state::wrap2 that uses ada_pop to pop both
265 operands, and then pushes a new Ada-wrapped operation of the
269 ada_un_wrap2
(enum exp_opcode op
)
271 operation_up rhs
= ada_pop
();
272 operation_up lhs
= ada_pop
();
274 operation_up wrapped
= maybe_overload
(op
, lhs
, rhs
);
275 if
(wrapped
== nullptr
)
277 wrapped
= make_operation
<T
> (std
::move
(lhs
), std
::move
(rhs
));
278 wrapped
= make_operation
<ada_wrapped_operation
> (std
::move
(wrapped
));
280 pstate
->push
(std
::move
(wrapped
));
283 /* A variant of parser_state::wrap2 that uses ada_pop to pop both
284 operands. Unlike ada_un_wrap2, ada_wrapped_operation is not
288 ada_wrap2
(enum exp_opcode op
)
290 operation_up rhs
= ada_pop
();
291 operation_up lhs
= ada_pop
();
292 operation_up call
= maybe_overload
(op
, lhs
, rhs
);
294 call
= make_operation
<T
> (std
::move
(lhs
), std
::move
(rhs
));
295 pstate
->push
(std
::move
(call
));
298 /* A variant of parser_state::wrap2 that uses ada_pop to pop both
299 operands. OP is also passed to the constructor of the new binary
303 ada_wrap_op
(enum exp_opcode op
)
305 operation_up rhs
= ada_pop
();
306 operation_up lhs
= ada_pop
();
307 operation_up call
= maybe_overload
(op
, lhs
, rhs
);
309 call
= make_operation
<T
> (op
, std
::move
(lhs
), std
::move
(rhs
));
310 pstate
->push
(std
::move
(call
));
313 /* Pop three operands using ada_pop, then construct a new ternary
314 operation of type T and push it. */
319 operation_up rhs
= ada_pop
();
320 operation_up mid
= ada_pop
();
321 operation_up lhs
= ada_pop
();
322 pstate
->push_new
<T
> (std
::move
(lhs
), std
::move
(mid
), std
::move
(rhs
));
325 /* Pop NARGS operands, then a callee operand, and use these to
326 construct and push a new Ada function call operation. */
328 ada_funcall
(int nargs
)
330 /* We use the ordinary pop here, because we're going to do
331 resolution in a separate step, in order to handle array
333 std
::vector
<operation_up
> args
= pstate
->pop_vector
(nargs
);
334 /* Call parser_state::pop here, because we don't want to
335 function-convert the callee slot of a call we're already
337 operation_up callee
= pstate
->pop
();
339 ada_var_value_operation
*vvo
340 = dynamic_cast
<ada_var_value_operation
*> (callee.get
());
342 struct type
*callee_t
= nullptr
;
344 || vvo
->get_symbol
()->domain
() != UNDEF_DOMAIN
)
346 struct value
*callee_v
= callee
->evaluate
(nullptr
,
347 pstate
->expout.get
(),
348 EVAL_AVOID_SIDE_EFFECTS
);
349 callee_t
= ada_check_typedef
(callee_v
->type
());
350 array_arity
= ada_array_arity
(callee_t
);
353 for
(int i
= 0; i
< nargs
; ++i
)
355 struct type
*subtype
= nullptr
;
357 subtype
= ada_index_type
(callee_t
, i
+ 1, "array type");
358 args
[i
] = resolve
(std
::move
(args
[i
]), true
, subtype
);
361 std
::unique_ptr
<ada_funcall_operation
> funcall
362 (new ada_funcall_operation
(std
::move
(callee
), std
::move
(args
)));
363 funcall
->resolve
(pstate
->expout.get
(), true
, pstate
->parse_completion
,
364 pstate
->block_tracker
, nullptr
);
365 pstate
->push
(std
::move
(funcall
));
368 /* Create a new ada_component_up of the indicated type and arguments,
369 and push it on the global 'components' vector. */
370 template
<typename T
, typename... Arg
>
372 push_component
(Arg... args
)
374 ada_parser
->components.emplace_back
(new T
(std
::forward
<Arg
> (args
)...
));
377 /* Examine the final element of the 'components' vector, and return it
378 as a pointer to an ada_choices_component. The caller is
379 responsible for ensuring that the final element is in fact an
380 ada_choices_component. */
381 static ada_choices_component
*
384 ada_component
*last
= ada_parser
->components.back
().get
();
385 return gdb
::checked_static_cast
<ada_choices_component
*> (last
);
388 /* Pop the most recent component from the global stack, and return
390 static ada_component_up
393 ada_component_up result
= std
::move
(ada_parser
->components.back
());
394 ada_parser
->components.pop_back
();
398 /* Pop the N most recent components from the global stack, and return
400 static std
::vector
<ada_component_up
>
401 pop_components
(int n
)
403 std
::vector
<ada_component_up
> result
(n
);
404 for
(int i
= 1; i
<= n
; ++i
)
405 result
[n
- i
] = pop_component
();
409 /* Create a new ada_association_up of the indicated type and
410 arguments, and push it on the global 'associations' vector. */
411 template
<typename T
, typename... Arg
>
413 push_association
(Arg... args
)
415 ada_parser
->associations.emplace_back
(new T
(std
::forward
<Arg
> (args
)...
));
418 /* Pop the most recent association from the global stack, and return
420 static ada_association_up
423 ada_association_up result
= std
::move
(ada_parser
->associations.back
());
424 ada_parser
->associations.pop_back
();
428 /* Pop the N most recent associations from the global stack, and
429 return them in a vector. */
430 static std
::vector
<ada_association_up
>
431 pop_associations
(int n
)
433 std
::vector
<ada_association_up
> result
(n
);
434 for
(int i
= 1; i
<= n
; ++i
)
435 result
[n
- i
] = pop_association
();
439 /* Expression completer for attributes. */
440 struct ada_tick_completer
: public expr_completion_base
442 explicit ada_tick_completer
(std
::string &&name
)
443 : m_name
(std
::move
(name
))
447 bool complete
(struct expression
*exp
,
448 completion_tracker
&tracker
) override
;
455 /* Make a new ada_tick_completer and wrap it in a unique pointer. */
456 static std
::unique_ptr
<expr_completion_base
>
457 make_tick_completer
(struct stoken tok
)
459 return
(std
::unique_ptr
<expr_completion_base
>
460 (new ada_tick_completer
(std
::string (tok.ptr
, tok.length
))));
482 const struct block
*bval
;
483 struct internalvar
*ivar
;
486 %type
<lval
> positional_list component_groups component_associations
487 %type
<lval
> aggregate_component_list
488 %type
<tval
> var_or_type type_prefix opt_type_prefix
490 %token
<typed_val
> INT NULL_PTR
491 %token
<typed_char
> CHARLIT
492 %token
<typed_val_float
> FLOAT
493 %token TRUEKEYWORD FALSEKEYWORD
496 %token
<sval
> STRING NAME DOT_ID TICK_COMPLETE DOT_COMPLETE NAME_COMPLETE
498 %type
<lval
> arglist tick_arglist
500 /* Special type cases, put in to allow the parser to distinguish different
502 %token
<sval
> DOLLAR_VARIABLE
505 %left _AND_ OR XOR THEN ELSE
506 %left
'=' NOTEQUAL
'<' '>' LEQ GEQ IN DOTDOT
510 %left
'*' '/' MOD REM
511 %right STARSTAR ABS NOT
513 /* Artificial token to give NAME => ... and NAME | priority over reducing
514 NAME to <primary> and to give <primary>' priority over reducing <primary>
520 %right TICK_ACCESS TICK_ADDRESS TICK_FIRST TICK_LAST TICK_LENGTH
521 %right TICK_MAX TICK_MIN TICK_MODULUS
522 %right TICK_POS TICK_RANGE TICK_SIZE TICK_TAG TICK_VAL
523 %right TICK_COMPLETE TICK_ENUM_REP TICK_ENUM_VAL
524 /* The following are right-associative only so that reductions at this
525 precedence have lower precedence than '.' and '('. The syntax still
526 forces a.b.c, e.g., to be LEFT-associated. */
527 %right
'.' '(' '[' DOT_ID DOT_COMPLETE
529 %token NEW OTHERS FOR
537 /* Expressions, including the sequencing operator. */
540 { ada_wrap2
<comma_operation
> (BINOP_COMMA
); }
543 ada_parser
->assignments.emplace_back
544 (new ada_assign_operation
(ada_pop
(), nullptr
));
546 exp
/* Extension for convenience */
549 = std
::move
(ada_parser
->assignments.back
());
550 ada_parser
->assignments.pop_back
();
551 value
*lhs_val
= (assign
->eval_for_resolution
552 (pstate
->expout.get
()));
554 operation_up rhs
= pstate
->pop
();
555 rhs
= resolve
(std
::move
(rhs
), true
,
558 assign
->set_rhs
(std
::move
(rhs
));
559 pstate
->push
(std
::move
(assign
));
563 /* Expressions, not including the sequencing operator. */
565 primary
: primary DOT_ID
567 if
(strcmp
($2.ptr
, "all") == 0)
568 ada_wrap
<ada_unop_ind_operation
> ();
571 operation_up arg
= ada_pop
();
572 pstate
->push_new
<ada_structop_operation
>
573 (std
::move
(arg
), copy_name
($2));
578 primary
: primary DOT_COMPLETE
580 /* This is done even for ".all", because
581 that might be a prefix. */
582 operation_up arg
= ada_pop
();
583 ada_structop_operation
*str_op
584 = (new ada_structop_operation
585 (std
::move
(arg
), copy_name
($2)));
586 str_op
->set_prefix
(ada_parser
->find_completion_bounds
());
587 pstate
->push
(operation_up
(str_op
));
588 pstate
->mark_struct_expression
(str_op
);
592 primary
: primary
'(' arglist
')'
593 { ada_funcall
($3); }
594 | var_or_type
'(' arglist
')'
599 error (_
("Invalid conversion"));
600 operation_up arg
= ada_pop
();
601 pstate
->push_new
<unop_cast_operation
>
602 (std
::move
(arg
), $1);
609 primary
: var_or_type
'\'' '(' exp
')'
612 error (_
("Type required for qualification"));
613 operation_up arg
= ada_pop
(true
,
615 pstate
->push_new
<ada_qual_operation
>
616 (std
::move
(arg
), $1);
621 primary
'(' simple_exp DOTDOT simple_exp
')'
622 { ada_wrap3
<ada_ternop_slice_operation
> (); }
623 | var_or_type
'(' simple_exp DOTDOT simple_exp
')'
625 ada_wrap3
<ada_ternop_slice_operation
> ();
627 error (_
("Cannot slice a type"));
631 primary
: '(' exp1
')' { }
634 /* The following rule causes a conflict with the type conversion
636 To get around it, we give '(' higher priority and add bridge rules for
637 var_or_type (exp, exp, ...)
638 var_or_type (exp .. exp)
639 We also have the action for var_or_type(exp) generate a function call
640 when the first symbol does not denote a type. */
642 primary
: var_or_type %prec VAR
644 pstate
->push_new
<type_operation
> ($1);
648 primary
: DOLLAR_VARIABLE
/* Various GDB extensions */
649 { pstate
->push_dollar
($1); }
654 pstate
->push_new
<ada_aggregate_operation
>
661 if
(ada_parser
->assignments.empty
())
662 error (_
("the target name symbol ('@') may only "
663 "appear in an assignment context"));
664 ada_assign_operation
*current
665 = ada_parser
->assignments.back
().get
();
666 pstate
->push_new
<ada_target_operation
> (current
);
673 simple_exp
: '-' simple_exp %prec UNARY
674 { ada_wrap_overload
<ada_neg_operation
> (UNOP_NEG
); }
677 simple_exp
: '+' simple_exp %prec UNARY
679 operation_up arg
= ada_pop
();
682 /* If an overloaded operator was found, use
683 it. Otherwise, unary + has no effect and
684 the argument can be pushed instead. */
685 operation_up call
= maybe_overload
(UNOP_PLUS
, arg
,
688 arg
= std
::move
(call
);
689 pstate
->push
(std
::move
(arg
));
693 simple_exp
: NOT simple_exp %prec UNARY
695 ada_wrap_overload
<unary_logical_not_operation
>
700 simple_exp
: ABS simple_exp %prec UNARY
701 { ada_wrap_overload
<ada_abs_operation
> (UNOP_ABS
); }
704 arglist
: { $$
= 0; }
713 | arglist
',' NAME ARROW exp
717 primary
: '{' var_or_type
'}' primary %prec
'.'
721 error (_
("Type required within braces in coercion"));
722 operation_up arg
= ada_pop
();
723 pstate
->push_new
<unop_memval_operation
>
724 (std
::move
(arg
), $2);
728 /* Binary operators in order of decreasing precedence. */
730 simple_exp
: simple_exp STARSTAR simple_exp
731 { ada_wrap2
<ada_binop_exp_operation
> (BINOP_EXP
); }
734 simple_exp
: simple_exp
'*' simple_exp
735 { ada_wrap2
<ada_binop_mul_operation
> (BINOP_MUL
); }
738 simple_exp
: simple_exp
'/' simple_exp
739 { ada_wrap2
<ada_binop_div_operation
> (BINOP_DIV
); }
742 simple_exp
: simple_exp REM simple_exp
/* May need to be fixed to give correct Ada REM */
743 { ada_wrap2
<ada_binop_rem_operation
> (BINOP_REM
); }
746 simple_exp
: simple_exp MOD simple_exp
747 { ada_wrap2
<ada_binop_mod_operation
> (BINOP_MOD
); }
750 simple_exp
: simple_exp
'@' simple_exp
/* GDB extension */
751 { ada_wrap2
<repeat_operation
> (BINOP_REPEAT
); }
754 simple_exp
: simple_exp
'+' simple_exp
755 { ada_wrap_op
<ada_binop_addsub_operation
> (BINOP_ADD
); }
758 simple_exp
: simple_exp
'&' simple_exp
759 { ada_wrap2
<ada_concat_operation
> (BINOP_CONCAT
); }
762 simple_exp
: simple_exp
'-' simple_exp
763 { ada_wrap_op
<ada_binop_addsub_operation
> (BINOP_SUB
); }
766 relation
: simple_exp
769 relation
: simple_exp
'=' simple_exp
770 { ada_wrap_op
<ada_binop_equal_operation
> (BINOP_EQUAL
); }
773 relation
: simple_exp NOTEQUAL simple_exp
774 { ada_wrap_op
<ada_binop_equal_operation
> (BINOP_NOTEQUAL
); }
777 relation
: simple_exp LEQ simple_exp
778 { ada_un_wrap2
<leq_operation
> (BINOP_LEQ
); }
781 relation
: simple_exp IN simple_exp DOTDOT simple_exp
782 { ada_wrap3
<ada_ternop_range_operation
> (); }
783 | simple_exp IN primary TICK_RANGE tick_arglist
785 operation_up rhs
= ada_pop
();
786 operation_up lhs
= ada_pop
();
787 pstate
->push_new
<ada_binop_in_bounds_operation
>
788 (std
::move
(lhs
), std
::move
(rhs
), $5);
790 | simple_exp IN var_or_type %prec TICK_ACCESS
793 error (_
("Right operand of 'in' must be type"));
794 operation_up arg
= ada_pop
();
795 pstate
->push_new
<ada_unop_range_operation
>
796 (std
::move
(arg
), $3);
798 | simple_exp NOT IN simple_exp DOTDOT simple_exp
799 { ada_wrap3
<ada_ternop_range_operation
> ();
800 ada_wrap
<unary_logical_not_operation
> (); }
801 | simple_exp NOT IN primary TICK_RANGE tick_arglist
803 operation_up rhs
= ada_pop
();
804 operation_up lhs
= ada_pop
();
805 pstate
->push_new
<ada_binop_in_bounds_operation
>
806 (std
::move
(lhs
), std
::move
(rhs
), $6);
807 ada_wrap
<unary_logical_not_operation
> ();
809 | simple_exp NOT IN var_or_type %prec TICK_ACCESS
812 error (_
("Right operand of 'in' must be type"));
813 operation_up arg
= ada_pop
();
814 pstate
->push_new
<ada_unop_range_operation
>
815 (std
::move
(arg
), $4);
816 ada_wrap
<unary_logical_not_operation
> ();
820 relation
: simple_exp GEQ simple_exp
821 { ada_un_wrap2
<geq_operation
> (BINOP_GEQ
); }
824 relation
: simple_exp
'<' simple_exp
825 { ada_un_wrap2
<less_operation
> (BINOP_LESS
); }
828 relation
: simple_exp
'>' simple_exp
829 { ada_un_wrap2
<gtr_operation
> (BINOP_GTR
); }
841 relation _AND_ relation
842 { ada_wrap2
<bitwise_and_operation
>
843 (BINOP_BITWISE_AND
); }
844 | and_exp _AND_ relation
845 { ada_wrap2
<bitwise_and_operation
>
846 (BINOP_BITWISE_AND
); }
850 relation _AND_ THEN relation
851 { ada_wrap2
<logical_and_operation
>
852 (BINOP_LOGICAL_AND
); }
853 | and_then_exp _AND_ THEN relation
854 { ada_wrap2
<logical_and_operation
>
855 (BINOP_LOGICAL_AND
); }
860 { ada_wrap2
<bitwise_ior_operation
>
861 (BINOP_BITWISE_IOR
); }
863 { ada_wrap2
<bitwise_ior_operation
>
864 (BINOP_BITWISE_IOR
); }
868 relation OR ELSE relation
869 { ada_wrap2
<logical_or_operation
> (BINOP_LOGICAL_OR
); }
870 | or_else_exp OR ELSE relation
871 { ada_wrap2
<logical_or_operation
> (BINOP_LOGICAL_OR
); }
874 xor_exp
: relation XOR relation
875 { ada_wrap2
<bitwise_xor_operation
>
876 (BINOP_BITWISE_XOR
); }
877 | xor_exp XOR relation
878 { ada_wrap2
<bitwise_xor_operation
>
879 (BINOP_BITWISE_XOR
); }
882 /* Primaries can denote types (OP_TYPE). In cases such as
883 primary TICK_ADDRESS, where a type would be invalid, it will be
884 caught when evaluate_subexp in ada-lang.c tries to evaluate the
885 primary, expecting a value. Precedence rules resolve the ambiguity
886 in NAME TICK_ACCESS in favor of shifting to form a var_or_type. A
887 construct such as aType'access'access will again cause an error when
888 aType'access evaluates to a type that evaluate_subexp attempts to
890 primary
: primary TICK_ACCESS
892 | primary TICK_ADDRESS
893 { ada_addrof
(type_system_address
(pstate
)); }
894 | primary TICK_COMPLETE
896 pstate
->mark_completion
(make_tick_completer
($2));
898 | primary TICK_FIRST tick_arglist
900 operation_up arg
= ada_pop
();
901 pstate
->push_new
<ada_unop_atr_operation
>
902 (std
::move
(arg
), OP_ATR_FIRST
, $3);
904 | primary TICK_LAST tick_arglist
906 operation_up arg
= ada_pop
();
907 pstate
->push_new
<ada_unop_atr_operation
>
908 (std
::move
(arg
), OP_ATR_LAST
, $3);
910 | primary TICK_LENGTH tick_arglist
912 operation_up arg
= ada_pop
();
913 pstate
->push_new
<ada_unop_atr_operation
>
914 (std
::move
(arg
), OP_ATR_LENGTH
, $3);
917 { ada_wrap
<ada_atr_size_operation
> (); }
919 { ada_wrap
<ada_atr_tag_operation
> (); }
920 | opt_type_prefix TICK_MIN
'(' exp
',' exp
')'
921 { ada_wrap2
<ada_binop_min_operation
> (BINOP_MIN
); }
922 | opt_type_prefix TICK_MAX
'(' exp
',' exp
')'
923 { ada_wrap2
<ada_binop_max_operation
> (BINOP_MAX
); }
924 | opt_type_prefix TICK_POS
'(' exp
')'
925 { ada_wrap
<ada_pos_operation
> (); }
926 | type_prefix TICK_VAL
'(' exp
')'
928 operation_up arg
= ada_pop
();
929 pstate
->push_new
<ada_atr_val_operation
>
930 ($1, std
::move
(arg
));
932 | type_prefix TICK_ENUM_REP
'(' exp
')'
934 operation_up arg
= ada_pop
(true
, $1);
935 pstate
->push_new
<ada_atr_enum_rep_operation
>
936 ($1, std
::move
(arg
));
938 | type_prefix TICK_ENUM_VAL
'(' exp
')'
940 operation_up arg
= ada_pop
(true
, $1);
941 pstate
->push_new
<ada_atr_enum_val_operation
>
942 ($1, std
::move
(arg
));
944 | type_prefix TICK_MODULUS
946 struct type
*type_arg
= check_typedef
($1);
947 if
(!ada_is_modular_type
(type_arg
))
948 error (_
("'modulus must be applied to modular type"));
949 write_int
(pstate
, ada_modulus
(type_arg
),
950 type_arg
->target_type
());
954 tick_arglist
: %prec
'('
957 { $$
= $2.val
->as_integer
<LONGEST
> (); }
964 error (_
("Prefix must be type"));
973 { $$
= parse_type
(pstate
)->builtin_void
; }
979 pstate
->push_new
<long_const_operation
> ($1.type
, *$1.val
);
980 ada_wrap
<ada_wrapped_operation
> ();
986 pstate
->push_new
<ada_char_operation
> ($1.type
, $1.val
);
993 std
::copy
(std
::begin
($1.val
), std
::end
($1.val
),
995 pstate
->push_new
<float_const_operation
>
997 ada_wrap
<ada_wrapped_operation
> ();
1003 struct type
*null_ptr_type
1004 = lookup_pointer_type
(parse_type
(pstate
)->builtin_int0
);
1005 write_int
(pstate
, 0, null_ptr_type
);
1011 pstate
->push_new
<ada_string_operation
>
1016 primary
: TRUEKEYWORD
1018 write_int
(pstate
, 1,
1019 parse_type
(pstate
)->builtin_bool
);
1023 write_int
(pstate
, 0,
1024 parse_type
(pstate
)->builtin_bool
);
1029 { error (_
("NEW not implemented.")); }
1032 var_or_type: NAME %prec VAR
1033 { $$
= write_var_or_type
(pstate
, NULL
, $1); }
1034 | NAME_COMPLETE %prec VAR
1036 $$
= write_var_or_type_completion
(pstate
,
1040 | block NAME %prec VAR
1041 { $$
= write_var_or_type
(pstate
, $1, $2); }
1042 | block NAME_COMPLETE %prec VAR
1044 $$
= write_var_or_type_completion
(pstate
,
1050 $$
= write_var_or_type
(pstate
, NULL
, $1);
1054 $$
= lookup_pointer_type
($$
);
1056 | block NAME TICK_ACCESS
1058 $$
= write_var_or_type
(pstate
, $1, $2);
1062 $$
= lookup_pointer_type
($$
);
1067 block
: NAME COLONCOLON
1068 { $$
= block_lookup
(NULL
, $1.ptr
); }
1069 | block NAME COLONCOLON
1070 { $$
= block_lookup
($1, $2.ptr
); }
1074 '(' exp WITH DELTA aggregate_component_list
')'
1076 std
::vector
<ada_component_up
> components
1077 = pop_components
($5);
1078 operation_up base
= ada_pop
();
1080 push_component
<ada_aggregate_component
>
1081 (std
::move
(base
), std
::move
(components
));
1083 |
'(' aggregate_component_list
')'
1085 std
::vector
<ada_component_up
> components
1086 = pop_components
($2);
1088 push_component
<ada_aggregate_component
>
1089 (std
::move
(components
));
1093 aggregate_component_list
:
1094 component_groups
{ $$
= $1; }
1095 | positional_list exp
1097 push_component
<ada_positional_component
>
1101 | positional_list component_groups
1108 push_component
<ada_positional_component
>
1112 | positional_list exp
','
1114 push_component
<ada_positional_component
>
1122 | component_group
{ $$
= 1; }
1123 | component_group
',' component_groups
1127 others
: OTHERS ARROW exp
1129 push_component
<ada_others_component
> (ada_pop
());
1134 component_associations
1136 ada_choices_component
*choices
= choice_component
();
1137 choices
->set_associations
(pop_associations
($1));
1141 std
::string name
= copy_name
($2);
1143 auto iter
= ada_parser
->iterated_associations.find
(name
);
1144 if
(iter
!= ada_parser
->iterated_associations.end
())
1145 error (_
("Nested use of index parameter '%s'"),
1148 ada_parser
->iterated_associations
[name
] = {};
1150 component_associations
1152 std
::string name
= copy_name
($2);
1154 ada_choices_component
*choices
= choice_component
();
1155 choices
->set_associations
(pop_associations
($5));
1157 auto iter
= ada_parser
->iterated_associations.find
(name
);
1158 gdb_assert
(iter
!= ada_parser
->iterated_associations.end
());
1159 for
(ada_index_var_operation
*var
: iter
->second
)
1160 var
->set_choices
(choices
);
1162 ada_parser
->iterated_associations.erase
(name
);
1164 choices
->set_name
(std
::move
(name
));
1168 /* We use this somewhat obscure definition in order to handle NAME => and
1169 NAME | differently from exp => and exp |. ARROW and '|' have a precedence
1170 above that of the reduction of NAME to var_or_type. By delaying
1171 decisions until after the => or '|', we convert the ambiguity to a
1172 resolved shift/reduce conflict. */
1173 component_associations
:
1176 push_component
<ada_choices_component
> (ada_pop
());
1177 write_name_assoc
(pstate
, $1);
1180 | simple_exp ARROW exp
1182 push_component
<ada_choices_component
> (ada_pop
());
1183 push_association
<ada_name_association
> (ada_pop
());
1186 | simple_exp DOTDOT simple_exp ARROW exp
1188 push_component
<ada_choices_component
> (ada_pop
());
1189 operation_up rhs
= ada_pop
();
1190 operation_up lhs
= ada_pop
();
1191 push_association
<ada_discrete_range_association
>
1192 (std
::move
(lhs
), std
::move
(rhs
));
1195 | NAME
'|' component_associations
1197 write_name_assoc
(pstate
, $1);
1200 | simple_exp
'|' component_associations
1202 push_association
<ada_name_association
> (ada_pop
());
1205 | simple_exp DOTDOT simple_exp
'|' component_associations
1208 operation_up rhs
= ada_pop
();
1209 operation_up lhs
= ada_pop
();
1210 push_association
<ada_discrete_range_association
>
1211 (std
::move
(lhs
), std
::move
(rhs
));
1216 /* Some extensions borrowed from C, for the benefit of those who find they
1217 can't get used to Ada notation in GDB. */
1219 primary
: '*' primary %prec
'.'
1220 { ada_wrap
<ada_unop_ind_operation
> (); }
1221 |
'&' primary %prec
'.'
1223 | primary
'[' exp
']'
1225 ada_wrap2
<subscript_operation
> (BINOP_SUBSCRIPT
);
1226 ada_wrap
<ada_wrapped_operation
> ();
1232 /* yylex defined in ada-lex.c: Reads one token, getting characters */
1233 /* through lexptr. */
1235 /* Remap normal flex interface names (yylex) as well as gratuitously */
1236 /* global symbol names, so we can have multiple flex-generated parsers */
1239 /* (See note above on previous definitions for YACC.) */
1241 #define yy_create_buffer ada_yy_create_buffer
1242 #define yy_delete_buffer ada_yy_delete_buffer
1243 #define yy_init_buffer ada_yy_init_buffer
1244 #define yy_load_buffer_state ada_yy_load_buffer_state
1245 #define yy_switch_to_buffer ada_yy_switch_to_buffer
1246 #define yyrestart ada_yyrestart
1247 #define yytext ada_yytext
1249 /* The following kludge was found necessary to prevent conflicts between */
1250 /* defs.h and non-standard stdlib.h files. */
1251 #define qsort __qsort__dummy
1252 #include "ada-lex.c"
1255 ada_parse
(struct parser_state
*par_state
)
1257 /* Setting up the parser state. */
1258 scoped_restore pstate_restore
= make_scoped_restore
(&pstate
, par_state
);
1259 gdb_assert
(par_state
!= NULL
);
1261 ada_parse_state parser
(par_state
->lexptr
);
1262 scoped_restore parser_restore
= make_scoped_restore
(&ada_parser
, &parser
);
1264 scoped_restore restore_yydebug
= make_scoped_restore
(&yydebug,
1267 lexer_init
(yyin
); /* (Re-)initialize lexer. */
1269 int result
= yyparse ();
1272 struct type
*context_type
= nullptr
;
1273 if
(par_state
->void_context_p
)
1274 context_type
= parse_type
(par_state
)->builtin_void
;
1275 pstate
->set_operation
(ada_pop
(true
, context_type
));
1281 yyerror (const char *msg
)
1283 pstate
->parse_error
(msg
);
1286 /* Emit expression to access an instance of SYM, in block BLOCK (if
1290 write_var_from_sym
(struct parser_state
*par_state
, block_symbol sym
)
1292 if
(symbol_read_needs_frame
(sym.symbol
))
1293 par_state
->block_tracker
->update
(sym.block
, INNERMOST_BLOCK_FOR_SYMBOLS
);
1295 par_state
->push_new
<ada_var_value_operation
> (sym
);
1298 /* Write integer or boolean constant ARG of type TYPE. */
1301 write_int
(struct parser_state
*par_state
, LONGEST arg
, struct type
*type
)
1303 pstate
->push_new
<long_const_operation
> (type
, arg
);
1304 ada_wrap
<ada_wrapped_operation
> ();
1307 /* Emit expression corresponding to the renamed object named
1308 designated by RENAMED_ENTITY[0 .. RENAMED_ENTITY_LEN-1] in the
1309 context of ORIG_LEFT_CONTEXT, to which is applied the operations
1310 encoded by RENAMING_EXPR. MAX_DEPTH is the maximum number of
1311 cascaded renamings to allow. If ORIG_LEFT_CONTEXT is null, it
1312 defaults to the currently selected block. ORIG_SYMBOL is the
1313 symbol that originally encoded the renaming. It is needed only
1314 because its prefix also qualifies any index variables used to index
1315 or slice an array. It should not be necessary once we go to the
1316 new encoding entirely (FIXME pnh 7/20/2007). */
1319 write_object_renaming
(struct parser_state
*par_state
,
1320 const struct block
*orig_left_context
,
1321 const char *renamed_entity
, int renamed_entity_len
,
1322 const char *renaming_expr
, int max_depth
)
1325 enum { SIMPLE_INDEX
, LOWER_BOUND
, UPPER_BOUND
} slice_state
;
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 block_symbol sym_info
= ada_lookup_encoded_symbol
(name
, orig_left_context
,
1337 if
(sym_info.symbol
== NULL
)
1338 error (_
("Could not find renamed variable: %s"), ada_decode
(name
).c_str
());
1339 else if
(sym_info.symbol
->aclass
() == LOC_TYPEDEF
)
1340 /* We have a renaming of an old-style renaming symbol. Don't
1341 trust the block information. */
1342 sym_info.block
= orig_left_context
;
1345 const char *inner_renamed_entity
;
1346 int inner_renamed_entity_len
;
1347 const char *inner_renaming_expr
;
1349 switch
(ada_parse_renaming
(sym_info.symbol
, &inner_renamed_entity
,
1350 &inner_renamed_entity_len
,
1351 &inner_renaming_expr
))
1353 case ADA_NOT_RENAMING
:
1354 write_var_from_sym
(par_state
, sym_info
);
1356 case ADA_OBJECT_RENAMING
:
1357 write_object_renaming
(par_state
, sym_info.block
,
1358 inner_renamed_entity
, inner_renamed_entity_len
,
1359 inner_renaming_expr
, max_depth
- 1);
1366 slice_state
= SIMPLE_INDEX
;
1367 while
(*renaming_expr
== 'X')
1371 switch
(*renaming_expr
) {
1374 ada_wrap
<ada_unop_ind_operation
> ();
1377 slice_state
= LOWER_BOUND
;
1381 if
(isdigit
(*renaming_expr
))
1384 long val
= strtol
(renaming_expr
, &next
, 10);
1385 if
(next
== renaming_expr
)
1387 renaming_expr
= next
;
1388 write_int
(par_state
, val
, parse_type
(par_state
)->builtin_int
);
1395 end
= strchr
(renaming_expr
, 'X');
1397 end
= renaming_expr
+ strlen
(renaming_expr
);
1399 index_name
= obstack_strndup
(&ada_parser
->temp_space
,
1401 end
- renaming_expr
);
1402 renaming_expr
= end
;
1404 block_symbol index_sym_info
1405 = ada_lookup_encoded_symbol
(index_name
, orig_left_context
,
1407 if
(index_sym_info.symbol
== NULL
)
1408 error (_
("Could not find %s"), index_name
);
1409 else if
(index_sym_info.symbol
->aclass
() == LOC_TYPEDEF
)
1410 /* Index is an old-style renaming symbol. */
1411 index_sym_info.block
= orig_left_context
;
1412 write_var_from_sym
(par_state
, index_sym_info
);
1414 if
(slice_state
== SIMPLE_INDEX
)
1416 else if
(slice_state
== LOWER_BOUND
)
1417 slice_state
= UPPER_BOUND
;
1418 else if
(slice_state
== UPPER_BOUND
)
1420 ada_wrap3
<ada_ternop_slice_operation
> ();
1421 slice_state
= SIMPLE_INDEX
;
1431 if
(slice_state
!= SIMPLE_INDEX
)
1433 end
= strchr
(renaming_expr
, 'X');
1435 end
= renaming_expr
+ strlen
(renaming_expr
);
1437 operation_up arg
= ada_pop
();
1438 pstate
->push_new
<ada_structop_operation
>
1439 (std
::move
(arg
), std
::string (renaming_expr
,
1440 end
- renaming_expr
));
1441 renaming_expr
= end
;
1449 if
(slice_state
== SIMPLE_INDEX
)
1453 error (_
("Internal error in encoding of renaming declaration"));
1456 static const struct block
*
1457 block_lookup
(const struct block
*context
, const char *raw_name
)
1460 struct symtab
*symtab
;
1461 const struct block
*result
= NULL
;
1463 std
::string name_storage
;
1464 if
(raw_name
[0] == '\'')
1471 name_storage
= ada_encode
(raw_name
);
1472 name
= name_storage.c_str
();
1475 std
::vector
<struct block_symbol
> syms
1476 = ada_lookup_symbol_list
(name
, context
, SEARCH_FUNCTION_DOMAIN
);
1479 && (syms.empty
() || syms
[0].symbol
->aclass
() != LOC_BLOCK
))
1480 symtab
= lookup_symtab
(name
);
1485 result
= symtab
->compunit
()->blockvector
()->static_block
();
1486 else if
(syms.empty
() || syms
[0].symbol
->aclass
() != LOC_BLOCK
)
1488 if
(context
== NULL
)
1489 error (_
("No file or function \"%s\"."), raw_name
);
1491 error (_
("No function \"%s\" in specified context."), raw_name
);
1495 if
(syms.size
() > 1)
1496 warning
(_
("Function name \"%s\" ambiguous here"), raw_name
);
1497 result
= syms
[0].symbol
->value_block
();
1503 static struct symbol
*
1504 select_possible_type_sym
(const std
::vector
<struct block_symbol
> &syms
)
1507 int preferred_index
;
1508 struct type
*preferred_type
;
1510 preferred_index
= -1; preferred_type
= NULL
;
1511 for
(i
= 0; i
< syms.size
(); i
+= 1)
1512 switch
(syms
[i
].symbol
->aclass
())
1515 if
(ada_prefer_type
(syms
[i
].symbol
->type
(), preferred_type
))
1517 preferred_index
= i
;
1518 preferred_type
= syms
[i
].symbol
->type
();
1524 case LOC_REGPARM_ADDR
:
1531 if
(preferred_type
== NULL
)
1533 return syms
[preferred_index
].symbol
;
1537 find_primitive_type
(struct parser_state
*par_state
, const char *name
)
1540 type
= language_lookup_primitive_type
(par_state
->language
(),
1541 par_state
->gdbarch
(),
1543 if
(type
== NULL
&& strcmp
("system__address", name
) == 0)
1544 type
= type_system_address
(par_state
);
1548 /* Check to see if we have a regular definition of this
1549 type that just didn't happen to have been read yet. */
1551 char *expanded_name
=
1552 (char *) alloca
(strlen
(name
) + sizeof
("standard__"));
1553 strcpy
(expanded_name
, "standard__");
1554 strcat
(expanded_name
, name
);
1555 sym
= ada_lookup_symbol
(expanded_name
, NULL
, SEARCH_TYPE_DOMAIN
).symbol
;
1556 if
(sym
!= NULL
&& sym
->aclass
() == LOC_TYPEDEF
)
1557 type
= sym
->type
();
1564 chop_selector
(const char *name
, int end
)
1567 for
(i
= end
- 1; i
> 0; i
-= 1)
1568 if
(name
[i
] == '.' ||
(name
[i
] == '_' && name
[i
+1] == '_'))
1573 /* If NAME is a string beginning with a separator (either '__', or
1574 '.'), chop this separator and return the result; else, return
1578 chop_separator
(const char *name
)
1583 if
(name
[0] == '_' && name
[1] == '_')
1589 /* Given that SELS is a string of the form (<sep><identifier>)*, where
1590 <sep> is '__' or '.', write the indicated sequence of
1591 STRUCTOP_STRUCT expression operators. Returns a pointer to the
1592 last operation that was pushed. */
1593 static ada_structop_operation
*
1594 write_selectors
(struct parser_state
*par_state
, const char *sels
)
1596 ada_structop_operation
*result
= nullptr
;
1597 while
(*sels
!= '\0')
1599 const char *p
= chop_separator
(sels
);
1601 while
(*sels
!= '\0' && *sels
!= '.'
1602 && (sels
[0] != '_' || sels
[1] != '_'))
1604 operation_up arg
= ada_pop
();
1605 result
= new ada_structop_operation
(std
::move
(arg
),
1606 std
::string (p
, sels
- p
));
1607 pstate
->push
(operation_up
(result
));
1612 /* Write a variable access (OP_VAR_VALUE) to ambiguous encoded name
1613 NAME[0..LEN-1], in block context BLOCK, to be resolved later. Writes
1614 a temporary symbol that is valid until the next call to ada_parse.
1617 write_ambiguous_var
(struct parser_state
*par_state
,
1618 const struct block
*block
, const char *name
, int len
)
1620 struct symbol
*sym
= new
(&ada_parser
->temp_space
) symbol
();
1622 sym
->set_domain
(UNDEF_DOMAIN
);
1623 sym
->set_linkage_name
(obstack_strndup
(&ada_parser
->temp_space
, name
, len
));
1624 sym
->set_language
(language_ada
, nullptr
);
1626 block_symbol bsym
{ sym
, block
};
1627 par_state
->push_new
<ada_var_value_operation
> (bsym
);
1630 /* A convenient wrapper around ada_get_field_index that takes
1631 a non NUL-terminated FIELD_NAME0 and a FIELD_NAME_LEN instead
1632 of a NUL-terminated field name. */
1635 ada_nget_field_index
(const struct type
*type
, const char *field_name0
,
1636 int field_name_len
, int maybe_missing
)
1638 char *field_name
= (char *) alloca
((field_name_len
+ 1) * sizeof
(char));
1640 strncpy
(field_name
, field_name0
, field_name_len
);
1641 field_name
[field_name_len
] = '\0';
1642 return ada_get_field_index
(type
, field_name
, maybe_missing
);
1645 /* If encoded_field_name is the name of a field inside symbol SYM,
1646 then return the type of that field. Otherwise, return NULL.
1648 This function is actually recursive, so if ENCODED_FIELD_NAME
1649 doesn't match one of the fields of our symbol, then try to see
1650 if ENCODED_FIELD_NAME could not be a succession of field names
1651 (in other words, the user entered an expression of the form
1652 TYPE_NAME.FIELD1.FIELD2.FIELD3), in which case we evaluate
1653 each field name sequentially to obtain the desired field type.
1654 In case of failure, we return NULL. */
1656 static struct type
*
1657 get_symbol_field_type
(struct symbol
*sym
, const char *encoded_field_name
)
1659 const char *field_name
= encoded_field_name
;
1660 const char *subfield_name
;
1661 struct type
*type
= sym
->type
();
1664 if
(type
== NULL || field_name
== NULL
)
1666 type
= check_typedef
(type
);
1668 while
(field_name
[0] != '\0')
1670 field_name
= chop_separator
(field_name
);
1672 fieldno
= ada_get_field_index
(type
, field_name
, 1);
1674 return type
->field
(fieldno
).type
();
1676 subfield_name
= field_name
;
1677 while
(*subfield_name
!= '\0' && *subfield_name
!= '.'
1678 && (subfield_name
[0] != '_' || subfield_name
[1] != '_'))
1681 if
(subfield_name
[0] == '\0')
1684 fieldno
= ada_nget_field_index
(type
, field_name
,
1685 subfield_name
- field_name
, 1);
1689 type
= type
->field
(fieldno
).type
();
1690 field_name
= subfield_name
;
1696 /* Look up NAME0 (an unencoded identifier or dotted name) in BLOCK (or
1697 expression_block_context if NULL). If it denotes a type, return
1698 that type. Otherwise, write expression code to evaluate it as an
1699 object and return NULL. In this second case, NAME0 will, in general,
1700 have the form <name>(.<selector_name>)*, where <name> is an object
1701 or renaming encoded in the debugging data. Calls error if no
1702 prefix <name> matches a name in the debugging data (i.e., matches
1703 either a complete name or, as a wild-card match, the final
1707 write_var_or_type
(struct parser_state
*par_state
,
1708 const struct block
*block
, struct stoken name0
)
1714 std
::string name_storage
= ada_encode
(name0.ptr
);
1716 if
(block
== nullptr
)
1718 auto iter
= ada_parser
->iterated_associations.find
(name_storage
);
1719 if
(iter
!= ada_parser
->iterated_associations.end
())
1721 auto op
= std
::make_unique
<ada_index_var_operation
> ();
1722 iter
->second.push_back
(op.get
());
1723 par_state
->push
(std
::move
(op
));
1727 block
= par_state
->expression_context_block
;
1730 name_len
= name_storage.size
();
1731 encoded_name
= obstack_strndup
(&ada_parser
->temp_space
,
1732 name_storage.c_str
(),
1734 for
(depth
= 0; depth
< MAX_RENAMING_CHAIN_LENGTH
; depth
+= 1)
1738 tail_index
= name_len
;
1739 while
(tail_index
> 0)
1741 struct symbol
*type_sym
;
1742 struct symbol
*renaming_sym
;
1743 const char* renaming
;
1745 const char* renaming_expr
;
1746 int terminator
= encoded_name
[tail_index
];
1748 encoded_name
[tail_index
] = '\0';
1749 /* In order to avoid double-encoding, we want to only pass
1750 the decoded form to lookup functions. */
1751 std
::string decoded_name
= ada_decode
(encoded_name
);
1752 encoded_name
[tail_index
] = terminator
;
1754 std
::vector
<struct block_symbol
> syms
1755 = ada_lookup_symbol_list
(decoded_name.c_str
(), block
,
1758 type_sym
= select_possible_type_sym
(syms
);
1760 if
(type_sym
!= NULL
)
1761 renaming_sym
= type_sym
;
1762 else if
(syms.size
() == 1)
1763 renaming_sym
= syms
[0].symbol
;
1765 renaming_sym
= NULL
;
1767 switch
(ada_parse_renaming
(renaming_sym
, &renaming
,
1768 &renaming_len
, &renaming_expr
))
1770 case ADA_NOT_RENAMING
:
1772 case ADA_PACKAGE_RENAMING
:
1773 case ADA_EXCEPTION_RENAMING
:
1774 case ADA_SUBPROGRAM_RENAMING
:
1776 int alloc_len
= renaming_len
+ name_len
- tail_index
+ 1;
1778 = (char *) obstack_alloc
(&ada_parser
->temp_space
,
1780 strncpy
(new_name
, renaming
, renaming_len
);
1781 strcpy
(new_name
+ renaming_len
, encoded_name
+ tail_index
);
1782 encoded_name
= new_name
;
1783 name_len
= renaming_len
+ name_len
- tail_index
;
1784 goto TryAfterRenaming
;
1786 case ADA_OBJECT_RENAMING
:
1787 write_object_renaming
(par_state
, block
, renaming
, renaming_len
,
1788 renaming_expr
, MAX_RENAMING_CHAIN_LENGTH
);
1789 write_selectors
(par_state
, encoded_name
+ tail_index
);
1792 internal_error
(_
("impossible value from ada_parse_renaming"));
1795 if
(type_sym
!= NULL
)
1797 struct type
*field_type
;
1799 if
(tail_index
== name_len
)
1800 return type_sym
->type
();
1802 /* We have some extraneous characters after the type name.
1803 If this is an expression "TYPE_NAME.FIELD0.[...].FIELDN",
1804 then try to get the type of FIELDN. */
1806 = get_symbol_field_type
(type_sym
, encoded_name
+ tail_index
);
1807 if
(field_type
!= NULL
)
1810 error (_
("Invalid attempt to select from type: \"%s\"."),
1813 else if
(tail_index
== name_len
&& syms.empty
())
1815 struct type
*type
= find_primitive_type
(par_state
,
1822 if
(syms.size
() == 1)
1824 write_var_from_sym
(par_state
, syms
[0]);
1825 write_selectors
(par_state
, encoded_name
+ tail_index
);
1828 else if
(syms.empty
())
1830 struct objfile
*objfile
= nullptr
;
1831 if
(block
!= nullptr
)
1832 objfile
= block
->objfile
();
1834 bound_minimal_symbol msym
1835 = ada_lookup_simple_minsym
(decoded_name.c_str
(), objfile
);
1836 if
(msym.minsym
!= NULL
)
1838 par_state
->push_new
<ada_var_msym_value_operation
> (msym
);
1839 /* Maybe cause error here rather than later? FIXME? */
1840 write_selectors
(par_state
, encoded_name
+ tail_index
);
1844 if
(tail_index
== name_len
1845 && strncmp
(encoded_name
, "standard__",
1846 sizeof
("standard__") - 1) == 0)
1847 error (_
("No definition of \"%s\" found."), name0.ptr
);
1849 tail_index
= chop_selector
(encoded_name
, tail_index
);
1853 write_ambiguous_var
(par_state
, block
, encoded_name
,
1855 write_selectors
(par_state
, encoded_name
+ tail_index
);
1860 if
(!have_full_symbols
(current_program_space
)
1861 && !have_partial_symbols
(current_program_space
)
1863 error (_
("No symbol table is loaded. Use the \"file\" command."));
1864 if
(block
== par_state
->expression_context_block
)
1865 error (_
("No definition of \"%s\" in current context."), name0.ptr
);
1867 error (_
("No definition of \"%s\" in specified context."), name0.ptr
);
1872 error (_
("Could not find renamed symbol \"%s\""), name0.ptr
);
1876 /* Because ada_completer_word_break_characters does not contain '.' --
1877 and it cannot easily be added, this breaks other completions -- we
1878 have to recreate the completion word-splitting here, so that we can
1879 provide a prefix that is then used when completing field names.
1880 Without this, an attempt like "complete print abc.d" will give a
1881 result like "print def" rather than "print abc.def". */
1884 ada_parse_state::find_completion_bounds
()
1886 const char *end
= pstate
->lexptr
;
1887 /* First the end of the prefix. Here we stop at the token start or
1889 for
(; end
> m_original_expr
&& end
[-1] != '.' && !isspace
(end
[-1]); --end
)
1893 /* Now find the start of the prefix. */
1894 const char *ptr
= end
;
1895 /* Here we allow '.'. */
1897 ptr
> m_original_expr
&& (ptr
[-1] == '.'
1899 ||
(ptr
[-1] >= 'a' && ptr
[-1] <= 'z')
1900 ||
(ptr
[-1] >= 'A' && ptr
[-1] <= 'Z')
1901 ||
(ptr
[-1] & 0xff) >= 0x80);
1906 /* ... except, skip leading spaces. */
1907 ptr
= skip_spaces
(ptr
);
1909 return std
::string (ptr
, end
);
1912 /* A wrapper for write_var_or_type that is used specifically when
1913 completion is requested for the last of a sequence of
1916 static struct type
*
1917 write_var_or_type_completion
(struct parser_state
*par_state
,
1918 const struct block
*block
, struct stoken name0
)
1920 int tail_index
= chop_selector
(name0.ptr
, name0.length
);
1921 /* If there's no separator, just defer to ordinary symbol
1923 if
(tail_index
== -1)
1924 return write_var_or_type
(par_state
, block
, name0
);
1926 std
::string copy
(name0.ptr
, tail_index
);
1927 struct type
*type
= write_var_or_type
(par_state
, block
,
1929 (int) copy.length
() });
1930 /* For completion purposes, it's enough that we return a type
1932 if
(type
!= nullptr
)
1935 ada_structop_operation
*op
= write_selectors
(par_state
,
1936 name0.ptr
+ tail_index
);
1937 op
->set_prefix
(ada_parser
->find_completion_bounds
());
1938 par_state
->mark_struct_expression
(op
);
1942 /* Write a left side of a component association (e.g., NAME in NAME =>
1943 exp). If NAME has the form of a selected component, write it as an
1944 ordinary expression. If it is a simple variable that unambiguously
1945 corresponds to exactly one symbol that does not denote a type or an
1946 object renaming, also write it normally as an OP_VAR_VALUE.
1947 Otherwise, write it as an OP_NAME.
1949 Unfortunately, we don't know at this point whether NAME is supposed
1950 to denote a record component name or the value of an array index.
1951 Therefore, it is not appropriate to disambiguate an ambiguous name
1952 as we normally would, nor to replace a renaming with its referent.
1953 As a result, in the (one hopes) rare case that one writes an
1954 aggregate such as (R => 42) where R renames an object or is an
1955 ambiguous name, one must write instead ((R) => 42). */
1958 write_name_assoc
(struct parser_state
*par_state
, struct stoken name
)
1960 if
(strchr
(name.ptr
, '.') == NULL
)
1962 std
::vector
<struct block_symbol
> syms
1963 = ada_lookup_symbol_list
(name.ptr
,
1964 par_state
->expression_context_block
,
1967 if
(syms.size
() != 1 || syms
[0].symbol
->aclass
() == LOC_TYPEDEF
)
1968 pstate
->push_new
<ada_string_operation
> (copy_name
(name
));
1970 write_var_from_sym
(par_state
, syms
[0]);
1973 if
(write_var_or_type
(par_state
, NULL
, name
) != NULL
)
1974 error (_
("Invalid use of type."));
1976 push_association
<ada_name_association
> (ada_pop
());
1979 static struct type
*
1980 type_for_char
(struct parser_state
*par_state
, ULONGEST value
)
1983 return language_string_char_type
(par_state
->language
(),
1984 par_state
->gdbarch
());
1985 else if
(value
<= 0xffff)
1986 return language_lookup_primitive_type
(par_state
->language
(),
1987 par_state
->gdbarch
(),
1989 return language_lookup_primitive_type
(par_state
->language
(),
1990 par_state
->gdbarch
(),
1991 "wide_wide_character");
1994 static struct type
*
1995 type_system_address
(struct parser_state
*par_state
)
1998 = language_lookup_primitive_type
(par_state
->language
(),
1999 par_state
->gdbarch
(),
2001 return type
!= NULL ? type
: parse_type
(par_state
)->builtin_data_ptr
;