1 ------------------------------------------------------------------------------
3 -- GNAT COMPILER COMPONENTS --
9 -- Copyright (C) 1992-2012, Free Software Foundation, Inc. --
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. --
21 -- GNAT was originally developed by the GNAT team at New York University. --
22 -- Extensive contributions were provided by Ada Core Technologies Inc. --
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
;
40 with Output
; use Output
;
41 with Restrict
; use Restrict
;
42 with Rident
; use Rident
;
44 with Sem_Aux
; use Sem_Aux
;
45 with Sem_Ch3
; use Sem_Ch3
;
46 with Sem_Ch6
; use Sem_Ch6
;
47 with Sem_Eval
; use Sem_Eval
;
48 with Sem_Type
; use Sem_Type
;
49 with Sem_Util
; use Sem_Util
;
50 with Snames
; use Snames
;
51 with Sinfo
; use Sinfo
;
52 with Targparm
; use Targparm
;
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
;
65 -- Add New_Op in the list of primitive operations of Tagged_Type
67 function Check_Controlling_Type
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 -------------------------------
89 -- Add_Dispatching_Operation --
90 -------------------------------
92 procedure Add_Dispatching_Operation
93 (Tagged_Type
: Entity_Id
;
96 List
: constant Elist_Id
:= Primitive_Operations
(Tagged_Type
);
99 -- The dispatching operation may already be on the list, if it is the
100 -- wrapper for an inherited function of a null extension (see Exp_Ch3
101 -- for the construction of function wrappers). The list of primitive
102 -- operations must not contain duplicates.
104 Append_Unique_Elmt
(New_Op
, List
);
105 end Add_Dispatching_Operation
;
107 ---------------------------
108 -- Covers_Some_Interface --
109 ---------------------------
111 function Covers_Some_Interface
(Prim
: Entity_Id
) return Boolean is
112 Tagged_Type
: constant Entity_Id
:= Find_Dispatching_Type
(Prim
);
117 pragma Assert
(Is_Dispatching_Operation
(Prim
));
119 -- Although this is a dispatching primitive we must check if its
120 -- dispatching type is available because it may be the primitive
121 -- of a private type not defined as tagged in its partial view.
123 if Present
(Tagged_Type
) and then Has_Interfaces
(Tagged_Type
) then
125 -- If the tagged type is frozen then the internal entities associated
126 -- with interfaces are available in the list of primitives of the
127 -- tagged type and can be used to speed up this search.
129 if Is_Frozen
(Tagged_Type
) then
130 Elmt
:= First_Elmt
(Primitive_Operations
(Tagged_Type
));
131 while Present
(Elmt
) loop
134 if Present
(Interface_Alias
(E
))
135 and then Alias
(E
) = Prim
143 -- Otherwise we must collect all the interface primitives and check
144 -- if the Prim will override some interface primitive.
148 Ifaces_List
: Elist_Id
;
149 Iface_Elmt
: Elmt_Id
;
151 Iface_Prim
: Entity_Id
;
154 Collect_Interfaces
(Tagged_Type
, Ifaces_List
);
155 Iface_Elmt
:= First_Elmt
(Ifaces_List
);
156 while Present
(Iface_Elmt
) loop
157 Iface
:= Node
(Iface_Elmt
);
159 Elmt
:= First_Elmt
(Primitive_Operations
(Iface
));
160 while Present
(Elmt
) loop
161 Iface_Prim
:= Node
(Elmt
);
163 if Chars
(Iface
) = Chars
(Prim
)
164 and then Is_Interface_Conformant
165 (Tagged_Type
, Iface_Prim
, Prim
)
173 Next_Elmt
(Iface_Elmt
);
180 end Covers_Some_Interface
;
182 -------------------------------
183 -- Check_Controlling_Formals --
184 -------------------------------
186 procedure Check_Controlling_Formals
191 Ctrl_Type
: Entity_Id
;
194 Formal
:= First_Formal
(Subp
);
195 while Present
(Formal
) loop
196 Ctrl_Type
:= Check_Controlling_Type
(Etype
(Formal
), Subp
);
198 if Present
(Ctrl_Type
) then
200 -- When controlling type is concurrent and declared within a
201 -- generic or inside an instance use corresponding record type.
203 if Is_Concurrent_Type
(Ctrl_Type
)
204 and then Present
(Corresponding_Record_Type
(Ctrl_Type
))
206 Ctrl_Type
:= Corresponding_Record_Type
(Ctrl_Type
);
209 if Ctrl_Type
= Typ
then
210 Set_Is_Controlling_Formal
(Formal
);
212 -- Ada 2005 (AI-231): Anonymous access types that are used in
213 -- controlling parameters exclude null because it is necessary
214 -- to read the tag to dispatch, and null has no tag.
216 if Ekind
(Etype
(Formal
)) = E_Anonymous_Access_Type
then
217 Set_Can_Never_Be_Null
(Etype
(Formal
));
218 Set_Is_Known_Non_Null
(Etype
(Formal
));
221 -- Check that the parameter's nominal subtype statically
222 -- matches the first subtype.
224 if Ekind
(Etype
(Formal
)) = E_Anonymous_Access_Type
then
225 if not Subtypes_Statically_Match
226 (Typ
, Designated_Type
(Etype
(Formal
)))
229 ("parameter subtype does not match controlling type",
233 elsif not Subtypes_Statically_Match
(Typ
, Etype
(Formal
)) then
235 ("parameter subtype does not match controlling type",
239 if Present
(Default_Value
(Formal
)) then
241 -- In Ada 2005, access parameters can have defaults
243 if Ekind
(Etype
(Formal
)) = E_Anonymous_Access_Type
244 and then Ada_Version
< Ada_2005
247 ("default not allowed for controlling access parameter",
248 Default_Value
(Formal
));
250 elsif not Is_Tag_Indeterminate
(Default_Value
(Formal
)) then
252 ("default expression must be a tag indeterminate" &
253 " function call", Default_Value
(Formal
));
257 elsif Comes_From_Source
(Subp
) then
259 ("operation can be dispatching in only one type", Subp
);
263 Next_Formal
(Formal
);
266 if Ekind_In
(Subp
, E_Function
, E_Generic_Function
) then
267 Ctrl_Type
:= Check_Controlling_Type
(Etype
(Subp
), Subp
);
269 if Present
(Ctrl_Type
) then
270 if Ctrl_Type
= Typ
then
271 Set_Has_Controlling_Result
(Subp
);
273 -- Check that result subtype statically matches first subtype
274 -- (Ada 2005): Subp may have a controlling access result.
276 if Subtypes_Statically_Match
(Typ
, Etype
(Subp
))
277 or else (Ekind
(Etype
(Subp
)) = E_Anonymous_Access_Type
279 Subtypes_Statically_Match
280 (Typ
, Designated_Type
(Etype
(Subp
))))
286 ("result subtype does not match controlling type", Subp
);
289 elsif Comes_From_Source
(Subp
) then
291 ("operation can be dispatching in only one type", Subp
);
295 end Check_Controlling_Formals
;
297 ----------------------------
298 -- Check_Controlling_Type --
299 ----------------------------
301 function Check_Controlling_Type
303 Subp
: Entity_Id
) return Entity_Id
305 Tagged_Type
: Entity_Id
:= Empty
;
308 if Is_Tagged_Type
(T
) then
309 if Is_First_Subtype
(T
) then
312 Tagged_Type
:= Base_Type
(T
);
315 elsif Ekind
(T
) = E_Anonymous_Access_Type
316 and then Is_Tagged_Type
(Designated_Type
(T
))
318 if Ekind
(Designated_Type
(T
)) /= E_Incomplete_Type
then
319 if Is_First_Subtype
(Designated_Type
(T
)) then
320 Tagged_Type
:= Designated_Type
(T
);
322 Tagged_Type
:= Base_Type
(Designated_Type
(T
));
325 -- Ada 2005: an incomplete type can be tagged. An operation with an
326 -- access parameter of the type is dispatching.
328 elsif Scope
(Designated_Type
(T
)) = Current_Scope
then
329 Tagged_Type
:= Designated_Type
(T
);
331 -- Ada 2005 (AI-50217)
333 elsif From_With_Type
(Designated_Type
(T
))
334 and then Present
(Non_Limited_View
(Designated_Type
(T
)))
336 if Is_First_Subtype
(Non_Limited_View
(Designated_Type
(T
))) then
337 Tagged_Type
:= Non_Limited_View
(Designated_Type
(T
));
339 Tagged_Type
:= Base_Type
(Non_Limited_View
340 (Designated_Type
(T
)));
345 if No
(Tagged_Type
) or else Is_Class_Wide_Type
(Tagged_Type
) then
348 -- The dispatching type and the primitive operation must be defined in
349 -- the same scope, except in the case of internal operations and formal
350 -- abstract subprograms.
352 elsif ((Scope
(Subp
) = Scope
(Tagged_Type
) or else Is_Internal
(Subp
))
353 and then (not Is_Generic_Type
(Tagged_Type
)
354 or else not Comes_From_Source
(Subp
)))
356 (Is_Formal_Subprogram
(Subp
) and then Is_Abstract_Subprogram
(Subp
))
358 (Nkind
(Parent
(Parent
(Subp
))) = N_Subprogram_Renaming_Declaration
360 Present
(Corresponding_Formal_Spec
(Parent
(Parent
(Subp
))))
362 Is_Abstract_Subprogram
(Subp
))
369 end Check_Controlling_Type
;
371 ----------------------------
372 -- Check_Dispatching_Call --
373 ----------------------------
375 procedure Check_Dispatching_Call
(N
: Node_Id
) is
376 Loc
: constant Source_Ptr
:= Sloc
(N
);
379 Control
: Node_Id
:= Empty
;
381 Subp_Entity
: Entity_Id
;
382 Indeterm_Ancestor_Call
: Boolean := False;
383 Indeterm_Ctrl_Type
: Entity_Id
;
385 Static_Tag
: Node_Id
:= Empty
;
386 -- If a controlling formal has a statically tagged actual, the tag of
387 -- this actual is to be used for any tag-indeterminate actual.
389 procedure Check_Direct_Call
;
390 -- In the case when the controlling actual is a class-wide type whose
391 -- root type's completion is a task or protected type, the call is in
392 -- fact direct. This routine detects the above case and modifies the
395 procedure Check_Dispatching_Context
;
396 -- If the call is tag-indeterminate and the entity being called is
397 -- abstract, verify that the context is a call that will eventually
398 -- provide a tag for dispatching, or has provided one already.
400 -----------------------
401 -- Check_Direct_Call --
402 -----------------------
404 procedure Check_Direct_Call
is
405 Typ
: Entity_Id
:= Etype
(Control
);
407 function Is_User_Defined_Equality
(Id
: Entity_Id
) return Boolean;
408 -- Determine whether an entity denotes a user-defined equality
410 ------------------------------
411 -- Is_User_Defined_Equality --
412 ------------------------------
414 function Is_User_Defined_Equality
(Id
: Entity_Id
) return Boolean is
417 Ekind
(Id
) = E_Function
418 and then Chars
(Id
) = Name_Op_Eq
419 and then Comes_From_Source
(Id
)
421 -- Internally generated equalities have a full type declaration
424 and then Nkind
(Parent
(Id
)) = N_Function_Specification
;
425 end Is_User_Defined_Equality
;
427 -- Start of processing for Check_Direct_Call
430 -- Predefined primitives do not receive wrappers since they are built
431 -- from scratch for the corresponding record of synchronized types.
432 -- Equality is in general predefined, but is excluded from the check
433 -- when it is user-defined.
435 if Is_Predefined_Dispatching_Operation
(Subp_Entity
)
436 and then not Is_User_Defined_Equality
(Subp_Entity
)
441 if Is_Class_Wide_Type
(Typ
) then
442 Typ
:= Root_Type
(Typ
);
445 if Is_Private_Type
(Typ
) and then Present
(Full_View
(Typ
)) then
446 Typ
:= Full_View
(Typ
);
449 if Is_Concurrent_Type
(Typ
)
451 Present
(Corresponding_Record_Type
(Typ
))
453 Typ
:= Corresponding_Record_Type
(Typ
);
455 -- The concurrent record's list of primitives should contain a
456 -- wrapper for the entity of the call, retrieve it.
461 Wrapper_Found
: Boolean := False;
464 Prim_Elmt
:= First_Elmt
(Primitive_Operations
(Typ
));
465 while Present
(Prim_Elmt
) loop
466 Prim
:= Node
(Prim_Elmt
);
468 if Is_Primitive_Wrapper
(Prim
)
469 and then Wrapped_Entity
(Prim
) = Subp_Entity
471 Wrapper_Found
:= True;
475 Next_Elmt
(Prim_Elmt
);
478 -- A primitive declared between two views should have a
479 -- corresponding wrapper.
481 pragma Assert
(Wrapper_Found
);
483 -- Modify the call by setting the proper entity
485 Set_Entity
(Name
(N
), Prim
);
488 end Check_Direct_Call
;
490 -------------------------------
491 -- Check_Dispatching_Context --
492 -------------------------------
494 procedure Check_Dispatching_Context
is
495 Subp
: constant Entity_Id
:= Entity
(Name
(N
));
496 Typ
: constant Entity_Id
:= Etype
(Subp
);
499 procedure Abstract_Context_Error
;
500 -- Error for abstract call dispatching on result is not dispatching
502 ----------------------------
503 -- Abstract_Context_Error --
504 ----------------------------
506 procedure Abstract_Context_Error
is
508 if Ekind
(Subp
) = E_Function
then
510 ("call to abstract function must be dispatching", N
);
512 -- This error can occur for a procedure in the case of a call to
513 -- an abstract formal procedure with a statically tagged operand.
517 ("call to abstract procedure must be dispatching",
520 end Abstract_Context_Error
;
522 -- Start of processing for Check_Dispatching_Context
525 if Is_Abstract_Subprogram
(Subp
)
526 and then No
(Controlling_Argument
(N
))
528 if Present
(Alias
(Subp
))
529 and then not Is_Abstract_Subprogram
(Alias
(Subp
))
530 and then No
(DTC_Entity
(Subp
))
532 -- Private overriding of inherited abstract operation, call is
535 Set_Entity
(Name
(N
), Alias
(Subp
));
539 -- We need to determine whether the context of the call
540 -- provides a tag to make the call dispatching. This requires
541 -- the call to be the actual in an enclosing call, and that
542 -- actual must be controlling. If the call is an operand of
543 -- equality, the other operand must not ve abstract.
545 if not Is_Tagged_Type
(Typ
)
547 (Ekind
(Typ
) = E_Anonymous_Access_Type
548 and then Is_Tagged_Type
(Designated_Type
(Typ
)))
550 Abstract_Context_Error
;
556 if Nkind
(Par
) = N_Parameter_Association
then
560 while Present
(Par
) loop
561 if Nkind_In
(Par
, N_Function_Call
,
562 N_Procedure_Call_Statement
)
563 and then Is_Entity_Name
(Name
(Par
))
570 -- Find formal for which call is the actual.
572 F
:= First_Formal
(Entity
(Name
(Par
)));
573 A
:= First_Actual
(Par
);
574 while Present
(F
) loop
575 if Is_Controlling_Formal
(F
)
576 and then (N
= A
or else Parent
(N
) = A
)
586 ("call to abstract function must be dispatching", N
);
590 -- For equalitiy operators, one of the operands must be
591 -- statically or dynamically tagged.
593 elsif Nkind_In
(Par
, N_Op_Eq
, N_Op_Ne
) then
594 if N
= Right_Opnd
(Par
)
595 and then Is_Tag_Indeterminate
(Left_Opnd
(Par
))
597 Abstract_Context_Error
;
599 elsif N
= Left_Opnd
(Par
)
600 and then Is_Tag_Indeterminate
(Right_Opnd
(Par
))
602 Abstract_Context_Error
;
607 elsif Nkind
(Par
) = N_Assignment_Statement
then
610 elsif Nkind
(Par
) = N_Qualified_Expression
611 or else Nkind
(Par
) = N_Unchecked_Type_Conversion
616 Abstract_Context_Error
;
622 end Check_Dispatching_Context
;
624 -- Start of processing for Check_Dispatching_Call
627 -- Find a controlling argument, if any
629 if Present
(Parameter_Associations
(N
)) then
630 Subp_Entity
:= Entity
(Name
(N
));
632 Actual
:= First_Actual
(N
);
633 Formal
:= First_Formal
(Subp_Entity
);
634 while Present
(Actual
) loop
635 Control
:= Find_Controlling_Arg
(Actual
);
636 exit when Present
(Control
);
638 -- Check for the case where the actual is a tag-indeterminate call
639 -- whose result type is different than the tagged type associated
640 -- with the containing call, but is an ancestor of the type.
642 if Is_Controlling_Formal
(Formal
)
643 and then Is_Tag_Indeterminate
(Actual
)
644 and then Base_Type
(Etype
(Actual
)) /= Base_Type
(Etype
(Formal
))
645 and then Is_Ancestor
(Etype
(Actual
), Etype
(Formal
))
647 Indeterm_Ancestor_Call
:= True;
648 Indeterm_Ctrl_Type
:= Etype
(Formal
);
650 -- If the formal is controlling but the actual is not, the type
651 -- of the actual is statically known, and may be used as the
652 -- controlling tag for some other tag-indeterminate actual.
654 elsif Is_Controlling_Formal
(Formal
)
655 and then Is_Entity_Name
(Actual
)
656 and then Is_Tagged_Type
(Etype
(Actual
))
658 Static_Tag
:= Actual
;
661 Next_Actual
(Actual
);
662 Next_Formal
(Formal
);
665 -- If the call doesn't have a controlling actual but does have an
666 -- indeterminate actual that requires dispatching treatment, then an
667 -- object is needed that will serve as the controlling argument for
668 -- a dispatching call on the indeterminate actual. This can only
669 -- occur in the unusual situation of a default actual given by
670 -- a tag-indeterminate call and where the type of the call is an
671 -- ancestor of the type associated with a containing call to an
672 -- inherited operation (see AI-239).
674 -- Rather than create an object of the tagged type, which would
675 -- be problematic for various reasons (default initialization,
676 -- discriminants), the tag of the containing call's associated
677 -- tagged type is directly used to control the dispatching.
680 and then Indeterm_Ancestor_Call
681 and then No
(Static_Tag
)
684 Make_Attribute_Reference
(Loc
,
685 Prefix
=> New_Occurrence_Of
(Indeterm_Ctrl_Type
, Loc
),
686 Attribute_Name
=> Name_Tag
);
691 if Present
(Control
) then
693 -- Verify that no controlling arguments are statically tagged
696 Write_Str
("Found Dispatching call");
701 Actual
:= First_Actual
(N
);
702 while Present
(Actual
) loop
703 if Actual
/= Control
then
705 if not Is_Controlling_Actual
(Actual
) then
706 null; -- Can be anything
708 elsif Is_Dynamically_Tagged
(Actual
) then
709 null; -- Valid parameter
711 elsif Is_Tag_Indeterminate
(Actual
) then
713 -- The tag is inherited from the enclosing call (the node
714 -- we are currently analyzing). Explicitly expand the
715 -- actual, since the previous call to Expand (from
716 -- Resolve_Call) had no way of knowing about the
717 -- required dispatching.
719 Propagate_Tag
(Control
, Actual
);
723 ("controlling argument is not dynamically tagged",
729 Next_Actual
(Actual
);
732 -- Mark call as a dispatching call
734 Set_Controlling_Argument
(N
, Control
);
735 Check_Restriction
(No_Dispatching_Calls
, N
);
737 -- The dispatching call may need to be converted into a direct
738 -- call in certain cases.
742 -- If there is a statically tagged actual and a tag-indeterminate
743 -- call to a function of the ancestor (such as that provided by a
744 -- default), then treat this as a dispatching call and propagate
745 -- the tag to the tag-indeterminate call(s).
747 elsif Present
(Static_Tag
) and then Indeterm_Ancestor_Call
then
749 Make_Attribute_Reference
(Loc
,
751 New_Occurrence_Of
(Etype
(Static_Tag
), Loc
),
752 Attribute_Name
=> Name_Tag
);
756 Actual
:= First_Actual
(N
);
757 Formal
:= First_Formal
(Subp_Entity
);
758 while Present
(Actual
) loop
759 if Is_Tag_Indeterminate
(Actual
)
760 and then Is_Controlling_Formal
(Formal
)
762 Propagate_Tag
(Control
, Actual
);
765 Next_Actual
(Actual
);
766 Next_Formal
(Formal
);
769 Check_Dispatching_Context
;
772 -- The call is not dispatching, so check that there aren't any
773 -- tag-indeterminate abstract calls left.
775 Actual
:= First_Actual
(N
);
776 while Present
(Actual
) loop
777 if Is_Tag_Indeterminate
(Actual
) then
779 -- Function call case
781 if Nkind
(Original_Node
(Actual
)) = N_Function_Call
then
782 Func
:= Entity
(Name
(Original_Node
(Actual
)));
784 -- If the actual is an attribute then it can't be abstract
785 -- (the only current case of a tag-indeterminate attribute
786 -- is the stream Input attribute).
789 Nkind
(Original_Node
(Actual
)) = N_Attribute_Reference
793 -- Only other possibility is a qualified expression whose
794 -- constituent expression is itself a call.
800 (Expression
(Original_Node
(Actual
)))));
803 if Present
(Func
) and then Is_Abstract_Subprogram
(Func
) then
805 ("call to abstract function must be dispatching", N
);
809 Next_Actual
(Actual
);
812 Check_Dispatching_Context
;
816 -- If dispatching on result, the enclosing call, if any, will
817 -- determine the controlling argument. Otherwise this is the
818 -- primitive operation of the root type.
820 Check_Dispatching_Context
;
822 end Check_Dispatching_Call
;
824 ---------------------------------
825 -- Check_Dispatching_Operation --
826 ---------------------------------
828 procedure Check_Dispatching_Operation
(Subp
, Old_Subp
: Entity_Id
) is
829 Tagged_Type
: Entity_Id
;
830 Has_Dispatching_Parent
: Boolean := False;
831 Body_Is_Last_Primitive
: Boolean := False;
832 Ovr_Subp
: Entity_Id
:= Empty
;
835 if not Ekind_In
(Subp
, E_Procedure
, E_Function
) then
839 Set_Is_Dispatching_Operation
(Subp
, False);
840 Tagged_Type
:= Find_Dispatching_Type
(Subp
);
842 -- Ada 2005 (AI-345): Use the corresponding record (if available).
843 -- Required because primitives of concurrent types are be attached
844 -- to the corresponding record (not to the concurrent type).
846 if Ada_Version
>= Ada_2005
847 and then Present
(Tagged_Type
)
848 and then Is_Concurrent_Type
(Tagged_Type
)
849 and then Present
(Corresponding_Record_Type
(Tagged_Type
))
851 Tagged_Type
:= Corresponding_Record_Type
(Tagged_Type
);
854 -- (AI-345): The task body procedure is not a primitive of the tagged
857 if Present
(Tagged_Type
)
858 and then Is_Concurrent_Record_Type
(Tagged_Type
)
859 and then Present
(Corresponding_Concurrent_Type
(Tagged_Type
))
860 and then Is_Task_Type
(Corresponding_Concurrent_Type
(Tagged_Type
))
861 and then Subp
= Get_Task_Body_Procedure
862 (Corresponding_Concurrent_Type
(Tagged_Type
))
867 -- If Subp is derived from a dispatching operation then it should
868 -- always be treated as dispatching. In this case various checks
869 -- below will be bypassed. Makes sure that late declarations for
870 -- inherited private subprograms are treated as dispatching, even
871 -- if the associated tagged type is already frozen.
873 Has_Dispatching_Parent
:=
874 Present
(Alias
(Subp
))
875 and then Is_Dispatching_Operation
(Alias
(Subp
));
877 if No
(Tagged_Type
) then
879 -- Ada 2005 (AI-251): Check that Subp is not a primitive associated
880 -- with an abstract interface type unless the interface acts as a
881 -- parent type in a derivation. If the interface type is a formal
882 -- type then the operation is not primitive and therefore legal.
889 E
:= First_Entity
(Subp
);
890 while Present
(E
) loop
892 -- For an access parameter, check designated type
894 if Ekind
(Etype
(E
)) = E_Anonymous_Access_Type
then
895 Typ
:= Designated_Type
(Etype
(E
));
900 if Comes_From_Source
(Subp
)
901 and then Is_Interface
(Typ
)
902 and then not Is_Class_Wide_Type
(Typ
)
903 and then not Is_Derived_Type
(Typ
)
904 and then not Is_Generic_Type
(Typ
)
905 and then not In_Instance
907 Error_Msg_N
("?declaration of& is too late!", Subp
);
908 Error_Msg_NE
-- CODEFIX??
909 ("\spec should appear immediately after declaration of &!",
917 -- In case of functions check also the result type
919 if Ekind
(Subp
) = E_Function
then
920 if Is_Access_Type
(Etype
(Subp
)) then
921 Typ
:= Designated_Type
(Etype
(Subp
));
926 -- The following should be better commented, especially since
927 -- we just added several new conditions here ???
929 if Comes_From_Source
(Subp
)
930 and then Is_Interface
(Typ
)
931 and then not Is_Class_Wide_Type
(Typ
)
932 and then not Is_Derived_Type
(Typ
)
933 and then not Is_Generic_Type
(Typ
)
934 and then not In_Instance
936 Error_Msg_N
("?declaration of& is too late!", Subp
);
938 ("\spec should appear immediately after declaration of &!",
946 -- The subprograms build internally after the freezing point (such as
947 -- init procs, interface thunks, type support subprograms, and Offset
948 -- to top functions for accessing interface components in variable
949 -- size tagged types) are not primitives.
951 elsif Is_Frozen
(Tagged_Type
)
952 and then not Comes_From_Source
(Subp
)
953 and then not Has_Dispatching_Parent
955 -- Complete decoration of internally built subprograms that override
956 -- a dispatching primitive. These entities correspond with the
959 -- 1. Ada 2005 (AI-391): Wrapper functions built by the expander
960 -- to override functions of nonabstract null extensions. These
961 -- primitives were added to the list of primitives of the tagged
962 -- type by Make_Controlling_Function_Wrappers. However, attribute
963 -- Is_Dispatching_Operation must be set to true.
965 -- 2. Ada 2005 (AI-251): Wrapper procedures of null interface
968 -- 3. Subprograms associated with stream attributes (built by
969 -- New_Stream_Subprogram)
971 if Present
(Old_Subp
)
972 and then Present
(Overridden_Operation
(Subp
))
973 and then Is_Dispatching_Operation
(Old_Subp
)
976 ((Ekind
(Subp
) = E_Function
977 and then Is_Dispatching_Operation
(Old_Subp
)
978 and then Is_Null_Extension
(Base_Type
(Etype
(Subp
))))
980 (Ekind
(Subp
) = E_Procedure
981 and then Is_Dispatching_Operation
(Old_Subp
)
982 and then Present
(Alias
(Old_Subp
))
983 and then Is_Null_Interface_Primitive
984 (Ultimate_Alias
(Old_Subp
)))
985 or else Get_TSS_Name
(Subp
) = TSS_Stream_Read
986 or else Get_TSS_Name
(Subp
) = TSS_Stream_Write
);
988 Check_Controlling_Formals
(Tagged_Type
, Subp
);
989 Override_Dispatching_Operation
(Tagged_Type
, Old_Subp
, Subp
);
990 Set_Is_Dispatching_Operation
(Subp
);
995 -- The operation may be a child unit, whose scope is the defining
996 -- package, but which is not a primitive operation of the type.
998 elsif Is_Child_Unit
(Subp
) then
1001 -- If the subprogram is not defined in a package spec, the only case
1002 -- where it can be a dispatching op is when it overrides an operation
1003 -- before the freezing point of the type.
1005 elsif ((not Is_Package_Or_Generic_Package
(Scope
(Subp
)))
1006 or else In_Package_Body
(Scope
(Subp
)))
1007 and then not Has_Dispatching_Parent
1009 if not Comes_From_Source
(Subp
)
1010 or else (Present
(Old_Subp
) and then not Is_Frozen
(Tagged_Type
))
1014 -- If the type is already frozen, the overriding is not allowed
1015 -- except when Old_Subp is not a dispatching operation (which can
1016 -- occur when Old_Subp was inherited by an untagged type). However,
1017 -- a body with no previous spec freezes the type *after* its
1018 -- declaration, and therefore is a legal overriding (unless the type
1019 -- has already been frozen). Only the first such body is legal.
1021 elsif Present
(Old_Subp
)
1022 and then Is_Dispatching_Operation
(Old_Subp
)
1024 if Comes_From_Source
(Subp
)
1026 (Nkind
(Unit_Declaration_Node
(Subp
)) = N_Subprogram_Body
1027 or else Nkind
(Unit_Declaration_Node
(Subp
)) in N_Body_Stub
)
1030 Subp_Body
: constant Node_Id
:= Unit_Declaration_Node
(Subp
);
1031 Decl_Item
: Node_Id
;
1034 -- ??? The checks here for whether the type has been frozen
1035 -- prior to the new body are not complete. It's not simple
1036 -- to check frozenness at this point since the body has
1037 -- already caused the type to be prematurely frozen in
1038 -- Analyze_Declarations, but we're forced to recheck this
1039 -- here because of the odd rule interpretation that allows
1040 -- the overriding if the type wasn't frozen prior to the
1041 -- body. The freezing action should probably be delayed
1042 -- until after the spec is seen, but that's a tricky
1043 -- change to the delicate freezing code.
1045 -- Look at each declaration following the type up until the
1046 -- new subprogram body. If any of the declarations is a body
1047 -- then the type has been frozen already so the overriding
1048 -- primitive is illegal.
1050 Decl_Item
:= Next
(Parent
(Tagged_Type
));
1051 while Present
(Decl_Item
)
1052 and then (Decl_Item
/= Subp_Body
)
1054 if Comes_From_Source
(Decl_Item
)
1055 and then (Nkind
(Decl_Item
) in N_Proper_Body
1056 or else Nkind
(Decl_Item
) in N_Body_Stub
)
1058 Error_Msg_N
("overriding of& is too late!", Subp
);
1060 ("\spec should appear immediately after the type!",
1068 -- If the subprogram doesn't follow in the list of
1069 -- declarations including the type then the type has
1070 -- definitely been frozen already and the body is illegal.
1072 if No
(Decl_Item
) then
1073 Error_Msg_N
("overriding of& is too late!", Subp
);
1075 ("\spec should appear immediately after the type!",
1078 elsif Is_Frozen
(Subp
) then
1080 -- The subprogram body declares a primitive operation.
1081 -- If the subprogram is already frozen, we must update
1082 -- its dispatching information explicitly here. The
1083 -- information is taken from the overridden subprogram.
1084 -- We must also generate a cross-reference entry because
1085 -- references to other primitives were already created
1086 -- when type was frozen.
1088 Body_Is_Last_Primitive
:= True;
1090 if Present
(DTC_Entity
(Old_Subp
)) then
1091 Set_DTC_Entity
(Subp
, DTC_Entity
(Old_Subp
));
1092 Set_DT_Position
(Subp
, DT_Position
(Old_Subp
));
1094 if not Restriction_Active
(No_Dispatching_Calls
) then
1095 if Building_Static_DT
(Tagged_Type
) then
1097 -- If the static dispatch table has not been
1098 -- built then there is nothing else to do now;
1099 -- otherwise we notify that we cannot build the
1100 -- static dispatch table.
1102 if Has_Dispatch_Table
(Tagged_Type
) then
1104 ("overriding of& is too late for building" &
1105 " static dispatch tables!", Subp
);
1107 ("\spec should appear immediately after" &
1108 " the type!", Subp
);
1111 -- No code required to register primitives in VM
1114 elsif VM_Target
/= No_VM
then
1118 Insert_Actions_After
(Subp_Body
,
1119 Register_Primitive
(Sloc
(Subp_Body
),
1123 -- Indicate that this is an overriding operation,
1124 -- and replace the overridden entry in the list of
1125 -- primitive operations, which is used for xref
1126 -- generation subsequently.
1128 Generate_Reference
(Tagged_Type
, Subp
, 'P', False);
1129 Override_Dispatching_Operation
1130 (Tagged_Type
, Old_Subp
, Subp
);
1137 Error_Msg_N
("overriding of& is too late!", Subp
);
1139 ("\subprogram spec should appear immediately after the type!",
1143 -- If the type is not frozen yet and we are not in the overriding
1144 -- case it looks suspiciously like an attempt to define a primitive
1145 -- operation, which requires the declaration to be in a package spec
1146 -- (3.2.3(6)). Only report cases where the type and subprogram are
1147 -- in the same declaration list (by checking the enclosing parent
1148 -- declarations), to avoid spurious warnings on subprograms in
1149 -- instance bodies when the type is declared in the instance spec
1150 -- but hasn't been frozen by the instance body.
1152 elsif not Is_Frozen
(Tagged_Type
)
1153 and then In_Same_List
(Parent
(Tagged_Type
), Parent
(Parent
(Subp
)))
1156 ("?not dispatching (must be defined in a package spec)", Subp
);
1159 -- When the type is frozen, it is legitimate to define a new
1160 -- non-primitive operation.
1166 -- Now, we are sure that the scope is a package spec. If the subprogram
1167 -- is declared after the freezing point of the type that's an error
1169 elsif Is_Frozen
(Tagged_Type
) and then not Has_Dispatching_Parent
then
1170 Error_Msg_N
("this primitive operation is declared too late", Subp
);
1172 ("?no primitive operations for& after this line",
1173 Freeze_Node
(Tagged_Type
),
1178 Check_Controlling_Formals
(Tagged_Type
, Subp
);
1180 Ovr_Subp
:= Old_Subp
;
1182 -- [Ada 2012:AI-0125]: Search for inherited hidden primitive that may be
1183 -- overridden by Subp
1186 and then Ada_Version
>= Ada_2012
1188 Ovr_Subp
:= Find_Hidden_Overridden_Primitive
(Subp
);
1191 -- Now it should be a correct primitive operation, put it in the list
1193 if Present
(Ovr_Subp
) then
1195 -- If the type has interfaces we complete this check after we set
1196 -- attribute Is_Dispatching_Operation.
1198 Check_Subtype_Conformant
(Subp
, Ovr_Subp
);
1200 if (Chars
(Subp
) = Name_Initialize
1201 or else Chars
(Subp
) = Name_Adjust
1202 or else Chars
(Subp
) = Name_Finalize
)
1203 and then Is_Controlled
(Tagged_Type
)
1204 and then not Is_Visibly_Controlled
(Tagged_Type
)
1206 Set_Overridden_Operation
(Subp
, Empty
);
1208 -- If the subprogram specification carries an overriding
1209 -- indicator, no need for the warning: it is either redundant,
1210 -- or else an error will be reported.
1212 if Nkind
(Parent
(Subp
)) = N_Procedure_Specification
1214 (Must_Override
(Parent
(Subp
))
1215 or else Must_Not_Override
(Parent
(Subp
)))
1219 -- Here we need the warning
1223 ("operation does not override inherited&?", Subp
, Subp
);
1227 Override_Dispatching_Operation
(Tagged_Type
, Ovr_Subp
, Subp
);
1229 -- Ada 2005 (AI-251): In case of late overriding of a primitive
1230 -- that covers abstract interface subprograms we must register it
1231 -- in all the secondary dispatch tables associated with abstract
1232 -- interfaces. We do this now only if not building static tables,
1233 -- nor when the expander is inactive (we avoid trying to register
1234 -- primitives in semantics-only mode, since the type may not have
1235 -- an associated dispatch table). Otherwise the patch code is
1236 -- emitted after those tables are built, to prevent access before
1237 -- elaboration in gigi.
1239 if Body_Is_Last_Primitive
and then Full_Expander_Active
then
1241 Subp_Body
: constant Node_Id
:= Unit_Declaration_Node
(Subp
);
1246 Elmt
:= First_Elmt
(Primitive_Operations
(Tagged_Type
));
1247 while Present
(Elmt
) loop
1248 Prim
:= Node
(Elmt
);
1250 -- No code required to register primitives in VM targets
1252 if Present
(Alias
(Prim
))
1253 and then Present
(Interface_Alias
(Prim
))
1254 and then Alias
(Prim
) = Subp
1255 and then not Building_Static_DT
(Tagged_Type
)
1256 and then VM_Target
= No_VM
1258 Insert_Actions_After
(Subp_Body
,
1259 Register_Primitive
(Sloc
(Subp_Body
), Prim
=> Prim
));
1265 -- Redisplay the contents of the updated dispatch table
1267 if Debug_Flag_ZZ
then
1268 Write_Str
("Late overriding: ");
1269 Write_DT
(Tagged_Type
);
1275 -- If the tagged type is a concurrent type then we must be compiling
1276 -- with no code generation (we are either compiling a generic unit or
1277 -- compiling under -gnatc mode) because we have previously tested that
1278 -- no serious errors has been reported. In this case we do not add the
1279 -- primitive to the list of primitives of Tagged_Type but we leave the
1280 -- primitive decorated as a dispatching operation to be able to analyze
1281 -- and report errors associated with the Object.Operation notation.
1283 elsif Is_Concurrent_Type
(Tagged_Type
) then
1284 pragma Assert
(not Expander_Active
);
1287 -- If no old subprogram, then we add this as a dispatching operation,
1288 -- but we avoid doing this if an error was posted, to prevent annoying
1291 elsif not Error_Posted
(Subp
) then
1292 Add_Dispatching_Operation
(Tagged_Type
, Subp
);
1295 Set_Is_Dispatching_Operation
(Subp
, True);
1297 -- Ada 2005 (AI-251): If the type implements interfaces we must check
1298 -- subtype conformance against all the interfaces covered by this
1301 if Present
(Ovr_Subp
)
1302 and then Has_Interfaces
(Tagged_Type
)
1305 Ifaces_List
: Elist_Id
;
1306 Iface_Elmt
: Elmt_Id
;
1307 Iface_Prim_Elmt
: Elmt_Id
;
1308 Iface_Prim
: Entity_Id
;
1309 Ret_Typ
: Entity_Id
;
1312 Collect_Interfaces
(Tagged_Type
, Ifaces_List
);
1314 Iface_Elmt
:= First_Elmt
(Ifaces_List
);
1315 while Present
(Iface_Elmt
) loop
1316 if not Is_Ancestor
(Node
(Iface_Elmt
), Tagged_Type
) then
1318 First_Elmt
(Primitive_Operations
(Node
(Iface_Elmt
)));
1319 while Present
(Iface_Prim_Elmt
) loop
1320 Iface_Prim
:= Node
(Iface_Prim_Elmt
);
1322 if Is_Interface_Conformant
1323 (Tagged_Type
, Iface_Prim
, Subp
)
1325 -- Handle procedures, functions whose return type
1326 -- matches, or functions not returning interfaces
1328 if Ekind
(Subp
) = E_Procedure
1329 or else Etype
(Iface_Prim
) = Etype
(Subp
)
1330 or else not Is_Interface
(Etype
(Iface_Prim
))
1332 Check_Subtype_Conformant
1334 Old_Id
=> Iface_Prim
,
1336 Skip_Controlling_Formals
=> True);
1338 -- Handle functions returning interfaces
1340 elsif Implements_Interface
1341 (Etype
(Subp
), Etype
(Iface_Prim
))
1343 -- Temporarily force both entities to return the
1344 -- same type. Required because Subtype_Conformant
1345 -- does not handle this case.
1347 Ret_Typ
:= Etype
(Iface_Prim
);
1348 Set_Etype
(Iface_Prim
, Etype
(Subp
));
1350 Check_Subtype_Conformant
1352 Old_Id
=> Iface_Prim
,
1354 Skip_Controlling_Formals
=> True);
1356 Set_Etype
(Iface_Prim
, Ret_Typ
);
1360 Next_Elmt
(Iface_Prim_Elmt
);
1364 Next_Elmt
(Iface_Elmt
);
1369 if not Body_Is_Last_Primitive
then
1370 Set_DT_Position
(Subp
, No_Uint
);
1372 elsif Has_Controlled_Component
(Tagged_Type
)
1374 (Chars
(Subp
) = Name_Initialize
or else
1375 Chars
(Subp
) = Name_Adjust
or else
1376 Chars
(Subp
) = Name_Finalize
or else
1377 Chars
(Subp
) = Name_Finalize_Address
)
1380 F_Node
: constant Node_Id
:= Freeze_Node
(Tagged_Type
);
1384 Old_Spec
: Entity_Id
;
1386 C_Names
: constant array (1 .. 4) of Name_Id
:=
1390 Name_Finalize_Address
);
1392 D_Names
: constant array (1 .. 4) of TSS_Name_Type
:=
1393 (TSS_Deep_Initialize
,
1396 TSS_Finalize_Address
);
1399 -- Remove previous controlled function which was constructed and
1400 -- analyzed when the type was frozen. This requires removing the
1401 -- body of the redefined primitive, as well as its specification
1402 -- if needed (there is no spec created for Deep_Initialize, see
1403 -- exp_ch3.adb). We must also dismantle the exception information
1404 -- that may have been generated for it when front end zero-cost
1405 -- tables are enabled.
1407 for J
in D_Names
'Range loop
1408 Old_P
:= TSS
(Tagged_Type
, D_Names
(J
));
1411 and then Chars
(Subp
) = C_Names
(J
)
1413 Old_Bod
:= Unit_Declaration_Node
(Old_P
);
1415 Set_Is_Eliminated
(Old_P
);
1416 Set_Scope
(Old_P
, Scope
(Current_Scope
));
1418 if Nkind
(Old_Bod
) = N_Subprogram_Body
1419 and then Present
(Corresponding_Spec
(Old_Bod
))
1421 Old_Spec
:= Corresponding_Spec
(Old_Bod
);
1422 Set_Has_Completion
(Old_Spec
, False);
1427 Build_Late_Proc
(Tagged_Type
, Chars
(Subp
));
1429 -- The new operation is added to the actions of the freeze node
1430 -- for the type, but this node has already been analyzed, so we
1431 -- must retrieve and analyze explicitly the new body.
1434 and then Present
(Actions
(F_Node
))
1436 Decl
:= Last
(Actions
(F_Node
));
1441 end Check_Dispatching_Operation
;
1443 ------------------------------------------
1444 -- Check_Operation_From_Incomplete_Type --
1445 ------------------------------------------
1447 procedure Check_Operation_From_Incomplete_Type
1451 Full
: constant Entity_Id
:= Full_View
(Typ
);
1452 Parent_Typ
: constant Entity_Id
:= Etype
(Full
);
1453 Old_Prim
: constant Elist_Id
:= Primitive_Operations
(Parent_Typ
);
1454 New_Prim
: constant Elist_Id
:= Primitive_Operations
(Full
);
1456 Prev
: Elmt_Id
:= No_Elmt
;
1458 function Derives_From
(Parent_Subp
: Entity_Id
) return Boolean;
1459 -- Check that Subp has profile of an operation derived from Parent_Subp.
1460 -- Subp must have a parameter or result type that is Typ or an access
1461 -- parameter or access result type that designates Typ.
1467 function Derives_From
(Parent_Subp
: Entity_Id
) return Boolean is
1471 if Chars
(Parent_Subp
) /= Chars
(Subp
) then
1475 -- Check that the type of controlling formals is derived from the
1476 -- parent subprogram's controlling formal type (or designated type
1477 -- if the formal type is an anonymous access type).
1479 F1
:= First_Formal
(Parent_Subp
);
1480 F2
:= First_Formal
(Subp
);
1481 while Present
(F1
) and then Present
(F2
) loop
1482 if Ekind
(Etype
(F1
)) = E_Anonymous_Access_Type
then
1483 if Ekind
(Etype
(F2
)) /= E_Anonymous_Access_Type
then
1485 elsif Designated_Type
(Etype
(F1
)) = Parent_Typ
1486 and then Designated_Type
(Etype
(F2
)) /= Full
1491 elsif Ekind
(Etype
(F2
)) = E_Anonymous_Access_Type
then
1494 elsif Etype
(F1
) = Parent_Typ
and then Etype
(F2
) /= Full
then
1502 -- Check that a controlling result type is derived from the parent
1503 -- subprogram's result type (or designated type if the result type
1504 -- is an anonymous access type).
1506 if Ekind
(Parent_Subp
) = E_Function
then
1507 if Ekind
(Subp
) /= E_Function
then
1510 elsif Ekind
(Etype
(Parent_Subp
)) = E_Anonymous_Access_Type
then
1511 if Ekind
(Etype
(Subp
)) /= E_Anonymous_Access_Type
then
1514 elsif Designated_Type
(Etype
(Parent_Subp
)) = Parent_Typ
1515 and then Designated_Type
(Etype
(Subp
)) /= Full
1520 elsif Ekind
(Etype
(Subp
)) = E_Anonymous_Access_Type
then
1523 elsif Etype
(Parent_Subp
) = Parent_Typ
1524 and then Etype
(Subp
) /= Full
1529 elsif Ekind
(Subp
) = E_Function
then
1533 return No
(F1
) and then No
(F2
);
1536 -- Start of processing for Check_Operation_From_Incomplete_Type
1539 -- The operation may override an inherited one, or may be a new one
1540 -- altogether. The inherited operation will have been hidden by the
1541 -- current one at the point of the type derivation, so it does not
1542 -- appear in the list of primitive operations of the type. We have to
1543 -- find the proper place of insertion in the list of primitive opera-
1544 -- tions by iterating over the list for the parent type.
1546 Op1
:= First_Elmt
(Old_Prim
);
1547 Op2
:= First_Elmt
(New_Prim
);
1548 while Present
(Op1
) and then Present
(Op2
) loop
1549 if Derives_From
(Node
(Op1
)) then
1552 -- Avoid adding it to the list of primitives if already there!
1554 if Node
(Op2
) /= Subp
then
1555 Prepend_Elmt
(Subp
, New_Prim
);
1559 Insert_Elmt_After
(Subp
, Prev
);
1570 -- Operation is a new primitive
1572 Append_Elmt
(Subp
, New_Prim
);
1573 end Check_Operation_From_Incomplete_Type
;
1575 ---------------------------------------
1576 -- Check_Operation_From_Private_View --
1577 ---------------------------------------
1579 procedure Check_Operation_From_Private_View
(Subp
, Old_Subp
: Entity_Id
) is
1580 Tagged_Type
: Entity_Id
;
1583 if Is_Dispatching_Operation
(Alias
(Subp
)) then
1584 Set_Scope
(Subp
, Current_Scope
);
1585 Tagged_Type
:= Find_Dispatching_Type
(Subp
);
1587 -- Add Old_Subp to primitive operations if not already present
1589 if Present
(Tagged_Type
) and then Is_Tagged_Type
(Tagged_Type
) then
1590 Append_Unique_Elmt
(Old_Subp
, Primitive_Operations
(Tagged_Type
));
1592 -- If Old_Subp isn't already marked as dispatching then this is
1593 -- the case of an operation of an untagged private type fulfilled
1594 -- by a tagged type that overrides an inherited dispatching
1595 -- operation, so we set the necessary dispatching attributes here.
1597 if not Is_Dispatching_Operation
(Old_Subp
) then
1599 -- If the untagged type has no discriminants, and the full
1600 -- view is constrained, there will be a spurious mismatch of
1601 -- subtypes on the controlling arguments, because the tagged
1602 -- type is the internal base type introduced in the derivation.
1603 -- Use the original type to verify conformance, rather than the
1606 if not Comes_From_Source
(Tagged_Type
)
1607 and then Has_Discriminants
(Tagged_Type
)
1613 Formal
:= First_Formal
(Old_Subp
);
1614 while Present
(Formal
) loop
1615 if Tagged_Type
= Base_Type
(Etype
(Formal
)) then
1616 Tagged_Type
:= Etype
(Formal
);
1619 Next_Formal
(Formal
);
1623 if Tagged_Type
= Base_Type
(Etype
(Old_Subp
)) then
1624 Tagged_Type
:= Etype
(Old_Subp
);
1628 Check_Controlling_Formals
(Tagged_Type
, Old_Subp
);
1629 Set_Is_Dispatching_Operation
(Old_Subp
, True);
1630 Set_DT_Position
(Old_Subp
, No_Uint
);
1633 -- If the old subprogram is an explicit renaming of some other
1634 -- entity, it is not overridden by the inherited subprogram.
1635 -- Otherwise, update its alias and other attributes.
1637 if Present
(Alias
(Old_Subp
))
1638 and then Nkind
(Unit_Declaration_Node
(Old_Subp
)) /=
1639 N_Subprogram_Renaming_Declaration
1641 Set_Alias
(Old_Subp
, Alias
(Subp
));
1643 -- The derived subprogram should inherit the abstractness of
1644 -- the parent subprogram (except in the case of a function
1645 -- returning the type). This sets the abstractness properly
1646 -- for cases where a private extension may have inherited an
1647 -- abstract operation, but the full type is derived from a
1648 -- descendant type and inherits a nonabstract version.
1650 if Etype
(Subp
) /= Tagged_Type
then
1651 Set_Is_Abstract_Subprogram
1652 (Old_Subp
, Is_Abstract_Subprogram
(Alias
(Subp
)));
1657 end Check_Operation_From_Private_View
;
1659 --------------------------
1660 -- Find_Controlling_Arg --
1661 --------------------------
1663 function Find_Controlling_Arg
(N
: Node_Id
) return Node_Id
is
1664 Orig_Node
: constant Node_Id
:= Original_Node
(N
);
1668 if Nkind
(Orig_Node
) = N_Qualified_Expression
then
1669 return Find_Controlling_Arg
(Expression
(Orig_Node
));
1672 -- Dispatching on result case. If expansion is disabled, the node still
1673 -- has the structure of a function call. However, if the function name
1674 -- is an operator and the call was given in infix form, the original
1675 -- node has no controlling result and we must examine the current node.
1677 if Nkind
(N
) = N_Function_Call
1678 and then Present
(Controlling_Argument
(N
))
1679 and then Has_Controlling_Result
(Entity
(Name
(N
)))
1681 return Controlling_Argument
(N
);
1683 -- If expansion is enabled, the call may have been transformed into
1684 -- an indirect call, and we need to recover the original node.
1686 elsif Nkind
(Orig_Node
) = N_Function_Call
1687 and then Present
(Controlling_Argument
(Orig_Node
))
1688 and then Has_Controlling_Result
(Entity
(Name
(Orig_Node
)))
1690 return Controlling_Argument
(Orig_Node
);
1692 -- Type conversions are dynamically tagged if the target type, or its
1693 -- designated type, are classwide. An interface conversion expands into
1694 -- a dereference, so test must be performed on the original node.
1696 elsif Nkind
(Orig_Node
) = N_Type_Conversion
1697 and then Nkind
(N
) = N_Explicit_Dereference
1698 and then Is_Controlling_Actual
(N
)
1701 Target_Type
: constant Entity_Id
:=
1702 Entity
(Subtype_Mark
(Orig_Node
));
1705 if Is_Class_Wide_Type
(Target_Type
) then
1708 elsif Is_Access_Type
(Target_Type
)
1709 and then Is_Class_Wide_Type
(Designated_Type
(Target_Type
))
1720 elsif Is_Controlling_Actual
(N
)
1722 (Nkind
(Parent
(N
)) = N_Qualified_Expression
1723 and then Is_Controlling_Actual
(Parent
(N
)))
1727 if Is_Access_Type
(Typ
) then
1729 -- In the case of an Access attribute, use the type of the prefix,
1730 -- since in the case of an actual for an access parameter, the
1731 -- attribute's type may be of a specific designated type, even
1732 -- though the prefix type is class-wide.
1734 if Nkind
(N
) = N_Attribute_Reference
then
1735 Typ
:= Etype
(Prefix
(N
));
1737 -- An allocator is dispatching if the type of qualified expression
1738 -- is class_wide, in which case this is the controlling type.
1740 elsif Nkind
(Orig_Node
) = N_Allocator
1741 and then Nkind
(Expression
(Orig_Node
)) = N_Qualified_Expression
1743 Typ
:= Etype
(Expression
(Orig_Node
));
1745 Typ
:= Designated_Type
(Typ
);
1749 if Is_Class_Wide_Type
(Typ
)
1751 (Nkind
(Parent
(N
)) = N_Qualified_Expression
1752 and then Is_Access_Type
(Etype
(N
))
1753 and then Is_Class_Wide_Type
(Designated_Type
(Etype
(N
))))
1760 end Find_Controlling_Arg
;
1762 ---------------------------
1763 -- Find_Dispatching_Type --
1764 ---------------------------
1766 function Find_Dispatching_Type
(Subp
: Entity_Id
) return Entity_Id
is
1767 A_Formal
: Entity_Id
;
1769 Ctrl_Type
: Entity_Id
;
1772 if Ekind_In
(Subp
, E_Function
, E_Procedure
)
1773 and then Present
(DTC_Entity
(Subp
))
1775 return Scope
(DTC_Entity
(Subp
));
1777 -- For subprograms internally generated by derivations of tagged types
1778 -- use the alias subprogram as a reference to locate the dispatching
1781 elsif not Comes_From_Source
(Subp
)
1782 and then Present
(Alias
(Subp
))
1783 and then Is_Dispatching_Operation
(Alias
(Subp
))
1785 if Ekind
(Alias
(Subp
)) = E_Function
1786 and then Has_Controlling_Result
(Alias
(Subp
))
1788 return Check_Controlling_Type
(Etype
(Subp
), Subp
);
1791 Formal
:= First_Formal
(Subp
);
1792 A_Formal
:= First_Formal
(Alias
(Subp
));
1793 while Present
(A_Formal
) loop
1794 if Is_Controlling_Formal
(A_Formal
) then
1795 return Check_Controlling_Type
(Etype
(Formal
), Subp
);
1798 Next_Formal
(Formal
);
1799 Next_Formal
(A_Formal
);
1802 pragma Assert
(False);
1809 Formal
:= First_Formal
(Subp
);
1810 while Present
(Formal
) loop
1811 Ctrl_Type
:= Check_Controlling_Type
(Etype
(Formal
), Subp
);
1813 if Present
(Ctrl_Type
) then
1817 Next_Formal
(Formal
);
1820 -- The subprogram may also be dispatching on result
1822 if Present
(Etype
(Subp
)) then
1823 return Check_Controlling_Type
(Etype
(Subp
), Subp
);
1827 pragma Assert
(not Is_Dispatching_Operation
(Subp
));
1829 end Find_Dispatching_Type
;
1831 --------------------------------------
1832 -- Find_Hidden_Overridden_Primitive --
1833 --------------------------------------
1835 function Find_Hidden_Overridden_Primitive
(S
: Entity_Id
) return Entity_Id
1837 Tag_Typ
: constant Entity_Id
:= Find_Dispatching_Type
(S
);
1839 Orig_Prim
: Entity_Id
;
1841 Vis_List
: Elist_Id
;
1844 -- This Ada 2012 rule is valid only for type extensions or private
1848 or else not Is_Record_Type
(Tag_Typ
)
1849 or else Etype
(Tag_Typ
) = Tag_Typ
1854 -- Collect the list of visible ancestor of the tagged type
1856 Vis_List
:= Visible_Ancestors
(Tag_Typ
);
1858 Elmt
:= First_Elmt
(Primitive_Operations
(Tag_Typ
));
1859 while Present
(Elmt
) loop
1860 Prim
:= Node
(Elmt
);
1862 -- Find an inherited hidden dispatching primitive with the name of S
1863 -- and a type-conformant profile.
1865 if Present
(Alias
(Prim
))
1866 and then Is_Hidden
(Alias
(Prim
))
1867 and then Find_Dispatching_Type
(Alias
(Prim
)) /= Tag_Typ
1868 and then Primitive_Names_Match
(S
, Prim
)
1869 and then Type_Conformant
(S
, Prim
)
1872 Vis_Ancestor
: Elmt_Id
;
1876 -- The original corresponding operation of Prim must be an
1877 -- operation of a visible ancestor of the dispatching type S,
1878 -- and the original corresponding operation of S2 must be
1881 Orig_Prim
:= Original_Corresponding_Operation
(Prim
);
1883 if Orig_Prim
/= Prim
1884 and then Is_Immediately_Visible
(Orig_Prim
)
1886 Vis_Ancestor
:= First_Elmt
(Vis_List
);
1887 while Present
(Vis_Ancestor
) loop
1889 First_Elmt
(Primitive_Operations
(Node
(Vis_Ancestor
)));
1890 while Present
(Elmt
) loop
1891 if Node
(Elmt
) = Orig_Prim
then
1892 Set_Overridden_Operation
(S
, Prim
);
1893 Set_Alias
(Prim
, Orig_Prim
);
1900 Next_Elmt
(Vis_Ancestor
);
1910 end Find_Hidden_Overridden_Primitive
;
1912 ---------------------------------------
1913 -- Find_Primitive_Covering_Interface --
1914 ---------------------------------------
1916 function Find_Primitive_Covering_Interface
1917 (Tagged_Type
: Entity_Id
;
1918 Iface_Prim
: Entity_Id
) return Entity_Id
1924 pragma Assert
(Is_Interface
(Find_Dispatching_Type
(Iface_Prim
))
1925 or else (Present
(Alias
(Iface_Prim
))
1928 (Find_Dispatching_Type
(Ultimate_Alias
(Iface_Prim
)))));
1930 -- Search in the homonym chain. Done to speed up locating visible
1931 -- entities and required to catch primitives associated with the partial
1932 -- view of private types when processing the corresponding full view.
1934 E
:= Current_Entity
(Iface_Prim
);
1935 while Present
(E
) loop
1936 if Is_Subprogram
(E
)
1937 and then Is_Dispatching_Operation
(E
)
1938 and then Is_Interface_Conformant
(Tagged_Type
, Iface_Prim
, E
)
1946 -- Search in the list of primitives of the type. Required to locate
1947 -- the covering primitive if the covering primitive is not visible
1948 -- (for example, non-visible inherited primitive of private type).
1950 El
:= First_Elmt
(Primitive_Operations
(Tagged_Type
));
1951 while Present
(El
) loop
1954 -- Keep separate the management of internal entities that link
1955 -- primitives with interface primitives from tagged type primitives.
1957 if No
(Interface_Alias
(E
)) then
1958 if Present
(Alias
(E
)) then
1960 -- This interface primitive has not been covered yet
1962 if Alias
(E
) = Iface_Prim
then
1965 -- The covering primitive was inherited
1967 elsif Overridden_Operation
(Ultimate_Alias
(E
))
1974 -- Check if E covers the interface primitive (includes case in
1975 -- which E is an inherited private primitive).
1977 if Is_Interface_Conformant
(Tagged_Type
, Iface_Prim
, E
) then
1981 -- Use the internal entity that links the interface primitive with
1982 -- the covering primitive to locate the entity.
1984 elsif Interface_Alias
(E
) = Iface_Prim
then
1994 end Find_Primitive_Covering_Interface
;
1996 ---------------------------
1997 -- Inherited_Subprograms --
1998 ---------------------------
2000 function Inherited_Subprograms
(S
: Entity_Id
) return Subprogram_List
is
2001 Result
: Subprogram_List
(1 .. 6000);
2002 -- 6000 here is intended to be infinity. We could use an expandable
2003 -- table, but it would be awfully heavy, and there is no way that we
2004 -- could reasonably exceed this value.
2007 -- Number of entries in Result
2009 Parent_Op
: Entity_Id
;
2010 -- Traverses the Overridden_Operation chain
2012 procedure Store_IS
(E
: Entity_Id
);
2013 -- Stores E in Result if not already stored
2019 procedure Store_IS
(E
: Entity_Id
) is
2021 for J
in 1 .. N
loop
2022 if E
= Result
(J
) then
2031 -- Start of processing for Inherited_Subprograms
2034 if Present
(S
) and then Is_Dispatching_Operation
(S
) then
2036 -- Deal with direct inheritance
2040 Parent_Op
:= Overridden_Operation
(Parent_Op
);
2041 exit when No
(Parent_Op
);
2043 if Is_Subprogram
(Parent_Op
)
2044 or else Is_Generic_Subprogram
(Parent_Op
)
2046 Store_IS
(Parent_Op
);
2050 -- Now deal with interfaces
2053 Tag_Typ
: Entity_Id
;
2058 Tag_Typ
:= Find_Dispatching_Type
(S
);
2060 if Is_Concurrent_Type
(Tag_Typ
) then
2061 Tag_Typ
:= Corresponding_Record_Type
(Tag_Typ
);
2064 -- Search primitive operations of dispatching type
2066 if Present
(Tag_Typ
)
2067 and then Present
(Primitive_Operations
(Tag_Typ
))
2069 Elmt
:= First_Elmt
(Primitive_Operations
(Tag_Typ
));
2070 while Present
(Elmt
) loop
2071 Prim
:= Node
(Elmt
);
2073 -- The following test eliminates some odd cases in which
2074 -- Ekind (Prim) is Void, to be investigated further ???
2076 if not (Is_Subprogram
(Prim
)
2078 Is_Generic_Subprogram
(Prim
))
2082 -- For [generic] subprogram, look at interface alias
2084 elsif Present
(Interface_Alias
(Prim
))
2085 and then Alias
(Prim
) = S
2087 -- We have found a primitive covered by S
2089 Store_IS
(Interface_Alias
(Prim
));
2098 return Result
(1 .. N
);
2099 end Inherited_Subprograms
;
2101 ---------------------------
2102 -- Is_Dynamically_Tagged --
2103 ---------------------------
2105 function Is_Dynamically_Tagged
(N
: Node_Id
) return Boolean is
2107 if Nkind
(N
) = N_Error
then
2110 return Find_Controlling_Arg
(N
) /= Empty
;
2112 end Is_Dynamically_Tagged
;
2114 ---------------------------------
2115 -- Is_Null_Interface_Primitive --
2116 ---------------------------------
2118 function Is_Null_Interface_Primitive
(E
: Entity_Id
) return Boolean is
2120 return Comes_From_Source
(E
)
2121 and then Is_Dispatching_Operation
(E
)
2122 and then Ekind
(E
) = E_Procedure
2123 and then Null_Present
(Parent
(E
))
2124 and then Is_Interface
(Find_Dispatching_Type
(E
));
2125 end Is_Null_Interface_Primitive
;
2127 --------------------------
2128 -- Is_Tag_Indeterminate --
2129 --------------------------
2131 function Is_Tag_Indeterminate
(N
: Node_Id
) return Boolean is
2134 Orig_Node
: constant Node_Id
:= Original_Node
(N
);
2137 if Nkind
(Orig_Node
) = N_Function_Call
2138 and then Is_Entity_Name
(Name
(Orig_Node
))
2140 Nam
:= Entity
(Name
(Orig_Node
));
2142 if not Has_Controlling_Result
(Nam
) then
2145 -- The function may have a controlling result, but if the return type
2146 -- is not visibly tagged, then this is not tag-indeterminate.
2148 elsif Is_Access_Type
(Etype
(Nam
))
2149 and then not Is_Tagged_Type
(Designated_Type
(Etype
(Nam
)))
2153 -- An explicit dereference means that the call has already been
2154 -- expanded and there is no tag to propagate.
2156 elsif Nkind
(N
) = N_Explicit_Dereference
then
2159 -- If there are no actuals, the call is tag-indeterminate
2161 elsif No
(Parameter_Associations
(Orig_Node
)) then
2165 Actual
:= First_Actual
(Orig_Node
);
2166 while Present
(Actual
) loop
2167 if Is_Controlling_Actual
(Actual
)
2168 and then not Is_Tag_Indeterminate
(Actual
)
2170 -- One operand is dispatching
2175 Next_Actual
(Actual
);
2181 elsif Nkind
(Orig_Node
) = N_Qualified_Expression
then
2182 return Is_Tag_Indeterminate
(Expression
(Orig_Node
));
2184 -- Case of a call to the Input attribute (possibly rewritten), which is
2185 -- always tag-indeterminate except when its prefix is a Class attribute.
2187 elsif Nkind
(Orig_Node
) = N_Attribute_Reference
2189 Get_Attribute_Id
(Attribute_Name
(Orig_Node
)) = Attribute_Input
2191 Nkind
(Prefix
(Orig_Node
)) /= N_Attribute_Reference
2195 -- In Ada 2005, a function that returns an anonymous access type can be
2196 -- dispatching, and the dereference of a call to such a function can
2197 -- also be tag-indeterminate if the call itself is.
2199 elsif Nkind
(Orig_Node
) = N_Explicit_Dereference
2200 and then Ada_Version
>= Ada_2005
2202 return Is_Tag_Indeterminate
(Prefix
(Orig_Node
));
2207 end Is_Tag_Indeterminate
;
2209 ------------------------------------
2210 -- Override_Dispatching_Operation --
2211 ------------------------------------
2213 procedure Override_Dispatching_Operation
2214 (Tagged_Type
: Entity_Id
;
2215 Prev_Op
: Entity_Id
;
2222 -- Diagnose failure to match No_Return in parent (Ada-2005, AI-414, but
2223 -- we do it unconditionally in Ada 95 now, since this is our pragma!)
2225 if No_Return
(Prev_Op
) and then not No_Return
(New_Op
) then
2226 Error_Msg_N
("procedure & must have No_Return pragma", New_Op
);
2227 Error_Msg_N
("\since overridden procedure has No_Return", New_Op
);
2230 -- If there is no previous operation to override, the type declaration
2231 -- was malformed, and an error must have been emitted already.
2233 Elmt
:= First_Elmt
(Primitive_Operations
(Tagged_Type
));
2234 while Present
(Elmt
)
2235 and then Node
(Elmt
) /= Prev_Op
2244 -- The location of entities that come from source in the list of
2245 -- primitives of the tagged type must follow their order of occurrence
2246 -- in the sources to fulfill the C++ ABI. If the overridden entity is a
2247 -- primitive of an interface that is not implemented by the parents of
2248 -- this tagged type (that is, it is an alias of an interface primitive
2249 -- generated by Derive_Interface_Progenitors), then we must append the
2250 -- new entity at the end of the list of primitives.
2252 if Present
(Alias
(Prev_Op
))
2253 and then Etype
(Tagged_Type
) /= Tagged_Type
2254 and then Is_Interface
(Find_Dispatching_Type
(Alias
(Prev_Op
)))
2255 and then not Is_Ancestor
(Find_Dispatching_Type
(Alias
(Prev_Op
)),
2256 Tagged_Type
, Use_Full_View
=> True)
2257 and then not Implements_Interface
2258 (Etype
(Tagged_Type
),
2259 Find_Dispatching_Type
(Alias
(Prev_Op
)))
2261 Remove_Elmt
(Primitive_Operations
(Tagged_Type
), Elmt
);
2262 Append_Elmt
(New_Op
, Primitive_Operations
(Tagged_Type
));
2264 -- The new primitive replaces the overridden entity. Required to ensure
2265 -- that overriding primitive is assigned the same dispatch table slot.
2268 Replace_Elmt
(Elmt
, New_Op
);
2271 if Ada_Version
>= Ada_2005
2272 and then Has_Interfaces
(Tagged_Type
)
2274 -- Ada 2005 (AI-251): Update the attribute alias of all the aliased
2275 -- entities of the overridden primitive to reference New_Op, and
2276 -- also propagate the proper value of Is_Abstract_Subprogram. Verify
2277 -- that the new operation is subtype conformant with the interface
2278 -- operations that it implements (for operations inherited from the
2279 -- parent itself, this check is made when building the derived type).
2281 -- Note: This code is only executed in case of late overriding
2283 Elmt
:= First_Elmt
(Primitive_Operations
(Tagged_Type
));
2284 while Present
(Elmt
) loop
2285 Prim
:= Node
(Elmt
);
2287 if Prim
= New_Op
then
2290 -- Note: The check on Is_Subprogram protects the frontend against
2291 -- reading attributes in entities that are not yet fully decorated
2293 elsif Is_Subprogram
(Prim
)
2294 and then Present
(Interface_Alias
(Prim
))
2295 and then Alias
(Prim
) = Prev_Op
2296 and then Present
(Etype
(New_Op
))
2298 Set_Alias
(Prim
, New_Op
);
2299 Check_Subtype_Conformant
(New_Op
, Prim
);
2300 Set_Is_Abstract_Subprogram
(Prim
,
2301 Is_Abstract_Subprogram
(New_Op
));
2303 -- Ensure that this entity will be expanded to fill the
2304 -- corresponding entry in its dispatch table.
2306 if not Is_Abstract_Subprogram
(Prim
) then
2307 Set_Has_Delayed_Freeze
(Prim
);
2315 if (not Is_Package_Or_Generic_Package
(Current_Scope
))
2316 or else not In_Private_Part
(Current_Scope
)
2318 -- Not a private primitive
2322 else pragma Assert
(Is_Inherited_Operation
(Prev_Op
));
2324 -- Make the overriding operation into an alias of the implicit one.
2325 -- In this fashion a call from outside ends up calling the new body
2326 -- even if non-dispatching, and a call from inside calls the over-
2327 -- riding operation because it hides the implicit one. To indicate
2328 -- that the body of Prev_Op is never called, set its dispatch table
2329 -- entity to Empty. If the overridden operation has a dispatching
2330 -- result, so does the overriding one.
2332 Set_Alias
(Prev_Op
, New_Op
);
2333 Set_DTC_Entity
(Prev_Op
, Empty
);
2334 Set_Has_Controlling_Result
(New_Op
, Has_Controlling_Result
(Prev_Op
));
2337 end Override_Dispatching_Operation
;
2343 procedure Propagate_Tag
(Control
: Node_Id
; Actual
: Node_Id
) is
2344 Call_Node
: Node_Id
;
2348 if Nkind
(Actual
) = N_Function_Call
then
2349 Call_Node
:= Actual
;
2351 elsif Nkind
(Actual
) = N_Identifier
2352 and then Nkind
(Original_Node
(Actual
)) = N_Function_Call
2354 -- Call rewritten as object declaration when stack-checking is
2355 -- enabled. Propagate tag to expression in declaration, which is
2358 Call_Node
:= Expression
(Parent
(Entity
(Actual
)));
2360 -- Ada 2005: If this is a dereference of a call to a function with a
2361 -- dispatching access-result, the tag is propagated when the dereference
2362 -- itself is expanded (see exp_ch6.adb) and there is nothing else to do.
2364 elsif Nkind
(Actual
) = N_Explicit_Dereference
2365 and then Nkind
(Original_Node
(Prefix
(Actual
))) = N_Function_Call
2369 -- When expansion is suppressed, an unexpanded call to 'Input can occur,
2370 -- and in that case we can simply return.
2372 elsif Nkind
(Actual
) = N_Attribute_Reference
then
2373 pragma Assert
(Attribute_Name
(Actual
) = Name_Input
);
2377 -- Only other possibilities are parenthesized or qualified expression,
2378 -- or an expander-generated unchecked conversion of a function call to
2379 -- a stream Input attribute.
2382 Call_Node
:= Expression
(Actual
);
2385 -- Do not set the Controlling_Argument if already set. This happens in
2386 -- the special case of _Input (see Exp_Attr, case Input).
2388 if No
(Controlling_Argument
(Call_Node
)) then
2389 Set_Controlling_Argument
(Call_Node
, Control
);
2392 Arg
:= First_Actual
(Call_Node
);
2393 while Present
(Arg
) loop
2394 if Is_Tag_Indeterminate
(Arg
) then
2395 Propagate_Tag
(Control
, Arg
);
2401 -- Expansion of dispatching calls is suppressed when VM_Target, because
2402 -- the VM back-ends directly handle the generation of dispatching calls
2403 -- and would have to undo any expansion to an indirect call.
2405 if Tagged_Type_Expansion
then
2407 Call_Typ
: constant Entity_Id
:= Etype
(Call_Node
);
2410 Expand_Dispatching_Call
(Call_Node
);
2412 -- If the controlling argument is an interface type and the type
2413 -- of Call_Node differs then we must add an implicit conversion to
2414 -- force displacement of the pointer to the object to reference
2415 -- the secondary dispatch table of the interface.
2417 if Is_Interface
(Etype
(Control
))
2418 and then Etype
(Control
) /= Call_Typ
2420 -- Cannot use Convert_To because the previous call to
2421 -- Expand_Dispatching_Call leaves decorated the Call_Node
2422 -- with the type of Control.
2425 Make_Type_Conversion
(Sloc
(Call_Node
),
2427 New_Occurrence_Of
(Etype
(Control
), Sloc
(Call_Node
)),
2428 Expression
=> Relocate_Node
(Call_Node
)));
2429 Set_Etype
(Call_Node
, Etype
(Control
));
2430 Set_Analyzed
(Call_Node
);
2432 Expand_Interface_Conversion
(Call_Node
, Is_Static
=> False);
2436 -- Expansion of a dispatching call results in an indirect call, which in
2437 -- turn causes current values to be killed (see Resolve_Call), so on VM
2438 -- targets we do the call here to ensure consistent warnings between VM
2439 -- and non-VM targets.
2442 Kill_Current_Values
;