ada: Fix wrong resolution for hidden discriminant in predicate
[official-gcc.git] / gcc / ada / sem_disp.adb
blobb22407aafb80f9fd6dbd415d7c4cdde76d8c2328
1 ------------------------------------------------------------------------------
2 -- --
3 -- GNAT COMPILER COMPONENTS --
4 -- --
5 -- S E M _ D I S P --
6 -- --
7 -- B o d y --
8 -- --
9 -- Copyright (C) 1992-2023, Free Software Foundation, Inc. --
10 -- --
11 -- GNAT is free software; you can redistribute it and/or modify it under --
12 -- terms of the GNU General Public License as published by the Free Soft- --
13 -- ware Foundation; either version 3, or (at your option) any later ver- --
14 -- sion. GNAT is distributed in the hope that it will be useful, but WITH- --
15 -- OUT ANY WARRANTY; without even the implied warranty of MERCHANTABILITY --
16 -- or FITNESS FOR A PARTICULAR PURPOSE. See the GNU General Public License --
17 -- for more details. You should have received a copy of the GNU General --
18 -- Public License distributed with GNAT; see file COPYING3. If not, go to --
19 -- http://www.gnu.org/licenses for a complete copy of the license. --
20 -- --
21 -- GNAT was originally developed by the GNAT team at New York University. --
22 -- Extensive contributions were provided by Ada Core Technologies Inc. --
23 -- --
24 ------------------------------------------------------------------------------
26 with Aspects; use Aspects;
27 with Atree; use Atree;
28 with Debug; use Debug;
29 with Elists; use Elists;
30 with Einfo; use Einfo;
31 with Einfo.Entities; use Einfo.Entities;
32 with Einfo.Utils; use Einfo.Utils;
33 with Exp_Disp; use Exp_Disp;
34 with Exp_Util; use Exp_Util;
35 with Exp_Ch6; use Exp_Ch6;
36 with Exp_Ch7; use Exp_Ch7;
37 with Exp_Tss; use Exp_Tss;
38 with Errout; use Errout;
39 with Freeze; use Freeze;
40 with Lib.Xref; use Lib.Xref;
41 with Namet; use Namet;
42 with Nlists; use Nlists;
43 with Nmake; use Nmake;
44 with Opt; use Opt;
45 with Output; use Output;
46 with Restrict; use Restrict;
47 with Rident; use Rident;
48 with Sem; use Sem;
49 with Sem_Aux; use Sem_Aux;
50 with Sem_Ch6; use Sem_Ch6;
51 with Sem_Ch8; use Sem_Ch8;
52 with Sem_Eval; use Sem_Eval;
53 with Sem_Type; use Sem_Type;
54 with Sem_Util; use Sem_Util;
55 with Snames; use Snames;
56 with Sinfo; use Sinfo;
57 with Sinfo.Nodes; use Sinfo.Nodes;
58 with Sinfo.Utils; use Sinfo.Utils;
59 with Tbuild; use Tbuild;
60 with Uintp; use Uintp;
61 with Warnsw; use Warnsw;
63 package body Sem_Disp is
65 -----------------------
66 -- Local Subprograms --
67 -----------------------
69 procedure Add_Dispatching_Operation
70 (Tagged_Type : Entity_Id;
71 New_Op : Entity_Id);
72 -- Add New_Op in the list of primitive operations of Tagged_Type
74 function Check_Controlling_Type
75 (T : Entity_Id;
76 Subp : Entity_Id) return Entity_Id;
77 -- T is the tagged type of a formal parameter or the result of Subp.
78 -- If the subprogram has a controlling parameter or result that matches
79 -- the type, then returns the tagged type of that parameter or result
80 -- (returning the designated tagged type in the case of an access
81 -- parameter); otherwise returns empty.
83 function Find_Hidden_Overridden_Primitive (S : Entity_Id) return Entity_Id;
84 -- [Ada 2012:AI-0125] Find an inherited hidden primitive of the dispatching
85 -- type of S that has the same name of S, a type-conformant profile, an
86 -- original corresponding operation O that is a primitive of a visible
87 -- ancestor of the dispatching type of S and O is visible at the point of
88 -- of declaration of S. If the entity is found the Alias of S is set to the
89 -- original corresponding operation S and its Overridden_Operation is set
90 -- to the found entity; otherwise return Empty.
92 -- This routine does not search for non-hidden primitives since they are
93 -- covered by the normal Ada 2005 rules.
95 function Is_Inherited_Public_Operation (Op : Entity_Id) return Boolean;
96 -- Check whether a primitive operation is inherited from an operation
97 -- declared in the visible part of its package.
99 -------------------------------
100 -- Add_Dispatching_Operation --
101 -------------------------------
103 procedure Add_Dispatching_Operation
104 (Tagged_Type : Entity_Id;
105 New_Op : Entity_Id)
107 List : constant Elist_Id := Primitive_Operations (Tagged_Type);
109 begin
110 -- The dispatching operation may already be on the list, if it is the
111 -- wrapper for an inherited function of a null extension (see Exp_Ch3
112 -- for the construction of function wrappers). The list of primitive
113 -- operations must not contain duplicates.
115 -- The Default_Initial_Condition and invariant procedures are not added
116 -- to the list of primitives even when they are generated for a tagged
117 -- type. These routines must not be targets of dispatching calls and
118 -- therefore must not appear in the dispatch table because they already
119 -- utilize class-wide-precondition semantics to handle inheritance and
120 -- overriding.
122 if Is_Suitable_Primitive (New_Op) then
123 Append_Unique_Elmt (New_Op, List);
124 end if;
125 end Add_Dispatching_Operation;
127 --------------------------
128 -- Covered_Interface_Op --
129 --------------------------
131 function Covered_Interface_Op (Prim : Entity_Id) return Entity_Id is
132 Tagged_Type : constant Entity_Id := Find_Dispatching_Type (Prim);
133 Elmt : Elmt_Id;
134 E : Entity_Id;
136 begin
137 pragma Assert (Is_Dispatching_Operation (Prim));
139 -- Although this is a dispatching primitive we must check if its
140 -- dispatching type is available because it may be the primitive
141 -- of a private type not defined as tagged in its partial view.
143 if Present (Tagged_Type) and then Has_Interfaces (Tagged_Type) then
145 -- If the tagged type is frozen then the internal entities associated
146 -- with interfaces are available in the list of primitives of the
147 -- tagged type and can be used to speed up this search.
149 if Is_Frozen (Tagged_Type) then
150 Elmt := First_Elmt (Primitive_Operations (Tagged_Type));
151 while Present (Elmt) loop
152 E := Node (Elmt);
154 if Present (Interface_Alias (E))
155 and then Alias (E) = Prim
156 then
157 return Interface_Alias (E);
158 end if;
160 Next_Elmt (Elmt);
161 end loop;
163 -- Otherwise we must collect all the interface primitives and check
164 -- if the Prim overrides (implements) some interface primitive.
166 else
167 declare
168 Ifaces_List : Elist_Id;
169 Iface_Elmt : Elmt_Id;
170 Iface : Entity_Id;
171 Iface_Prim : Entity_Id;
173 begin
174 Collect_Interfaces (Tagged_Type, Ifaces_List);
175 Iface_Elmt := First_Elmt (Ifaces_List);
176 while Present (Iface_Elmt) loop
177 Iface := Node (Iface_Elmt);
179 Elmt := First_Elmt (Primitive_Operations (Iface));
180 while Present (Elmt) loop
181 Iface_Prim := Node (Elmt);
183 if Chars (Iface_Prim) = Chars (Prim)
184 and then Is_Interface_Conformant
185 (Tagged_Type, Iface_Prim, Prim)
186 then
187 return Iface_Prim;
188 end if;
190 Next_Elmt (Elmt);
191 end loop;
193 Next_Elmt (Iface_Elmt);
194 end loop;
195 end;
196 end if;
197 end if;
199 return Empty;
200 end Covered_Interface_Op;
202 ----------------------------------
203 -- Covered_Interface_Primitives --
204 ----------------------------------
206 function Covered_Interface_Primitives (Prim : Entity_Id) return Elist_Id is
207 Tagged_Type : constant Entity_Id := Find_Dispatching_Type (Prim);
208 Elmt : Elmt_Id;
209 E : Entity_Id;
210 Result : Elist_Id := No_Elist;
212 begin
213 pragma Assert (Is_Dispatching_Operation (Prim));
215 -- Although this is a dispatching primitive we must check if its
216 -- dispatching type is available because it may be the primitive
217 -- of a private type not defined as tagged in its partial view.
219 if Present (Tagged_Type) and then Has_Interfaces (Tagged_Type) then
221 -- If the tagged type is frozen then the internal entities associated
222 -- with interfaces are available in the list of primitives of the
223 -- tagged type and can be used to speed up this search.
225 if Is_Frozen (Tagged_Type) then
226 Elmt := First_Elmt (Primitive_Operations (Tagged_Type));
227 while Present (Elmt) loop
228 E := Node (Elmt);
230 if Present (Interface_Alias (E))
231 and then Alias (E) = Prim
232 then
233 if No (Result) then
234 Result := New_Elmt_List;
235 end if;
237 Append_Elmt (Interface_Alias (E), Result);
238 end if;
240 Next_Elmt (Elmt);
241 end loop;
243 -- Otherwise we must collect all the interface primitives and check
244 -- whether the Prim overrides (implements) some interface primitive.
246 else
247 declare
248 Ifaces_List : Elist_Id;
249 Iface_Elmt : Elmt_Id;
250 Iface : Entity_Id;
251 Iface_Prim : Entity_Id;
253 begin
254 Collect_Interfaces (Tagged_Type, Ifaces_List);
256 Iface_Elmt := First_Elmt (Ifaces_List);
257 while Present (Iface_Elmt) loop
258 Iface := Node (Iface_Elmt);
260 Elmt := First_Elmt (Primitive_Operations (Iface));
261 while Present (Elmt) loop
262 Iface_Prim := Node (Elmt);
264 if Chars (Iface_Prim) = Chars (Prim)
265 and then Is_Interface_Conformant
266 (Tagged_Type, Iface_Prim, Prim)
267 then
268 if No (Result) then
269 Result := New_Elmt_List;
270 end if;
272 Append_Elmt (Iface_Prim, Result);
273 end if;
275 Next_Elmt (Elmt);
276 end loop;
278 Next_Elmt (Iface_Elmt);
279 end loop;
280 end;
281 end if;
282 end if;
284 return Result;
285 end Covered_Interface_Primitives;
287 -------------------------------
288 -- Check_Controlling_Formals --
289 -------------------------------
291 procedure Check_Controlling_Formals
292 (Typ : Entity_Id;
293 Subp : Entity_Id)
295 Formal : Entity_Id;
296 Ctrl_Type : Entity_Id;
298 begin
299 -- We skip the check for thunks
301 if Is_Thunk (Subp) then
302 return;
303 end if;
305 Formal := First_Formal (Subp);
306 while Present (Formal) loop
307 Ctrl_Type := Check_Controlling_Type (Etype (Formal), Subp);
309 if Present (Ctrl_Type) then
311 -- Obtain the full type in case we are looking at an incomplete
312 -- view.
314 if Ekind (Ctrl_Type) = E_Incomplete_Type
315 and then Present (Full_View (Ctrl_Type))
316 then
317 Ctrl_Type := Full_View (Ctrl_Type);
318 end if;
320 -- When controlling type is concurrent and declared within a
321 -- generic or inside an instance use corresponding record type.
323 if Is_Concurrent_Type (Ctrl_Type)
324 and then Present (Corresponding_Record_Type (Ctrl_Type))
325 then
326 Ctrl_Type := Corresponding_Record_Type (Ctrl_Type);
327 end if;
329 if Ctrl_Type = Typ then
330 Set_Is_Controlling_Formal (Formal);
332 -- Ada 2005 (AI-231): Anonymous access types that are used in
333 -- controlling parameters exclude null because it is necessary
334 -- to read the tag to dispatch, and null has no tag.
336 if Ekind (Etype (Formal)) = E_Anonymous_Access_Type then
337 Set_Can_Never_Be_Null (Etype (Formal));
338 Set_Is_Known_Non_Null (Etype (Formal));
339 end if;
341 -- Check that the parameter's nominal subtype statically
342 -- matches the first subtype.
344 if Ekind (Etype (Formal)) = E_Anonymous_Access_Type then
345 if not Subtypes_Statically_Match
346 (Typ, Designated_Type (Etype (Formal)))
347 then
348 Error_Msg_N
349 ("parameter subtype does not match controlling type",
350 Formal);
351 end if;
353 -- Within a predicate function, the formal may be a subtype
354 -- of a tagged type, given that the predicate is expressed
355 -- in terms of the subtype.
357 elsif not Subtypes_Statically_Match (Typ, Etype (Formal))
358 and then not Is_Predicate_Function (Subp)
359 then
360 Error_Msg_N
361 ("parameter subtype does not match controlling type",
362 Formal);
363 end if;
365 if Present (Default_Value (Formal)) then
367 -- In Ada 2005, access parameters can have defaults
369 if Ekind (Etype (Formal)) = E_Anonymous_Access_Type
370 and then Ada_Version < Ada_2005
371 then
372 Error_Msg_N
373 ("default not allowed for controlling access parameter",
374 Default_Value (Formal));
376 elsif not Is_Tag_Indeterminate (Default_Value (Formal)) then
377 Error_Msg_N
378 ("default expression must be a tag indeterminate" &
379 " function call", Default_Value (Formal));
380 end if;
381 end if;
383 elsif Comes_From_Source (Subp) then
384 Error_Msg_N
385 ("operation can be dispatching in only one type", Subp);
386 end if;
387 end if;
389 Next_Formal (Formal);
390 end loop;
392 if Ekind (Subp) in E_Function | E_Generic_Function then
393 Ctrl_Type := Check_Controlling_Type (Etype (Subp), Subp);
395 if Present (Ctrl_Type) then
396 if Ctrl_Type = Typ then
397 Set_Has_Controlling_Result (Subp);
399 -- Check that result subtype statically matches first subtype
400 -- (Ada 2005): Subp may have a controlling access result.
402 if Subtypes_Statically_Match (Typ, Etype (Subp))
403 or else (Ekind (Etype (Subp)) = E_Anonymous_Access_Type
404 and then
405 Subtypes_Statically_Match
406 (Typ, Designated_Type (Etype (Subp))))
407 then
408 null;
410 else
411 Error_Msg_N
412 ("result subtype does not match controlling type", Subp);
413 end if;
415 elsif Comes_From_Source (Subp) then
416 Error_Msg_N
417 ("operation can be dispatching in only one type", Subp);
418 end if;
419 end if;
420 end if;
421 end Check_Controlling_Formals;
423 ----------------------------
424 -- Check_Controlling_Type --
425 ----------------------------
427 function Check_Controlling_Type
428 (T : Entity_Id;
429 Subp : Entity_Id) return Entity_Id
431 Tagged_Type : Entity_Id := Empty;
433 begin
434 if Is_Tagged_Type (T) then
435 if Is_First_Subtype (T) then
436 Tagged_Type := T;
437 else
438 Tagged_Type := Base_Type (T);
439 end if;
441 -- If the type is incomplete, it may have been declared without a
442 -- Tagged indication, but the full view may be tagged, in which case
443 -- that is the controlling type of the subprogram. This is one of the
444 -- approx. 579 places in the language where a lookahead would help.
446 elsif Ekind (T) = E_Incomplete_Type
447 and then Present (Full_View (T))
448 and then Is_Tagged_Type (Full_View (T))
449 then
450 Set_Is_Tagged_Type (T);
451 Tagged_Type := Full_View (T);
453 elsif Ekind (T) = E_Anonymous_Access_Type
454 and then Is_Tagged_Type (Designated_Type (T))
455 then
456 if Ekind (Designated_Type (T)) /= E_Incomplete_Type then
457 if Is_First_Subtype (Designated_Type (T)) then
458 Tagged_Type := Designated_Type (T);
459 else
460 Tagged_Type := Base_Type (Designated_Type (T));
461 end if;
463 -- Ada 2005: an incomplete type can be tagged. An operation with an
464 -- access parameter of the type is dispatching.
466 elsif Scope (Designated_Type (T)) = Current_Scope then
467 Tagged_Type := Designated_Type (T);
469 -- Ada 2005 (AI-50217)
471 elsif From_Limited_With (Designated_Type (T))
472 and then Has_Non_Limited_View (Designated_Type (T))
473 and then Scope (Designated_Type (T)) = Scope (Subp)
474 then
475 if Is_First_Subtype (Non_Limited_View (Designated_Type (T))) then
476 Tagged_Type := Non_Limited_View (Designated_Type (T));
477 else
478 Tagged_Type := Base_Type (Non_Limited_View
479 (Designated_Type (T)));
480 end if;
481 end if;
482 end if;
484 if No (Tagged_Type) or else Is_Class_Wide_Type (Tagged_Type) then
485 return Empty;
487 -- In the special case of a protected subprogram of a tagged protected
488 -- type that has a formal of a tagged type (or access formal whose type
489 -- designates a tagged type), such a formal is not controlling unless
490 -- it's of the protected type's corresponding record type. The latter
491 -- can occur for the special wrapper subprograms created for protected
492 -- subprograms. Such subprograms may occur in the same scope where some
493 -- formal's tagged type is declared, and we don't want formals of that
494 -- tagged type being marked as controlling, for one thing because they
495 -- aren't controlling from the language point of view, but also because
496 -- this can cause errors for access formals when conformance is checked
497 -- between the spec and body of the protected subprogram (null-exclusion
498 -- status of the formals may be set differently, which is the case that
499 -- led to adding this check).
501 elsif Is_Subprogram (Subp)
502 and then Present (Protected_Subprogram (Subp))
503 and then Ekind (Scope (Protected_Subprogram (Subp))) = E_Protected_Type
504 and then
505 Base_Type (Tagged_Type)
506 /= Corresponding_Record_Type (Scope (Protected_Subprogram (Subp)))
507 then
508 return Empty;
510 -- The dispatching type and the primitive operation must be defined in
511 -- the same scope, except in the case of abstract formal subprograms.
513 elsif (Scope (Subp) = Scope (Tagged_Type)
514 and then (not Is_Generic_Type (Tagged_Type)
515 or else not Comes_From_Source (Subp)))
516 or else
517 (Is_Formal_Subprogram (Subp) and then Is_Abstract_Subprogram (Subp))
518 or else
519 (Nkind (Parent (Parent (Subp))) = N_Subprogram_Renaming_Declaration
520 and then
521 Present (Corresponding_Formal_Spec (Parent (Parent (Subp))))
522 and then
523 Is_Abstract_Subprogram (Subp))
524 then
525 return Tagged_Type;
527 else
528 return Empty;
529 end if;
530 end Check_Controlling_Type;
532 ----------------------------
533 -- Check_Dispatching_Call --
534 ----------------------------
536 procedure Check_Dispatching_Call (N : Node_Id) is
537 Loc : constant Source_Ptr := Sloc (N);
538 Actual : Node_Id;
539 Formal : Entity_Id;
540 Control : Node_Id := Empty;
541 Func : Entity_Id;
542 Subp_Entity : Entity_Id;
544 Indeterm_Ctrl_Type : Entity_Id := Empty;
545 -- Type of a controlling formal whose actual is a tag-indeterminate call
546 -- whose result type is different from, but is an ancestor of, the type.
548 Static_Tag : Node_Id := Empty;
549 -- If a controlling formal has a statically tagged actual, the tag of
550 -- this actual is to be used for any tag-indeterminate actual.
552 procedure Check_Direct_Call;
553 -- In the case when the controlling actual is a class-wide type whose
554 -- root type's completion is a task or protected type, the call is in
555 -- fact direct. This routine detects the above case and modifies the
556 -- call accordingly.
558 procedure Check_Dispatching_Context (Call : Node_Id);
559 -- If the call is tag-indeterminate and the entity being called is
560 -- abstract, verify that the context is a call that will eventually
561 -- provide a tag for dispatching, or has provided one already.
563 -----------------------
564 -- Check_Direct_Call --
565 -----------------------
567 procedure Check_Direct_Call is
568 Typ : Entity_Id := Etype (Control);
569 begin
570 -- Predefined primitives do not receive wrappers since they are built
571 -- from scratch for the corresponding record of synchronized types.
572 -- Equality is in general predefined, but is excluded from the check
573 -- when it is user-defined.
575 if Is_Predefined_Dispatching_Operation (Subp_Entity)
576 and then not (Is_User_Defined_Equality (Subp_Entity)
577 and then Comes_From_Source (Subp_Entity)
578 and then Nkind (Parent (Subp_Entity)) =
579 N_Function_Specification)
580 then
581 return;
582 end if;
584 if Is_Class_Wide_Type (Typ) then
585 Typ := Root_Type (Typ);
586 end if;
588 if Is_Private_Type (Typ) and then Present (Full_View (Typ)) then
589 Typ := Full_View (Typ);
590 end if;
592 if Is_Concurrent_Type (Typ)
593 and then
594 Present (Corresponding_Record_Type (Typ))
595 then
596 Typ := Corresponding_Record_Type (Typ);
598 -- The concurrent record's list of primitives should contain a
599 -- wrapper for the entity of the call, retrieve it.
601 declare
602 Prim : Entity_Id;
603 Prim_Elmt : Elmt_Id;
604 Wrapper_Found : Boolean := False;
606 begin
607 Prim_Elmt := First_Elmt (Primitive_Operations (Typ));
608 while Present (Prim_Elmt) loop
609 Prim := Node (Prim_Elmt);
611 if Is_Primitive_Wrapper (Prim)
612 and then Wrapped_Entity (Prim) = Subp_Entity
613 then
614 Wrapper_Found := True;
615 exit;
616 end if;
618 Next_Elmt (Prim_Elmt);
619 end loop;
621 -- A primitive declared between two views should have a
622 -- corresponding wrapper.
624 pragma Assert (Wrapper_Found);
626 -- Modify the call by setting the proper entity
628 Set_Entity (Name (N), Prim);
629 end;
630 end if;
631 end Check_Direct_Call;
633 -------------------------------
634 -- Check_Dispatching_Context --
635 -------------------------------
637 procedure Check_Dispatching_Context (Call : Node_Id) is
638 Subp : constant Entity_Id := Entity (Name (Call));
640 procedure Abstract_Context_Error;
641 -- Error for abstract call dispatching on result is not dispatching
643 function Has_Controlling_Current_Instance_Actual_In_DIC
644 (Call : Node_Id) return Boolean;
645 -- Return True if the subprogram call Call has a controlling actual
646 -- given directly by a current instance referenced within a DIC
647 -- aspect.
649 ----------------------------
650 -- Abstract_Context_Error --
651 ----------------------------
653 procedure Abstract_Context_Error is
654 begin
655 if Ekind (Subp) = E_Function then
656 Error_Msg_N
657 ("call to abstract function must be dispatching", N);
659 -- This error can occur for a procedure in the case of a call to
660 -- an abstract formal procedure with a statically tagged operand.
662 else
663 Error_Msg_N
664 ("call to abstract procedure must be dispatching", N);
665 end if;
666 end Abstract_Context_Error;
668 ----------------------------------------
669 -- Has_Current_Instance_Actual_In_DIC --
670 ----------------------------------------
672 function Has_Controlling_Current_Instance_Actual_In_DIC
673 (Call : Node_Id) return Boolean
675 A : Node_Id;
676 F : Entity_Id;
677 begin
678 F := First_Formal (Subp_Entity);
679 A := First_Actual (Call);
681 while Present (F) loop
683 -- Return True if the actual denotes a current instance (which
684 -- will be represented by an in-mode formal of the enclosing
685 -- DIC_Procedure) passed to a controlling formal. We don't have
686 -- to worry about controlling access formals here, because its
687 -- illegal to apply Access (etc.) attributes to a current
688 -- instance within an aspect (by AI12-0068).
690 if Is_Controlling_Formal (F)
691 and then Nkind (A) = N_Identifier
692 and then Ekind (Entity (A)) = E_In_Parameter
693 and then Is_Subprogram (Scope (Entity (A)))
694 and then Is_DIC_Procedure (Scope (Entity (A)))
695 then
696 return True;
697 end if;
699 Next_Formal (F);
700 Next_Actual (A);
701 end loop;
703 return False;
704 end Has_Controlling_Current_Instance_Actual_In_DIC;
706 -- Local variables
708 Scop : constant Entity_Id := Current_Scope_No_Loops;
709 Typ : constant Entity_Id := Etype (Subp);
710 Par : Node_Id;
712 -- Start of processing for Check_Dispatching_Context
714 begin
715 -- Skip checking context of dispatching calls during preanalysis of
716 -- class-wide conditions since at that stage the expression is not
717 -- installed yet on its definite context.
719 if Inside_Class_Condition_Preanalysis then
720 return;
721 end if;
723 -- If the called subprogram is a private overriding, replace it
724 -- with its alias, which has the correct body. Verify that the
725 -- two subprograms have the same controlling type (this is not the
726 -- case for an inherited subprogram that has become abstract).
728 if Is_Abstract_Subprogram (Subp)
729 and then No (Controlling_Argument (Call))
730 then
731 if Present (Alias (Subp))
732 and then not Is_Abstract_Subprogram (Alias (Subp))
733 and then No (DTC_Entity (Subp))
734 and then Find_Dispatching_Type (Subp) =
735 Find_Dispatching_Type (Alias (Subp))
736 then
737 -- Private overriding of inherited abstract operation, call is
738 -- legal.
740 Set_Entity (Name (N), Alias (Subp));
741 return;
743 -- If this is a pre/postcondition for an abstract subprogram,
744 -- it may call another abstract function that is a primitive
745 -- of an abstract type. The call is nondispatching but will be
746 -- legal in overridings of the operation. However, if the call
747 -- is tag-indeterminate we want to continue with with the error
748 -- checking below, as this case is illegal even for abstract
749 -- subprograms (see AI12-0170).
751 -- Similarly, as per AI12-0412, a nonabstract subprogram may
752 -- have a class-wide pre/postcondition that includes a call to
753 -- an abstract primitive of the subprogram's controlling type.
754 -- Certain operations (nondispatching calls, 'Access, use as
755 -- a generic actual) applied to such a nonabstract subprogram
756 -- are illegal in the case where the type is abstract (see
757 -- RM 6.1.1(18.2/5)).
759 elsif Is_Subprogram (Scop)
760 and then not Is_Tag_Indeterminate (N)
761 and then
762 -- The context is an internally built helper or an indirect
763 -- call wrapper that handles class-wide preconditions
764 (Present (Class_Preconditions_Subprogram (Scop))
766 -- ... or the context is a class-wide pre/postcondition.
767 or else
768 (In_Pre_Post_Condition (Call, Class_Wide_Only => True)
770 -- The tagged type associated with the called
771 -- subprogram must be the same as that of the
772 -- subprogram with a class-wide aspect.
774 and then Is_Dispatching_Operation (Scop)
775 and then Find_Dispatching_Type (Subp)
776 = Find_Dispatching_Type (Scop)))
777 then
778 null;
780 -- Similarly to the dispensation for postconditions, a call to
781 -- an abstract function within a Default_Initial_Condition aspect
782 -- can be legal when passed a current instance of the type. Such
783 -- a call will be effectively mapped to a call to a primitive of
784 -- a descendant type (see AI12-0397, as well as AI12-0170), so
785 -- doesn't need to be dispatching. We test for being within a DIC
786 -- procedure, since that's where the call will be analyzed.
788 elsif Is_Subprogram (Scop)
789 and then Is_DIC_Procedure (Scop)
790 and then Has_Controlling_Current_Instance_Actual_In_DIC (Call)
791 then
792 null;
794 elsif Ekind (Current_Scope) = E_Function
795 and then Nkind (Unit_Declaration_Node (Scop)) =
796 N_Generic_Subprogram_Declaration
797 then
798 null;
800 else
801 -- We need to determine whether the context of the call
802 -- provides a tag to make the call dispatching. This requires
803 -- the call to be the actual in an enclosing call, and that
804 -- actual must be controlling. If the call is an operand of
805 -- equality, the other operand must not be abstract.
807 if not Is_Tagged_Type (Typ)
808 and then not
809 (Ekind (Typ) = E_Anonymous_Access_Type
810 and then Is_Tagged_Type (Designated_Type (Typ)))
811 then
812 Abstract_Context_Error;
813 return;
814 end if;
816 Par := Parent (Call);
818 if Nkind (Par) = N_Parameter_Association then
819 Par := Parent (Par);
820 end if;
822 if Nkind (Par) = N_Qualified_Expression
823 or else Nkind (Par) = N_Unchecked_Type_Conversion
824 then
825 Par := Parent (Par);
826 end if;
828 if Nkind (Par) in N_Subprogram_Call
829 and then Is_Entity_Name (Name (Par))
830 then
831 declare
832 Enc_Subp : constant Entity_Id := Entity (Name (Par));
833 A : Node_Id;
834 F : Entity_Id;
835 Control : Entity_Id;
836 Ret_Type : Entity_Id;
838 begin
839 -- Find controlling formal that can provide tag for the
840 -- tag-indeterminate actual. The corresponding actual
841 -- must be the corresponding class-wide type.
843 F := First_Formal (Enc_Subp);
844 A := First_Actual (Par);
846 -- Find controlling type of call. Dereference if function
847 -- returns an access type.
849 Ret_Type := Etype (Call);
850 if Is_Access_Type (Etype (Call)) then
851 Ret_Type := Designated_Type (Ret_Type);
852 end if;
854 while Present (F) loop
855 Control := Etype (A);
857 if Is_Access_Type (Control) then
858 Control := Designated_Type (Control);
859 end if;
861 if Is_Controlling_Formal (F)
862 and then not (Call = A or else Parent (Call) = A)
863 and then Control = Class_Wide_Type (Ret_Type)
864 then
865 return;
866 end if;
868 Next_Formal (F);
869 Next_Actual (A);
870 end loop;
872 if Nkind (Par) = N_Function_Call
873 and then Is_Tag_Indeterminate (Par)
874 then
875 -- The parent may be an actual of an enclosing call
877 Check_Dispatching_Context (Par);
878 return;
880 else
881 Error_Msg_N
882 ("call to abstract function must be dispatching",
883 Call);
884 return;
885 end if;
886 end;
888 -- For equality operators, one of the operands must be
889 -- statically or dynamically tagged.
891 elsif Nkind (Par) in N_Op_Eq | N_Op_Ne then
892 if N = Right_Opnd (Par)
893 and then Is_Tag_Indeterminate (Left_Opnd (Par))
894 then
895 Abstract_Context_Error;
897 elsif N = Left_Opnd (Par)
898 and then Is_Tag_Indeterminate (Right_Opnd (Par))
899 then
900 Abstract_Context_Error;
901 end if;
903 return;
905 -- The left-hand side of an assignment provides the tag
907 elsif Nkind (Par) = N_Assignment_Statement then
908 return;
910 else
911 Abstract_Context_Error;
912 end if;
913 end if;
914 end if;
915 end Check_Dispatching_Context;
917 -- Start of processing for Check_Dispatching_Call
919 begin
920 -- Find a controlling argument, if any
922 if Present (Parameter_Associations (N)) then
923 Subp_Entity := Entity (Name (N));
925 Actual := First_Actual (N);
926 Formal := First_Formal (Subp_Entity);
927 while Present (Actual) loop
928 Control := Find_Controlling_Arg (Actual);
929 exit when Present (Control);
931 -- Check for the case where the actual is a tag-indeterminate call
932 -- whose result type is different than the tagged type associated
933 -- with the containing call, but is an ancestor of the type.
935 if Is_Controlling_Formal (Formal)
936 and then Is_Tag_Indeterminate (Actual)
937 and then Base_Type (Etype (Actual)) /= Base_Type (Etype (Formal))
938 and then Is_Ancestor (Etype (Actual), Etype (Formal))
939 then
940 Indeterm_Ctrl_Type := Etype (Formal);
942 -- If the formal is controlling but the actual is not, the type
943 -- of the actual is statically known, and may be used as the
944 -- controlling tag for some other tag-indeterminate actual.
946 elsif Is_Controlling_Formal (Formal)
947 and then Is_Entity_Name (Actual)
948 and then Is_Tagged_Type (Etype (Actual))
949 then
950 Static_Tag := Etype (Actual);
951 end if;
953 Next_Actual (Actual);
954 Next_Formal (Formal);
955 end loop;
957 if Present (Control) then
959 -- Verify that no controlling arguments are statically tagged
961 if Debug_Flag_E then
962 Write_Str ("Found Dispatching call");
963 Write_Int (Int (N));
964 Write_Eol;
965 end if;
967 Actual := First_Actual (N);
968 while Present (Actual) loop
969 if Actual /= Control then
971 if not Is_Controlling_Actual (Actual) then
972 null; -- Can be anything
974 elsif Is_Dynamically_Tagged (Actual) then
975 null; -- Valid parameter
977 elsif Is_Tag_Indeterminate (Actual) then
979 -- The tag is inherited from the enclosing call (the node
980 -- we are currently analyzing). Explicitly expand the
981 -- actual, since the previous call to Expand (from
982 -- Resolve_Call) had no way of knowing about the
983 -- required dispatching.
985 Propagate_Tag (Control, Actual);
987 else
988 Error_Msg_N
989 ("controlling argument is not dynamically tagged",
990 Actual);
991 return;
992 end if;
993 end if;
995 Next_Actual (Actual);
996 end loop;
998 -- Mark call as a dispatching call
1000 Set_Controlling_Argument (N, Control);
1001 Check_Restriction (No_Dispatching_Calls, N);
1003 -- The dispatching call may need to be converted into a direct
1004 -- call in certain cases.
1006 Check_Direct_Call;
1008 -- If the call doesn't have a controlling actual but does have an
1009 -- indeterminate actual that requires dispatching treatment, then an
1010 -- object is needed that will serve as the controlling argument for
1011 -- a dispatching call on the indeterminate actual. This can occur
1012 -- in the unusual situation of a default actual given by a tag-
1013 -- indeterminate call and where the type of the call is an ancestor
1014 -- of the type associated with a containing call to an inherited
1015 -- operation (see AI-239).
1017 -- Rather than create an object of the tagged type, which would
1018 -- be problematic for various reasons (default initialization,
1019 -- discriminants), the tag of the containing call's associated
1020 -- tagged type is directly used to control the dispatching.
1022 elsif Present (Indeterm_Ctrl_Type) then
1023 if Present (Static_Tag) then
1024 Control :=
1025 Make_Attribute_Reference (Loc,
1026 Prefix =>
1027 New_Occurrence_Of (Static_Tag, Loc),
1028 Attribute_Name => Name_Tag);
1030 else
1031 Control :=
1032 Make_Attribute_Reference (Loc,
1033 Prefix =>
1034 New_Occurrence_Of (Indeterm_Ctrl_Type, Loc),
1035 Attribute_Name => Name_Tag);
1036 end if;
1038 Analyze (Control);
1040 Actual := First_Actual (N);
1041 Formal := First_Formal (Subp_Entity);
1042 while Present (Actual) loop
1043 if Is_Tag_Indeterminate (Actual)
1044 and then Is_Controlling_Formal (Formal)
1045 then
1046 Propagate_Tag (Control, Actual);
1047 end if;
1049 Next_Actual (Actual);
1050 Next_Formal (Formal);
1051 end loop;
1053 Check_Dispatching_Context (N);
1055 elsif Nkind (N) /= N_Function_Call then
1057 -- The call is not dispatching, so check that there aren't any
1058 -- tag-indeterminate abstract calls left among its actuals.
1060 Actual := First_Actual (N);
1061 while Present (Actual) loop
1062 if Is_Tag_Indeterminate (Actual) then
1064 -- Function call case
1066 if Nkind (Original_Node (Actual)) = N_Function_Call then
1067 Func := Entity (Name (Original_Node (Actual)));
1069 -- If the actual is an attribute then it can't be abstract
1070 -- (the only current case of a tag-indeterminate attribute
1071 -- is the stream Input attribute).
1073 elsif Nkind (Original_Node (Actual)) = N_Attribute_Reference
1074 then
1075 Func := Empty;
1077 -- Ditto if it is an explicit dereference
1079 elsif Nkind (Original_Node (Actual)) = N_Explicit_Dereference
1080 then
1081 Func := Empty;
1083 -- Only other possibility is a qualified expression whose
1084 -- constituent expression is itself a call.
1086 else
1087 Func :=
1088 Entity (Name (Original_Node
1089 (Expression (Original_Node (Actual)))));
1090 end if;
1092 if Present (Func) and then Is_Abstract_Subprogram (Func) then
1093 Error_Msg_N
1094 ("call to abstract function must be dispatching",
1095 Actual);
1096 end if;
1097 end if;
1099 Next_Actual (Actual);
1100 end loop;
1102 Check_Dispatching_Context (N);
1104 elsif Nkind (Parent (N)) in N_Subexpr then
1105 Check_Dispatching_Context (N);
1107 elsif Nkind (Parent (N)) = N_Assignment_Statement
1108 and then Is_Class_Wide_Type (Etype (Name (Parent (N))))
1109 then
1110 return;
1112 elsif Is_Abstract_Subprogram (Subp_Entity) then
1113 Check_Dispatching_Context (N);
1114 return;
1115 end if;
1117 -- If this is a nondispatching call to a nonabstract subprogram
1118 -- and the subprogram has any Pre'Class or Post'Class aspects with
1119 -- nonstatic values, then report an error. This is specified by
1120 -- RM 6.1.1(18.2/5) (by AI12-0412).
1122 -- Skip reporting this error on helpers and indirect-call wrappers
1123 -- built to support class-wide preconditions.
1125 if No (Control)
1126 and then not Is_Abstract_Subprogram (Subp_Entity)
1127 and then
1128 Is_Prim_Of_Abst_Type_With_Nonstatic_CW_Pre_Post (Subp_Entity)
1129 and then not
1130 (Is_Subprogram (Current_Scope)
1131 and then
1132 Present (Class_Preconditions_Subprogram (Current_Scope)))
1133 then
1134 Error_Msg_N
1135 ("nondispatching call to nonabstract subprogram of "
1136 & "abstract type with nonstatic class-wide "
1137 & "pre/postconditions",
1139 end if;
1141 else
1142 -- If dispatching on result, the enclosing call, if any, will
1143 -- determine the controlling argument. Otherwise this is the
1144 -- primitive operation of the root type.
1146 Check_Dispatching_Context (N);
1147 end if;
1148 end Check_Dispatching_Call;
1150 ---------------------------------
1151 -- Check_Dispatching_Operation --
1152 ---------------------------------
1154 procedure Check_Dispatching_Operation (Subp, Old_Subp : Entity_Id) is
1155 function Is_Access_To_Subprogram_Wrapper (E : Entity_Id) return Boolean;
1156 -- Return True if E is an access to subprogram wrapper
1158 procedure Warn_On_Late_Primitive_After_Private_Extension
1159 (Typ : Entity_Id;
1160 Prim : Entity_Id);
1161 -- Prim is a dispatching primitive of the tagged type Typ. Warn on Prim
1162 -- if it is a public primitive defined after some private extension of
1163 -- the tagged type.
1165 -------------------------------------
1166 -- Is_Access_To_Subprogram_Wrapper --
1167 -------------------------------------
1169 function Is_Access_To_Subprogram_Wrapper (E : Entity_Id) return Boolean
1171 Decl_N : constant Node_Id := Unit_Declaration_Node (E);
1172 Par_N : constant Node_Id := Parent (List_Containing (Decl_N));
1174 begin
1175 -- Access to subprogram wrappers are declared in the freezing actions
1177 return Nkind (Par_N) = N_Freeze_Entity
1178 and then Ekind (Entity (Par_N)) = E_Access_Subprogram_Type;
1179 end Is_Access_To_Subprogram_Wrapper;
1181 ----------------------------------------------------
1182 -- Warn_On_Late_Primitive_After_Private_Extension --
1183 ----------------------------------------------------
1185 procedure Warn_On_Late_Primitive_After_Private_Extension
1186 (Typ : Entity_Id;
1187 Prim : Entity_Id)
1189 E : Entity_Id;
1191 begin
1192 if Warn_On_Late_Primitives
1193 and then Comes_From_Source (Prim)
1194 and then Has_Private_Extension (Typ)
1195 and then Is_Package_Or_Generic_Package (Current_Scope)
1196 and then not In_Private_Part (Current_Scope)
1197 then
1198 E := Next_Entity (Typ);
1200 while E /= Prim loop
1201 if Ekind (E) = E_Record_Type_With_Private
1202 and then Etype (E) = Typ
1203 then
1204 Error_Msg_Name_1 := Chars (Typ);
1205 Error_Msg_Name_2 := Chars (E);
1206 Error_Msg_Sloc := Sloc (E);
1207 Error_Msg_N
1208 ("?.j?primitive of type % defined after private extension "
1209 & "% #?", Prim);
1210 Error_Msg_Name_1 := Chars (Prim);
1211 Error_Msg_Name_2 := Chars (E);
1212 Error_Msg_N
1213 ("\spec of % should appear before declaration of type %!",
1214 Prim);
1215 exit;
1216 end if;
1218 Next_Entity (E);
1219 end loop;
1220 end if;
1221 end Warn_On_Late_Primitive_After_Private_Extension;
1223 -- Local variables
1225 Body_Is_Last_Primitive : Boolean := False;
1226 Has_Dispatching_Parent : Boolean := False;
1227 Ovr_Subp : Entity_Id := Empty;
1228 Tagged_Type : Entity_Id;
1230 -- Start of processing for Check_Dispatching_Operation
1232 begin
1233 if Ekind (Subp) not in E_Function | E_Procedure then
1234 return;
1236 -- The Default_Initial_Condition procedure is not a primitive subprogram
1237 -- even if it relates to a tagged type. This routine is not meant to be
1238 -- inherited or overridden.
1240 elsif Is_DIC_Procedure (Subp) then
1241 return;
1243 -- The "partial" and "full" type invariant procedures are not primitive
1244 -- subprograms even if they relate to a tagged type. These routines are
1245 -- not meant to be inherited or overridden.
1247 elsif Is_Invariant_Procedure (Subp)
1248 or else Is_Partial_Invariant_Procedure (Subp)
1249 then
1250 return;
1252 -- Wrappers of access to subprograms are not primitive subprograms.
1254 elsif Is_Wrapper (Subp)
1255 and then Is_Access_To_Subprogram_Wrapper (Subp)
1256 then
1257 return;
1258 end if;
1260 Set_Is_Dispatching_Operation (Subp, False);
1261 Tagged_Type := Find_Dispatching_Type (Subp);
1263 -- Ada 2005 (AI-345): Use the corresponding record (if available).
1264 -- Required because primitives of concurrent types are attached
1265 -- to the corresponding record (not to the concurrent type).
1267 if Ada_Version >= Ada_2005
1268 and then Present (Tagged_Type)
1269 and then Is_Concurrent_Type (Tagged_Type)
1270 and then Present (Corresponding_Record_Type (Tagged_Type))
1271 then
1272 Tagged_Type := Corresponding_Record_Type (Tagged_Type);
1273 end if;
1275 -- (AI-345): The task body procedure is not a primitive of the tagged
1276 -- type
1278 if Present (Tagged_Type)
1279 and then Is_Concurrent_Record_Type (Tagged_Type)
1280 and then Present (Corresponding_Concurrent_Type (Tagged_Type))
1281 and then Is_Task_Type (Corresponding_Concurrent_Type (Tagged_Type))
1282 and then Subp = Get_Task_Body_Procedure
1283 (Corresponding_Concurrent_Type (Tagged_Type))
1284 then
1285 return;
1286 end if;
1288 -- If Subp is derived from a dispatching operation then it should
1289 -- always be treated as dispatching. In this case various checks
1290 -- below will be bypassed. Makes sure that late declarations for
1291 -- inherited private subprograms are treated as dispatching, even
1292 -- if the associated tagged type is already frozen.
1294 Has_Dispatching_Parent :=
1295 Present (Alias (Subp))
1296 and then Is_Dispatching_Operation (Alias (Subp));
1298 if No (Tagged_Type) then
1300 -- Ada 2005 (AI-251): Check that Subp is not a primitive associated
1301 -- with an abstract interface type unless the interface acts as a
1302 -- parent type in a derivation. If the interface type is a formal
1303 -- type then the operation is not primitive and therefore legal.
1305 declare
1306 E : Entity_Id;
1307 Typ : Entity_Id;
1309 begin
1310 E := First_Entity (Subp);
1311 while Present (E) loop
1313 -- For an access parameter, check designated type
1315 if Ekind (Etype (E)) = E_Anonymous_Access_Type then
1316 Typ := Designated_Type (Etype (E));
1317 else
1318 Typ := Etype (E);
1319 end if;
1321 if Comes_From_Source (Subp)
1322 and then Is_Interface (Typ)
1323 and then not Is_Class_Wide_Type (Typ)
1324 and then not Is_Derived_Type (Typ)
1325 and then not Is_Generic_Type (Typ)
1326 and then not In_Instance
1327 then
1328 Error_Msg_N ("??declaration of& is too late!", Subp);
1329 Error_Msg_NE -- CODEFIX??
1330 ("\??spec should appear immediately after declaration of "
1331 & "& !", Subp, Typ);
1332 exit;
1333 end if;
1335 Next_Entity (E);
1336 end loop;
1338 -- In case of functions check also the result type
1340 if Ekind (Subp) = E_Function then
1341 if Is_Access_Type (Etype (Subp)) then
1342 Typ := Designated_Type (Etype (Subp));
1343 else
1344 Typ := Etype (Subp);
1345 end if;
1347 -- The following should be better commented, especially since
1348 -- we just added several new conditions here ???
1350 if Comes_From_Source (Subp)
1351 and then Is_Interface (Typ)
1352 and then not Is_Class_Wide_Type (Typ)
1353 and then not Is_Derived_Type (Typ)
1354 and then not Is_Generic_Type (Typ)
1355 and then not In_Instance
1356 then
1357 Error_Msg_N ("??declaration of& is too late!", Subp);
1358 Error_Msg_NE
1359 ("\??spec should appear immediately after declaration of "
1360 & "& !", Subp, Typ);
1361 end if;
1362 end if;
1363 end;
1365 return;
1367 -- The subprograms build internally after the freezing point (such as
1368 -- init procs, interface thunks, type support subprograms, and Offset
1369 -- to top functions for accessing interface components in variable
1370 -- size tagged types) are not primitives.
1372 elsif Is_Frozen (Tagged_Type)
1373 and then not Comes_From_Source (Subp)
1374 and then not Has_Dispatching_Parent
1375 then
1376 -- Complete decoration of internally built subprograms that override
1377 -- a dispatching primitive. These entities correspond with the
1378 -- following cases:
1380 -- 1. Ada 2005 (AI-391): Wrapper functions built by the expander
1381 -- to override functions of nonabstract null extensions. These
1382 -- primitives were added to the list of primitives of the tagged
1383 -- type by Make_Controlling_Function_Wrappers. However, attribute
1384 -- Is_Dispatching_Operation must be set to true.
1386 -- 2. Ada 2005 (AI-251): Wrapper procedures of null interface
1387 -- primitives.
1389 -- 3. Subprograms associated with stream attributes (built by
1390 -- New_Stream_Subprogram) or with the Put_Image attribute.
1392 -- 4. Wrappers built for inherited operations with inherited class-
1393 -- wide conditions, where the conditions include calls to other
1394 -- overridden primitives. The wrappers include checks on these
1395 -- modified conditions. (AI12-195).
1397 -- 5. Declarations built for subprograms without separate specs that
1398 -- are eligible for inlining in GNATprove (inside
1399 -- Sem_Ch6.Analyze_Subprogram_Body_Helper).
1401 if Present (Old_Subp)
1402 and then Present (Overridden_Operation (Subp))
1403 and then Is_Dispatching_Operation (Old_Subp)
1404 then
1405 pragma Assert
1406 ((Ekind (Subp) = E_Function
1407 and then Is_Dispatching_Operation (Old_Subp)
1408 and then Is_Null_Extension (Base_Type (Etype (Subp))))
1410 or else
1411 (Ekind (Subp) = E_Procedure
1412 and then Is_Dispatching_Operation (Old_Subp)
1413 and then Present (Alias (Old_Subp))
1414 and then Is_Null_Interface_Primitive
1415 (Ultimate_Alias (Old_Subp)))
1417 or else Get_TSS_Name (Subp) in TSS_Stream_Read
1418 | TSS_Stream_Write
1419 | TSS_Put_Image
1421 or else
1422 (Is_Wrapper (Subp)
1423 and then Present (LSP_Subprogram (Subp)))
1425 or else GNATprove_Mode);
1427 Check_Controlling_Formals (Tagged_Type, Subp);
1428 Override_Dispatching_Operation (Tagged_Type, Old_Subp, Subp);
1429 Set_Is_Dispatching_Operation (Subp);
1430 end if;
1432 return;
1434 -- The operation may be a child unit, whose scope is the defining
1435 -- package, but which is not a primitive operation of the type.
1437 elsif Is_Child_Unit (Subp) then
1438 return;
1440 -- If the subprogram is not defined in a package spec, the only case
1441 -- where it can be a dispatching op is when it overrides an operation
1442 -- before the freezing point of the type.
1444 elsif (not Is_Package_Or_Generic_Package (Scope (Subp))
1445 or else In_Package_Body (Scope (Subp)))
1446 and then not Has_Dispatching_Parent
1447 then
1448 if not Comes_From_Source (Subp)
1449 or else (Present (Old_Subp) and then not Is_Frozen (Tagged_Type))
1450 then
1451 null;
1453 -- If the type is already frozen, the overriding is not allowed
1454 -- except when Old_Subp is not a dispatching operation (which can
1455 -- occur when Old_Subp was inherited by an untagged type). However,
1456 -- a body with no previous spec freezes the type *after* its
1457 -- declaration, and therefore is a legal overriding (unless the type
1458 -- has already been frozen). Only the first such body is legal.
1460 elsif Present (Old_Subp)
1461 and then Is_Dispatching_Operation (Old_Subp)
1462 then
1463 if Comes_From_Source (Subp)
1464 and then
1465 (Nkind (Unit_Declaration_Node (Subp)) = N_Subprogram_Body
1466 or else Nkind (Unit_Declaration_Node (Subp)) in N_Body_Stub)
1467 then
1468 declare
1469 Subp_Body : constant Node_Id := Unit_Declaration_Node (Subp);
1470 Decl_Item : Node_Id;
1472 begin
1473 -- ??? The checks here for whether the type has been frozen
1474 -- prior to the new body are not complete. It's not simple
1475 -- to check frozenness at this point since the body has
1476 -- already caused the type to be prematurely frozen in
1477 -- Analyze_Declarations, but we're forced to recheck this
1478 -- here because of the odd rule interpretation that allows
1479 -- the overriding if the type wasn't frozen prior to the
1480 -- body. The freezing action should probably be delayed
1481 -- until after the spec is seen, but that's a tricky
1482 -- change to the delicate freezing code.
1484 -- Look at each declaration following the type up until the
1485 -- new subprogram body. If any of the declarations is a body
1486 -- then the type has been frozen already so the overriding
1487 -- primitive is illegal.
1489 Decl_Item := Next (Parent (Tagged_Type));
1490 while Present (Decl_Item)
1491 and then Decl_Item /= Subp_Body
1492 loop
1493 if Comes_From_Source (Decl_Item)
1494 and then (Nkind (Decl_Item) in N_Proper_Body
1495 or else Nkind (Decl_Item) in N_Body_Stub)
1496 then
1497 Error_Msg_N ("overriding of& is too late!", Subp);
1498 Error_Msg_N
1499 ("\spec should appear immediately after the type!",
1500 Subp);
1501 exit;
1502 end if;
1504 Next (Decl_Item);
1505 end loop;
1507 -- If the subprogram doesn't follow in the list of
1508 -- declarations including the type then the type has
1509 -- definitely been frozen already and the body is illegal.
1511 if No (Decl_Item) then
1512 Error_Msg_N ("overriding of& is too late!", Subp);
1513 Error_Msg_N
1514 ("\spec should appear immediately after the type!",
1515 Subp);
1517 else
1519 -- The subprogram body declares a primitive operation.
1520 -- We must update its dispatching information here. The
1521 -- information is taken from the overridden subprogram.
1522 -- We must also generate a cross-reference entry because
1523 -- references to other primitives were already created
1524 -- when type was frozen.
1526 Body_Is_Last_Primitive := True;
1528 if Present (DTC_Entity (Old_Subp)) then
1529 Set_DTC_Entity (Subp, DTC_Entity (Old_Subp));
1530 Set_DT_Position_Value (Subp, DT_Position (Old_Subp));
1532 if not Restriction_Active (No_Dispatching_Calls) then
1533 if Building_Static_DT (Tagged_Type) then
1535 -- If the static dispatch table has not been
1536 -- built then there is nothing else to do now;
1537 -- otherwise we notify that we cannot build the
1538 -- static dispatch table.
1540 if Has_Dispatch_Table (Tagged_Type) then
1541 Error_Msg_N
1542 ("overriding of& is too late for building "
1543 & " static dispatch tables!", Subp);
1544 Error_Msg_N
1545 ("\spec should appear immediately after "
1546 & "the type!", Subp);
1547 end if;
1549 -- No code required to register primitives in VM
1550 -- targets
1552 elsif not Tagged_Type_Expansion then
1553 null;
1555 else
1556 Insert_Actions_After (Subp_Body,
1557 Register_Primitive (Sloc (Subp_Body),
1558 Prim => Subp));
1559 end if;
1561 -- Indicate that this is an overriding operation,
1562 -- and replace the overridden entry in the list of
1563 -- primitive operations, which is used for xref
1564 -- generation subsequently.
1566 Generate_Reference (Tagged_Type, Subp, 'P', False);
1567 Override_Dispatching_Operation
1568 (Tagged_Type, Old_Subp, Subp);
1569 Set_Is_Dispatching_Operation (Subp);
1571 -- Inherit decoration of controlling formals and
1572 -- controlling result.
1574 if Ekind (Old_Subp) = E_Function
1575 and then Has_Controlling_Result (Old_Subp)
1576 then
1577 Set_Has_Controlling_Result (Subp);
1578 end if;
1580 if Present (First_Formal (Old_Subp)) then
1581 declare
1582 Old_Formal : Entity_Id;
1583 Formal : Entity_Id;
1585 begin
1586 Formal := First_Formal (Subp);
1587 Old_Formal := First_Formal (Old_Subp);
1589 while Present (Old_Formal) loop
1590 Set_Is_Controlling_Formal (Formal,
1591 Is_Controlling_Formal (Old_Formal));
1593 Next_Formal (Formal);
1594 Next_Formal (Old_Formal);
1595 end loop;
1596 end;
1597 end if;
1598 end if;
1600 Check_Inherited_Conditions (Tagged_Type,
1601 Late_Overriding => True);
1602 end if;
1603 end if;
1604 end;
1606 else
1607 Error_Msg_N ("overriding of& is too late!", Subp);
1608 Error_Msg_N
1609 ("\subprogram spec should appear immediately after the type!",
1610 Subp);
1611 end if;
1613 -- If the type is not frozen yet and we are not in the overriding
1614 -- case it looks suspiciously like an attempt to define a primitive
1615 -- operation, which requires the declaration to be in a package spec
1616 -- (3.2.3(6)). Only report cases where the type and subprogram are
1617 -- in the same declaration list (by checking the enclosing parent
1618 -- declarations), to avoid spurious warnings on subprograms in
1619 -- instance bodies when the type is declared in the instance spec
1620 -- but hasn't been frozen by the instance body.
1622 elsif not Is_Frozen (Tagged_Type)
1623 and then In_Same_List (Parent (Tagged_Type), Parent (Parent (Subp)))
1624 then
1625 Error_Msg_N
1626 ("??not dispatching (must be defined in a package spec)", Subp);
1627 return;
1629 -- When the type is frozen, it is legitimate to define a new
1630 -- non-primitive operation.
1632 else
1633 return;
1634 end if;
1636 -- Now, we are sure that the scope is a package spec. If the subprogram
1637 -- is declared after the freezing point of the type that's an error
1639 elsif Is_Frozen (Tagged_Type) and then not Has_Dispatching_Parent then
1640 Error_Msg_N ("this primitive operation is declared too late", Subp);
1641 Error_Msg_NE
1642 ("??no primitive operations for& after this line",
1643 Freeze_Node (Tagged_Type),
1644 Tagged_Type);
1645 return;
1646 end if;
1648 Check_Controlling_Formals (Tagged_Type, Subp);
1650 Ovr_Subp := Old_Subp;
1652 -- [Ada 2012:AI-0125]: Search for inherited hidden primitive that may be
1653 -- overridden by Subp. This only applies to source subprograms, and
1654 -- their declaration must carry an explicit overriding indicator.
1656 if No (Ovr_Subp)
1657 and then Ada_Version >= Ada_2012
1658 and then Comes_From_Source (Subp)
1659 and then
1660 Nkind (Unit_Declaration_Node (Subp)) = N_Subprogram_Declaration
1661 then
1662 Ovr_Subp := Find_Hidden_Overridden_Primitive (Subp);
1664 -- Verify that the proper overriding indicator has been supplied.
1666 if Present (Ovr_Subp)
1667 and then
1668 not Must_Override (Specification (Unit_Declaration_Node (Subp)))
1669 then
1670 Error_Msg_NE ("missing overriding indicator for&", Subp, Subp);
1671 end if;
1672 end if;
1674 -- Now it should be a correct primitive operation, put it in the list
1676 if Present (Ovr_Subp) then
1678 -- If the type has interfaces we complete this check after we set
1679 -- attribute Is_Dispatching_Operation.
1681 Check_Subtype_Conformant (Subp, Ovr_Subp);
1683 -- A primitive operation with the name of a primitive controlled
1684 -- operation does not override a non-visible overriding controlled
1685 -- operation, i.e. one declared in a private part when the full
1686 -- view of a type is controlled. Conversely, it will override a
1687 -- visible operation that may be declared in a partial view when
1688 -- the full view is controlled.
1690 if Chars (Subp) in Name_Initialize | Name_Adjust | Name_Finalize
1691 and then Is_Controlled (Tagged_Type)
1692 and then not Is_Visibly_Controlled (Tagged_Type)
1693 and then not Is_Inherited_Public_Operation (Ovr_Subp)
1694 then
1695 Set_Overridden_Operation (Subp, Empty);
1697 -- If the subprogram specification carries an overriding
1698 -- indicator, no need for the warning: it is either redundant,
1699 -- or else an error will be reported.
1701 if Nkind (Parent (Subp)) = N_Procedure_Specification
1702 and then
1703 (Must_Override (Parent (Subp))
1704 or else Must_Not_Override (Parent (Subp)))
1705 then
1706 null;
1708 -- Here we need the warning
1710 else
1711 Error_Msg_NE
1712 ("operation does not override inherited&??", Subp, Subp);
1713 end if;
1715 else
1716 Override_Dispatching_Operation (Tagged_Type, Ovr_Subp, Subp);
1718 -- Ada 2005 (AI-251): In case of late overriding of a primitive
1719 -- that covers abstract interface subprograms we must register it
1720 -- in all the secondary dispatch tables associated with abstract
1721 -- interfaces. We do this now only if not building static tables,
1722 -- nor when the expander is inactive (we avoid trying to register
1723 -- primitives in semantics-only mode, since the type may not have
1724 -- an associated dispatch table). Otherwise the patch code is
1725 -- emitted after those tables are built, to prevent access before
1726 -- elaboration in gigi.
1728 if Body_Is_Last_Primitive
1729 and then not Building_Static_DT (Tagged_Type)
1730 and then Expander_Active
1731 and then Tagged_Type_Expansion
1732 then
1733 declare
1734 Subp_Body : constant Node_Id := Unit_Declaration_Node (Subp);
1735 Elmt : Elmt_Id;
1736 Prim : Node_Id;
1738 begin
1739 Elmt := First_Elmt (Primitive_Operations (Tagged_Type));
1740 while Present (Elmt) loop
1741 Prim := Node (Elmt);
1743 if Present (Alias (Prim))
1744 and then Present (Interface_Alias (Prim))
1745 and then Alias (Prim) = Subp
1746 then
1747 Insert_Actions_After (Subp_Body,
1748 Register_Primitive (Sloc (Subp_Body), Prim => Prim));
1749 end if;
1751 Next_Elmt (Elmt);
1752 end loop;
1754 -- Redisplay the contents of the updated dispatch table
1756 if Debug_Flag_ZZ then
1757 Write_Str ("Late overriding: ");
1758 Write_DT (Tagged_Type);
1759 end if;
1760 end;
1761 end if;
1762 end if;
1764 -- If no old subprogram, then we add this as a dispatching operation,
1765 -- but we avoid doing this if an error was posted, to prevent annoying
1766 -- cascaded errors.
1768 elsif not Error_Posted (Subp) then
1769 Add_Dispatching_Operation (Tagged_Type, Subp);
1770 end if;
1772 Set_Is_Dispatching_Operation (Subp, True);
1774 -- Ada 2005 (AI-251): If the type implements interfaces we must check
1775 -- subtype conformance against all the interfaces covered by this
1776 -- primitive.
1778 if Present (Ovr_Subp)
1779 and then Has_Interfaces (Tagged_Type)
1780 then
1781 declare
1782 Ifaces_List : Elist_Id;
1783 Iface_Elmt : Elmt_Id;
1784 Iface_Prim_Elmt : Elmt_Id;
1785 Iface_Prim : Entity_Id;
1786 Ret_Typ : Entity_Id;
1788 begin
1789 Collect_Interfaces (Tagged_Type, Ifaces_List);
1791 Iface_Elmt := First_Elmt (Ifaces_List);
1792 while Present (Iface_Elmt) loop
1793 if not Is_Ancestor (Node (Iface_Elmt), Tagged_Type) then
1794 Iface_Prim_Elmt :=
1795 First_Elmt (Primitive_Operations (Node (Iface_Elmt)));
1796 while Present (Iface_Prim_Elmt) loop
1797 Iface_Prim := Node (Iface_Prim_Elmt);
1799 if Is_Interface_Conformant
1800 (Tagged_Type, Iface_Prim, Subp)
1801 then
1802 -- Handle procedures, functions whose return type
1803 -- matches, or functions not returning interfaces
1805 if Ekind (Subp) = E_Procedure
1806 or else Etype (Iface_Prim) = Etype (Subp)
1807 or else not Is_Interface (Etype (Iface_Prim))
1808 then
1809 Check_Subtype_Conformant
1810 (New_Id => Subp,
1811 Old_Id => Iface_Prim,
1812 Err_Loc => Subp,
1813 Skip_Controlling_Formals => True);
1815 -- Handle functions returning interfaces
1817 elsif Implements_Interface
1818 (Etype (Subp), Etype (Iface_Prim))
1819 then
1820 -- Temporarily force both entities to return the
1821 -- same type. Required because Subtype_Conformant
1822 -- does not handle this case.
1824 Ret_Typ := Etype (Iface_Prim);
1825 Set_Etype (Iface_Prim, Etype (Subp));
1827 Check_Subtype_Conformant
1828 (New_Id => Subp,
1829 Old_Id => Iface_Prim,
1830 Err_Loc => Subp,
1831 Skip_Controlling_Formals => True);
1833 Set_Etype (Iface_Prim, Ret_Typ);
1834 end if;
1835 end if;
1837 Next_Elmt (Iface_Prim_Elmt);
1838 end loop;
1839 end if;
1841 Next_Elmt (Iface_Elmt);
1842 end loop;
1843 end;
1844 end if;
1846 if not Body_Is_Last_Primitive then
1847 Set_DT_Position_Value (Subp, No_Uint);
1849 elsif Has_Controlled_Component (Tagged_Type)
1850 and then Chars (Subp) in Name_Initialize
1851 | Name_Adjust
1852 | Name_Finalize
1853 | Name_Finalize_Address
1854 then
1855 declare
1856 F_Node : constant Node_Id := Freeze_Node (Tagged_Type);
1857 Decl : Node_Id;
1858 Old_P : Entity_Id;
1859 Old_Bod : Node_Id;
1860 Old_Spec : Entity_Id;
1862 C_Names : constant array (1 .. 4) of Name_Id :=
1863 (Name_Initialize,
1864 Name_Adjust,
1865 Name_Finalize,
1866 Name_Finalize_Address);
1868 D_Names : constant array (1 .. 4) of TSS_Name_Type :=
1869 (TSS_Deep_Initialize,
1870 TSS_Deep_Adjust,
1871 TSS_Deep_Finalize,
1872 TSS_Finalize_Address);
1874 begin
1875 -- Remove previous controlled function which was constructed and
1876 -- analyzed when the type was frozen. This requires removing the
1877 -- body of the redefined primitive, as well as its specification
1878 -- if needed (there is no spec created for Deep_Initialize, see
1879 -- exp_ch3.adb). We must also dismantle the exception information
1880 -- that may have been generated for it when front end zero-cost
1881 -- tables are enabled.
1883 for J in D_Names'Range loop
1884 Old_P := TSS (Tagged_Type, D_Names (J));
1886 if Present (Old_P)
1887 and then Chars (Subp) = C_Names (J)
1888 then
1889 Old_Bod := Unit_Declaration_Node (Old_P);
1890 Remove (Old_Bod);
1891 Set_Is_Eliminated (Old_P);
1892 Set_Scope (Old_P, Scope (Current_Scope));
1894 if Nkind (Old_Bod) = N_Subprogram_Body
1895 and then Present (Corresponding_Spec (Old_Bod))
1896 then
1897 Old_Spec := Corresponding_Spec (Old_Bod);
1898 Set_Has_Completion (Old_Spec, False);
1899 end if;
1900 end if;
1901 end loop;
1903 Build_Late_Proc (Tagged_Type, Chars (Subp));
1905 -- The new operation is added to the actions of the freeze node
1906 -- for the type, but this node has already been analyzed, so we
1907 -- must retrieve and analyze explicitly the new body.
1909 if Present (F_Node)
1910 and then Present (Actions (F_Node))
1911 then
1912 Decl := Last (Actions (F_Node));
1913 Analyze (Decl);
1914 end if;
1915 end;
1916 end if;
1918 -- AI12-0279: If the Yield aspect is specified for a dispatching
1919 -- subprogram that inherits the aspect, the specified value shall
1920 -- be confirming.
1922 if Is_Dispatching_Operation (Subp)
1923 and then Is_Primitive_Wrapper (Subp)
1924 and then Present (Wrapped_Entity (Subp))
1925 and then Comes_From_Source (Wrapped_Entity (Subp))
1926 and then Present (Overridden_Operation (Subp))
1927 and then Has_Yield_Aspect (Overridden_Operation (Subp))
1928 /= Has_Yield_Aspect (Wrapped_Entity (Subp))
1929 then
1930 declare
1931 W_Ent : constant Entity_Id := Wrapped_Entity (Subp);
1932 W_Decl : constant Node_Id := Parent (W_Ent);
1933 Asp : Node_Id;
1935 begin
1936 if Present (Aspect_Specifications (W_Decl)) then
1937 Asp := First (Aspect_Specifications (W_Decl));
1938 while Present (Asp) loop
1939 if Chars (Identifier (Asp)) = Name_Yield then
1940 Error_Msg_Name_1 := Name_Yield;
1941 Error_Msg_N
1942 ("specification of inherited aspect% can only confirm "
1943 & "parent value", Asp);
1944 end if;
1946 Next (Asp);
1947 end loop;
1948 end if;
1950 Set_Has_Yield_Aspect (Wrapped_Entity (Subp));
1951 end;
1952 end if;
1954 -- For similarity with record extensions, in Ada 9X the language should
1955 -- have disallowed adding visible operations to a tagged type after
1956 -- deriving a private extension from it. Report a warning if this
1957 -- primitive is defined after a private extension of Tagged_Type.
1959 Warn_On_Late_Primitive_After_Private_Extension (Tagged_Type, Subp);
1960 end Check_Dispatching_Operation;
1962 ------------------------------------------
1963 -- Check_Operation_From_Incomplete_Type --
1964 ------------------------------------------
1966 procedure Check_Operation_From_Incomplete_Type
1967 (Subp : Entity_Id;
1968 Typ : Entity_Id)
1970 Full : constant Entity_Id := Full_View (Typ);
1971 Parent_Typ : constant Entity_Id := Etype (Full);
1972 Old_Prim : constant Elist_Id := Primitive_Operations (Parent_Typ);
1973 New_Prim : constant Elist_Id := Primitive_Operations (Full);
1974 Op1, Op2 : Elmt_Id;
1975 Prev : Elmt_Id := No_Elmt;
1977 function Derives_From (Parent_Subp : Entity_Id) return Boolean;
1978 -- Check that Subp has profile of an operation derived from Parent_Subp.
1979 -- Subp must have a parameter or result type that is Typ or an access
1980 -- parameter or access result type that designates Typ.
1982 ------------------
1983 -- Derives_From --
1984 ------------------
1986 function Derives_From (Parent_Subp : Entity_Id) return Boolean is
1987 F1, F2 : Entity_Id;
1989 begin
1990 if Chars (Parent_Subp) /= Chars (Subp) then
1991 return False;
1992 end if;
1994 -- Check that the type of controlling formals is derived from the
1995 -- parent subprogram's controlling formal type (or designated type
1996 -- if the formal type is an anonymous access type).
1998 F1 := First_Formal (Parent_Subp);
1999 F2 := First_Formal (Subp);
2000 while Present (F1) and then Present (F2) loop
2001 if Ekind (Etype (F1)) = E_Anonymous_Access_Type then
2002 if Ekind (Etype (F2)) /= E_Anonymous_Access_Type then
2003 return False;
2004 elsif Designated_Type (Etype (F1)) = Parent_Typ
2005 and then Designated_Type (Etype (F2)) /= Full
2006 then
2007 return False;
2008 end if;
2010 elsif Ekind (Etype (F2)) = E_Anonymous_Access_Type then
2011 return False;
2013 elsif Etype (F1) = Parent_Typ and then Etype (F2) /= Full then
2014 return False;
2015 end if;
2017 Next_Formal (F1);
2018 Next_Formal (F2);
2019 end loop;
2021 -- Check that a controlling result type is derived from the parent
2022 -- subprogram's result type (or designated type if the result type
2023 -- is an anonymous access type).
2025 if Ekind (Parent_Subp) = E_Function then
2026 if Ekind (Subp) /= E_Function then
2027 return False;
2029 elsif Ekind (Etype (Parent_Subp)) = E_Anonymous_Access_Type then
2030 if Ekind (Etype (Subp)) /= E_Anonymous_Access_Type then
2031 return False;
2033 elsif Designated_Type (Etype (Parent_Subp)) = Parent_Typ
2034 and then Designated_Type (Etype (Subp)) /= Full
2035 then
2036 return False;
2037 end if;
2039 elsif Ekind (Etype (Subp)) = E_Anonymous_Access_Type then
2040 return False;
2042 elsif Etype (Parent_Subp) = Parent_Typ
2043 and then Etype (Subp) /= Full
2044 then
2045 return False;
2046 end if;
2048 elsif Ekind (Subp) = E_Function then
2049 return False;
2050 end if;
2052 return No (F1) and then No (F2);
2053 end Derives_From;
2055 -- Start of processing for Check_Operation_From_Incomplete_Type
2057 begin
2058 -- The operation may override an inherited one, or may be a new one
2059 -- altogether. The inherited operation will have been hidden by the
2060 -- current one at the point of the type derivation, so it does not
2061 -- appear in the list of primitive operations of the type. We have to
2062 -- find the proper place of insertion in the list of primitive opera-
2063 -- tions by iterating over the list for the parent type.
2065 Op1 := First_Elmt (Old_Prim);
2066 Op2 := First_Elmt (New_Prim);
2067 while Present (Op1) and then Present (Op2) loop
2068 if Derives_From (Node (Op1)) then
2069 if No (Prev) then
2071 -- Avoid adding it to the list of primitives if already there
2073 if Node (Op2) /= Subp then
2074 Prepend_Elmt (Subp, New_Prim);
2075 end if;
2077 else
2078 Insert_Elmt_After (Subp, Prev);
2079 end if;
2081 return;
2082 end if;
2084 Prev := Op2;
2085 Next_Elmt (Op1);
2086 Next_Elmt (Op2);
2087 end loop;
2089 -- Operation is a new primitive
2091 Append_Elmt (Subp, New_Prim);
2092 end Check_Operation_From_Incomplete_Type;
2094 ---------------------------------------
2095 -- Check_Operation_From_Private_View --
2096 ---------------------------------------
2098 procedure Check_Operation_From_Private_View (Subp, Old_Subp : Entity_Id) is
2099 Tagged_Type : Entity_Id;
2101 begin
2102 if Is_Dispatching_Operation (Alias (Subp)) then
2103 Set_Scope (Subp, Current_Scope);
2104 Tagged_Type := Find_Dispatching_Type (Subp);
2106 -- Add Old_Subp to primitive operations if not already present
2108 if Present (Tagged_Type) and then Is_Tagged_Type (Tagged_Type) then
2109 Add_Dispatching_Operation (Tagged_Type, Old_Subp);
2111 -- If Old_Subp isn't already marked as dispatching then this is
2112 -- the case of an operation of an untagged private type fulfilled
2113 -- by a tagged type that overrides an inherited dispatching
2114 -- operation, so we set the necessary dispatching attributes here.
2116 if not Is_Dispatching_Operation (Old_Subp) then
2118 -- If the untagged type has no discriminants, and the full
2119 -- view is constrained, there will be a spurious mismatch of
2120 -- subtypes on the controlling arguments, because the tagged
2121 -- type is the internal base type introduced in the derivation.
2122 -- Use the original type to verify conformance, rather than the
2123 -- base type.
2125 if not Comes_From_Source (Tagged_Type)
2126 and then Has_Discriminants (Tagged_Type)
2127 then
2128 declare
2129 Formal : Entity_Id;
2131 begin
2132 Formal := First_Formal (Old_Subp);
2133 while Present (Formal) loop
2134 if Tagged_Type = Base_Type (Etype (Formal)) then
2135 Tagged_Type := Etype (Formal);
2136 end if;
2138 Next_Formal (Formal);
2139 end loop;
2140 end;
2142 if Tagged_Type = Base_Type (Etype (Old_Subp)) then
2143 Tagged_Type := Etype (Old_Subp);
2144 end if;
2145 end if;
2147 Check_Controlling_Formals (Tagged_Type, Old_Subp);
2148 Set_Is_Dispatching_Operation (Old_Subp, True);
2149 Set_DT_Position_Value (Old_Subp, No_Uint);
2150 end if;
2152 -- If the old subprogram is an explicit renaming of some other
2153 -- entity, it is not overridden by the inherited subprogram.
2154 -- Otherwise, update its alias and other attributes.
2156 if Present (Alias (Old_Subp))
2157 and then Nkind (Unit_Declaration_Node (Old_Subp)) /=
2158 N_Subprogram_Renaming_Declaration
2159 then
2160 Set_Alias (Old_Subp, Alias (Subp));
2162 -- The derived subprogram should inherit the abstractness of
2163 -- the parent subprogram (except in the case of a function
2164 -- returning the type). This sets the abstractness properly
2165 -- for cases where a private extension may have inherited an
2166 -- abstract operation, but the full type is derived from a
2167 -- descendant type and inherits a nonabstract version.
2169 if Etype (Subp) /= Tagged_Type then
2170 Set_Is_Abstract_Subprogram
2171 (Old_Subp, Is_Abstract_Subprogram (Alias (Subp)));
2172 end if;
2173 end if;
2174 end if;
2175 end if;
2176 end Check_Operation_From_Private_View;
2178 --------------------------
2179 -- Find_Controlling_Arg --
2180 --------------------------
2182 function Find_Controlling_Arg (N : Node_Id) return Node_Id is
2183 Orig_Node : constant Node_Id := Original_Node (N);
2184 Typ : Entity_Id;
2186 begin
2187 if Nkind (Orig_Node) = N_Qualified_Expression then
2188 return Find_Controlling_Arg (Expression (Orig_Node));
2189 end if;
2191 -- Dispatching on result case. If expansion is disabled, the node still
2192 -- has the structure of a function call. However, if the function name
2193 -- is an operator and the call was given in infix form, the original
2194 -- node has no controlling result and we must examine the current node.
2196 if Nkind (N) = N_Function_Call
2197 and then Present (Controlling_Argument (N))
2198 and then Has_Controlling_Result (Entity (Name (N)))
2199 then
2200 return Controlling_Argument (N);
2202 -- If expansion is enabled, the call may have been transformed into
2203 -- an indirect call, and we need to recover the original node.
2205 elsif Nkind (Orig_Node) = N_Function_Call
2206 and then Present (Controlling_Argument (Orig_Node))
2207 and then Has_Controlling_Result (Entity (Name (Orig_Node)))
2208 then
2209 return Controlling_Argument (Orig_Node);
2211 -- Type conversions are dynamically tagged if the target type, or its
2212 -- designated type, are classwide. An interface conversion expands into
2213 -- a dereference, so test must be performed on the original node.
2215 elsif Nkind (Orig_Node) = N_Type_Conversion
2216 and then Nkind (N) = N_Explicit_Dereference
2217 and then Is_Controlling_Actual (N)
2218 then
2219 declare
2220 Target_Type : constant Entity_Id :=
2221 Entity (Subtype_Mark (Orig_Node));
2223 begin
2224 if Is_Class_Wide_Type (Target_Type) then
2225 return N;
2227 elsif Is_Access_Type (Target_Type)
2228 and then Is_Class_Wide_Type (Designated_Type (Target_Type))
2229 then
2230 return N;
2232 else
2233 return Empty;
2234 end if;
2235 end;
2237 -- Normal case
2239 elsif Is_Controlling_Actual (N)
2240 or else
2241 (Nkind (Parent (N)) = N_Qualified_Expression
2242 and then Is_Controlling_Actual (Parent (N)))
2243 then
2244 Typ := Etype (N);
2246 if Is_Access_Type (Typ) then
2248 -- In the case of an Access attribute, use the type of the prefix,
2249 -- since in the case of an actual for an access parameter, the
2250 -- attribute's type may be of a specific designated type, even
2251 -- though the prefix type is class-wide.
2253 if Nkind (N) = N_Attribute_Reference then
2254 Typ := Etype (Prefix (N));
2256 -- An allocator is dispatching if the type of qualified expression
2257 -- is class_wide, in which case this is the controlling type.
2259 elsif Nkind (Orig_Node) = N_Allocator
2260 and then Nkind (Expression (Orig_Node)) = N_Qualified_Expression
2261 then
2262 Typ := Etype (Expression (Orig_Node));
2263 else
2264 Typ := Designated_Type (Typ);
2265 end if;
2266 end if;
2268 if Is_Class_Wide_Type (Typ)
2269 or else
2270 (Nkind (Parent (N)) = N_Qualified_Expression
2271 and then Is_Access_Type (Etype (N))
2272 and then Is_Class_Wide_Type (Designated_Type (Etype (N))))
2273 then
2274 return N;
2275 end if;
2276 end if;
2278 return Empty;
2279 end Find_Controlling_Arg;
2281 ---------------------------
2282 -- Find_Dispatching_Type --
2283 ---------------------------
2285 function Find_Dispatching_Type (Subp : Entity_Id) return Entity_Id is
2286 A_Formal : Entity_Id;
2287 Formal : Entity_Id;
2288 Ctrl_Type : Entity_Id;
2290 begin
2291 if Ekind (Subp) in E_Function | E_Procedure
2292 and then Present (DTC_Entity (Subp))
2293 then
2294 return Scope (DTC_Entity (Subp));
2296 -- For subprograms internally generated by derivations of tagged types
2297 -- use the alias subprogram as a reference to locate the dispatching
2298 -- type of Subp.
2300 elsif not Comes_From_Source (Subp)
2301 and then Present (Alias (Subp))
2302 and then Is_Dispatching_Operation (Alias (Subp))
2303 then
2304 if Ekind (Alias (Subp)) = E_Function
2305 and then Has_Controlling_Result (Alias (Subp))
2306 then
2307 return Check_Controlling_Type (Etype (Subp), Subp);
2309 else
2310 Formal := First_Formal (Subp);
2311 A_Formal := First_Formal (Alias (Subp));
2312 while Present (A_Formal) loop
2313 if Is_Controlling_Formal (A_Formal) then
2314 return Check_Controlling_Type (Etype (Formal), Subp);
2315 end if;
2317 Next_Formal (Formal);
2318 Next_Formal (A_Formal);
2319 end loop;
2321 pragma Assert (False);
2322 return Empty;
2323 end if;
2325 -- General case
2327 else
2328 Formal := First_Formal (Subp);
2329 while Present (Formal) loop
2330 Ctrl_Type := Check_Controlling_Type (Etype (Formal), Subp);
2332 if Present (Ctrl_Type) then
2333 return Ctrl_Type;
2334 end if;
2336 Next_Formal (Formal);
2337 end loop;
2339 -- The subprogram may also be dispatching on result
2341 if Present (Etype (Subp)) then
2342 return Check_Controlling_Type (Etype (Subp), Subp);
2343 end if;
2344 end if;
2346 pragma Assert (not Is_Dispatching_Operation (Subp));
2347 return Empty;
2348 end Find_Dispatching_Type;
2350 --------------------------------------
2351 -- Find_Hidden_Overridden_Primitive --
2352 --------------------------------------
2354 function Find_Hidden_Overridden_Primitive (S : Entity_Id) return Entity_Id
2356 Tag_Typ : constant Entity_Id := Find_Dispatching_Type (S);
2357 Elmt : Elmt_Id;
2358 Orig_Prim : Entity_Id;
2359 Prim : Entity_Id;
2360 Vis_List : Elist_Id;
2362 begin
2363 -- This Ada 2012 rule applies only for type extensions or private
2364 -- extensions, where the parent type is not in a parent unit, and
2365 -- where an operation is never declared but still inherited.
2367 if No (Tag_Typ)
2368 or else not Is_Record_Type (Tag_Typ)
2369 or else Etype (Tag_Typ) = Tag_Typ
2370 or else In_Open_Scopes (Scope (Etype (Tag_Typ)))
2371 then
2372 return Empty;
2373 end if;
2375 -- Collect the list of visible ancestor of the tagged type
2377 Vis_List := Visible_Ancestors (Tag_Typ);
2379 Elmt := First_Elmt (Primitive_Operations (Tag_Typ));
2380 while Present (Elmt) loop
2381 Prim := Node (Elmt);
2383 -- Find an inherited hidden dispatching primitive with the name of S
2384 -- and a type-conformant profile.
2386 if Present (Alias (Prim))
2387 and then Is_Hidden (Alias (Prim))
2388 and then Find_Dispatching_Type (Alias (Prim)) /= Tag_Typ
2389 and then Primitive_Names_Match (S, Prim)
2390 and then Type_Conformant (S, Prim)
2391 then
2392 declare
2393 Vis_Ancestor : Elmt_Id;
2394 Elmt : Elmt_Id;
2396 begin
2397 -- The original corresponding operation of Prim must be an
2398 -- operation of a visible ancestor of the dispatching type S,
2399 -- and the original corresponding operation of S2 must be
2400 -- visible.
2402 Orig_Prim := Original_Corresponding_Operation (Prim);
2404 if Orig_Prim /= Prim
2405 and then Is_Immediately_Visible (Orig_Prim)
2406 then
2407 Vis_Ancestor := First_Elmt (Vis_List);
2408 while Present (Vis_Ancestor) loop
2409 Elmt :=
2410 First_Elmt (Primitive_Operations (Node (Vis_Ancestor)));
2411 while Present (Elmt) loop
2412 if Node (Elmt) = Orig_Prim then
2413 Set_Overridden_Operation (S, Prim);
2414 Set_Is_Ada_2022_Only (S,
2415 Is_Ada_2022_Only (Prim));
2416 Set_Alias (Prim, Orig_Prim);
2417 return Prim;
2418 end if;
2420 Next_Elmt (Elmt);
2421 end loop;
2423 Next_Elmt (Vis_Ancestor);
2424 end loop;
2425 end if;
2426 end;
2427 end if;
2429 Next_Elmt (Elmt);
2430 end loop;
2432 return Empty;
2433 end Find_Hidden_Overridden_Primitive;
2435 ---------------------------------------
2436 -- Find_Primitive_Covering_Interface --
2437 ---------------------------------------
2439 function Find_Primitive_Covering_Interface
2440 (Tagged_Type : Entity_Id;
2441 Iface_Prim : Entity_Id) return Entity_Id
2443 E : Entity_Id;
2444 El : Elmt_Id;
2446 begin
2447 pragma Assert (Is_Interface (Find_Dispatching_Type (Iface_Prim))
2448 or else (Present (Alias (Iface_Prim))
2449 and then
2450 Is_Interface
2451 (Find_Dispatching_Type (Ultimate_Alias (Iface_Prim)))));
2453 -- Search in the homonym chain. Done to speed up locating visible
2454 -- entities and required to catch primitives associated with the partial
2455 -- view of private types when processing the corresponding full view.
2457 E := Current_Entity (Iface_Prim);
2458 while Present (E) loop
2459 if Is_Subprogram (E)
2460 and then Is_Dispatching_Operation (E)
2461 and then Is_Interface_Conformant (Tagged_Type, Iface_Prim, E)
2462 then
2463 return E;
2464 end if;
2466 E := Homonym (E);
2467 end loop;
2469 -- Search in the list of primitives of the type. Required to locate
2470 -- the covering primitive if the covering primitive is not visible
2471 -- (for example, non-visible inherited primitive of private type).
2473 El := First_Elmt (Primitive_Operations (Tagged_Type));
2474 while Present (El) loop
2475 E := Node (El);
2477 -- Keep separate the management of internal entities that link
2478 -- primitives with interface primitives from tagged type primitives.
2480 if No (Interface_Alias (E)) then
2481 if Present (Alias (E)) then
2483 -- This interface primitive has not been covered yet
2485 if Alias (E) = Iface_Prim then
2486 return E;
2488 -- The covering primitive was inherited
2490 elsif Overridden_Operation (Ultimate_Alias (E))
2491 = Iface_Prim
2492 then
2493 return E;
2494 end if;
2495 end if;
2497 -- Check if E covers the interface primitive (includes case in
2498 -- which E is an inherited private primitive).
2500 if Is_Interface_Conformant (Tagged_Type, Iface_Prim, E) then
2501 return E;
2502 end if;
2504 -- Use the internal entity that links the interface primitive with
2505 -- the covering primitive to locate the entity.
2507 elsif Interface_Alias (E) = Iface_Prim then
2508 return Alias (E);
2509 end if;
2511 Next_Elmt (El);
2512 end loop;
2514 -- Not found
2516 return Empty;
2517 end Find_Primitive_Covering_Interface;
2519 ---------------------------
2520 -- Inheritance_Utilities --
2521 ---------------------------
2523 package body Inheritance_Utilities is
2525 ---------------------------
2526 -- Inherited_Subprograms --
2527 ---------------------------
2529 function Inherited_Subprograms
2530 (S : Entity_Id;
2531 No_Interfaces : Boolean := False;
2532 Interfaces_Only : Boolean := False;
2533 Skip_Overridden : Boolean := False;
2534 One_Only : Boolean := False) return Subprogram_List
2536 Result : Subprogram_List (1 .. 6000);
2537 -- 6000 here is intended to be infinity. We could use an expandable
2538 -- table, but it would be awfully heavy, and there is no way that we
2539 -- could reasonably exceed this value.
2541 N : Nat := 0;
2542 -- Number of entries in Result
2544 Parent_Op : Entity_Id;
2545 -- Traverses the Overridden_Operation chain
2547 procedure Store_IS (E : Entity_Id);
2548 -- Stores E in Result if not already stored
2550 --------------
2551 -- Store_IS --
2552 --------------
2554 procedure Store_IS (E : Entity_Id) is
2555 begin
2556 for J in 1 .. N loop
2557 if E = Result (J) then
2558 return;
2559 end if;
2560 end loop;
2562 N := N + 1;
2563 Result (N) := E;
2564 end Store_IS;
2566 -- Start of processing for Inherited_Subprograms
2568 begin
2569 pragma Assert (not (No_Interfaces and Interfaces_Only));
2571 -- When used from backends, visibility can be handled differently
2572 -- resulting in no dispatching type being found.
2574 if Present (S)
2575 and then Is_Dispatching_Operation (S)
2576 and then Present (Find_DT (S))
2577 then
2578 -- Deal with direct inheritance
2580 if not Interfaces_Only then
2581 Parent_Op := S;
2582 loop
2583 Parent_Op := Overridden_Operation (Parent_Op);
2584 exit when No (Parent_Op)
2585 or else (No_Interfaces
2586 and then Is_Interface (Find_DT (Parent_Op)));
2588 if Is_Subprogram_Or_Generic_Subprogram (Parent_Op) then
2589 Store_IS (Parent_Op);
2591 if One_Only then
2592 goto Done;
2593 end if;
2594 end if;
2595 end loop;
2596 end if;
2598 -- Now deal with interfaces
2600 if not No_Interfaces then
2601 declare
2602 Tag_Typ : Entity_Id;
2603 Prim : Entity_Id;
2604 Elmt : Elmt_Id;
2606 begin
2607 Tag_Typ := Find_DT (S);
2609 -- In the presence of limited views there may be no visible
2610 -- dispatching type. Primitives will be inherited when non-
2611 -- limited view is frozen.
2613 if No (Tag_Typ) then
2614 return Result (1 .. 0);
2616 -- Prevent cascaded errors
2618 elsif Is_Concurrent_Type (Tag_Typ)
2619 and then No (Corresponding_Record_Type (Tag_Typ))
2620 and then Serious_Errors_Detected > 0
2621 then
2622 return Result (1 .. 0);
2623 end if;
2625 if Is_Concurrent_Type (Tag_Typ) then
2626 Tag_Typ := Corresponding_Record_Type (Tag_Typ);
2627 end if;
2629 if Present (Tag_Typ)
2630 and then Is_Private_Type (Tag_Typ)
2631 and then Present (Full_View (Tag_Typ))
2632 then
2633 Tag_Typ := Full_View (Tag_Typ);
2634 end if;
2636 -- Search primitive operations of dispatching type
2638 if Present (Tag_Typ)
2639 and then Present (Primitive_Operations (Tag_Typ))
2640 then
2641 Elmt := First_Elmt (Primitive_Operations (Tag_Typ));
2642 while Present (Elmt) loop
2643 Prim := Node (Elmt);
2645 -- The following test eliminates some odd cases in
2646 -- which Ekind (Prim) is Void, to be investigated
2647 -- further ???
2649 if not Is_Subprogram_Or_Generic_Subprogram (Prim) then
2650 null;
2652 -- For [generic] subprogram, look at interface
2653 -- alias.
2655 elsif Present (Interface_Alias (Prim))
2656 and then Alias (Prim) = S
2657 then
2658 -- We have found a primitive covered by S
2660 Store_IS (Interface_Alias (Prim));
2662 if One_Only then
2663 goto Done;
2664 end if;
2665 end if;
2667 Next_Elmt (Elmt);
2668 end loop;
2669 end if;
2670 end;
2671 end if;
2672 end if;
2674 -- Do not keep an overridden operation if its overridding operation
2675 -- is in the results too, and it is not S. This can happen for
2676 -- inheritance between interfaces.
2678 if Skip_Overridden then
2679 declare
2680 Res : constant Subprogram_List (1 .. N) := Result (1 .. N);
2681 M : Nat := 0;
2682 begin
2683 for J in 1 .. N loop
2684 for K in 1 .. N loop
2685 if Res (K) /= S
2686 and then Res (J) = Overridden_Operation (Res (K))
2687 then
2688 goto Skip;
2689 end if;
2690 end loop;
2692 M := M + 1;
2693 Result (M) := Res (J);
2695 <<Skip>>
2696 end loop;
2698 N := M;
2699 end;
2700 end if;
2702 <<Done>>
2704 return Result (1 .. N);
2705 end Inherited_Subprograms;
2707 ------------------------------
2708 -- Is_Overriding_Subprogram --
2709 ------------------------------
2711 function Is_Overriding_Subprogram (E : Entity_Id) return Boolean is
2712 Inherited : constant Subprogram_List :=
2713 Inherited_Subprograms (E, One_Only => True);
2714 begin
2715 return Inherited'Length > 0;
2716 end Is_Overriding_Subprogram;
2717 end Inheritance_Utilities;
2719 --------------------------------
2720 -- Inheritance_Utilities_Inst --
2721 --------------------------------
2723 package Inheritance_Utilities_Inst is new
2724 Inheritance_Utilities (Find_Dispatching_Type);
2726 ---------------------------
2727 -- Inherited_Subprograms --
2728 ---------------------------
2730 function Inherited_Subprograms
2731 (S : Entity_Id;
2732 No_Interfaces : Boolean := False;
2733 Interfaces_Only : Boolean := False;
2734 Skip_Overridden : Boolean := False;
2735 One_Only : Boolean := False) return Subprogram_List renames
2736 Inheritance_Utilities_Inst.Inherited_Subprograms;
2738 ---------------------------
2739 -- Is_Dynamically_Tagged --
2740 ---------------------------
2742 function Is_Dynamically_Tagged (N : Node_Id) return Boolean is
2743 begin
2744 if Nkind (N) = N_Error then
2745 return False;
2747 elsif Present (Find_Controlling_Arg (N)) then
2748 return True;
2750 -- Special cases: entities, and calls that dispatch on result
2752 elsif Is_Entity_Name (N) then
2753 return Is_Class_Wide_Type (Etype (N));
2755 elsif Nkind (N) = N_Function_Call
2756 and then Is_Class_Wide_Type (Etype (N))
2757 then
2758 return True;
2760 -- Otherwise check whether call has controlling argument
2762 else
2763 return False;
2764 end if;
2765 end Is_Dynamically_Tagged;
2767 ---------------------------------
2768 -- Is_Null_Interface_Primitive --
2769 ---------------------------------
2771 function Is_Null_Interface_Primitive (E : Entity_Id) return Boolean is
2772 begin
2773 return Comes_From_Source (E)
2774 and then Is_Dispatching_Operation (E)
2775 and then Ekind (E) = E_Procedure
2776 and then Null_Present (Parent (E))
2777 and then Is_Interface (Find_Dispatching_Type (E));
2778 end Is_Null_Interface_Primitive;
2780 -----------------------------------
2781 -- Is_Inherited_Public_Operation --
2782 -----------------------------------
2784 function Is_Inherited_Public_Operation (Op : Entity_Id) return Boolean is
2785 Pack_Decl : Node_Id;
2786 Prim : Entity_Id := Op;
2787 Scop : Entity_Id := Prim;
2789 begin
2790 -- Locate the ultimate non-hidden alias entity
2792 while Present (Alias (Prim)) and then not Is_Hidden (Alias (Prim)) loop
2793 pragma Assert (Alias (Prim) /= Prim);
2794 Prim := Alias (Prim);
2795 Scop := Scope (Prim);
2796 end loop;
2798 if Comes_From_Source (Prim) and then Ekind (Scop) = E_Package then
2799 Pack_Decl := Unit_Declaration_Node (Scop);
2801 return
2802 Nkind (Pack_Decl) = N_Package_Declaration
2803 and then List_Containing (Unit_Declaration_Node (Prim)) =
2804 Visible_Declarations (Specification (Pack_Decl));
2806 else
2807 return False;
2808 end if;
2809 end Is_Inherited_Public_Operation;
2811 ------------------------------
2812 -- Is_Overriding_Subprogram --
2813 ------------------------------
2815 function Is_Overriding_Subprogram (E : Entity_Id) return Boolean renames
2816 Inheritance_Utilities_Inst.Is_Overriding_Subprogram;
2818 --------------------------
2819 -- Is_Tag_Indeterminate --
2820 --------------------------
2822 function Is_Tag_Indeterminate (N : Node_Id) return Boolean is
2823 Nam : Entity_Id;
2824 Actual : Node_Id;
2825 Orig_Node : constant Node_Id := Original_Node (N);
2827 begin
2828 if Nkind (Orig_Node) = N_Function_Call
2829 and then Is_Entity_Name (Name (Orig_Node))
2830 then
2831 Nam := Entity (Name (Orig_Node));
2833 if not Has_Controlling_Result (Nam) then
2834 return False;
2836 -- The function may have a controlling result, but if the return type
2837 -- is not visibly tagged, then this is not tag-indeterminate.
2839 elsif Is_Access_Type (Etype (Nam))
2840 and then not Is_Tagged_Type (Designated_Type (Etype (Nam)))
2841 then
2842 return False;
2844 -- An explicit dereference means that the call has already been
2845 -- expanded and there is no tag to propagate.
2847 elsif Nkind (N) = N_Explicit_Dereference then
2848 return False;
2850 -- If there are no actuals, the call is tag-indeterminate
2852 elsif No (Parameter_Associations (Orig_Node)) then
2853 return True;
2855 else
2856 Actual := First_Actual (Orig_Node);
2857 while Present (Actual) loop
2858 if Is_Controlling_Actual (Actual)
2859 and then not Is_Tag_Indeterminate (Actual)
2860 then
2861 -- One operand is dispatching
2863 return False;
2864 end if;
2866 Next_Actual (Actual);
2867 end loop;
2869 return True;
2870 end if;
2872 elsif Nkind (Orig_Node) = N_Qualified_Expression then
2873 return Is_Tag_Indeterminate (Expression (Orig_Node));
2875 -- Case of a call to the Input attribute (possibly rewritten), which is
2876 -- always tag-indeterminate except when its prefix is a Class attribute.
2878 elsif Nkind (Orig_Node) = N_Attribute_Reference
2879 and then
2880 Get_Attribute_Id (Attribute_Name (Orig_Node)) = Attribute_Input
2881 and then Nkind (Prefix (Orig_Node)) /= N_Attribute_Reference
2882 then
2883 return True;
2885 -- In Ada 2005, a function that returns an anonymous access type can be
2886 -- dispatching, and the dereference of a call to such a function can
2887 -- also be tag-indeterminate if the call itself is.
2889 elsif Nkind (Orig_Node) = N_Explicit_Dereference
2890 and then Ada_Version >= Ada_2005
2891 then
2892 return Is_Tag_Indeterminate (Prefix (Orig_Node));
2894 else
2895 return False;
2896 end if;
2897 end Is_Tag_Indeterminate;
2899 ------------------------------------
2900 -- Override_Dispatching_Operation --
2901 ------------------------------------
2903 procedure Override_Dispatching_Operation
2904 (Tagged_Type : Entity_Id;
2905 Prev_Op : Entity_Id;
2906 New_Op : Entity_Id)
2908 Elmt : Elmt_Id;
2909 Prim : Node_Id;
2911 begin
2912 -- If there is no previous operation to override, the type declaration
2913 -- was malformed, and an error must have been emitted already.
2915 Elmt := First_Elmt (Primitive_Operations (Tagged_Type));
2916 while Present (Elmt) and then Node (Elmt) /= Prev_Op loop
2917 Next_Elmt (Elmt);
2918 end loop;
2920 if No (Elmt) then
2921 return;
2922 end if;
2924 -- The location of entities that come from source in the list of
2925 -- primitives of the tagged type must follow their order of occurrence
2926 -- in the sources to fulfill the C++ ABI. If the overridden entity is a
2927 -- primitive of an interface that is not implemented by the parents of
2928 -- this tagged type (that is, it is an alias of an interface primitive
2929 -- generated by Derive_Interface_Progenitors), then we must append the
2930 -- new entity at the end of the list of primitives.
2932 if Present (Alias (Prev_Op))
2933 and then Etype (Tagged_Type) /= Tagged_Type
2934 and then Is_Interface (Find_Dispatching_Type (Alias (Prev_Op)))
2935 and then not Is_Ancestor (Find_Dispatching_Type (Alias (Prev_Op)),
2936 Tagged_Type, Use_Full_View => True)
2937 and then not Implements_Interface
2938 (Etype (Tagged_Type),
2939 Find_Dispatching_Type (Alias (Prev_Op)))
2940 then
2941 Remove_Elmt (Primitive_Operations (Tagged_Type), Elmt);
2942 Add_Dispatching_Operation (Tagged_Type, New_Op);
2944 -- The new primitive replaces the overridden entity. Required to ensure
2945 -- that overriding primitive is assigned the same dispatch table slot.
2947 else
2948 Replace_Elmt (Elmt, New_Op);
2949 end if;
2951 if Ada_Version >= Ada_2005 and then Has_Interfaces (Tagged_Type) then
2953 -- Ada 2005 (AI-251): Update the attribute alias of all the aliased
2954 -- entities of the overridden primitive to reference New_Op, and
2955 -- also propagate the proper value of Is_Abstract_Subprogram. Verify
2956 -- that the new operation is subtype conformant with the interface
2957 -- operations that it implements (for operations inherited from the
2958 -- parent itself, this check is made when building the derived type).
2960 -- Note: This code is executed with internally generated wrappers of
2961 -- functions with controlling result and late overridings.
2963 Elmt := First_Elmt (Primitive_Operations (Tagged_Type));
2964 while Present (Elmt) loop
2965 Prim := Node (Elmt);
2967 if Prim = New_Op then
2968 null;
2970 -- Note: The check on Is_Subprogram protects the frontend against
2971 -- reading attributes in entities that are not yet fully decorated
2973 elsif Is_Subprogram (Prim)
2974 and then Present (Interface_Alias (Prim))
2975 and then Alias (Prim) = Prev_Op
2976 then
2977 Set_Alias (Prim, New_Op);
2979 -- No further decoration needed yet for internally generated
2980 -- wrappers of controlling functions since (at this stage)
2981 -- they are not yet decorated.
2983 if not Is_Wrapper (New_Op) then
2984 Check_Subtype_Conformant (New_Op, Prim);
2986 Set_Is_Abstract_Subprogram (Prim,
2987 Is_Abstract_Subprogram (New_Op));
2989 -- Ensure that this entity will be expanded to fill the
2990 -- corresponding entry in its dispatch table.
2992 if not Is_Abstract_Subprogram (Prim) then
2993 Set_Has_Delayed_Freeze (Prim);
2994 end if;
2995 end if;
2996 end if;
2998 Next_Elmt (Elmt);
2999 end loop;
3000 end if;
3002 if not Is_Package_Or_Generic_Package (Current_Scope)
3003 or else not In_Private_Part (Current_Scope)
3004 then
3005 -- Not a private primitive
3007 null;
3009 else pragma Assert (Is_Inherited_Operation (Prev_Op));
3011 -- Make the overriding operation into an alias of the implicit one.
3012 -- In this fashion a call from outside ends up calling the new body
3013 -- even if non-dispatching, and a call from inside calls the over-
3014 -- riding operation because it hides the implicit one. To indicate
3015 -- that the body of Prev_Op is never called, set its dispatch table
3016 -- entity to Empty. If the overridden operation has a dispatching
3017 -- result, so does the overriding one.
3019 Set_Alias (Prev_Op, New_Op);
3020 Set_DTC_Entity (Prev_Op, Empty);
3021 Set_Has_Controlling_Result (New_Op, Has_Controlling_Result (Prev_Op));
3022 Set_Is_Ada_2022_Only (New_Op, Is_Ada_2022_Only (Prev_Op));
3023 end if;
3024 end Override_Dispatching_Operation;
3026 -------------------
3027 -- Propagate_Tag --
3028 -------------------
3030 procedure Propagate_Tag (Control : Node_Id; Actual : Node_Id) is
3031 Call_Node : Node_Id;
3032 Arg : Node_Id;
3034 begin
3035 if Nkind (Actual) = N_Function_Call then
3036 Call_Node := Actual;
3038 elsif Nkind (Actual) = N_Identifier
3039 and then Nkind (Original_Node (Actual)) = N_Function_Call
3040 then
3041 -- Call rewritten as object declaration when stack-checking is
3042 -- enabled. Propagate tag to expression in declaration, which is
3043 -- original call.
3045 Call_Node := Expression (Parent (Entity (Actual)));
3047 -- Ada 2005: If this is a dereference of a call to a function with a
3048 -- dispatching access-result, the tag is propagated when the dereference
3049 -- itself is expanded (see exp_ch6.adb) and there is nothing else to do.
3051 elsif Nkind (Actual) = N_Explicit_Dereference
3052 and then Nkind (Original_Node (Prefix (Actual))) = N_Function_Call
3053 then
3054 return;
3056 -- When expansion is suppressed, an unexpanded call to 'Input can occur,
3057 -- and in that case we can simply return.
3059 elsif Nkind (Actual) = N_Attribute_Reference then
3060 pragma Assert (Attribute_Name (Actual) = Name_Input);
3062 return;
3064 -- Only other possibilities are parenthesized or qualified expression,
3065 -- or an expander-generated unchecked conversion of a function call to
3066 -- a stream Input attribute.
3068 else
3069 Call_Node := Expression (Actual);
3070 end if;
3072 -- No action needed if the call has been already expanded
3074 if Is_Expanded_Dispatching_Call (Call_Node) then
3075 return;
3076 end if;
3078 -- Do not set the Controlling_Argument if already set. This happens in
3079 -- the special case of _Input (see Exp_Attr, case Input).
3081 if No (Controlling_Argument (Call_Node)) then
3082 Set_Controlling_Argument (Call_Node, Control);
3083 end if;
3085 Arg := First_Actual (Call_Node);
3086 while Present (Arg) loop
3087 if Is_Tag_Indeterminate (Arg) then
3088 Propagate_Tag (Control, Arg);
3089 end if;
3091 Next_Actual (Arg);
3092 end loop;
3094 -- Add class-wide precondition check if the target of this dispatching
3095 -- call has or inherits class-wide preconditions.
3097 Install_Class_Preconditions_Check (Call_Node);
3099 -- Expansion of dispatching calls is suppressed on VM targets, because
3100 -- the VM back-ends directly handle the generation of dispatching calls
3101 -- and would have to undo any expansion to an indirect call.
3103 if Tagged_Type_Expansion then
3104 declare
3105 Call_Typ : Entity_Id := Etype (Call_Node);
3106 Ctrl_Typ : Entity_Id := Etype (Control);
3108 begin
3109 Expand_Dispatching_Call (Call_Node);
3111 if Is_Class_Wide_Type (Call_Typ) then
3112 Call_Typ := Root_Type (Call_Typ);
3113 end if;
3115 if Is_Class_Wide_Type (Ctrl_Typ) then
3116 Ctrl_Typ := Root_Type (Ctrl_Typ);
3117 end if;
3119 -- If the controlling argument is an interface type and the type
3120 -- of Call_Node differs then we must add an implicit conversion to
3121 -- force displacement of the pointer to the object to reference
3122 -- the secondary dispatch table of the interface.
3124 if Is_Interface (Ctrl_Typ)
3125 and then Ctrl_Typ /= Call_Typ
3126 then
3127 -- Cannot use Convert_To because the previous call to
3128 -- Expand_Dispatching_Call leaves decorated the Call_Node
3129 -- with the type of Control.
3131 Rewrite (Call_Node,
3132 Make_Type_Conversion (Sloc (Call_Node),
3133 Subtype_Mark =>
3134 New_Occurrence_Of (Etype (Control), Sloc (Call_Node)),
3135 Expression => Relocate_Node (Call_Node)));
3136 Set_Etype (Call_Node, Etype (Control));
3137 Set_Analyzed (Call_Node);
3139 Expand_Interface_Conversion (Call_Node);
3140 end if;
3141 end;
3143 -- Expansion of a dispatching call results in an indirect call, which in
3144 -- turn causes current values to be killed (see Resolve_Call), so on VM
3145 -- targets we do the call here to ensure consistent warnings between VM
3146 -- and non-VM targets.
3148 else
3149 Kill_Current_Values;
3150 end if;
3151 end Propagate_Tag;
3153 end Sem_Disp;