PR c/79855: add full stop to store merging param descriptions
[official-gcc.git] / gcc / ada / sem_disp.adb
blobef1a20b151ae8dd19fd7050bf7d0bb881b1b95dd
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-2016, 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 Atree; use Atree;
27 with Debug; use Debug;
28 with Elists; use Elists;
29 with Einfo; use Einfo;
30 with Exp_Disp; use Exp_Disp;
31 with Exp_Util; use Exp_Util;
32 with Exp_Ch7; use Exp_Ch7;
33 with Exp_Tss; use Exp_Tss;
34 with Errout; use Errout;
35 with Lib.Xref; use Lib.Xref;
36 with Namet; use Namet;
37 with Nlists; use Nlists;
38 with Nmake; use Nmake;
39 with Opt; use Opt;
40 with Output; use Output;
41 with Restrict; use Restrict;
42 with Rident; use Rident;
43 with Sem; use Sem;
44 with Sem_Aux; use Sem_Aux;
45 with Sem_Ch3; use Sem_Ch3;
46 with Sem_Ch6; use Sem_Ch6;
47 with Sem_Ch8; use Sem_Ch8;
48 with Sem_Eval; use Sem_Eval;
49 with Sem_Type; use Sem_Type;
50 with Sem_Util; use Sem_Util;
51 with Snames; use Snames;
52 with Sinfo; use Sinfo;
53 with Tbuild; use Tbuild;
54 with Uintp; use Uintp;
56 package body Sem_Disp is
58 -----------------------
59 -- Local Subprograms --
60 -----------------------
62 procedure Add_Dispatching_Operation
63 (Tagged_Type : Entity_Id;
64 New_Op : Entity_Id);
65 -- Add New_Op in the list of primitive operations of Tagged_Type
67 function Check_Controlling_Type
68 (T : Entity_Id;
69 Subp : Entity_Id) return Entity_Id;
70 -- T is the tagged type of a formal parameter or the result of Subp.
71 -- If the subprogram has a controlling parameter or result that matches
72 -- the type, then returns the tagged type of that parameter or result
73 -- (returning the designated tagged type in the case of an access
74 -- parameter); otherwise returns empty.
76 function Find_Hidden_Overridden_Primitive (S : Entity_Id) return Entity_Id;
77 -- [Ada 2012:AI-0125] Find an inherited hidden primitive of the dispatching
78 -- type of S that has the same name of S, a type-conformant profile, an
79 -- original corresponding operation O that is a primitive of a visible
80 -- ancestor of the dispatching type of S and O is visible at the point of
81 -- of declaration of S. If the entity is found the Alias of S is set to the
82 -- original corresponding operation S and its Overridden_Operation is set
83 -- to the found entity; otherwise return Empty.
85 -- This routine does not search for non-hidden primitives since they are
86 -- covered by the normal Ada 2005 rules.
88 function Is_Inherited_Public_Operation (Op : Entity_Id) return Boolean;
89 -- Check whether a primitive operation is inherited from an operation
90 -- declared in the visible part of its package.
92 -------------------------------
93 -- Add_Dispatching_Operation --
94 -------------------------------
96 procedure Add_Dispatching_Operation
97 (Tagged_Type : Entity_Id;
98 New_Op : Entity_Id)
100 List : constant Elist_Id := Primitive_Operations (Tagged_Type);
102 begin
103 -- The dispatching operation may already be on the list, if it is the
104 -- wrapper for an inherited function of a null extension (see Exp_Ch3
105 -- for the construction of function wrappers). The list of primitive
106 -- operations must not contain duplicates.
108 Append_Unique_Elmt (New_Op, List);
109 end Add_Dispatching_Operation;
111 ---------------------------
112 -- Covers_Some_Interface --
113 ---------------------------
115 function Covers_Some_Interface (Prim : Entity_Id) return Boolean is
116 Tagged_Type : constant Entity_Id := Find_Dispatching_Type (Prim);
117 Elmt : Elmt_Id;
118 E : Entity_Id;
120 begin
121 pragma Assert (Is_Dispatching_Operation (Prim));
123 -- Although this is a dispatching primitive we must check if its
124 -- dispatching type is available because it may be the primitive
125 -- of a private type not defined as tagged in its partial view.
127 if Present (Tagged_Type) and then Has_Interfaces (Tagged_Type) then
129 -- If the tagged type is frozen then the internal entities associated
130 -- with interfaces are available in the list of primitives of the
131 -- tagged type and can be used to speed up this search.
133 if Is_Frozen (Tagged_Type) then
134 Elmt := First_Elmt (Primitive_Operations (Tagged_Type));
135 while Present (Elmt) loop
136 E := Node (Elmt);
138 if Present (Interface_Alias (E))
139 and then Alias (E) = Prim
140 then
141 return True;
142 end if;
144 Next_Elmt (Elmt);
145 end loop;
147 -- Otherwise we must collect all the interface primitives and check
148 -- if the Prim will override some interface primitive.
150 else
151 declare
152 Ifaces_List : Elist_Id;
153 Iface_Elmt : Elmt_Id;
154 Iface : Entity_Id;
155 Iface_Prim : Entity_Id;
157 begin
158 Collect_Interfaces (Tagged_Type, Ifaces_List);
159 Iface_Elmt := First_Elmt (Ifaces_List);
160 while Present (Iface_Elmt) loop
161 Iface := Node (Iface_Elmt);
163 Elmt := First_Elmt (Primitive_Operations (Iface));
164 while Present (Elmt) loop
165 Iface_Prim := Node (Elmt);
167 if Chars (Iface) = Chars (Prim)
168 and then Is_Interface_Conformant
169 (Tagged_Type, Iface_Prim, Prim)
170 then
171 return True;
172 end if;
174 Next_Elmt (Elmt);
175 end loop;
177 Next_Elmt (Iface_Elmt);
178 end loop;
179 end;
180 end if;
181 end if;
183 return False;
184 end Covers_Some_Interface;
186 -------------------------------
187 -- Check_Controlling_Formals --
188 -------------------------------
190 procedure Check_Controlling_Formals
191 (Typ : Entity_Id;
192 Subp : Entity_Id)
194 Formal : Entity_Id;
195 Ctrl_Type : Entity_Id;
197 begin
198 Formal := First_Formal (Subp);
199 while Present (Formal) loop
200 Ctrl_Type := Check_Controlling_Type (Etype (Formal), Subp);
202 if Present (Ctrl_Type) then
204 -- When controlling type is concurrent and declared within a
205 -- generic or inside an instance use corresponding record type.
207 if Is_Concurrent_Type (Ctrl_Type)
208 and then Present (Corresponding_Record_Type (Ctrl_Type))
209 then
210 Ctrl_Type := Corresponding_Record_Type (Ctrl_Type);
211 end if;
213 if Ctrl_Type = Typ then
214 Set_Is_Controlling_Formal (Formal);
216 -- Ada 2005 (AI-231): Anonymous access types that are used in
217 -- controlling parameters exclude null because it is necessary
218 -- to read the tag to dispatch, and null has no tag.
220 if Ekind (Etype (Formal)) = E_Anonymous_Access_Type then
221 Set_Can_Never_Be_Null (Etype (Formal));
222 Set_Is_Known_Non_Null (Etype (Formal));
223 end if;
225 -- Check that the parameter's nominal subtype statically
226 -- matches the first subtype.
228 if Ekind (Etype (Formal)) = E_Anonymous_Access_Type then
229 if not Subtypes_Statically_Match
230 (Typ, Designated_Type (Etype (Formal)))
231 then
232 Error_Msg_N
233 ("parameter subtype does not match controlling type",
234 Formal);
235 end if;
237 -- Within a predicate function, the formal may be a subtype
238 -- of a tagged type, given that the predicate is expressed
239 -- in terms of the subtype.
241 elsif not Subtypes_Statically_Match (Typ, Etype (Formal))
242 and then not Is_Predicate_Function (Subp)
243 then
244 Error_Msg_N
245 ("parameter subtype does not match controlling type",
246 Formal);
247 end if;
249 if Present (Default_Value (Formal)) then
251 -- In Ada 2005, access parameters can have defaults
253 if Ekind (Etype (Formal)) = E_Anonymous_Access_Type
254 and then Ada_Version < Ada_2005
255 then
256 Error_Msg_N
257 ("default not allowed for controlling access parameter",
258 Default_Value (Formal));
260 elsif not Is_Tag_Indeterminate (Default_Value (Formal)) then
261 Error_Msg_N
262 ("default expression must be a tag indeterminate" &
263 " function call", Default_Value (Formal));
264 end if;
265 end if;
267 elsif Comes_From_Source (Subp) then
268 Error_Msg_N
269 ("operation can be dispatching in only one type", Subp);
270 end if;
271 end if;
273 Next_Formal (Formal);
274 end loop;
276 if Ekind_In (Subp, E_Function, E_Generic_Function) then
277 Ctrl_Type := Check_Controlling_Type (Etype (Subp), Subp);
279 if Present (Ctrl_Type) then
280 if Ctrl_Type = Typ then
281 Set_Has_Controlling_Result (Subp);
283 -- Check that result subtype statically matches first subtype
284 -- (Ada 2005): Subp may have a controlling access result.
286 if Subtypes_Statically_Match (Typ, Etype (Subp))
287 or else (Ekind (Etype (Subp)) = E_Anonymous_Access_Type
288 and then
289 Subtypes_Statically_Match
290 (Typ, Designated_Type (Etype (Subp))))
291 then
292 null;
294 else
295 Error_Msg_N
296 ("result subtype does not match controlling type", Subp);
297 end if;
299 elsif Comes_From_Source (Subp) then
300 Error_Msg_N
301 ("operation can be dispatching in only one type", Subp);
302 end if;
303 end if;
304 end if;
305 end Check_Controlling_Formals;
307 ----------------------------
308 -- Check_Controlling_Type --
309 ----------------------------
311 function Check_Controlling_Type
312 (T : Entity_Id;
313 Subp : Entity_Id) return Entity_Id
315 Tagged_Type : Entity_Id := Empty;
317 begin
318 if Is_Tagged_Type (T) then
319 if Is_First_Subtype (T) then
320 Tagged_Type := T;
321 else
322 Tagged_Type := Base_Type (T);
323 end if;
325 -- If the type is incomplete, it may have been declared without a
326 -- Tagged indication, but the full view may be tagged, in which case
327 -- that is the controlling type of the subprogram. This is one of the
328 -- approx. 579 places in the language where a lookahead would help.
330 elsif Ekind (T) = E_Incomplete_Type
331 and then Present (Full_View (T))
332 and then Is_Tagged_Type (Full_View (T))
333 then
334 Set_Is_Tagged_Type (T);
335 Tagged_Type := Full_View (T);
337 elsif Ekind (T) = E_Anonymous_Access_Type
338 and then Is_Tagged_Type (Designated_Type (T))
339 then
340 if Ekind (Designated_Type (T)) /= E_Incomplete_Type then
341 if Is_First_Subtype (Designated_Type (T)) then
342 Tagged_Type := Designated_Type (T);
343 else
344 Tagged_Type := Base_Type (Designated_Type (T));
345 end if;
347 -- Ada 2005: an incomplete type can be tagged. An operation with an
348 -- access parameter of the type is dispatching.
350 elsif Scope (Designated_Type (T)) = Current_Scope then
351 Tagged_Type := Designated_Type (T);
353 -- Ada 2005 (AI-50217)
355 elsif From_Limited_With (Designated_Type (T))
356 and then Has_Non_Limited_View (Designated_Type (T))
357 and then Scope (Designated_Type (T)) = Scope (Subp)
358 then
359 if Is_First_Subtype (Non_Limited_View (Designated_Type (T))) then
360 Tagged_Type := Non_Limited_View (Designated_Type (T));
361 else
362 Tagged_Type := Base_Type (Non_Limited_View
363 (Designated_Type (T)));
364 end if;
365 end if;
366 end if;
368 if No (Tagged_Type) or else Is_Class_Wide_Type (Tagged_Type) then
369 return Empty;
371 -- The dispatching type and the primitive operation must be defined in
372 -- the same scope, except in the case of internal operations and formal
373 -- abstract subprograms.
375 elsif ((Scope (Subp) = Scope (Tagged_Type) or else Is_Internal (Subp))
376 and then (not Is_Generic_Type (Tagged_Type)
377 or else not Comes_From_Source (Subp)))
378 or else
379 (Is_Formal_Subprogram (Subp) and then Is_Abstract_Subprogram (Subp))
380 or else
381 (Nkind (Parent (Parent (Subp))) = N_Subprogram_Renaming_Declaration
382 and then
383 Present (Corresponding_Formal_Spec (Parent (Parent (Subp))))
384 and then
385 Is_Abstract_Subprogram (Subp))
386 then
387 return Tagged_Type;
389 else
390 return Empty;
391 end if;
392 end Check_Controlling_Type;
394 ----------------------------
395 -- Check_Dispatching_Call --
396 ----------------------------
398 procedure Check_Dispatching_Call (N : Node_Id) is
399 Loc : constant Source_Ptr := Sloc (N);
400 Actual : Node_Id;
401 Formal : Entity_Id;
402 Control : Node_Id := Empty;
403 Func : Entity_Id;
404 Subp_Entity : Entity_Id;
405 Indeterm_Ancestor_Call : Boolean := False;
406 Indeterm_Ctrl_Type : Entity_Id;
408 Static_Tag : Node_Id := Empty;
409 -- If a controlling formal has a statically tagged actual, the tag of
410 -- this actual is to be used for any tag-indeterminate actual.
412 procedure Check_Direct_Call;
413 -- In the case when the controlling actual is a class-wide type whose
414 -- root type's completion is a task or protected type, the call is in
415 -- fact direct. This routine detects the above case and modifies the
416 -- call accordingly.
418 procedure Check_Dispatching_Context (Call : Node_Id);
419 -- If the call is tag-indeterminate and the entity being called is
420 -- abstract, verify that the context is a call that will eventually
421 -- provide a tag for dispatching, or has provided one already.
423 -----------------------
424 -- Check_Direct_Call --
425 -----------------------
427 procedure Check_Direct_Call is
428 Typ : Entity_Id := Etype (Control);
430 function Is_User_Defined_Equality (Id : Entity_Id) return Boolean;
431 -- Determine whether an entity denotes a user-defined equality
433 ------------------------------
434 -- Is_User_Defined_Equality --
435 ------------------------------
437 function Is_User_Defined_Equality (Id : Entity_Id) return Boolean is
438 begin
439 return
440 Ekind (Id) = E_Function
441 and then Chars (Id) = Name_Op_Eq
442 and then Comes_From_Source (Id)
444 -- Internally generated equalities have a full type declaration
445 -- as their parent.
447 and then Nkind (Parent (Id)) = N_Function_Specification;
448 end Is_User_Defined_Equality;
450 -- Start of processing for Check_Direct_Call
452 begin
453 -- Predefined primitives do not receive wrappers since they are built
454 -- from scratch for the corresponding record of synchronized types.
455 -- Equality is in general predefined, but is excluded from the check
456 -- when it is user-defined.
458 if Is_Predefined_Dispatching_Operation (Subp_Entity)
459 and then not Is_User_Defined_Equality (Subp_Entity)
460 then
461 return;
462 end if;
464 if Is_Class_Wide_Type (Typ) then
465 Typ := Root_Type (Typ);
466 end if;
468 if Is_Private_Type (Typ) and then Present (Full_View (Typ)) then
469 Typ := Full_View (Typ);
470 end if;
472 if Is_Concurrent_Type (Typ)
473 and then
474 Present (Corresponding_Record_Type (Typ))
475 then
476 Typ := Corresponding_Record_Type (Typ);
478 -- The concurrent record's list of primitives should contain a
479 -- wrapper for the entity of the call, retrieve it.
481 declare
482 Prim : Entity_Id;
483 Prim_Elmt : Elmt_Id;
484 Wrapper_Found : Boolean := False;
486 begin
487 Prim_Elmt := First_Elmt (Primitive_Operations (Typ));
488 while Present (Prim_Elmt) loop
489 Prim := Node (Prim_Elmt);
491 if Is_Primitive_Wrapper (Prim)
492 and then Wrapped_Entity (Prim) = Subp_Entity
493 then
494 Wrapper_Found := True;
495 exit;
496 end if;
498 Next_Elmt (Prim_Elmt);
499 end loop;
501 -- A primitive declared between two views should have a
502 -- corresponding wrapper.
504 pragma Assert (Wrapper_Found);
506 -- Modify the call by setting the proper entity
508 Set_Entity (Name (N), Prim);
509 end;
510 end if;
511 end Check_Direct_Call;
513 -------------------------------
514 -- Check_Dispatching_Context --
515 -------------------------------
517 procedure Check_Dispatching_Context (Call : Node_Id) is
518 Subp : constant Entity_Id := Entity (Name (Call));
520 procedure Abstract_Context_Error;
521 -- Error for abstract call dispatching on result is not dispatching
523 ----------------------------
524 -- Abstract_Context_Error --
525 ----------------------------
527 procedure Abstract_Context_Error is
528 begin
529 if Ekind (Subp) = E_Function then
530 Error_Msg_N
531 ("call to abstract function must be dispatching", N);
533 -- This error can occur for a procedure in the case of a call to
534 -- an abstract formal procedure with a statically tagged operand.
536 else
537 Error_Msg_N
538 ("call to abstract procedure must be dispatching", N);
539 end if;
540 end Abstract_Context_Error;
542 -- Local variables
544 Scop : constant Entity_Id := Current_Scope_No_Loops;
545 Typ : constant Entity_Id := Etype (Subp);
546 Par : Node_Id;
548 -- Start of processing for Check_Dispatching_Context
550 begin
551 if Is_Abstract_Subprogram (Subp)
552 and then No (Controlling_Argument (Call))
553 then
554 if Present (Alias (Subp))
555 and then not Is_Abstract_Subprogram (Alias (Subp))
556 and then No (DTC_Entity (Subp))
557 then
558 -- Private overriding of inherited abstract operation, call is
559 -- legal.
561 Set_Entity (Name (N), Alias (Subp));
562 return;
564 -- An obscure special case: a null procedure may have a class-
565 -- wide pre/postcondition that includes a call to an abstract
566 -- subp. Calls within the expression may not have been rewritten
567 -- as dispatching calls yet, because the null body appears in
568 -- the current declarative part. The expression will be properly
569 -- rewritten/reanalyzed when the postcondition procedure is built.
571 -- Similarly, if this is a pre/postcondition for an abstract
572 -- subprogram, it may call another abstract function which is
573 -- a primitive of an abstract type. The call is non-dispatching
574 -- but will be legal in overridings of the operation.
576 elsif In_Spec_Expression
577 and then
578 (Is_Subprogram (Scop)
579 or else Chars (Scop) = Name_Postcondition)
580 and then
581 (Is_Abstract_Subprogram (Scop)
582 or else
583 (Nkind (Parent (Scop)) = N_Procedure_Specification
584 and then Null_Present (Parent (Scop))))
585 then
586 null;
588 elsif Ekind (Current_Scope) = E_Function
589 and then Nkind (Unit_Declaration_Node (Scop)) =
590 N_Generic_Subprogram_Declaration
591 then
592 null;
594 else
595 -- We need to determine whether the context of the call
596 -- provides a tag to make the call dispatching. This requires
597 -- the call to be the actual in an enclosing call, and that
598 -- actual must be controlling. If the call is an operand of
599 -- equality, the other operand must not ve abstract.
601 if not Is_Tagged_Type (Typ)
602 and then not
603 (Ekind (Typ) = E_Anonymous_Access_Type
604 and then Is_Tagged_Type (Designated_Type (Typ)))
605 then
606 Abstract_Context_Error;
607 return;
608 end if;
610 Par := Parent (Call);
612 if Nkind (Par) = N_Parameter_Association then
613 Par := Parent (Par);
614 end if;
616 if Nkind (Par) = N_Qualified_Expression
617 or else Nkind (Par) = N_Unchecked_Type_Conversion
618 then
619 Par := Parent (Par);
620 end if;
622 if Nkind_In (Par, N_Function_Call, N_Procedure_Call_Statement)
623 and then Is_Entity_Name (Name (Par))
624 then
625 declare
626 Enc_Subp : constant Entity_Id := Entity (Name (Par));
627 A : Node_Id;
628 F : Entity_Id;
629 Control : Entity_Id;
630 Ret_Type : Entity_Id;
632 begin
633 -- Find controlling formal that can provide tag for the
634 -- tag-indeterminate actual. The corresponding actual
635 -- must be the corresponding class-wide type.
637 F := First_Formal (Enc_Subp);
638 A := First_Actual (Par);
640 -- Find controlling type of call. Dereference if function
641 -- returns an access type.
643 Ret_Type := Etype (Call);
644 if Is_Access_Type (Etype (Call)) then
645 Ret_Type := Designated_Type (Ret_Type);
646 end if;
648 while Present (F) loop
649 Control := Etype (A);
651 if Is_Access_Type (Control) then
652 Control := Designated_Type (Control);
653 end if;
655 if Is_Controlling_Formal (F)
656 and then not (Call = A or else Parent (Call) = A)
657 and then Control = Class_Wide_Type (Ret_Type)
658 then
659 return;
660 end if;
662 Next_Formal (F);
663 Next_Actual (A);
664 end loop;
666 if Nkind (Par) = N_Function_Call
667 and then Is_Tag_Indeterminate (Par)
668 then
669 -- The parent may be an actual of an enclosing call
671 Check_Dispatching_Context (Par);
672 return;
674 else
675 Error_Msg_N
676 ("call to abstract function must be dispatching",
677 Call);
678 return;
679 end if;
680 end;
682 -- For equality operators, one of the operands must be
683 -- statically or dynamically tagged.
685 elsif Nkind_In (Par, N_Op_Eq, N_Op_Ne) then
686 if N = Right_Opnd (Par)
687 and then Is_Tag_Indeterminate (Left_Opnd (Par))
688 then
689 Abstract_Context_Error;
691 elsif N = Left_Opnd (Par)
692 and then Is_Tag_Indeterminate (Right_Opnd (Par))
693 then
694 Abstract_Context_Error;
695 end if;
697 return;
699 -- The left-hand side of an assignment provides the tag
701 elsif Nkind (Par) = N_Assignment_Statement then
702 return;
704 else
705 Abstract_Context_Error;
706 end if;
707 end if;
708 end if;
709 end Check_Dispatching_Context;
711 -- Start of processing for Check_Dispatching_Call
713 begin
714 -- Find a controlling argument, if any
716 if Present (Parameter_Associations (N)) then
717 Subp_Entity := Entity (Name (N));
719 Actual := First_Actual (N);
720 Formal := First_Formal (Subp_Entity);
721 while Present (Actual) loop
722 Control := Find_Controlling_Arg (Actual);
723 exit when Present (Control);
725 -- Check for the case where the actual is a tag-indeterminate call
726 -- whose result type is different than the tagged type associated
727 -- with the containing call, but is an ancestor of the type.
729 if Is_Controlling_Formal (Formal)
730 and then Is_Tag_Indeterminate (Actual)
731 and then Base_Type (Etype (Actual)) /= Base_Type (Etype (Formal))
732 and then Is_Ancestor (Etype (Actual), Etype (Formal))
733 then
734 Indeterm_Ancestor_Call := True;
735 Indeterm_Ctrl_Type := Etype (Formal);
737 -- If the formal is controlling but the actual is not, the type
738 -- of the actual is statically known, and may be used as the
739 -- controlling tag for some other tag-indeterminate actual.
741 elsif Is_Controlling_Formal (Formal)
742 and then Is_Entity_Name (Actual)
743 and then Is_Tagged_Type (Etype (Actual))
744 then
745 Static_Tag := Actual;
746 end if;
748 Next_Actual (Actual);
749 Next_Formal (Formal);
750 end loop;
752 -- If the call doesn't have a controlling actual but does have an
753 -- indeterminate actual that requires dispatching treatment, then an
754 -- object is needed that will serve as the controlling argument for
755 -- a dispatching call on the indeterminate actual. This can occur
756 -- in the unusual situation of a default actual given by a tag-
757 -- indeterminate call and where the type of the call is an ancestor
758 -- of the type associated with a containing call to an inherited
759 -- operation (see AI-239).
761 -- Rather than create an object of the tagged type, which would
762 -- be problematic for various reasons (default initialization,
763 -- discriminants), the tag of the containing call's associated
764 -- tagged type is directly used to control the dispatching.
766 if No (Control)
767 and then Indeterm_Ancestor_Call
768 and then No (Static_Tag)
769 then
770 Control :=
771 Make_Attribute_Reference (Loc,
772 Prefix => New_Occurrence_Of (Indeterm_Ctrl_Type, Loc),
773 Attribute_Name => Name_Tag);
775 Analyze (Control);
776 end if;
778 if Present (Control) then
780 -- Verify that no controlling arguments are statically tagged
782 if Debug_Flag_E then
783 Write_Str ("Found Dispatching call");
784 Write_Int (Int (N));
785 Write_Eol;
786 end if;
788 Actual := First_Actual (N);
789 while Present (Actual) loop
790 if Actual /= Control then
792 if not Is_Controlling_Actual (Actual) then
793 null; -- Can be anything
795 elsif Is_Dynamically_Tagged (Actual) then
796 null; -- Valid parameter
798 elsif Is_Tag_Indeterminate (Actual) then
800 -- The tag is inherited from the enclosing call (the node
801 -- we are currently analyzing). Explicitly expand the
802 -- actual, since the previous call to Expand (from
803 -- Resolve_Call) had no way of knowing about the
804 -- required dispatching.
806 Propagate_Tag (Control, Actual);
808 else
809 Error_Msg_N
810 ("controlling argument is not dynamically tagged",
811 Actual);
812 return;
813 end if;
814 end if;
816 Next_Actual (Actual);
817 end loop;
819 -- Mark call as a dispatching call
821 Set_Controlling_Argument (N, Control);
822 Check_Restriction (No_Dispatching_Calls, N);
824 -- The dispatching call may need to be converted into a direct
825 -- call in certain cases.
827 Check_Direct_Call;
829 -- If there is a statically tagged actual and a tag-indeterminate
830 -- call to a function of the ancestor (such as that provided by a
831 -- default), then treat this as a dispatching call and propagate
832 -- the tag to the tag-indeterminate call(s).
834 elsif Present (Static_Tag) and then Indeterm_Ancestor_Call then
835 Control :=
836 Make_Attribute_Reference (Loc,
837 Prefix =>
838 New_Occurrence_Of (Etype (Static_Tag), Loc),
839 Attribute_Name => Name_Tag);
841 Analyze (Control);
843 Actual := First_Actual (N);
844 Formal := First_Formal (Subp_Entity);
845 while Present (Actual) loop
846 if Is_Tag_Indeterminate (Actual)
847 and then Is_Controlling_Formal (Formal)
848 then
849 Propagate_Tag (Control, Actual);
850 end if;
852 Next_Actual (Actual);
853 Next_Formal (Formal);
854 end loop;
856 Check_Dispatching_Context (N);
858 elsif Nkind (N) /= N_Function_Call then
860 -- The call is not dispatching, so check that there aren't any
861 -- tag-indeterminate abstract calls left among its actuals.
863 Actual := First_Actual (N);
864 while Present (Actual) loop
865 if Is_Tag_Indeterminate (Actual) then
867 -- Function call case
869 if Nkind (Original_Node (Actual)) = N_Function_Call then
870 Func := Entity (Name (Original_Node (Actual)));
872 -- If the actual is an attribute then it can't be abstract
873 -- (the only current case of a tag-indeterminate attribute
874 -- is the stream Input attribute).
876 elsif Nkind (Original_Node (Actual)) = N_Attribute_Reference
877 then
878 Func := Empty;
880 -- Ditto if it is an explicit dereference
882 elsif Nkind (Original_Node (Actual)) = N_Explicit_Dereference
883 then
884 Func := Empty;
886 -- Only other possibility is a qualified expression whose
887 -- constituent expression is itself a call.
889 else
890 Func :=
891 Entity (Name (Original_Node
892 (Expression (Original_Node (Actual)))));
893 end if;
895 if Present (Func) and then Is_Abstract_Subprogram (Func) then
896 Error_Msg_N
897 ("call to abstract function must be dispatching",
898 Actual);
899 end if;
900 end if;
902 Next_Actual (Actual);
903 end loop;
905 Check_Dispatching_Context (N);
906 return;
908 elsif Nkind (Parent (N)) in N_Subexpr then
909 Check_Dispatching_Context (N);
911 elsif Nkind (Parent (N)) = N_Assignment_Statement
912 and then Is_Class_Wide_Type (Etype (Name (Parent (N))))
913 then
914 return;
916 elsif Is_Abstract_Subprogram (Subp_Entity) then
917 Check_Dispatching_Context (N);
918 return;
919 end if;
921 else
922 -- If dispatching on result, the enclosing call, if any, will
923 -- determine the controlling argument. Otherwise this is the
924 -- primitive operation of the root type.
926 Check_Dispatching_Context (N);
927 end if;
928 end Check_Dispatching_Call;
930 ---------------------------------
931 -- Check_Dispatching_Operation --
932 ---------------------------------
934 procedure Check_Dispatching_Operation (Subp, Old_Subp : Entity_Id) is
935 Body_Is_Last_Primitive : Boolean := False;
936 Has_Dispatching_Parent : Boolean := False;
937 Ovr_Subp : Entity_Id := Empty;
938 Tagged_Type : Entity_Id;
940 begin
941 if not Ekind_In (Subp, E_Function, E_Procedure) then
942 return;
944 -- The Default_Initial_Condition procedure is not a primitive subprogram
945 -- even if it relates to a tagged type. This routine is not meant to be
946 -- inherited or overridden.
948 elsif Is_DIC_Procedure (Subp) then
949 return;
951 -- The "partial" and "full" type invariant procedures are not primitive
952 -- subprograms even if they relate to a tagged type. These routines are
953 -- not meant to be inherited or overridden.
955 elsif Is_Invariant_Procedure (Subp)
956 or else Is_Partial_Invariant_Procedure (Subp)
957 then
958 return;
959 end if;
961 Set_Is_Dispatching_Operation (Subp, False);
962 Tagged_Type := Find_Dispatching_Type (Subp);
964 -- Ada 2005 (AI-345): Use the corresponding record (if available).
965 -- Required because primitives of concurrent types are attached
966 -- to the corresponding record (not to the concurrent type).
968 if Ada_Version >= Ada_2005
969 and then Present (Tagged_Type)
970 and then Is_Concurrent_Type (Tagged_Type)
971 and then Present (Corresponding_Record_Type (Tagged_Type))
972 then
973 Tagged_Type := Corresponding_Record_Type (Tagged_Type);
974 end if;
976 -- (AI-345): The task body procedure is not a primitive of the tagged
977 -- type
979 if Present (Tagged_Type)
980 and then Is_Concurrent_Record_Type (Tagged_Type)
981 and then Present (Corresponding_Concurrent_Type (Tagged_Type))
982 and then Is_Task_Type (Corresponding_Concurrent_Type (Tagged_Type))
983 and then Subp = Get_Task_Body_Procedure
984 (Corresponding_Concurrent_Type (Tagged_Type))
985 then
986 return;
987 end if;
989 -- If Subp is derived from a dispatching operation then it should
990 -- always be treated as dispatching. In this case various checks
991 -- below will be bypassed. Makes sure that late declarations for
992 -- inherited private subprograms are treated as dispatching, even
993 -- if the associated tagged type is already frozen.
995 Has_Dispatching_Parent :=
996 Present (Alias (Subp))
997 and then Is_Dispatching_Operation (Alias (Subp));
999 if No (Tagged_Type) then
1001 -- Ada 2005 (AI-251): Check that Subp is not a primitive associated
1002 -- with an abstract interface type unless the interface acts as a
1003 -- parent type in a derivation. If the interface type is a formal
1004 -- type then the operation is not primitive and therefore legal.
1006 declare
1007 E : Entity_Id;
1008 Typ : Entity_Id;
1010 begin
1011 E := First_Entity (Subp);
1012 while Present (E) loop
1014 -- For an access parameter, check designated type
1016 if Ekind (Etype (E)) = E_Anonymous_Access_Type then
1017 Typ := Designated_Type (Etype (E));
1018 else
1019 Typ := Etype (E);
1020 end if;
1022 if Comes_From_Source (Subp)
1023 and then Is_Interface (Typ)
1024 and then not Is_Class_Wide_Type (Typ)
1025 and then not Is_Derived_Type (Typ)
1026 and then not Is_Generic_Type (Typ)
1027 and then not In_Instance
1028 then
1029 Error_Msg_N ("??declaration of& is too late!", Subp);
1030 Error_Msg_NE -- CODEFIX??
1031 ("\??spec should appear immediately after declaration "
1032 & "of & !", Subp, Typ);
1033 exit;
1034 end if;
1036 Next_Entity (E);
1037 end loop;
1039 -- In case of functions check also the result type
1041 if Ekind (Subp) = E_Function then
1042 if Is_Access_Type (Etype (Subp)) then
1043 Typ := Designated_Type (Etype (Subp));
1044 else
1045 Typ := Etype (Subp);
1046 end if;
1048 -- The following should be better commented, especially since
1049 -- we just added several new conditions here ???
1051 if Comes_From_Source (Subp)
1052 and then Is_Interface (Typ)
1053 and then not Is_Class_Wide_Type (Typ)
1054 and then not Is_Derived_Type (Typ)
1055 and then not Is_Generic_Type (Typ)
1056 and then not In_Instance
1057 then
1058 Error_Msg_N ("??declaration of& is too late!", Subp);
1059 Error_Msg_NE
1060 ("\??spec should appear immediately after declaration "
1061 & "of & !", Subp, Typ);
1062 end if;
1063 end if;
1064 end;
1066 return;
1068 -- The subprograms build internally after the freezing point (such as
1069 -- init procs, interface thunks, type support subprograms, and Offset
1070 -- to top functions for accessing interface components in variable
1071 -- size tagged types) are not primitives.
1073 elsif Is_Frozen (Tagged_Type)
1074 and then not Comes_From_Source (Subp)
1075 and then not Has_Dispatching_Parent
1076 then
1077 -- Complete decoration of internally built subprograms that override
1078 -- a dispatching primitive. These entities correspond with the
1079 -- following cases:
1081 -- 1. Ada 2005 (AI-391): Wrapper functions built by the expander
1082 -- to override functions of nonabstract null extensions. These
1083 -- primitives were added to the list of primitives of the tagged
1084 -- type by Make_Controlling_Function_Wrappers. However, attribute
1085 -- Is_Dispatching_Operation must be set to true.
1087 -- 2. Ada 2005 (AI-251): Wrapper procedures of null interface
1088 -- primitives.
1090 -- 3. Subprograms associated with stream attributes (built by
1091 -- New_Stream_Subprogram)
1093 if Present (Old_Subp)
1094 and then Present (Overridden_Operation (Subp))
1095 and then Is_Dispatching_Operation (Old_Subp)
1096 then
1097 pragma Assert
1098 ((Ekind (Subp) = E_Function
1099 and then Is_Dispatching_Operation (Old_Subp)
1100 and then Is_Null_Extension (Base_Type (Etype (Subp))))
1101 or else
1102 (Ekind (Subp) = E_Procedure
1103 and then Is_Dispatching_Operation (Old_Subp)
1104 and then Present (Alias (Old_Subp))
1105 and then Is_Null_Interface_Primitive
1106 (Ultimate_Alias (Old_Subp)))
1107 or else Get_TSS_Name (Subp) = TSS_Stream_Read
1108 or else Get_TSS_Name (Subp) = TSS_Stream_Write);
1110 Check_Controlling_Formals (Tagged_Type, Subp);
1111 Override_Dispatching_Operation (Tagged_Type, Old_Subp, Subp);
1112 Set_Is_Dispatching_Operation (Subp);
1113 end if;
1115 return;
1117 -- The operation may be a child unit, whose scope is the defining
1118 -- package, but which is not a primitive operation of the type.
1120 elsif Is_Child_Unit (Subp) then
1121 return;
1123 -- If the subprogram is not defined in a package spec, the only case
1124 -- where it can be a dispatching op is when it overrides an operation
1125 -- before the freezing point of the type.
1127 elsif ((not Is_Package_Or_Generic_Package (Scope (Subp)))
1128 or else In_Package_Body (Scope (Subp)))
1129 and then not Has_Dispatching_Parent
1130 then
1131 if not Comes_From_Source (Subp)
1132 or else (Present (Old_Subp) and then not Is_Frozen (Tagged_Type))
1133 then
1134 null;
1136 -- If the type is already frozen, the overriding is not allowed
1137 -- except when Old_Subp is not a dispatching operation (which can
1138 -- occur when Old_Subp was inherited by an untagged type). However,
1139 -- a body with no previous spec freezes the type *after* its
1140 -- declaration, and therefore is a legal overriding (unless the type
1141 -- has already been frozen). Only the first such body is legal.
1143 elsif Present (Old_Subp)
1144 and then Is_Dispatching_Operation (Old_Subp)
1145 then
1146 if Comes_From_Source (Subp)
1147 and then
1148 (Nkind (Unit_Declaration_Node (Subp)) = N_Subprogram_Body
1149 or else Nkind (Unit_Declaration_Node (Subp)) in N_Body_Stub)
1150 then
1151 declare
1152 Subp_Body : constant Node_Id := Unit_Declaration_Node (Subp);
1153 Decl_Item : Node_Id;
1155 begin
1156 -- ??? The checks here for whether the type has been frozen
1157 -- prior to the new body are not complete. It's not simple
1158 -- to check frozenness at this point since the body has
1159 -- already caused the type to be prematurely frozen in
1160 -- Analyze_Declarations, but we're forced to recheck this
1161 -- here because of the odd rule interpretation that allows
1162 -- the overriding if the type wasn't frozen prior to the
1163 -- body. The freezing action should probably be delayed
1164 -- until after the spec is seen, but that's a tricky
1165 -- change to the delicate freezing code.
1167 -- Look at each declaration following the type up until the
1168 -- new subprogram body. If any of the declarations is a body
1169 -- then the type has been frozen already so the overriding
1170 -- primitive is illegal.
1172 Decl_Item := Next (Parent (Tagged_Type));
1173 while Present (Decl_Item)
1174 and then (Decl_Item /= Subp_Body)
1175 loop
1176 if Comes_From_Source (Decl_Item)
1177 and then (Nkind (Decl_Item) in N_Proper_Body
1178 or else Nkind (Decl_Item) in N_Body_Stub)
1179 then
1180 Error_Msg_N ("overriding of& is too late!", Subp);
1181 Error_Msg_N
1182 ("\spec should appear immediately after the type!",
1183 Subp);
1184 exit;
1185 end if;
1187 Next (Decl_Item);
1188 end loop;
1190 -- If the subprogram doesn't follow in the list of
1191 -- declarations including the type then the type has
1192 -- definitely been frozen already and the body is illegal.
1194 if No (Decl_Item) then
1195 Error_Msg_N ("overriding of& is too late!", Subp);
1196 Error_Msg_N
1197 ("\spec should appear immediately after the type!",
1198 Subp);
1200 elsif Is_Frozen (Subp) then
1202 -- The subprogram body declares a primitive operation.
1203 -- If the subprogram is already frozen, we must update
1204 -- its dispatching information explicitly here. The
1205 -- information is taken from the overridden subprogram.
1206 -- We must also generate a cross-reference entry because
1207 -- references to other primitives were already created
1208 -- when type was frozen.
1210 Body_Is_Last_Primitive := True;
1212 if Present (DTC_Entity (Old_Subp)) then
1213 Set_DTC_Entity (Subp, DTC_Entity (Old_Subp));
1214 Set_DT_Position_Value (Subp, DT_Position (Old_Subp));
1216 if not Restriction_Active (No_Dispatching_Calls) then
1217 if Building_Static_DT (Tagged_Type) then
1219 -- If the static dispatch table has not been
1220 -- built then there is nothing else to do now;
1221 -- otherwise we notify that we cannot build the
1222 -- static dispatch table.
1224 if Has_Dispatch_Table (Tagged_Type) then
1225 Error_Msg_N
1226 ("overriding of& is too late for building "
1227 & " static dispatch tables!", Subp);
1228 Error_Msg_N
1229 ("\spec should appear immediately after "
1230 & "the type!", Subp);
1231 end if;
1233 -- No code required to register primitives in VM
1234 -- targets
1236 elsif not Tagged_Type_Expansion then
1237 null;
1239 else
1240 Insert_Actions_After (Subp_Body,
1241 Register_Primitive (Sloc (Subp_Body),
1242 Prim => Subp));
1243 end if;
1245 -- Indicate that this is an overriding operation,
1246 -- and replace the overridden entry in the list of
1247 -- primitive operations, which is used for xref
1248 -- generation subsequently.
1250 Generate_Reference (Tagged_Type, Subp, 'P', False);
1251 Override_Dispatching_Operation
1252 (Tagged_Type, Old_Subp, Subp);
1253 end if;
1254 end if;
1255 end if;
1256 end;
1258 else
1259 Error_Msg_N ("overriding of& is too late!", Subp);
1260 Error_Msg_N
1261 ("\subprogram spec should appear immediately after the type!",
1262 Subp);
1263 end if;
1265 -- If the type is not frozen yet and we are not in the overriding
1266 -- case it looks suspiciously like an attempt to define a primitive
1267 -- operation, which requires the declaration to be in a package spec
1268 -- (3.2.3(6)). Only report cases where the type and subprogram are
1269 -- in the same declaration list (by checking the enclosing parent
1270 -- declarations), to avoid spurious warnings on subprograms in
1271 -- instance bodies when the type is declared in the instance spec
1272 -- but hasn't been frozen by the instance body.
1274 elsif not Is_Frozen (Tagged_Type)
1275 and then In_Same_List (Parent (Tagged_Type), Parent (Parent (Subp)))
1276 then
1277 Error_Msg_N
1278 ("??not dispatching (must be defined in a package spec)", Subp);
1279 return;
1281 -- When the type is frozen, it is legitimate to define a new
1282 -- non-primitive operation.
1284 else
1285 return;
1286 end if;
1288 -- Now, we are sure that the scope is a package spec. If the subprogram
1289 -- is declared after the freezing point of the type that's an error
1291 elsif Is_Frozen (Tagged_Type) and then not Has_Dispatching_Parent then
1292 Error_Msg_N ("this primitive operation is declared too late", Subp);
1293 Error_Msg_NE
1294 ("??no primitive operations for& after this line",
1295 Freeze_Node (Tagged_Type),
1296 Tagged_Type);
1297 return;
1298 end if;
1300 Check_Controlling_Formals (Tagged_Type, Subp);
1302 Ovr_Subp := Old_Subp;
1304 -- [Ada 2012:AI-0125]: Search for inherited hidden primitive that may be
1305 -- overridden by Subp. This only applies to source subprograms, and
1306 -- their declaration must carry an explicit overriding indicator.
1308 if No (Ovr_Subp)
1309 and then Ada_Version >= Ada_2012
1310 and then Comes_From_Source (Subp)
1311 and then
1312 Nkind (Unit_Declaration_Node (Subp)) = N_Subprogram_Declaration
1313 then
1314 Ovr_Subp := Find_Hidden_Overridden_Primitive (Subp);
1316 -- Verify that the proper overriding indicator has been supplied.
1318 if Present (Ovr_Subp)
1319 and then
1320 not Must_Override (Specification (Unit_Declaration_Node (Subp)))
1321 then
1322 Error_Msg_NE ("missing overriding indicator for&", Subp, Subp);
1323 end if;
1324 end if;
1326 -- Now it should be a correct primitive operation, put it in the list
1328 if Present (Ovr_Subp) then
1330 -- If the type has interfaces we complete this check after we set
1331 -- attribute Is_Dispatching_Operation.
1333 Check_Subtype_Conformant (Subp, Ovr_Subp);
1335 -- A primitive operation with the name of a primitive controlled
1336 -- operation does not override a non-visible overriding controlled
1337 -- operation, i.e. one declared in a private part when the full
1338 -- view of a type is controlled. Conversely, it will override a
1339 -- visible operation that may be declared in a partial view when
1340 -- the full view is controlled.
1342 if Nam_In (Chars (Subp), Name_Initialize, Name_Adjust, Name_Finalize)
1343 and then Is_Controlled (Tagged_Type)
1344 and then not Is_Visibly_Controlled (Tagged_Type)
1345 and then not Is_Inherited_Public_Operation (Ovr_Subp)
1346 then
1347 Set_Overridden_Operation (Subp, Empty);
1349 -- If the subprogram specification carries an overriding
1350 -- indicator, no need for the warning: it is either redundant,
1351 -- or else an error will be reported.
1353 if Nkind (Parent (Subp)) = N_Procedure_Specification
1354 and then
1355 (Must_Override (Parent (Subp))
1356 or else Must_Not_Override (Parent (Subp)))
1357 then
1358 null;
1360 -- Here we need the warning
1362 else
1363 Error_Msg_NE
1364 ("operation does not override inherited&??", Subp, Subp);
1365 end if;
1367 else
1368 Override_Dispatching_Operation (Tagged_Type, Ovr_Subp, Subp);
1370 -- Ada 2005 (AI-251): In case of late overriding of a primitive
1371 -- that covers abstract interface subprograms we must register it
1372 -- in all the secondary dispatch tables associated with abstract
1373 -- interfaces. We do this now only if not building static tables,
1374 -- nor when the expander is inactive (we avoid trying to register
1375 -- primitives in semantics-only mode, since the type may not have
1376 -- an associated dispatch table). Otherwise the patch code is
1377 -- emitted after those tables are built, to prevent access before
1378 -- elaboration in gigi.
1380 if Body_Is_Last_Primitive and then Expander_Active then
1381 declare
1382 Subp_Body : constant Node_Id := Unit_Declaration_Node (Subp);
1383 Elmt : Elmt_Id;
1384 Prim : Node_Id;
1386 begin
1387 Elmt := First_Elmt (Primitive_Operations (Tagged_Type));
1388 while Present (Elmt) loop
1389 Prim := Node (Elmt);
1391 -- No code required to register primitives in VM targets
1393 if Present (Alias (Prim))
1394 and then Present (Interface_Alias (Prim))
1395 and then Alias (Prim) = Subp
1396 and then not Building_Static_DT (Tagged_Type)
1397 and then Tagged_Type_Expansion
1398 then
1399 Insert_Actions_After (Subp_Body,
1400 Register_Primitive (Sloc (Subp_Body), Prim => Prim));
1401 end if;
1403 Next_Elmt (Elmt);
1404 end loop;
1406 -- Redisplay the contents of the updated dispatch table
1408 if Debug_Flag_ZZ then
1409 Write_Str ("Late overriding: ");
1410 Write_DT (Tagged_Type);
1411 end if;
1412 end;
1413 end if;
1414 end if;
1416 -- If the tagged type is a concurrent type then we must be compiling
1417 -- with no code generation (we are either compiling a generic unit or
1418 -- compiling under -gnatc mode) because we have previously tested that
1419 -- no serious errors has been reported. In this case we do not add the
1420 -- primitive to the list of primitives of Tagged_Type but we leave the
1421 -- primitive decorated as a dispatching operation to be able to analyze
1422 -- and report errors associated with the Object.Operation notation.
1424 elsif Is_Concurrent_Type (Tagged_Type) then
1425 pragma Assert (not Expander_Active);
1427 -- Attach operation to list of primitives of the synchronized type
1428 -- itself, for ASIS use.
1430 Append_Elmt (Subp, Direct_Primitive_Operations (Tagged_Type));
1432 -- If no old subprogram, then we add this as a dispatching operation,
1433 -- but we avoid doing this if an error was posted, to prevent annoying
1434 -- cascaded errors.
1436 elsif not Error_Posted (Subp) then
1437 Add_Dispatching_Operation (Tagged_Type, Subp);
1438 end if;
1440 Set_Is_Dispatching_Operation (Subp, True);
1442 -- Ada 2005 (AI-251): If the type implements interfaces we must check
1443 -- subtype conformance against all the interfaces covered by this
1444 -- primitive.
1446 if Present (Ovr_Subp)
1447 and then Has_Interfaces (Tagged_Type)
1448 then
1449 declare
1450 Ifaces_List : Elist_Id;
1451 Iface_Elmt : Elmt_Id;
1452 Iface_Prim_Elmt : Elmt_Id;
1453 Iface_Prim : Entity_Id;
1454 Ret_Typ : Entity_Id;
1456 begin
1457 Collect_Interfaces (Tagged_Type, Ifaces_List);
1459 Iface_Elmt := First_Elmt (Ifaces_List);
1460 while Present (Iface_Elmt) loop
1461 if not Is_Ancestor (Node (Iface_Elmt), Tagged_Type) then
1462 Iface_Prim_Elmt :=
1463 First_Elmt (Primitive_Operations (Node (Iface_Elmt)));
1464 while Present (Iface_Prim_Elmt) loop
1465 Iface_Prim := Node (Iface_Prim_Elmt);
1467 if Is_Interface_Conformant
1468 (Tagged_Type, Iface_Prim, Subp)
1469 then
1470 -- Handle procedures, functions whose return type
1471 -- matches, or functions not returning interfaces
1473 if Ekind (Subp) = E_Procedure
1474 or else Etype (Iface_Prim) = Etype (Subp)
1475 or else not Is_Interface (Etype (Iface_Prim))
1476 then
1477 Check_Subtype_Conformant
1478 (New_Id => Subp,
1479 Old_Id => Iface_Prim,
1480 Err_Loc => Subp,
1481 Skip_Controlling_Formals => True);
1483 -- Handle functions returning interfaces
1485 elsif Implements_Interface
1486 (Etype (Subp), Etype (Iface_Prim))
1487 then
1488 -- Temporarily force both entities to return the
1489 -- same type. Required because Subtype_Conformant
1490 -- does not handle this case.
1492 Ret_Typ := Etype (Iface_Prim);
1493 Set_Etype (Iface_Prim, Etype (Subp));
1495 Check_Subtype_Conformant
1496 (New_Id => Subp,
1497 Old_Id => Iface_Prim,
1498 Err_Loc => Subp,
1499 Skip_Controlling_Formals => True);
1501 Set_Etype (Iface_Prim, Ret_Typ);
1502 end if;
1503 end if;
1505 Next_Elmt (Iface_Prim_Elmt);
1506 end loop;
1507 end if;
1509 Next_Elmt (Iface_Elmt);
1510 end loop;
1511 end;
1512 end if;
1514 if not Body_Is_Last_Primitive then
1515 Set_DT_Position_Value (Subp, No_Uint);
1517 elsif Has_Controlled_Component (Tagged_Type)
1518 and then Nam_In (Chars (Subp), Name_Initialize,
1519 Name_Adjust,
1520 Name_Finalize,
1521 Name_Finalize_Address)
1522 then
1523 declare
1524 F_Node : constant Node_Id := Freeze_Node (Tagged_Type);
1525 Decl : Node_Id;
1526 Old_P : Entity_Id;
1527 Old_Bod : Node_Id;
1528 Old_Spec : Entity_Id;
1530 C_Names : constant array (1 .. 4) of Name_Id :=
1531 (Name_Initialize,
1532 Name_Adjust,
1533 Name_Finalize,
1534 Name_Finalize_Address);
1536 D_Names : constant array (1 .. 4) of TSS_Name_Type :=
1537 (TSS_Deep_Initialize,
1538 TSS_Deep_Adjust,
1539 TSS_Deep_Finalize,
1540 TSS_Finalize_Address);
1542 begin
1543 -- Remove previous controlled function which was constructed and
1544 -- analyzed when the type was frozen. This requires removing the
1545 -- body of the redefined primitive, as well as its specification
1546 -- if needed (there is no spec created for Deep_Initialize, see
1547 -- exp_ch3.adb). We must also dismantle the exception information
1548 -- that may have been generated for it when front end zero-cost
1549 -- tables are enabled.
1551 for J in D_Names'Range loop
1552 Old_P := TSS (Tagged_Type, D_Names (J));
1554 if Present (Old_P)
1555 and then Chars (Subp) = C_Names (J)
1556 then
1557 Old_Bod := Unit_Declaration_Node (Old_P);
1558 Remove (Old_Bod);
1559 Set_Is_Eliminated (Old_P);
1560 Set_Scope (Old_P, Scope (Current_Scope));
1562 if Nkind (Old_Bod) = N_Subprogram_Body
1563 and then Present (Corresponding_Spec (Old_Bod))
1564 then
1565 Old_Spec := Corresponding_Spec (Old_Bod);
1566 Set_Has_Completion (Old_Spec, False);
1567 end if;
1568 end if;
1569 end loop;
1571 Build_Late_Proc (Tagged_Type, Chars (Subp));
1573 -- The new operation is added to the actions of the freeze node
1574 -- for the type, but this node has already been analyzed, so we
1575 -- must retrieve and analyze explicitly the new body.
1577 if Present (F_Node)
1578 and then Present (Actions (F_Node))
1579 then
1580 Decl := Last (Actions (F_Node));
1581 Analyze (Decl);
1582 end if;
1583 end;
1584 end if;
1585 end Check_Dispatching_Operation;
1587 ------------------------------------------
1588 -- Check_Operation_From_Incomplete_Type --
1589 ------------------------------------------
1591 procedure Check_Operation_From_Incomplete_Type
1592 (Subp : Entity_Id;
1593 Typ : Entity_Id)
1595 Full : constant Entity_Id := Full_View (Typ);
1596 Parent_Typ : constant Entity_Id := Etype (Full);
1597 Old_Prim : constant Elist_Id := Primitive_Operations (Parent_Typ);
1598 New_Prim : constant Elist_Id := Primitive_Operations (Full);
1599 Op1, Op2 : Elmt_Id;
1600 Prev : Elmt_Id := No_Elmt;
1602 function Derives_From (Parent_Subp : Entity_Id) return Boolean;
1603 -- Check that Subp has profile of an operation derived from Parent_Subp.
1604 -- Subp must have a parameter or result type that is Typ or an access
1605 -- parameter or access result type that designates Typ.
1607 ------------------
1608 -- Derives_From --
1609 ------------------
1611 function Derives_From (Parent_Subp : Entity_Id) return Boolean is
1612 F1, F2 : Entity_Id;
1614 begin
1615 if Chars (Parent_Subp) /= Chars (Subp) then
1616 return False;
1617 end if;
1619 -- Check that the type of controlling formals is derived from the
1620 -- parent subprogram's controlling formal type (or designated type
1621 -- if the formal type is an anonymous access type).
1623 F1 := First_Formal (Parent_Subp);
1624 F2 := First_Formal (Subp);
1625 while Present (F1) and then Present (F2) loop
1626 if Ekind (Etype (F1)) = E_Anonymous_Access_Type then
1627 if Ekind (Etype (F2)) /= E_Anonymous_Access_Type then
1628 return False;
1629 elsif Designated_Type (Etype (F1)) = Parent_Typ
1630 and then Designated_Type (Etype (F2)) /= Full
1631 then
1632 return False;
1633 end if;
1635 elsif Ekind (Etype (F2)) = E_Anonymous_Access_Type then
1636 return False;
1638 elsif Etype (F1) = Parent_Typ and then Etype (F2) /= Full then
1639 return False;
1640 end if;
1642 Next_Formal (F1);
1643 Next_Formal (F2);
1644 end loop;
1646 -- Check that a controlling result type is derived from the parent
1647 -- subprogram's result type (or designated type if the result type
1648 -- is an anonymous access type).
1650 if Ekind (Parent_Subp) = E_Function then
1651 if Ekind (Subp) /= E_Function then
1652 return False;
1654 elsif Ekind (Etype (Parent_Subp)) = E_Anonymous_Access_Type then
1655 if Ekind (Etype (Subp)) /= E_Anonymous_Access_Type then
1656 return False;
1658 elsif Designated_Type (Etype (Parent_Subp)) = Parent_Typ
1659 and then Designated_Type (Etype (Subp)) /= Full
1660 then
1661 return False;
1662 end if;
1664 elsif Ekind (Etype (Subp)) = E_Anonymous_Access_Type then
1665 return False;
1667 elsif Etype (Parent_Subp) = Parent_Typ
1668 and then Etype (Subp) /= Full
1669 then
1670 return False;
1671 end if;
1673 elsif Ekind (Subp) = E_Function then
1674 return False;
1675 end if;
1677 return No (F1) and then No (F2);
1678 end Derives_From;
1680 -- Start of processing for Check_Operation_From_Incomplete_Type
1682 begin
1683 -- The operation may override an inherited one, or may be a new one
1684 -- altogether. The inherited operation will have been hidden by the
1685 -- current one at the point of the type derivation, so it does not
1686 -- appear in the list of primitive operations of the type. We have to
1687 -- find the proper place of insertion in the list of primitive opera-
1688 -- tions by iterating over the list for the parent type.
1690 Op1 := First_Elmt (Old_Prim);
1691 Op2 := First_Elmt (New_Prim);
1692 while Present (Op1) and then Present (Op2) loop
1693 if Derives_From (Node (Op1)) then
1694 if No (Prev) then
1696 -- Avoid adding it to the list of primitives if already there
1698 if Node (Op2) /= Subp then
1699 Prepend_Elmt (Subp, New_Prim);
1700 end if;
1702 else
1703 Insert_Elmt_After (Subp, Prev);
1704 end if;
1706 return;
1707 end if;
1709 Prev := Op2;
1710 Next_Elmt (Op1);
1711 Next_Elmt (Op2);
1712 end loop;
1714 -- Operation is a new primitive
1716 Append_Elmt (Subp, New_Prim);
1717 end Check_Operation_From_Incomplete_Type;
1719 ---------------------------------------
1720 -- Check_Operation_From_Private_View --
1721 ---------------------------------------
1723 procedure Check_Operation_From_Private_View (Subp, Old_Subp : Entity_Id) is
1724 Tagged_Type : Entity_Id;
1726 begin
1727 if Is_Dispatching_Operation (Alias (Subp)) then
1728 Set_Scope (Subp, Current_Scope);
1729 Tagged_Type := Find_Dispatching_Type (Subp);
1731 -- Add Old_Subp to primitive operations if not already present
1733 if Present (Tagged_Type) and then Is_Tagged_Type (Tagged_Type) then
1734 Append_Unique_Elmt (Old_Subp, Primitive_Operations (Tagged_Type));
1736 -- If Old_Subp isn't already marked as dispatching then this is
1737 -- the case of an operation of an untagged private type fulfilled
1738 -- by a tagged type that overrides an inherited dispatching
1739 -- operation, so we set the necessary dispatching attributes here.
1741 if not Is_Dispatching_Operation (Old_Subp) then
1743 -- If the untagged type has no discriminants, and the full
1744 -- view is constrained, there will be a spurious mismatch of
1745 -- subtypes on the controlling arguments, because the tagged
1746 -- type is the internal base type introduced in the derivation.
1747 -- Use the original type to verify conformance, rather than the
1748 -- base type.
1750 if not Comes_From_Source (Tagged_Type)
1751 and then Has_Discriminants (Tagged_Type)
1752 then
1753 declare
1754 Formal : Entity_Id;
1756 begin
1757 Formal := First_Formal (Old_Subp);
1758 while Present (Formal) loop
1759 if Tagged_Type = Base_Type (Etype (Formal)) then
1760 Tagged_Type := Etype (Formal);
1761 end if;
1763 Next_Formal (Formal);
1764 end loop;
1765 end;
1767 if Tagged_Type = Base_Type (Etype (Old_Subp)) then
1768 Tagged_Type := Etype (Old_Subp);
1769 end if;
1770 end if;
1772 Check_Controlling_Formals (Tagged_Type, Old_Subp);
1773 Set_Is_Dispatching_Operation (Old_Subp, True);
1774 Set_DT_Position_Value (Old_Subp, No_Uint);
1775 end if;
1777 -- If the old subprogram is an explicit renaming of some other
1778 -- entity, it is not overridden by the inherited subprogram.
1779 -- Otherwise, update its alias and other attributes.
1781 if Present (Alias (Old_Subp))
1782 and then Nkind (Unit_Declaration_Node (Old_Subp)) /=
1783 N_Subprogram_Renaming_Declaration
1784 then
1785 Set_Alias (Old_Subp, Alias (Subp));
1787 -- The derived subprogram should inherit the abstractness of
1788 -- the parent subprogram (except in the case of a function
1789 -- returning the type). This sets the abstractness properly
1790 -- for cases where a private extension may have inherited an
1791 -- abstract operation, but the full type is derived from a
1792 -- descendant type and inherits a nonabstract version.
1794 if Etype (Subp) /= Tagged_Type then
1795 Set_Is_Abstract_Subprogram
1796 (Old_Subp, Is_Abstract_Subprogram (Alias (Subp)));
1797 end if;
1798 end if;
1799 end if;
1800 end if;
1801 end Check_Operation_From_Private_View;
1803 --------------------------
1804 -- Find_Controlling_Arg --
1805 --------------------------
1807 function Find_Controlling_Arg (N : Node_Id) return Node_Id is
1808 Orig_Node : constant Node_Id := Original_Node (N);
1809 Typ : Entity_Id;
1811 begin
1812 if Nkind (Orig_Node) = N_Qualified_Expression then
1813 return Find_Controlling_Arg (Expression (Orig_Node));
1814 end if;
1816 -- Dispatching on result case. If expansion is disabled, the node still
1817 -- has the structure of a function call. However, if the function name
1818 -- is an operator and the call was given in infix form, the original
1819 -- node has no controlling result and we must examine the current node.
1821 if Nkind (N) = N_Function_Call
1822 and then Present (Controlling_Argument (N))
1823 and then Has_Controlling_Result (Entity (Name (N)))
1824 then
1825 return Controlling_Argument (N);
1827 -- If expansion is enabled, the call may have been transformed into
1828 -- an indirect call, and we need to recover the original node.
1830 elsif Nkind (Orig_Node) = N_Function_Call
1831 and then Present (Controlling_Argument (Orig_Node))
1832 and then Has_Controlling_Result (Entity (Name (Orig_Node)))
1833 then
1834 return Controlling_Argument (Orig_Node);
1836 -- Type conversions are dynamically tagged if the target type, or its
1837 -- designated type, are classwide. An interface conversion expands into
1838 -- a dereference, so test must be performed on the original node.
1840 elsif Nkind (Orig_Node) = N_Type_Conversion
1841 and then Nkind (N) = N_Explicit_Dereference
1842 and then Is_Controlling_Actual (N)
1843 then
1844 declare
1845 Target_Type : constant Entity_Id :=
1846 Entity (Subtype_Mark (Orig_Node));
1848 begin
1849 if Is_Class_Wide_Type (Target_Type) then
1850 return N;
1852 elsif Is_Access_Type (Target_Type)
1853 and then Is_Class_Wide_Type (Designated_Type (Target_Type))
1854 then
1855 return N;
1857 else
1858 return Empty;
1859 end if;
1860 end;
1862 -- Normal case
1864 elsif Is_Controlling_Actual (N)
1865 or else
1866 (Nkind (Parent (N)) = N_Qualified_Expression
1867 and then Is_Controlling_Actual (Parent (N)))
1868 then
1869 Typ := Etype (N);
1871 if Is_Access_Type (Typ) then
1873 -- In the case of an Access attribute, use the type of the prefix,
1874 -- since in the case of an actual for an access parameter, the
1875 -- attribute's type may be of a specific designated type, even
1876 -- though the prefix type is class-wide.
1878 if Nkind (N) = N_Attribute_Reference then
1879 Typ := Etype (Prefix (N));
1881 -- An allocator is dispatching if the type of qualified expression
1882 -- is class_wide, in which case this is the controlling type.
1884 elsif Nkind (Orig_Node) = N_Allocator
1885 and then Nkind (Expression (Orig_Node)) = N_Qualified_Expression
1886 then
1887 Typ := Etype (Expression (Orig_Node));
1888 else
1889 Typ := Designated_Type (Typ);
1890 end if;
1891 end if;
1893 if Is_Class_Wide_Type (Typ)
1894 or else
1895 (Nkind (Parent (N)) = N_Qualified_Expression
1896 and then Is_Access_Type (Etype (N))
1897 and then Is_Class_Wide_Type (Designated_Type (Etype (N))))
1898 then
1899 return N;
1900 end if;
1901 end if;
1903 return Empty;
1904 end Find_Controlling_Arg;
1906 ---------------------------
1907 -- Find_Dispatching_Type --
1908 ---------------------------
1910 function Find_Dispatching_Type (Subp : Entity_Id) return Entity_Id is
1911 A_Formal : Entity_Id;
1912 Formal : Entity_Id;
1913 Ctrl_Type : Entity_Id;
1915 begin
1916 if Ekind_In (Subp, E_Function, E_Procedure)
1917 and then Present (DTC_Entity (Subp))
1918 then
1919 return Scope (DTC_Entity (Subp));
1921 -- For subprograms internally generated by derivations of tagged types
1922 -- use the alias subprogram as a reference to locate the dispatching
1923 -- type of Subp.
1925 elsif not Comes_From_Source (Subp)
1926 and then Present (Alias (Subp))
1927 and then Is_Dispatching_Operation (Alias (Subp))
1928 then
1929 if Ekind (Alias (Subp)) = E_Function
1930 and then Has_Controlling_Result (Alias (Subp))
1931 then
1932 return Check_Controlling_Type (Etype (Subp), Subp);
1934 else
1935 Formal := First_Formal (Subp);
1936 A_Formal := First_Formal (Alias (Subp));
1937 while Present (A_Formal) loop
1938 if Is_Controlling_Formal (A_Formal) then
1939 return Check_Controlling_Type (Etype (Formal), Subp);
1940 end if;
1942 Next_Formal (Formal);
1943 Next_Formal (A_Formal);
1944 end loop;
1946 pragma Assert (False);
1947 return Empty;
1948 end if;
1950 -- General case
1952 else
1953 Formal := First_Formal (Subp);
1954 while Present (Formal) loop
1955 Ctrl_Type := Check_Controlling_Type (Etype (Formal), Subp);
1957 if Present (Ctrl_Type) then
1958 return Ctrl_Type;
1959 end if;
1961 Next_Formal (Formal);
1962 end loop;
1964 -- The subprogram may also be dispatching on result
1966 if Present (Etype (Subp)) then
1967 return Check_Controlling_Type (Etype (Subp), Subp);
1968 end if;
1969 end if;
1971 pragma Assert (not Is_Dispatching_Operation (Subp));
1972 return Empty;
1973 end Find_Dispatching_Type;
1975 --------------------------------------
1976 -- Find_Hidden_Overridden_Primitive --
1977 --------------------------------------
1979 function Find_Hidden_Overridden_Primitive (S : Entity_Id) return Entity_Id
1981 Tag_Typ : constant Entity_Id := Find_Dispatching_Type (S);
1982 Elmt : Elmt_Id;
1983 Orig_Prim : Entity_Id;
1984 Prim : Entity_Id;
1985 Vis_List : Elist_Id;
1987 begin
1988 -- This Ada 2012 rule applies only for type extensions or private
1989 -- extensions, where the parent type is not in a parent unit, and
1990 -- where an operation is never declared but still inherited.
1992 if No (Tag_Typ)
1993 or else not Is_Record_Type (Tag_Typ)
1994 or else Etype (Tag_Typ) = Tag_Typ
1995 or else In_Open_Scopes (Scope (Etype (Tag_Typ)))
1996 then
1997 return Empty;
1998 end if;
2000 -- Collect the list of visible ancestor of the tagged type
2002 Vis_List := Visible_Ancestors (Tag_Typ);
2004 Elmt := First_Elmt (Primitive_Operations (Tag_Typ));
2005 while Present (Elmt) loop
2006 Prim := Node (Elmt);
2008 -- Find an inherited hidden dispatching primitive with the name of S
2009 -- and a type-conformant profile.
2011 if Present (Alias (Prim))
2012 and then Is_Hidden (Alias (Prim))
2013 and then Find_Dispatching_Type (Alias (Prim)) /= Tag_Typ
2014 and then Primitive_Names_Match (S, Prim)
2015 and then Type_Conformant (S, Prim)
2016 then
2017 declare
2018 Vis_Ancestor : Elmt_Id;
2019 Elmt : Elmt_Id;
2021 begin
2022 -- The original corresponding operation of Prim must be an
2023 -- operation of a visible ancestor of the dispatching type S,
2024 -- and the original corresponding operation of S2 must be
2025 -- visible.
2027 Orig_Prim := Original_Corresponding_Operation (Prim);
2029 if Orig_Prim /= Prim
2030 and then Is_Immediately_Visible (Orig_Prim)
2031 then
2032 Vis_Ancestor := First_Elmt (Vis_List);
2033 while Present (Vis_Ancestor) loop
2034 Elmt :=
2035 First_Elmt (Primitive_Operations (Node (Vis_Ancestor)));
2036 while Present (Elmt) loop
2037 if Node (Elmt) = Orig_Prim then
2038 Set_Overridden_Operation (S, Prim);
2039 Set_Alias (Prim, Orig_Prim);
2040 return Prim;
2041 end if;
2043 Next_Elmt (Elmt);
2044 end loop;
2046 Next_Elmt (Vis_Ancestor);
2047 end loop;
2048 end if;
2049 end;
2050 end if;
2052 Next_Elmt (Elmt);
2053 end loop;
2055 return Empty;
2056 end Find_Hidden_Overridden_Primitive;
2058 ---------------------------------------
2059 -- Find_Primitive_Covering_Interface --
2060 ---------------------------------------
2062 function Find_Primitive_Covering_Interface
2063 (Tagged_Type : Entity_Id;
2064 Iface_Prim : Entity_Id) return Entity_Id
2066 E : Entity_Id;
2067 El : Elmt_Id;
2069 begin
2070 pragma Assert (Is_Interface (Find_Dispatching_Type (Iface_Prim))
2071 or else (Present (Alias (Iface_Prim))
2072 and then
2073 Is_Interface
2074 (Find_Dispatching_Type (Ultimate_Alias (Iface_Prim)))));
2076 -- Search in the homonym chain. Done to speed up locating visible
2077 -- entities and required to catch primitives associated with the partial
2078 -- view of private types when processing the corresponding full view.
2080 E := Current_Entity (Iface_Prim);
2081 while Present (E) loop
2082 if Is_Subprogram (E)
2083 and then Is_Dispatching_Operation (E)
2084 and then Is_Interface_Conformant (Tagged_Type, Iface_Prim, E)
2085 then
2086 return E;
2087 end if;
2089 E := Homonym (E);
2090 end loop;
2092 -- Search in the list of primitives of the type. Required to locate
2093 -- the covering primitive if the covering primitive is not visible
2094 -- (for example, non-visible inherited primitive of private type).
2096 El := First_Elmt (Primitive_Operations (Tagged_Type));
2097 while Present (El) loop
2098 E := Node (El);
2100 -- Keep separate the management of internal entities that link
2101 -- primitives with interface primitives from tagged type primitives.
2103 if No (Interface_Alias (E)) then
2104 if Present (Alias (E)) then
2106 -- This interface primitive has not been covered yet
2108 if Alias (E) = Iface_Prim then
2109 return E;
2111 -- The covering primitive was inherited
2113 elsif Overridden_Operation (Ultimate_Alias (E))
2114 = Iface_Prim
2115 then
2116 return E;
2117 end if;
2118 end if;
2120 -- Check if E covers the interface primitive (includes case in
2121 -- which E is an inherited private primitive).
2123 if Is_Interface_Conformant (Tagged_Type, Iface_Prim, E) then
2124 return E;
2125 end if;
2127 -- Use the internal entity that links the interface primitive with
2128 -- the covering primitive to locate the entity.
2130 elsif Interface_Alias (E) = Iface_Prim then
2131 return Alias (E);
2132 end if;
2134 Next_Elmt (El);
2135 end loop;
2137 -- Not found
2139 return Empty;
2140 end Find_Primitive_Covering_Interface;
2142 ---------------------------
2143 -- Inherited_Subprograms --
2144 ---------------------------
2146 function Inherited_Subprograms
2147 (S : Entity_Id;
2148 No_Interfaces : Boolean := False;
2149 Interfaces_Only : Boolean := False;
2150 One_Only : Boolean := False) return Subprogram_List
2152 Result : Subprogram_List (1 .. 6000);
2153 -- 6000 here is intended to be infinity. We could use an expandable
2154 -- table, but it would be awfully heavy, and there is no way that we
2155 -- could reasonably exceed this value.
2157 N : Nat := 0;
2158 -- Number of entries in Result
2160 Parent_Op : Entity_Id;
2161 -- Traverses the Overridden_Operation chain
2163 procedure Store_IS (E : Entity_Id);
2164 -- Stores E in Result if not already stored
2166 --------------
2167 -- Store_IS --
2168 --------------
2170 procedure Store_IS (E : Entity_Id) is
2171 begin
2172 for J in 1 .. N loop
2173 if E = Result (J) then
2174 return;
2175 end if;
2176 end loop;
2178 N := N + 1;
2179 Result (N) := E;
2180 end Store_IS;
2182 -- Start of processing for Inherited_Subprograms
2184 begin
2185 pragma Assert (not (No_Interfaces and Interfaces_Only));
2187 if Present (S) and then Is_Dispatching_Operation (S) then
2189 -- Deal with direct inheritance
2191 if not Interfaces_Only then
2192 Parent_Op := S;
2193 loop
2194 Parent_Op := Overridden_Operation (Parent_Op);
2195 exit when No (Parent_Op)
2196 or else
2197 (No_Interfaces
2198 and then
2199 Is_Interface (Find_Dispatching_Type (Parent_Op)));
2201 if Is_Subprogram_Or_Generic_Subprogram (Parent_Op) then
2202 Store_IS (Parent_Op);
2204 if One_Only then
2205 goto Done;
2206 end if;
2207 end if;
2208 end loop;
2209 end if;
2211 -- Now deal with interfaces
2213 if not No_Interfaces then
2214 declare
2215 Tag_Typ : Entity_Id;
2216 Prim : Entity_Id;
2217 Elmt : Elmt_Id;
2219 begin
2220 Tag_Typ := Find_Dispatching_Type (S);
2222 -- In the presence of limited views there may be no visible
2223 -- dispatching type. Primitives will be inherited when non-
2224 -- limited view is frozen.
2226 if No (Tag_Typ) then
2227 return Result (1 .. 0);
2228 end if;
2230 if Is_Concurrent_Type (Tag_Typ) then
2231 Tag_Typ := Corresponding_Record_Type (Tag_Typ);
2232 end if;
2234 -- Search primitive operations of dispatching type
2236 if Present (Tag_Typ)
2237 and then Present (Primitive_Operations (Tag_Typ))
2238 then
2239 Elmt := First_Elmt (Primitive_Operations (Tag_Typ));
2240 while Present (Elmt) loop
2241 Prim := Node (Elmt);
2243 -- The following test eliminates some odd cases in which
2244 -- Ekind (Prim) is Void, to be investigated further ???
2246 if not Is_Subprogram_Or_Generic_Subprogram (Prim) then
2247 null;
2249 -- For [generic] subprogram, look at interface alias
2251 elsif Present (Interface_Alias (Prim))
2252 and then Alias (Prim) = S
2253 then
2254 -- We have found a primitive covered by S
2256 Store_IS (Interface_Alias (Prim));
2258 if One_Only then
2259 goto Done;
2260 end if;
2261 end if;
2263 Next_Elmt (Elmt);
2264 end loop;
2265 end if;
2266 end;
2267 end if;
2268 end if;
2270 <<Done>>
2272 return Result (1 .. N);
2273 end Inherited_Subprograms;
2275 ---------------------------
2276 -- Is_Dynamically_Tagged --
2277 ---------------------------
2279 function Is_Dynamically_Tagged (N : Node_Id) return Boolean is
2280 begin
2281 if Nkind (N) = N_Error then
2282 return False;
2284 elsif Present (Find_Controlling_Arg (N)) then
2285 return True;
2287 -- Special cases: entities, and calls that dispatch on result
2289 elsif Is_Entity_Name (N) then
2290 return Is_Class_Wide_Type (Etype (N));
2292 elsif Nkind (N) = N_Function_Call
2293 and then Is_Class_Wide_Type (Etype (N))
2294 then
2295 return True;
2297 -- Otherwise check whether call has controlling argument
2299 else
2300 return False;
2301 end if;
2302 end Is_Dynamically_Tagged;
2304 ---------------------------------
2305 -- Is_Null_Interface_Primitive --
2306 ---------------------------------
2308 function Is_Null_Interface_Primitive (E : Entity_Id) return Boolean is
2309 begin
2310 return Comes_From_Source (E)
2311 and then Is_Dispatching_Operation (E)
2312 and then Ekind (E) = E_Procedure
2313 and then Null_Present (Parent (E))
2314 and then Is_Interface (Find_Dispatching_Type (E));
2315 end Is_Null_Interface_Primitive;
2317 -----------------------------------
2318 -- Is_Inherited_Public_Operation --
2319 -----------------------------------
2321 function Is_Inherited_Public_Operation (Op : Entity_Id) return Boolean is
2322 Prim : constant Entity_Id := Alias (Op);
2323 Scop : constant Entity_Id := Scope (Prim);
2324 Pack_Decl : Node_Id;
2326 begin
2327 if Comes_From_Source (Prim) and then Ekind (Scop) = E_Package then
2328 Pack_Decl := Unit_Declaration_Node (Scop);
2329 return Nkind (Pack_Decl) = N_Package_Declaration
2330 and then List_Containing (Unit_Declaration_Node (Prim)) =
2331 Visible_Declarations (Specification (Pack_Decl));
2333 else
2334 return False;
2335 end if;
2336 end Is_Inherited_Public_Operation;
2338 ------------------------------
2339 -- Is_Overriding_Subprogram --
2340 ------------------------------
2342 function Is_Overriding_Subprogram (E : Entity_Id) return Boolean is
2343 Inherited : constant Subprogram_List :=
2344 Inherited_Subprograms (E, One_Only => True);
2345 begin
2346 return Inherited'Length > 0;
2347 end Is_Overriding_Subprogram;
2349 --------------------------
2350 -- Is_Tag_Indeterminate --
2351 --------------------------
2353 function Is_Tag_Indeterminate (N : Node_Id) return Boolean is
2354 Nam : Entity_Id;
2355 Actual : Node_Id;
2356 Orig_Node : constant Node_Id := Original_Node (N);
2358 begin
2359 if Nkind (Orig_Node) = N_Function_Call
2360 and then Is_Entity_Name (Name (Orig_Node))
2361 then
2362 Nam := Entity (Name (Orig_Node));
2364 if not Has_Controlling_Result (Nam) then
2365 return False;
2367 -- The function may have a controlling result, but if the return type
2368 -- is not visibly tagged, then this is not tag-indeterminate.
2370 elsif Is_Access_Type (Etype (Nam))
2371 and then not Is_Tagged_Type (Designated_Type (Etype (Nam)))
2372 then
2373 return False;
2375 -- An explicit dereference means that the call has already been
2376 -- expanded and there is no tag to propagate.
2378 elsif Nkind (N) = N_Explicit_Dereference then
2379 return False;
2381 -- If there are no actuals, the call is tag-indeterminate
2383 elsif No (Parameter_Associations (Orig_Node)) then
2384 return True;
2386 else
2387 Actual := First_Actual (Orig_Node);
2388 while Present (Actual) loop
2389 if Is_Controlling_Actual (Actual)
2390 and then not Is_Tag_Indeterminate (Actual)
2391 then
2392 -- One operand is dispatching
2394 return False;
2395 end if;
2397 Next_Actual (Actual);
2398 end loop;
2400 return True;
2401 end if;
2403 elsif Nkind (Orig_Node) = N_Qualified_Expression then
2404 return Is_Tag_Indeterminate (Expression (Orig_Node));
2406 -- Case of a call to the Input attribute (possibly rewritten), which is
2407 -- always tag-indeterminate except when its prefix is a Class attribute.
2409 elsif Nkind (Orig_Node) = N_Attribute_Reference
2410 and then
2411 Get_Attribute_Id (Attribute_Name (Orig_Node)) = Attribute_Input
2412 and then Nkind (Prefix (Orig_Node)) /= N_Attribute_Reference
2413 then
2414 return True;
2416 -- In Ada 2005, a function that returns an anonymous access type can be
2417 -- dispatching, and the dereference of a call to such a function can
2418 -- also be tag-indeterminate if the call itself is.
2420 elsif Nkind (Orig_Node) = N_Explicit_Dereference
2421 and then Ada_Version >= Ada_2005
2422 then
2423 return Is_Tag_Indeterminate (Prefix (Orig_Node));
2425 else
2426 return False;
2427 end if;
2428 end Is_Tag_Indeterminate;
2430 ------------------------------------
2431 -- Override_Dispatching_Operation --
2432 ------------------------------------
2434 procedure Override_Dispatching_Operation
2435 (Tagged_Type : Entity_Id;
2436 Prev_Op : Entity_Id;
2437 New_Op : Entity_Id;
2438 Is_Wrapper : Boolean := False)
2440 Elmt : Elmt_Id;
2441 Prim : Node_Id;
2443 begin
2444 -- Diagnose failure to match No_Return in parent (Ada-2005, AI-414, but
2445 -- we do it unconditionally in Ada 95 now, since this is our pragma).
2447 if No_Return (Prev_Op) and then not No_Return (New_Op) then
2448 Error_Msg_N ("procedure & must have No_Return pragma", New_Op);
2449 Error_Msg_N ("\since overridden procedure has No_Return", New_Op);
2450 end if;
2452 -- If there is no previous operation to override, the type declaration
2453 -- was malformed, and an error must have been emitted already.
2455 Elmt := First_Elmt (Primitive_Operations (Tagged_Type));
2456 while Present (Elmt) and then Node (Elmt) /= Prev_Op loop
2457 Next_Elmt (Elmt);
2458 end loop;
2460 if No (Elmt) then
2461 return;
2462 end if;
2464 -- The location of entities that come from source in the list of
2465 -- primitives of the tagged type must follow their order of occurrence
2466 -- in the sources to fulfill the C++ ABI. If the overridden entity is a
2467 -- primitive of an interface that is not implemented by the parents of
2468 -- this tagged type (that is, it is an alias of an interface primitive
2469 -- generated by Derive_Interface_Progenitors), then we must append the
2470 -- new entity at the end of the list of primitives.
2472 if Present (Alias (Prev_Op))
2473 and then Etype (Tagged_Type) /= Tagged_Type
2474 and then Is_Interface (Find_Dispatching_Type (Alias (Prev_Op)))
2475 and then not Is_Ancestor (Find_Dispatching_Type (Alias (Prev_Op)),
2476 Tagged_Type, Use_Full_View => True)
2477 and then not Implements_Interface
2478 (Etype (Tagged_Type),
2479 Find_Dispatching_Type (Alias (Prev_Op)))
2480 then
2481 Remove_Elmt (Primitive_Operations (Tagged_Type), Elmt);
2482 Append_Elmt (New_Op, Primitive_Operations (Tagged_Type));
2484 -- The new primitive replaces the overridden entity. Required to ensure
2485 -- that overriding primitive is assigned the same dispatch table slot.
2487 else
2488 Replace_Elmt (Elmt, New_Op);
2489 end if;
2491 if Ada_Version >= Ada_2005 and then Has_Interfaces (Tagged_Type) then
2493 -- Ada 2005 (AI-251): Update the attribute alias of all the aliased
2494 -- entities of the overridden primitive to reference New_Op, and
2495 -- also propagate the proper value of Is_Abstract_Subprogram. Verify
2496 -- that the new operation is subtype conformant with the interface
2497 -- operations that it implements (for operations inherited from the
2498 -- parent itself, this check is made when building the derived type).
2500 -- Note: This code is executed with internally generated wrappers of
2501 -- functions with controlling result and late overridings.
2503 Elmt := First_Elmt (Primitive_Operations (Tagged_Type));
2504 while Present (Elmt) loop
2505 Prim := Node (Elmt);
2507 if Prim = New_Op then
2508 null;
2510 -- Note: The check on Is_Subprogram protects the frontend against
2511 -- reading attributes in entities that are not yet fully decorated
2513 elsif Is_Subprogram (Prim)
2514 and then Present (Interface_Alias (Prim))
2515 and then Alias (Prim) = Prev_Op
2516 then
2517 Set_Alias (Prim, New_Op);
2519 -- No further decoration needed yet for internally generated
2520 -- wrappers of controlling functions since (at this stage)
2521 -- they are not yet decorated.
2523 if not Is_Wrapper then
2524 Check_Subtype_Conformant (New_Op, Prim);
2526 Set_Is_Abstract_Subprogram (Prim,
2527 Is_Abstract_Subprogram (New_Op));
2529 -- Ensure that this entity will be expanded to fill the
2530 -- corresponding entry in its dispatch table.
2532 if not Is_Abstract_Subprogram (Prim) then
2533 Set_Has_Delayed_Freeze (Prim);
2534 end if;
2535 end if;
2536 end if;
2538 Next_Elmt (Elmt);
2539 end loop;
2540 end if;
2542 if (not Is_Package_Or_Generic_Package (Current_Scope))
2543 or else not In_Private_Part (Current_Scope)
2544 then
2545 -- Not a private primitive
2547 null;
2549 else pragma Assert (Is_Inherited_Operation (Prev_Op));
2551 -- Make the overriding operation into an alias of the implicit one.
2552 -- In this fashion a call from outside ends up calling the new body
2553 -- even if non-dispatching, and a call from inside calls the over-
2554 -- riding operation because it hides the implicit one. To indicate
2555 -- that the body of Prev_Op is never called, set its dispatch table
2556 -- entity to Empty. If the overridden operation has a dispatching
2557 -- result, so does the overriding one.
2559 Set_Alias (Prev_Op, New_Op);
2560 Set_DTC_Entity (Prev_Op, Empty);
2561 Set_Has_Controlling_Result (New_Op, Has_Controlling_Result (Prev_Op));
2562 return;
2563 end if;
2564 end Override_Dispatching_Operation;
2566 -------------------
2567 -- Propagate_Tag --
2568 -------------------
2570 procedure Propagate_Tag (Control : Node_Id; Actual : Node_Id) is
2571 Call_Node : Node_Id;
2572 Arg : Node_Id;
2574 begin
2575 if Nkind (Actual) = N_Function_Call then
2576 Call_Node := Actual;
2578 elsif Nkind (Actual) = N_Identifier
2579 and then Nkind (Original_Node (Actual)) = N_Function_Call
2580 then
2581 -- Call rewritten as object declaration when stack-checking is
2582 -- enabled. Propagate tag to expression in declaration, which is
2583 -- original call.
2585 Call_Node := Expression (Parent (Entity (Actual)));
2587 -- Ada 2005: If this is a dereference of a call to a function with a
2588 -- dispatching access-result, the tag is propagated when the dereference
2589 -- itself is expanded (see exp_ch6.adb) and there is nothing else to do.
2591 elsif Nkind (Actual) = N_Explicit_Dereference
2592 and then Nkind (Original_Node (Prefix (Actual))) = N_Function_Call
2593 then
2594 return;
2596 -- When expansion is suppressed, an unexpanded call to 'Input can occur,
2597 -- and in that case we can simply return.
2599 elsif Nkind (Actual) = N_Attribute_Reference then
2600 pragma Assert (Attribute_Name (Actual) = Name_Input);
2602 return;
2604 -- Only other possibilities are parenthesized or qualified expression,
2605 -- or an expander-generated unchecked conversion of a function call to
2606 -- a stream Input attribute.
2608 else
2609 Call_Node := Expression (Actual);
2610 end if;
2612 -- No action needed if the call has been already expanded
2614 if Is_Expanded_Dispatching_Call (Call_Node) then
2615 return;
2616 end if;
2618 -- Do not set the Controlling_Argument if already set. This happens in
2619 -- the special case of _Input (see Exp_Attr, case Input).
2621 if No (Controlling_Argument (Call_Node)) then
2622 Set_Controlling_Argument (Call_Node, Control);
2623 end if;
2625 Arg := First_Actual (Call_Node);
2626 while Present (Arg) loop
2627 if Is_Tag_Indeterminate (Arg) then
2628 Propagate_Tag (Control, Arg);
2629 end if;
2631 Next_Actual (Arg);
2632 end loop;
2634 -- Expansion of dispatching calls is suppressed on VM targets, because
2635 -- the VM back-ends directly handle the generation of dispatching calls
2636 -- and would have to undo any expansion to an indirect call.
2638 if Tagged_Type_Expansion then
2639 declare
2640 Call_Typ : constant Entity_Id := Etype (Call_Node);
2642 begin
2643 Expand_Dispatching_Call (Call_Node);
2645 -- If the controlling argument is an interface type and the type
2646 -- of Call_Node differs then we must add an implicit conversion to
2647 -- force displacement of the pointer to the object to reference
2648 -- the secondary dispatch table of the interface.
2650 if Is_Interface (Etype (Control))
2651 and then Etype (Control) /= Call_Typ
2652 then
2653 -- Cannot use Convert_To because the previous call to
2654 -- Expand_Dispatching_Call leaves decorated the Call_Node
2655 -- with the type of Control.
2657 Rewrite (Call_Node,
2658 Make_Type_Conversion (Sloc (Call_Node),
2659 Subtype_Mark =>
2660 New_Occurrence_Of (Etype (Control), Sloc (Call_Node)),
2661 Expression => Relocate_Node (Call_Node)));
2662 Set_Etype (Call_Node, Etype (Control));
2663 Set_Analyzed (Call_Node);
2665 Expand_Interface_Conversion (Call_Node);
2666 end if;
2667 end;
2669 -- Expansion of a dispatching call results in an indirect call, which in
2670 -- turn causes current values to be killed (see Resolve_Call), so on VM
2671 -- targets we do the call here to ensure consistent warnings between VM
2672 -- and non-VM targets.
2674 else
2675 Kill_Current_Values;
2676 end if;
2677 end Propagate_Tag;
2679 end Sem_Disp;