OSDN Git Service

* gcc-interface/ada-tree.h (SET_TYPE_RM_VALUE): Mark the expression
[pf3gnuchains/gcc-fork.git] / gcc / ada / sem_disp.adb
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-2009, 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 ------------------------------------------------------------------------------
25
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_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 Stand;    use Stand;
52 with Sinfo;    use Sinfo;
53 with Tbuild;   use Tbuild;
54 with Uintp;    use Uintp;
55
56 package body Sem_Disp is
57
58    -----------------------
59    -- Local Subprograms --
60    -----------------------
61
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
66
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.
75
76    -------------------------------
77    -- Add_Dispatching_Operation --
78    -------------------------------
79
80    procedure Add_Dispatching_Operation
81      (Tagged_Type : Entity_Id;
82       New_Op      : Entity_Id)
83    is
84       List : constant Elist_Id := Primitive_Operations (Tagged_Type);
85
86    begin
87       --  The dispatching operation may already be on the list, if it is the
88       --  wrapper for an inherited function of a null extension (see Exp_Ch3
89       --  for the construction of function wrappers). The list of primitive
90       --  operations must not contain duplicates.
91
92       Append_Unique_Elmt (New_Op, List);
93    end Add_Dispatching_Operation;
94
95    -------------------------------
96    -- Check_Controlling_Formals --
97    -------------------------------
98
99    procedure Check_Controlling_Formals
100      (Typ  : Entity_Id;
101       Subp : Entity_Id)
102    is
103       Formal    : Entity_Id;
104       Ctrl_Type : Entity_Id;
105
106    begin
107       Formal := First_Formal (Subp);
108       while Present (Formal) loop
109          Ctrl_Type := Check_Controlling_Type (Etype (Formal), Subp);
110
111          if Present (Ctrl_Type) then
112
113             --  When controlling type is concurrent and declared within a
114             --  generic or inside an instance use corresponding record type.
115
116             if Is_Concurrent_Type (Ctrl_Type)
117               and then Present (Corresponding_Record_Type (Ctrl_Type))
118             then
119                Ctrl_Type := Corresponding_Record_Type (Ctrl_Type);
120             end if;
121
122             if Ctrl_Type = Typ then
123                Set_Is_Controlling_Formal (Formal);
124
125                --  Ada 2005 (AI-231): Anonymous access types that are used in
126                --  controlling parameters exclude null because it is necessary
127                --  to read the tag to dispatch, and null has no tag.
128
129                if Ekind (Etype (Formal)) = E_Anonymous_Access_Type then
130                   Set_Can_Never_Be_Null (Etype (Formal));
131                   Set_Is_Known_Non_Null (Etype (Formal));
132                end if;
133
134                --  Check that the parameter's nominal subtype statically
135                --  matches the first subtype.
136
137                if Ekind (Etype (Formal)) = E_Anonymous_Access_Type then
138                   if not Subtypes_Statically_Match
139                            (Typ, Designated_Type (Etype (Formal)))
140                   then
141                      Error_Msg_N
142                        ("parameter subtype does not match controlling type",
143                         Formal);
144                   end if;
145
146                elsif not Subtypes_Statically_Match (Typ, Etype (Formal)) then
147                   Error_Msg_N
148                     ("parameter subtype does not match controlling type",
149                      Formal);
150                end if;
151
152                if Present (Default_Value (Formal)) then
153
154                   --  In Ada 2005, access parameters can have defaults
155
156                   if Ekind (Etype (Formal)) = E_Anonymous_Access_Type
157                     and then Ada_Version < Ada_05
158                   then
159                      Error_Msg_N
160                        ("default not allowed for controlling access parameter",
161                         Default_Value (Formal));
162
163                   elsif not Is_Tag_Indeterminate (Default_Value (Formal)) then
164                      Error_Msg_N
165                        ("default expression must be a tag indeterminate" &
166                         " function call", Default_Value (Formal));
167                   end if;
168                end if;
169
170             elsif Comes_From_Source (Subp) then
171                Error_Msg_N
172                  ("operation can be dispatching in only one type", Subp);
173             end if;
174          end if;
175
176          Next_Formal (Formal);
177       end loop;
178
179       if Ekind (Subp) = E_Function
180            or else
181          Ekind (Subp) = E_Generic_Function
182       then
183          Ctrl_Type := Check_Controlling_Type (Etype (Subp), Subp);
184
185          if Present (Ctrl_Type) then
186             if Ctrl_Type = Typ then
187                Set_Has_Controlling_Result (Subp);
188
189                --  Check that result subtype statically matches first subtype
190                --  (Ada 2005): Subp may have a controlling access result.
191
192                if Subtypes_Statically_Match (Typ, Etype (Subp))
193                  or else (Ekind (Etype (Subp)) = E_Anonymous_Access_Type
194                             and then
195                               Subtypes_Statically_Match
196                                 (Typ, Designated_Type (Etype (Subp))))
197                then
198                   null;
199
200                else
201                   Error_Msg_N
202                     ("result subtype does not match controlling type", Subp);
203                end if;
204
205             elsif Comes_From_Source (Subp) then
206                Error_Msg_N
207                  ("operation can be dispatching in only one type", Subp);
208             end if;
209          end if;
210       end if;
211    end Check_Controlling_Formals;
212
213    ----------------------------
214    -- Check_Controlling_Type --
215    ----------------------------
216
217    function Check_Controlling_Type
218      (T    : Entity_Id;
219       Subp : Entity_Id) return Entity_Id
220    is
221       Tagged_Type : Entity_Id := Empty;
222
223    begin
224       if Is_Tagged_Type (T) then
225          if Is_First_Subtype (T) then
226             Tagged_Type := T;
227          else
228             Tagged_Type := Base_Type (T);
229          end if;
230
231       elsif Ekind (T) = E_Anonymous_Access_Type
232         and then Is_Tagged_Type (Designated_Type (T))
233       then
234          if Ekind (Designated_Type (T)) /= E_Incomplete_Type then
235             if Is_First_Subtype (Designated_Type (T)) then
236                Tagged_Type := Designated_Type (T);
237             else
238                Tagged_Type := Base_Type (Designated_Type (T));
239             end if;
240
241          --  Ada 2005: an incomplete type can be tagged. An operation with an
242          --  access parameter of the type is dispatching.
243
244          elsif Scope (Designated_Type (T)) = Current_Scope then
245             Tagged_Type := Designated_Type (T);
246
247          --  Ada 2005 (AI-50217)
248
249          elsif From_With_Type (Designated_Type (T))
250            and then Present (Non_Limited_View (Designated_Type (T)))
251          then
252             if Is_First_Subtype (Non_Limited_View (Designated_Type (T))) then
253                Tagged_Type := Non_Limited_View (Designated_Type (T));
254             else
255                Tagged_Type := Base_Type (Non_Limited_View
256                                          (Designated_Type (T)));
257             end if;
258          end if;
259       end if;
260
261       if No (Tagged_Type) or else Is_Class_Wide_Type (Tagged_Type) then
262          return Empty;
263
264       --  The dispatching type and the primitive operation must be defined in
265       --  the same scope, except in the case of internal operations and formal
266       --  abstract subprograms.
267
268       elsif ((Scope (Subp) = Scope (Tagged_Type) or else Is_Internal (Subp))
269                and then (not Is_Generic_Type (Tagged_Type)
270                           or else not Comes_From_Source (Subp)))
271         or else
272           (Is_Formal_Subprogram (Subp) and then Is_Abstract_Subprogram (Subp))
273         or else
274           (Nkind (Parent (Parent (Subp))) = N_Subprogram_Renaming_Declaration
275             and then
276               Present (Corresponding_Formal_Spec (Parent (Parent (Subp))))
277             and then
278               Is_Abstract_Subprogram (Subp))
279       then
280          return Tagged_Type;
281
282       else
283          return Empty;
284       end if;
285    end Check_Controlling_Type;
286
287    ----------------------------
288    -- Check_Dispatching_Call --
289    ----------------------------
290
291    procedure Check_Dispatching_Call (N : Node_Id) is
292       Loc                    : constant Source_Ptr := Sloc (N);
293       Actual                 : Node_Id;
294       Formal                 : Entity_Id;
295       Control                : Node_Id := Empty;
296       Func                   : Entity_Id;
297       Subp_Entity            : Entity_Id;
298       Indeterm_Ancestor_Call : Boolean := False;
299       Indeterm_Ctrl_Type     : Entity_Id;
300
301       Static_Tag : Node_Id := Empty;
302       --  If a controlling formal has a statically tagged actual, the tag of
303       --  this actual is to be used for any tag-indeterminate actual.
304
305       procedure Check_Direct_Call;
306       --  In the case when the controlling actual is a class-wide type whose
307       --  root type's completion is a task or protected type, the call is in
308       --  fact direct. This routine detects the above case and modifies the
309       --  call accordingly.
310
311       procedure Check_Dispatching_Context;
312       --  If the call is tag-indeterminate and the entity being called is
313       --  abstract, verify that the context is a call that will eventually
314       --  provide a tag for dispatching, or has provided one already.
315
316       -----------------------
317       -- Check_Direct_Call --
318       -----------------------
319
320       procedure Check_Direct_Call is
321          Typ : Entity_Id := Etype (Control);
322
323          function Is_User_Defined_Equality (Id : Entity_Id) return Boolean;
324          --  Determine whether an entity denotes a user-defined equality
325
326          ------------------------------
327          -- Is_User_Defined_Equality --
328          ------------------------------
329
330          function Is_User_Defined_Equality (Id : Entity_Id) return Boolean is
331          begin
332             return
333               Ekind (Id) = E_Function
334                 and then Chars (Id) = Name_Op_Eq
335                 and then Comes_From_Source (Id)
336
337                --  Internally generated equalities have a full type declaration
338                --  as their parent.
339
340                 and then Nkind (Parent (Id)) = N_Function_Specification;
341          end Is_User_Defined_Equality;
342
343       --  Start of processing for Check_Direct_Call
344
345       begin
346          --  Predefined primitives do not receive wrappers since they are built
347          --  from scratch for the corresponding record of synchronized types.
348          --  Equality is in general predefined, but is excluded from the check
349          --  when it is user-defined.
350
351          if Is_Predefined_Dispatching_Operation (Subp_Entity)
352            and then not Is_User_Defined_Equality (Subp_Entity)
353          then
354             return;
355          end if;
356
357          if Is_Class_Wide_Type (Typ) then
358             Typ := Root_Type (Typ);
359          end if;
360
361          if Is_Private_Type (Typ) and then Present (Full_View (Typ)) then
362             Typ := Full_View (Typ);
363          end if;
364
365          if Is_Concurrent_Type (Typ)
366               and then
367             Present (Corresponding_Record_Type (Typ))
368          then
369             Typ := Corresponding_Record_Type (Typ);
370
371             --  The concurrent record's list of primitives should contain a
372             --  wrapper for the entity of the call, retrieve it.
373
374             declare
375                Prim          : Entity_Id;
376                Prim_Elmt     : Elmt_Id;
377                Wrapper_Found : Boolean := False;
378
379             begin
380                Prim_Elmt := First_Elmt (Primitive_Operations (Typ));
381                while Present (Prim_Elmt) loop
382                   Prim := Node (Prim_Elmt);
383
384                   if Is_Primitive_Wrapper (Prim)
385                     and then Wrapped_Entity (Prim) = Subp_Entity
386                   then
387                      Wrapper_Found := True;
388                      exit;
389                   end if;
390
391                   Next_Elmt (Prim_Elmt);
392                end loop;
393
394                --  A primitive declared between two views should have a
395                --  corresponding wrapper.
396
397                pragma Assert (Wrapper_Found);
398
399                --  Modify the call by setting the proper entity
400
401                Set_Entity (Name (N), Prim);
402             end;
403          end if;
404       end Check_Direct_Call;
405
406       -------------------------------
407       -- Check_Dispatching_Context --
408       -------------------------------
409
410       procedure Check_Dispatching_Context is
411          Subp : constant Entity_Id := Entity (Name (N));
412          Par  : Node_Id;
413
414       begin
415          if Is_Abstract_Subprogram (Subp)
416            and then No (Controlling_Argument (N))
417          then
418             if Present (Alias (Subp))
419               and then not Is_Abstract_Subprogram (Alias (Subp))
420               and then No (DTC_Entity (Subp))
421             then
422                --  Private overriding of inherited abstract operation, call is
423                --  legal.
424
425                Set_Entity (Name (N), Alias (Subp));
426                return;
427
428             else
429                Par := Parent (N);
430                while Present (Par) loop
431                   if Nkind_In (Par, N_Function_Call,
432                                     N_Procedure_Call_Statement,
433                                     N_Assignment_Statement,
434                                     N_Op_Eq,
435                                     N_Op_Ne)
436                     and then Is_Tagged_Type (Etype (Subp))
437                   then
438                      return;
439
440                   elsif Nkind (Par) = N_Qualified_Expression
441                     or else Nkind (Par) = N_Unchecked_Type_Conversion
442                   then
443                      Par := Parent (Par);
444
445                   else
446                      if Ekind (Subp) = E_Function then
447                         Error_Msg_N
448                           ("call to abstract function must be dispatching", N);
449
450                      --  This error can occur for a procedure in the case of a
451                      --  call to an abstract formal procedure with a statically
452                      --  tagged operand.
453
454                      else
455                         Error_Msg_N
456                           ("call to abstract procedure must be dispatching",
457                            N);
458                      end if;
459
460                      return;
461                   end if;
462                end loop;
463             end if;
464          end if;
465       end Check_Dispatching_Context;
466
467    --  Start of processing for Check_Dispatching_Call
468
469    begin
470       --  Find a controlling argument, if any
471
472       if Present (Parameter_Associations (N)) then
473          Subp_Entity := Entity (Name (N));
474
475          Actual := First_Actual (N);
476          Formal := First_Formal (Subp_Entity);
477          while Present (Actual) loop
478             Control := Find_Controlling_Arg (Actual);
479             exit when Present (Control);
480
481             --  Check for the case where the actual is a tag-indeterminate call
482             --  whose result type is different than the tagged type associated
483             --  with the containing call, but is an ancestor of the type.
484
485             if Is_Controlling_Formal (Formal)
486               and then Is_Tag_Indeterminate (Actual)
487               and then Base_Type (Etype (Actual)) /= Base_Type (Etype (Formal))
488               and then Is_Ancestor (Etype (Actual), Etype (Formal))
489             then
490                Indeterm_Ancestor_Call := True;
491                Indeterm_Ctrl_Type     := Etype (Formal);
492
493             --  If the formal is controlling but the actual is not, the type
494             --  of the actual is statically known, and may be used as the
495             --  controlling tag for some other tag-indeterminate actual.
496
497             elsif Is_Controlling_Formal (Formal)
498               and then Is_Entity_Name (Actual)
499               and then Is_Tagged_Type (Etype (Actual))
500             then
501                Static_Tag := Actual;
502             end if;
503
504             Next_Actual (Actual);
505             Next_Formal (Formal);
506          end loop;
507
508          --  If the call doesn't have a controlling actual but does have an
509          --  indeterminate actual that requires dispatching treatment, then an
510          --  object is needed that will serve as the controlling argument for a
511          --  dispatching call on the indeterminate actual. This can only occur
512          --  in the unusual situation of a default actual given by a
513          --  tag-indeterminate call and where the type of the call is an
514          --  ancestor of the type associated with a containing call to an
515          --  inherited operation (see AI-239).
516
517          --  Rather than create an object of the tagged type, which would be
518          --  problematic for various reasons (default initialization,
519          --  discriminants), the tag of the containing call's associated tagged
520          --  type is directly used to control the dispatching.
521
522          if No (Control)
523            and then Indeterm_Ancestor_Call
524            and then No (Static_Tag)
525          then
526             Control :=
527               Make_Attribute_Reference (Loc,
528                 Prefix         => New_Occurrence_Of (Indeterm_Ctrl_Type, Loc),
529                 Attribute_Name => Name_Tag);
530
531             Analyze (Control);
532          end if;
533
534          if Present (Control) then
535
536             --  Verify that no controlling arguments are statically tagged
537
538             if Debug_Flag_E then
539                Write_Str ("Found Dispatching call");
540                Write_Int (Int (N));
541                Write_Eol;
542             end if;
543
544             Actual := First_Actual (N);
545             while Present (Actual) loop
546                if Actual /= Control then
547
548                   if not Is_Controlling_Actual (Actual) then
549                      null; -- Can be anything
550
551                   elsif Is_Dynamically_Tagged (Actual) then
552                      null; -- Valid parameter
553
554                   elsif Is_Tag_Indeterminate (Actual) then
555
556                      --  The tag is inherited from the enclosing call (the node
557                      --  we are currently analyzing). Explicitly expand the
558                      --  actual, since the previous call to Expand (from
559                      --  Resolve_Call) had no way of knowing about the required
560                      --  dispatching.
561
562                      Propagate_Tag (Control, Actual);
563
564                   else
565                      Error_Msg_N
566                        ("controlling argument is not dynamically tagged",
567                         Actual);
568                      return;
569                   end if;
570                end if;
571
572                Next_Actual (Actual);
573             end loop;
574
575             --  Mark call as a dispatching call
576
577             Set_Controlling_Argument (N, Control);
578             Check_Restriction (No_Dispatching_Calls, N);
579
580             --  The dispatching call may need to be converted into a direct
581             --  call in certain cases.
582
583             Check_Direct_Call;
584
585          --  If there is a statically tagged actual and a tag-indeterminate
586          --  call to a function of the ancestor (such as that provided by a
587          --  default), then treat this as a dispatching call and propagate
588          --  the tag to the tag-indeterminate call(s).
589
590          elsif Present (Static_Tag) and then Indeterm_Ancestor_Call then
591             Control :=
592               Make_Attribute_Reference (Loc,
593                 Prefix         =>
594                   New_Occurrence_Of (Etype (Static_Tag), Loc),
595                 Attribute_Name => Name_Tag);
596
597             Analyze (Control);
598
599             Actual := First_Actual (N);
600             Formal := First_Formal (Subp_Entity);
601             while Present (Actual) loop
602                if Is_Tag_Indeterminate (Actual)
603                  and then Is_Controlling_Formal (Formal)
604                then
605                   Propagate_Tag (Control, Actual);
606                end if;
607
608                Next_Actual (Actual);
609                Next_Formal (Formal);
610             end loop;
611
612             Check_Dispatching_Context;
613
614          else
615             --  The call is not dispatching, so check that there aren't any
616             --  tag-indeterminate abstract calls left.
617
618             Actual := First_Actual (N);
619             while Present (Actual) loop
620                if Is_Tag_Indeterminate (Actual) then
621
622                   --  Function call case
623
624                   if Nkind (Original_Node (Actual)) = N_Function_Call then
625                      Func := Entity (Name (Original_Node (Actual)));
626
627                   --  If the actual is an attribute then it can't be abstract
628                   --  (the only current case of a tag-indeterminate attribute
629                   --  is the stream Input attribute).
630
631                   elsif
632                     Nkind (Original_Node (Actual)) = N_Attribute_Reference
633                   then
634                      Func := Empty;
635
636                   --  Only other possibility is a qualified expression whose
637                   --  constituent expression is itself a call.
638
639                   else
640                      Func :=
641                        Entity (Name
642                          (Original_Node
643                            (Expression (Original_Node (Actual)))));
644                   end if;
645
646                   if Present (Func) and then Is_Abstract_Subprogram (Func) then
647                      Error_Msg_N (
648                        "call to abstract function must be dispatching", N);
649                   end if;
650                end if;
651
652                Next_Actual (Actual);
653             end loop;
654
655             Check_Dispatching_Context;
656          end if;
657
658       else
659          --  If dispatching on result, the enclosing call, if any, will
660          --  determine the controlling argument. Otherwise this is the
661          --  primitive operation of the root type.
662
663          Check_Dispatching_Context;
664       end if;
665    end Check_Dispatching_Call;
666
667    ---------------------------------
668    -- Check_Dispatching_Operation --
669    ---------------------------------
670
671    procedure Check_Dispatching_Operation (Subp, Old_Subp : Entity_Id) is
672       Tagged_Type            : Entity_Id;
673       Has_Dispatching_Parent : Boolean := False;
674       Body_Is_Last_Primitive : Boolean := False;
675
676       function Is_Visibly_Controlled (T : Entity_Id) return Boolean;
677       --  Check whether T is derived from a visibly controlled type.
678       --  This is true if the root type is declared in Ada.Finalization.
679       --  If T is derived instead from a private type whose full view
680       --  is controlled, an explicit Initialize/Adjust/Finalize subprogram
681       --  does not override the inherited one.
682
683       ---------------------------
684       -- Is_Visibly_Controlled --
685       ---------------------------
686
687       function Is_Visibly_Controlled (T : Entity_Id) return Boolean is
688          Root : constant Entity_Id := Root_Type (T);
689       begin
690          return Chars (Scope (Root)) = Name_Finalization
691            and then Chars (Scope (Scope (Root))) = Name_Ada
692            and then Scope (Scope (Scope (Root))) = Standard_Standard;
693       end Is_Visibly_Controlled;
694
695    --  Start of processing for Check_Dispatching_Operation
696
697    begin
698       if Ekind (Subp) /= E_Procedure and then Ekind (Subp) /= E_Function then
699          return;
700       end if;
701
702       Set_Is_Dispatching_Operation (Subp, False);
703       Tagged_Type := Find_Dispatching_Type (Subp);
704
705       --  Ada 2005 (AI-345)
706
707       if Ada_Version = Ada_05
708         and then Present (Tagged_Type)
709         and then Is_Concurrent_Type (Tagged_Type)
710       then
711          --  Protect the frontend against previously detected errors
712
713          if No (Corresponding_Record_Type (Tagged_Type)) then
714             return;
715          end if;
716
717          Tagged_Type := Corresponding_Record_Type (Tagged_Type);
718       end if;
719
720       --  (AI-345): The task body procedure is not a primitive of the tagged
721       --  type
722
723       if Present (Tagged_Type)
724         and then Is_Concurrent_Record_Type (Tagged_Type)
725         and then Present (Corresponding_Concurrent_Type (Tagged_Type))
726         and then Is_Task_Type (Corresponding_Concurrent_Type (Tagged_Type))
727         and then Subp = Get_Task_Body_Procedure
728                           (Corresponding_Concurrent_Type (Tagged_Type))
729       then
730          return;
731       end if;
732
733       --  If Subp is derived from a dispatching operation then it should
734       --  always be treated as dispatching. In this case various checks
735       --  below will be bypassed. Makes sure that late declarations for
736       --  inherited private subprograms are treated as dispatching, even
737       --  if the associated tagged type is already frozen.
738
739       Has_Dispatching_Parent :=
740          Present (Alias (Subp))
741            and then Is_Dispatching_Operation (Alias (Subp));
742
743       if No (Tagged_Type) then
744
745          --  Ada 2005 (AI-251): Check that Subp is not a primitive associated
746          --  with an abstract interface type unless the interface acts as a
747          --  parent type in a derivation. If the interface type is a formal
748          --  type then the operation is not primitive and therefore legal.
749
750          declare
751             E   : Entity_Id;
752             Typ : Entity_Id;
753
754          begin
755             E := First_Entity (Subp);
756             while Present (E) loop
757
758                --  For an access parameter, check designated type
759
760                if Ekind (Etype (E)) = E_Anonymous_Access_Type then
761                   Typ := Designated_Type (Etype (E));
762                else
763                   Typ := Etype (E);
764                end if;
765
766                if Comes_From_Source (Subp)
767                  and then Is_Interface (Typ)
768                  and then not Is_Class_Wide_Type (Typ)
769                  and then not Is_Derived_Type (Typ)
770                  and then not Is_Generic_Type (Typ)
771                  and then not In_Instance
772                then
773                   Error_Msg_N ("?declaration of& is too late!", Subp);
774                   Error_Msg_NE
775                     ("\spec should appear immediately after declaration of &!",
776                      Subp, Typ);
777                   exit;
778                end if;
779
780                Next_Entity (E);
781             end loop;
782
783             --  In case of functions check also the result type
784
785             if Ekind (Subp) = E_Function then
786                if Is_Access_Type (Etype (Subp)) then
787                   Typ := Designated_Type (Etype (Subp));
788                else
789                   Typ := Etype (Subp);
790                end if;
791
792                if not Is_Class_Wide_Type (Typ)
793                  and then Is_Interface (Typ)
794                  and then not Is_Derived_Type (Typ)
795                then
796                   Error_Msg_N ("?declaration of& is too late!", Subp);
797                   Error_Msg_NE
798                     ("\spec should appear immediately after declaration of &!",
799                      Subp, Typ);
800                end if;
801             end if;
802          end;
803
804          return;
805
806       --  The subprograms build internally after the freezing point (such as
807       --  init procs, interface thunks, type support subprograms, and Offset
808       --  to top functions for accessing interface components in variable
809       --  size tagged types) are not primitives.
810
811       elsif Is_Frozen (Tagged_Type)
812         and then not Comes_From_Source (Subp)
813         and then not Has_Dispatching_Parent
814       then
815          --  Complete decoration if internally built subprograms that override
816          --  a dispatching primitive. These entities correspond with the
817          --  following cases:
818
819          --  1. Ada 2005 (AI-391): Wrapper functions built by the expander
820          --     to override functions of nonabstract null extensions. These
821          --     primitives were added to the list of primitives of the tagged
822          --     type by Make_Controlling_Function_Wrappers. However, attribute
823          --     Is_Dispatching_Operation must be set to true.
824
825          --  2. Subprograms associated with stream attributes (built by
826          --     New_Stream_Subprogram)
827
828          if Present (Old_Subp)
829            and then Is_Overriding_Operation (Subp)
830            and then Is_Dispatching_Operation (Old_Subp)
831          then
832             pragma Assert
833              ((Ekind (Subp) = E_Function
834                 and then Is_Dispatching_Operation (Old_Subp)
835                 and then Is_Null_Extension (Base_Type (Etype (Subp))))
836                or else Get_TSS_Name (Subp) = TSS_Stream_Read
837                or else Get_TSS_Name (Subp) = TSS_Stream_Write);
838
839             Set_Is_Dispatching_Operation (Subp);
840          end if;
841
842          return;
843
844       --  The operation may be a child unit, whose scope is the defining
845       --  package, but which is not a primitive operation of the type.
846
847       elsif Is_Child_Unit (Subp) then
848          return;
849
850       --  If the subprogram is not defined in a package spec, the only case
851       --  where it can be a dispatching op is when it overrides an operation
852       --  before the freezing point of the type.
853
854       elsif ((not Is_Package_Or_Generic_Package (Scope (Subp)))
855                or else In_Package_Body (Scope (Subp)))
856         and then not Has_Dispatching_Parent
857       then
858          if not Comes_From_Source (Subp)
859            or else (Present (Old_Subp) and then not Is_Frozen (Tagged_Type))
860          then
861             null;
862
863          --  If the type is already frozen, the overriding is not allowed
864          --  except when Old_Subp is not a dispatching operation (which can
865          --  occur when Old_Subp was inherited by an untagged type). However,
866          --  a body with no previous spec freezes the type *after* its
867          --  declaration, and therefore is a legal overriding (unless the type
868          --  has already been frozen). Only the first such body is legal.
869
870          elsif Present (Old_Subp)
871            and then Is_Dispatching_Operation (Old_Subp)
872          then
873             if Comes_From_Source (Subp)
874               and then
875                 (Nkind (Unit_Declaration_Node (Subp)) = N_Subprogram_Body
876                   or else Nkind (Unit_Declaration_Node (Subp)) in N_Body_Stub)
877             then
878                declare
879                   Subp_Body : constant Node_Id := Unit_Declaration_Node (Subp);
880                   Decl_Item : Node_Id;
881
882                begin
883                   --  ??? The checks here for whether the type has been
884                   --  frozen prior to the new body are not complete. It's
885                   --  not simple to check frozenness at this point since
886                   --  the body has already caused the type to be prematurely
887                   --  frozen in Analyze_Declarations, but we're forced to
888                   --  recheck this here because of the odd rule interpretation
889                   --  that allows the overriding if the type wasn't frozen
890                   --  prior to the body. The freezing action should probably
891                   --  be delayed until after the spec is seen, but that's
892                   --  a tricky change to the delicate freezing code.
893
894                   --  Look at each declaration following the type up until the
895                   --  new subprogram body. If any of the declarations is a body
896                   --  then the type has been frozen already so the overriding
897                   --  primitive is illegal.
898
899                   Decl_Item := Next (Parent (Tagged_Type));
900                   while Present (Decl_Item)
901                     and then (Decl_Item /= Subp_Body)
902                   loop
903                      if Comes_From_Source (Decl_Item)
904                        and then (Nkind (Decl_Item) in N_Proper_Body
905                                   or else Nkind (Decl_Item) in N_Body_Stub)
906                      then
907                         Error_Msg_N ("overriding of& is too late!", Subp);
908                         Error_Msg_N
909                           ("\spec should appear immediately after the type!",
910                            Subp);
911                         exit;
912                      end if;
913
914                      Next (Decl_Item);
915                   end loop;
916
917                   --  If the subprogram doesn't follow in the list of
918                   --  declarations including the type then the type has
919                   --  definitely been frozen already and the body is illegal.
920
921                   if No (Decl_Item) then
922                      Error_Msg_N ("overriding of& is too late!", Subp);
923                      Error_Msg_N
924                        ("\spec should appear immediately after the type!",
925                         Subp);
926
927                   elsif Is_Frozen (Subp) then
928
929                      --  The subprogram body declares a primitive operation.
930                      --  if the subprogram is already frozen, we must update
931                      --  its dispatching information explicitly here. The
932                      --  information is taken from the overridden subprogram.
933                      --  We must also generate a cross-reference entry because
934                      --  references to other primitives were already created
935                      --  when type was frozen.
936
937                      Body_Is_Last_Primitive := True;
938
939                      if Present (DTC_Entity (Old_Subp)) then
940                         Set_DTC_Entity (Subp, DTC_Entity (Old_Subp));
941                         Set_DT_Position (Subp, DT_Position (Old_Subp));
942
943                         if not Restriction_Active (No_Dispatching_Calls) then
944                            if Building_Static_DT (Tagged_Type) then
945
946                               --  If the static dispatch table has not been
947                               --  built then there is nothing else to do now;
948                               --  otherwise we notify that we cannot build the
949                               --  static dispatch table.
950
951                               if Has_Dispatch_Table (Tagged_Type) then
952                                  Error_Msg_N
953                                    ("overriding of& is too late for building" &
954                                     " static dispatch tables!", Subp);
955                                  Error_Msg_N
956                                    ("\spec should appear immediately after" &
957                                     " the type!", Subp);
958                               end if;
959
960                            else
961                               Insert_Actions_After (Subp_Body,
962                                 Register_Primitive (Sloc (Subp_Body),
963                                 Prim    => Subp));
964                            end if;
965
966                            --  Indicate that this is an overriding operation,
967                            --  and replace the overriden entry in the list of
968                            --  primitive operations, which is used for xref
969                            --  generation subsequently.
970
971                            Generate_Reference (Tagged_Type, Subp, 'P', False);
972                            Override_Dispatching_Operation
973                              (Tagged_Type, Old_Subp, Subp);
974                         end if;
975                      end if;
976                   end if;
977                end;
978
979             else
980                Error_Msg_N ("overriding of& is too late!", Subp);
981                Error_Msg_N
982                  ("\subprogram spec should appear immediately after the type!",
983                   Subp);
984             end if;
985
986          --  If the type is not frozen yet and we are not in the overriding
987          --  case it looks suspiciously like an attempt to define a primitive
988          --  operation, which requires the declaration to be in a package spec
989          --  (3.2.3(6)).
990
991          elsif not Is_Frozen (Tagged_Type) then
992             Error_Msg_N
993               ("?not dispatching (must be defined in a package spec)", Subp);
994             return;
995
996          --  When the type is frozen, it is legitimate to define a new
997          --  non-primitive operation.
998
999          else
1000             return;
1001          end if;
1002
1003       --  Now, we are sure that the scope is a package spec. If the subprogram
1004       --  is declared after the freezing point of the type that's an error
1005
1006       elsif Is_Frozen (Tagged_Type) and then not Has_Dispatching_Parent then
1007          Error_Msg_N ("this primitive operation is declared too late", Subp);
1008          Error_Msg_NE
1009            ("?no primitive operations for& after this line",
1010             Freeze_Node (Tagged_Type),
1011             Tagged_Type);
1012          return;
1013       end if;
1014
1015       Check_Controlling_Formals (Tagged_Type, Subp);
1016
1017       --  Now it should be a correct primitive operation, put it in the list
1018
1019       if Present (Old_Subp) then
1020
1021          --  If the type has interfaces we complete this check after we set
1022          --  attribute Is_Dispatching_Operation.
1023
1024          Check_Subtype_Conformant (Subp, Old_Subp);
1025
1026          if (Chars (Subp) = Name_Initialize
1027            or else Chars (Subp) = Name_Adjust
1028            or else Chars (Subp) = Name_Finalize)
1029            and then Is_Controlled (Tagged_Type)
1030            and then not Is_Visibly_Controlled (Tagged_Type)
1031          then
1032             Set_Is_Overriding_Operation (Subp, False);
1033             Error_Msg_NE
1034               ("operation does not override inherited&?", Subp, Subp);
1035          else
1036             Override_Dispatching_Operation (Tagged_Type, Old_Subp, Subp);
1037             Set_Is_Overriding_Operation (Subp);
1038
1039             --  Ada 2005 (AI-251): In case of late overriding of a primitive
1040             --  that covers abstract interface subprograms we must register it
1041             --  in all the secondary dispatch tables associated with abstract
1042             --  interfaces. We do this now only if not building static tables.
1043             --  Otherwise the patch code is emitted after those tables are
1044             --  built, to prevent access_before_elaboration in gigi.
1045
1046             if Body_Is_Last_Primitive then
1047                declare
1048                   Subp_Body : constant Node_Id := Unit_Declaration_Node (Subp);
1049                   Elmt      : Elmt_Id;
1050                   Prim      : Node_Id;
1051
1052                begin
1053                   Elmt := First_Elmt (Primitive_Operations (Tagged_Type));
1054                   while Present (Elmt) loop
1055                      Prim := Node (Elmt);
1056
1057                      if Present (Alias (Prim))
1058                        and then Present (Interface_Alias (Prim))
1059                        and then Alias (Prim) = Subp
1060                        and then not Building_Static_DT (Tagged_Type)
1061                      then
1062                         Insert_Actions_After (Subp_Body,
1063                           Register_Primitive (Sloc (Subp_Body), Prim => Prim));
1064                      end if;
1065
1066                      Next_Elmt (Elmt);
1067                   end loop;
1068
1069                   --  Redisplay the contents of the updated dispatch table
1070
1071                   if Debug_Flag_ZZ then
1072                      Write_Str ("Late overriding: ");
1073                      Write_DT (Tagged_Type);
1074                   end if;
1075                end;
1076             end if;
1077          end if;
1078
1079       --  If no old subprogram, then we add this as a dispatching operation,
1080       --  but we avoid doing this if an error was posted, to prevent annoying
1081       --  cascaded errors.
1082
1083       elsif not Error_Posted (Subp) then
1084          Add_Dispatching_Operation (Tagged_Type, Subp);
1085       end if;
1086
1087       Set_Is_Dispatching_Operation (Subp, True);
1088
1089       --  Ada 2005 (AI-251): If the type implements interfaces we must check
1090       --  subtype conformance against all the interfaces covered by this
1091       --  primitive.
1092
1093       if Present (Old_Subp)
1094         and then Has_Interfaces (Tagged_Type)
1095       then
1096          declare
1097             Ifaces_List     : Elist_Id;
1098             Iface_Elmt      : Elmt_Id;
1099             Iface_Prim_Elmt : Elmt_Id;
1100             Iface_Prim      : Entity_Id;
1101             Ret_Typ         : Entity_Id;
1102
1103          begin
1104             Collect_Interfaces (Tagged_Type, Ifaces_List);
1105
1106             Iface_Elmt := First_Elmt (Ifaces_List);
1107             while Present (Iface_Elmt) loop
1108                if not Is_Ancestor (Node (Iface_Elmt), Tagged_Type) then
1109                   Iface_Prim_Elmt :=
1110                     First_Elmt (Primitive_Operations (Node (Iface_Elmt)));
1111                   while Present (Iface_Prim_Elmt) loop
1112                      Iface_Prim := Node (Iface_Prim_Elmt);
1113
1114                      if Is_Interface_Conformant
1115                           (Tagged_Type, Iface_Prim, Subp)
1116                      then
1117                         --  Handle procedures, functions whose return type
1118                         --  matches, or functions not returning interfaces
1119
1120                         if Ekind (Subp) = E_Procedure
1121                           or else Etype (Iface_Prim) = Etype (Subp)
1122                           or else not Is_Interface (Etype (Iface_Prim))
1123                         then
1124                            Check_Subtype_Conformant
1125                              (New_Id  => Subp,
1126                               Old_Id  => Iface_Prim,
1127                               Err_Loc => Subp,
1128                               Skip_Controlling_Formals => True);
1129
1130                         --  Handle functions returning interfaces
1131
1132                         elsif Implements_Interface
1133                                 (Etype (Subp), Etype (Iface_Prim))
1134                         then
1135                            --  Temporarily force both entities to return the
1136                            --  same type. Required because Subtype_Conformant
1137                            --  does not handle this case.
1138
1139                            Ret_Typ := Etype (Iface_Prim);
1140                            Set_Etype (Iface_Prim, Etype (Subp));
1141
1142                            Check_Subtype_Conformant
1143                              (New_Id  => Subp,
1144                               Old_Id  => Iface_Prim,
1145                               Err_Loc => Subp,
1146                               Skip_Controlling_Formals => True);
1147
1148                            Set_Etype (Iface_Prim, Ret_Typ);
1149                         end if;
1150                      end if;
1151
1152                      Next_Elmt (Iface_Prim_Elmt);
1153                   end loop;
1154                end if;
1155
1156                Next_Elmt (Iface_Elmt);
1157             end loop;
1158          end;
1159       end if;
1160
1161       if not Body_Is_Last_Primitive then
1162          Set_DT_Position (Subp, No_Uint);
1163
1164       elsif Has_Controlled_Component (Tagged_Type)
1165         and then
1166          (Chars (Subp) = Name_Initialize
1167             or else
1168           Chars (Subp) = Name_Adjust
1169             or else
1170           Chars (Subp) = Name_Finalize)
1171       then
1172          declare
1173             F_Node   : constant Node_Id := Freeze_Node (Tagged_Type);
1174             Decl     : Node_Id;
1175             Old_P    : Entity_Id;
1176             Old_Bod  : Node_Id;
1177             Old_Spec : Entity_Id;
1178
1179             C_Names : constant array (1 .. 3) of Name_Id :=
1180                         (Name_Initialize,
1181                          Name_Adjust,
1182                          Name_Finalize);
1183
1184             D_Names : constant array (1 .. 3) of TSS_Name_Type :=
1185                         (TSS_Deep_Initialize,
1186                          TSS_Deep_Adjust,
1187                          TSS_Deep_Finalize);
1188
1189          begin
1190             --  Remove previous controlled function which was constructed and
1191             --  analyzed when the type was frozen. This requires removing the
1192             --  body of the redefined primitive, as well as its specification
1193             --  if needed (there is no spec created for Deep_Initialize, see
1194             --  exp_ch3.adb). We must also dismantle the exception information
1195             --  that may have been generated for it when front end zero-cost
1196             --  tables are enabled.
1197
1198             for J in D_Names'Range loop
1199                Old_P := TSS (Tagged_Type, D_Names (J));
1200
1201                if Present (Old_P)
1202                 and then Chars (Subp) = C_Names (J)
1203                then
1204                   Old_Bod := Unit_Declaration_Node (Old_P);
1205                   Remove (Old_Bod);
1206                   Set_Is_Eliminated (Old_P);
1207                   Set_Scope (Old_P,  Scope (Current_Scope));
1208
1209                   if Nkind (Old_Bod) = N_Subprogram_Body
1210                     and then Present (Corresponding_Spec (Old_Bod))
1211                   then
1212                      Old_Spec := Corresponding_Spec (Old_Bod);
1213                      Set_Has_Completion             (Old_Spec, False);
1214                   end if;
1215                end if;
1216             end loop;
1217
1218             Build_Late_Proc (Tagged_Type, Chars (Subp));
1219
1220             --  The new operation is added to the actions of the freeze node
1221             --  for the type, but this node has already been analyzed, so we
1222             --  must retrieve and analyze explicitly the new body.
1223
1224             if Present (F_Node)
1225               and then Present (Actions (F_Node))
1226             then
1227                Decl := Last (Actions (F_Node));
1228                Analyze (Decl);
1229             end if;
1230          end;
1231       end if;
1232    end Check_Dispatching_Operation;
1233
1234    ------------------------------------------
1235    -- Check_Operation_From_Incomplete_Type --
1236    ------------------------------------------
1237
1238    procedure Check_Operation_From_Incomplete_Type
1239      (Subp : Entity_Id;
1240       Typ  : Entity_Id)
1241    is
1242       Full       : constant Entity_Id := Full_View (Typ);
1243       Parent_Typ : constant Entity_Id := Etype (Full);
1244       Old_Prim   : constant Elist_Id  := Primitive_Operations (Parent_Typ);
1245       New_Prim   : constant Elist_Id  := Primitive_Operations (Full);
1246       Op1, Op2   : Elmt_Id;
1247       Prev       : Elmt_Id := No_Elmt;
1248
1249       function Derives_From (Proc : Entity_Id) return Boolean;
1250       --  Check that Subp has the signature of an operation derived from Proc.
1251       --  Subp has an access parameter that designates Typ.
1252
1253       ------------------
1254       -- Derives_From --
1255       ------------------
1256
1257       function Derives_From (Proc : Entity_Id) return Boolean is
1258          F1, F2 : Entity_Id;
1259
1260       begin
1261          if Chars (Proc) /= Chars (Subp) then
1262             return False;
1263          end if;
1264
1265          F1 := First_Formal (Proc);
1266          F2 := First_Formal (Subp);
1267          while Present (F1) and then Present (F2) loop
1268             if Ekind (Etype (F1)) = E_Anonymous_Access_Type then
1269                if Ekind (Etype (F2)) /= E_Anonymous_Access_Type then
1270                   return False;
1271                elsif Designated_Type (Etype (F1)) = Parent_Typ
1272                  and then Designated_Type (Etype (F2)) /= Full
1273                then
1274                   return False;
1275                end if;
1276
1277             elsif Ekind (Etype (F2)) = E_Anonymous_Access_Type then
1278                return False;
1279
1280             elsif Etype (F1) /= Etype (F2) then
1281                return False;
1282             end if;
1283
1284             Next_Formal (F1);
1285             Next_Formal (F2);
1286          end loop;
1287
1288          return No (F1) and then No (F2);
1289       end Derives_From;
1290
1291    --  Start of processing for Check_Operation_From_Incomplete_Type
1292
1293    begin
1294       --  The operation may override an inherited one, or may be a new one
1295       --  altogether. The inherited operation will have been hidden by the
1296       --  current one at the point of the type derivation, so it does not
1297       --  appear in the list of primitive operations of the type. We have to
1298       --  find the proper place of insertion in the list of primitive opera-
1299       --  tions by iterating over the list for the parent type.
1300
1301       Op1 := First_Elmt (Old_Prim);
1302       Op2 := First_Elmt (New_Prim);
1303       while Present (Op1) and then Present (Op2) loop
1304          if Derives_From (Node (Op1)) then
1305             if No (Prev) then
1306
1307                --  Avoid adding it to the list of primitives if already there!
1308
1309                if Node (Op2) /= Subp then
1310                   Prepend_Elmt (Subp, New_Prim);
1311                end if;
1312
1313             else
1314                Insert_Elmt_After (Subp, Prev);
1315             end if;
1316
1317             return;
1318          end if;
1319
1320          Prev := Op2;
1321          Next_Elmt (Op1);
1322          Next_Elmt (Op2);
1323       end loop;
1324
1325       --  Operation is a new primitive
1326
1327       Append_Elmt (Subp, New_Prim);
1328    end Check_Operation_From_Incomplete_Type;
1329
1330    ---------------------------------------
1331    -- Check_Operation_From_Private_View --
1332    ---------------------------------------
1333
1334    procedure Check_Operation_From_Private_View (Subp, Old_Subp : Entity_Id) is
1335       Tagged_Type : Entity_Id;
1336
1337    begin
1338       if Is_Dispatching_Operation (Alias (Subp)) then
1339          Set_Scope (Subp, Current_Scope);
1340          Tagged_Type := Find_Dispatching_Type (Subp);
1341
1342          --  Add Old_Subp to primitive operations if not already present
1343
1344          if Present (Tagged_Type) and then Is_Tagged_Type (Tagged_Type) then
1345             Append_Unique_Elmt (Old_Subp, Primitive_Operations (Tagged_Type));
1346
1347             --  If Old_Subp isn't already marked as dispatching then
1348             --  this is the case of an operation of an untagged private
1349             --  type fulfilled by a tagged type that overrides an
1350             --  inherited dispatching operation, so we set the necessary
1351             --  dispatching attributes here.
1352
1353             if not Is_Dispatching_Operation (Old_Subp) then
1354
1355                --  If the untagged type has no discriminants, and the full
1356                --  view is constrained, there will be a spurious mismatch
1357                --  of subtypes on the controlling arguments, because the tagged
1358                --  type is the internal base type introduced in the derivation.
1359                --  Use the original type to verify conformance, rather than the
1360                --  base type.
1361
1362                if not Comes_From_Source (Tagged_Type)
1363                  and then Has_Discriminants (Tagged_Type)
1364                then
1365                   declare
1366                      Formal : Entity_Id;
1367
1368                   begin
1369                      Formal := First_Formal (Old_Subp);
1370                      while Present (Formal) loop
1371                         if Tagged_Type = Base_Type (Etype (Formal)) then
1372                            Tagged_Type := Etype (Formal);
1373                         end if;
1374
1375                         Next_Formal (Formal);
1376                      end loop;
1377                   end;
1378
1379                   if Tagged_Type = Base_Type (Etype (Old_Subp)) then
1380                      Tagged_Type := Etype (Old_Subp);
1381                   end if;
1382                end if;
1383
1384                Check_Controlling_Formals (Tagged_Type, Old_Subp);
1385                Set_Is_Dispatching_Operation (Old_Subp, True);
1386                Set_DT_Position (Old_Subp, No_Uint);
1387             end if;
1388
1389             --  If the old subprogram is an explicit renaming of some other
1390             --  entity, it is not overridden by the inherited subprogram.
1391             --  Otherwise, update its alias and other attributes.
1392
1393             if Present (Alias (Old_Subp))
1394               and then Nkind (Unit_Declaration_Node (Old_Subp)) /=
1395                                         N_Subprogram_Renaming_Declaration
1396             then
1397                Set_Alias (Old_Subp, Alias (Subp));
1398
1399                --  The derived subprogram should inherit the abstractness
1400                --  of the parent subprogram (except in the case of a function
1401                --  returning the type). This sets the abstractness properly
1402                --  for cases where a private extension may have inherited
1403                --  an abstract operation, but the full type is derived from
1404                --  a descendant type and inherits a nonabstract version.
1405
1406                if Etype (Subp) /= Tagged_Type then
1407                   Set_Is_Abstract_Subprogram
1408                     (Old_Subp, Is_Abstract_Subprogram (Alias (Subp)));
1409                end if;
1410             end if;
1411          end if;
1412       end if;
1413    end Check_Operation_From_Private_View;
1414
1415    --------------------------
1416    -- Find_Controlling_Arg --
1417    --------------------------
1418
1419    function Find_Controlling_Arg (N : Node_Id) return Node_Id is
1420       Orig_Node : constant Node_Id := Original_Node (N);
1421       Typ       : Entity_Id;
1422
1423    begin
1424       if Nkind (Orig_Node) = N_Qualified_Expression then
1425          return Find_Controlling_Arg (Expression (Orig_Node));
1426       end if;
1427
1428       --  Dispatching on result case. If expansion is disabled, the node still
1429       --  has the structure of a function call. However, if the function name
1430       --  is an operator and the call was given in infix form, the original
1431       --  node has no controlling result and we must examine the current node.
1432
1433       if Nkind (N) = N_Function_Call
1434         and then Present (Controlling_Argument (N))
1435         and then Has_Controlling_Result (Entity (Name (N)))
1436       then
1437          return Controlling_Argument (N);
1438
1439       --  If expansion is enabled, the call may have been transformed into
1440       --  an indirect call, and we need to recover the original node.
1441
1442       elsif Nkind (Orig_Node) = N_Function_Call
1443         and then Present (Controlling_Argument (Orig_Node))
1444         and then Has_Controlling_Result (Entity (Name (Orig_Node)))
1445       then
1446          return Controlling_Argument (Orig_Node);
1447
1448       --  Normal case
1449
1450       elsif Is_Controlling_Actual (N)
1451         or else
1452          (Nkind (Parent (N)) = N_Qualified_Expression
1453            and then Is_Controlling_Actual (Parent (N)))
1454       then
1455          Typ := Etype (N);
1456
1457          if Is_Access_Type (Typ) then
1458
1459             --  In the case of an Access attribute, use the type of the prefix,
1460             --  since in the case of an actual for an access parameter, the
1461             --  attribute's type may be of a specific designated type, even
1462             --  though the prefix type is class-wide.
1463
1464             if Nkind (N) = N_Attribute_Reference then
1465                Typ := Etype (Prefix (N));
1466
1467             --  An allocator is dispatching if the type of qualified expression
1468             --  is class_wide, in which case this is the controlling type.
1469
1470             elsif Nkind (Orig_Node) = N_Allocator
1471                and then Nkind (Expression (Orig_Node)) = N_Qualified_Expression
1472             then
1473                Typ := Etype (Expression (Orig_Node));
1474             else
1475                Typ := Designated_Type (Typ);
1476             end if;
1477          end if;
1478
1479          if Is_Class_Wide_Type (Typ)
1480            or else
1481              (Nkind (Parent (N)) = N_Qualified_Expression
1482                and then Is_Access_Type (Etype (N))
1483                and then Is_Class_Wide_Type (Designated_Type (Etype (N))))
1484          then
1485             return N;
1486          end if;
1487       end if;
1488
1489       return Empty;
1490    end Find_Controlling_Arg;
1491
1492    ---------------------------
1493    -- Find_Dispatching_Type --
1494    ---------------------------
1495
1496    function Find_Dispatching_Type (Subp : Entity_Id) return Entity_Id is
1497       A_Formal  : Entity_Id;
1498       Formal    : Entity_Id;
1499       Ctrl_Type : Entity_Id;
1500
1501    begin
1502       if Present (DTC_Entity (Subp)) then
1503          return Scope (DTC_Entity (Subp));
1504
1505       --  For subprograms internally generated by derivations of tagged types
1506       --  use the alias subprogram as a reference to locate the dispatching
1507       --  type of Subp
1508
1509       elsif not Comes_From_Source (Subp)
1510         and then Present (Alias (Subp))
1511         and then Is_Dispatching_Operation (Alias (Subp))
1512       then
1513          if Ekind (Alias (Subp)) = E_Function
1514            and then Has_Controlling_Result (Alias (Subp))
1515          then
1516             return Check_Controlling_Type (Etype (Subp), Subp);
1517
1518          else
1519             Formal   := First_Formal (Subp);
1520             A_Formal := First_Formal (Alias (Subp));
1521             while Present (A_Formal) loop
1522                if Is_Controlling_Formal (A_Formal) then
1523                   return Check_Controlling_Type (Etype (Formal), Subp);
1524                end if;
1525
1526                Next_Formal (Formal);
1527                Next_Formal (A_Formal);
1528             end loop;
1529
1530             pragma Assert (False);
1531             return Empty;
1532          end if;
1533
1534       --  General case
1535
1536       else
1537          Formal := First_Formal (Subp);
1538          while Present (Formal) loop
1539             Ctrl_Type := Check_Controlling_Type (Etype (Formal), Subp);
1540
1541             if Present (Ctrl_Type) then
1542                return Ctrl_Type;
1543             end if;
1544
1545             Next_Formal (Formal);
1546          end loop;
1547
1548          --  The subprogram may also be dispatching on result
1549
1550          if Present (Etype (Subp)) then
1551             return Check_Controlling_Type (Etype (Subp), Subp);
1552          end if;
1553       end if;
1554
1555       pragma Assert (not Is_Dispatching_Operation (Subp));
1556       return Empty;
1557    end Find_Dispatching_Type;
1558
1559    ---------------------------------------
1560    -- Find_Primitive_Covering_Interface --
1561    ---------------------------------------
1562
1563    function Find_Primitive_Covering_Interface
1564      (Tagged_Type : Entity_Id;
1565       Iface_Prim  : Entity_Id) return Entity_Id
1566    is
1567       E : Entity_Id;
1568
1569    begin
1570       pragma Assert (Is_Interface (Find_Dispatching_Type (Iface_Prim))
1571         or else (Present (Alias (Iface_Prim))
1572                    and then
1573                      Is_Interface
1574                        (Find_Dispatching_Type (Ultimate_Alias (Iface_Prim)))));
1575
1576       E := Current_Entity (Iface_Prim);
1577       while Present (E) loop
1578          if Is_Subprogram (E)
1579            and then Is_Dispatching_Operation (E)
1580            and then Is_Interface_Conformant (Tagged_Type, Iface_Prim, E)
1581          then
1582             return E;
1583          end if;
1584
1585          E := Homonym (E);
1586       end loop;
1587
1588       return Empty;
1589    end Find_Primitive_Covering_Interface;
1590
1591    ---------------------------
1592    -- Is_Dynamically_Tagged --
1593    ---------------------------
1594
1595    function Is_Dynamically_Tagged (N : Node_Id) return Boolean is
1596    begin
1597       if Nkind (N) = N_Error then
1598          return False;
1599       else
1600          return Find_Controlling_Arg (N) /= Empty;
1601       end if;
1602    end Is_Dynamically_Tagged;
1603
1604    --------------------------
1605    -- Is_Tag_Indeterminate --
1606    --------------------------
1607
1608    function Is_Tag_Indeterminate (N : Node_Id) return Boolean is
1609       Nam       : Entity_Id;
1610       Actual    : Node_Id;
1611       Orig_Node : constant Node_Id := Original_Node (N);
1612
1613    begin
1614       if Nkind (Orig_Node) = N_Function_Call
1615         and then Is_Entity_Name (Name (Orig_Node))
1616       then
1617          Nam := Entity (Name (Orig_Node));
1618
1619          if not Has_Controlling_Result (Nam) then
1620             return False;
1621
1622          --  An explicit dereference means that the call has already been
1623          --  expanded and there is no tag to propagate.
1624
1625          elsif Nkind (N) = N_Explicit_Dereference then
1626             return False;
1627
1628          --  If there are no actuals, the call is tag-indeterminate
1629
1630          elsif No (Parameter_Associations (Orig_Node)) then
1631             return True;
1632
1633          else
1634             Actual := First_Actual (Orig_Node);
1635             while Present (Actual) loop
1636                if Is_Controlling_Actual (Actual)
1637                  and then not Is_Tag_Indeterminate (Actual)
1638                then
1639                   return False; -- one operand is dispatching
1640                end if;
1641
1642                Next_Actual (Actual);
1643             end loop;
1644
1645             return True;
1646          end if;
1647
1648       elsif Nkind (Orig_Node) = N_Qualified_Expression then
1649          return Is_Tag_Indeterminate (Expression (Orig_Node));
1650
1651       --  Case of a call to the Input attribute (possibly rewritten), which is
1652       --  always tag-indeterminate except when its prefix is a Class attribute.
1653
1654       elsif Nkind (Orig_Node) = N_Attribute_Reference
1655         and then
1656           Get_Attribute_Id (Attribute_Name (Orig_Node)) = Attribute_Input
1657         and then
1658           Nkind (Prefix (Orig_Node)) /= N_Attribute_Reference
1659       then
1660          return True;
1661
1662       --  In Ada 2005 a function that returns an anonymous access type can
1663       --  dispatching, and the dereference of a call to such a function
1664       --  is also tag-indeterminate.
1665
1666       elsif Nkind (Orig_Node) = N_Explicit_Dereference
1667         and then Ada_Version >= Ada_05
1668       then
1669          return Is_Tag_Indeterminate (Prefix (Orig_Node));
1670
1671       else
1672          return False;
1673       end if;
1674    end Is_Tag_Indeterminate;
1675
1676    ------------------------------------
1677    -- Override_Dispatching_Operation --
1678    ------------------------------------
1679
1680    procedure Override_Dispatching_Operation
1681      (Tagged_Type : Entity_Id;
1682       Prev_Op     : Entity_Id;
1683       New_Op      : Entity_Id)
1684    is
1685       Elmt : Elmt_Id;
1686       Prim : Node_Id;
1687
1688    begin
1689       --  Diagnose failure to match No_Return in parent (Ada-2005, AI-414, but
1690       --  we do it unconditionally in Ada 95 now, since this is our pragma!)
1691
1692       if No_Return (Prev_Op) and then not No_Return (New_Op) then
1693          Error_Msg_N ("procedure & must have No_Return pragma", New_Op);
1694          Error_Msg_N ("\since overridden procedure has No_Return", New_Op);
1695       end if;
1696
1697       --  If there is no previous operation to override, the type declaration
1698       --  was malformed, and an error must have been emitted already.
1699
1700       Elmt := First_Elmt (Primitive_Operations (Tagged_Type));
1701       while Present (Elmt)
1702         and then Node (Elmt) /= Prev_Op
1703       loop
1704          Next_Elmt (Elmt);
1705       end loop;
1706
1707       if No (Elmt) then
1708          return;
1709       end if;
1710
1711       Replace_Elmt (Elmt, New_Op);
1712
1713       if Ada_Version >= Ada_05
1714         and then Has_Interfaces (Tagged_Type)
1715       then
1716          --  Ada 2005 (AI-251): Update the attribute alias of all the aliased
1717          --  entities of the overridden primitive to reference New_Op, and also
1718          --  propagate the proper value of Is_Abstract_Subprogram. Verify
1719          --  that the new operation is subtype conformant with the interface
1720          --  operations that it implements (for operations inherited from the
1721          --  parent itself, this check is made when building the derived type).
1722
1723          --  Note: This code is only executed in case of late overriding
1724
1725          Elmt := First_Elmt (Primitive_Operations (Tagged_Type));
1726          while Present (Elmt) loop
1727             Prim := Node (Elmt);
1728
1729             if Prim = New_Op then
1730                null;
1731
1732             --  Note: The check on Is_Subprogram protects the frontend against
1733             --  reading attributes in entities that are not yet fully decorated
1734
1735             elsif Is_Subprogram (Prim)
1736               and then Present (Interface_Alias (Prim))
1737               and then Alias (Prim) = Prev_Op
1738               and then Present (Etype (New_Op))
1739             then
1740                Set_Alias (Prim, New_Op);
1741                Check_Subtype_Conformant (New_Op, Prim);
1742                Set_Is_Abstract_Subprogram (Prim,
1743                  Is_Abstract_Subprogram (New_Op));
1744
1745                --  Ensure that this entity will be expanded to fill the
1746                --  corresponding entry in its dispatch table.
1747
1748                if not Is_Abstract_Subprogram (Prim) then
1749                   Set_Has_Delayed_Freeze (Prim);
1750                end if;
1751             end if;
1752
1753             Next_Elmt (Elmt);
1754          end loop;
1755       end if;
1756
1757       if (not Is_Package_Or_Generic_Package (Current_Scope))
1758         or else not In_Private_Part (Current_Scope)
1759       then
1760          --  Not a private primitive
1761
1762          null;
1763
1764       else pragma Assert (Is_Inherited_Operation (Prev_Op));
1765
1766          --  Make the overriding operation into an alias of the implicit one.
1767          --  In this fashion a call from outside ends up calling the new body
1768          --  even if non-dispatching, and a call from inside calls the
1769          --  overriding operation because it hides the implicit one. To
1770          --  indicate that the body of Prev_Op is never called, set its
1771          --  dispatch table entity to Empty. If the overridden operation
1772          --  has a dispatching result, so does the overriding one.
1773
1774          Set_Alias (Prev_Op, New_Op);
1775          Set_DTC_Entity (Prev_Op, Empty);
1776          Set_Has_Controlling_Result (New_Op, Has_Controlling_Result (Prev_Op));
1777          return;
1778       end if;
1779    end Override_Dispatching_Operation;
1780
1781    -------------------
1782    -- Propagate_Tag --
1783    -------------------
1784
1785    procedure Propagate_Tag (Control : Node_Id; Actual : Node_Id) is
1786       Call_Node : Node_Id;
1787       Arg       : Node_Id;
1788
1789    begin
1790       if Nkind (Actual) = N_Function_Call then
1791          Call_Node := Actual;
1792
1793       elsif Nkind (Actual) = N_Identifier
1794         and then Nkind (Original_Node (Actual)) = N_Function_Call
1795       then
1796          --  Call rewritten as object declaration when stack-checking is
1797          --  enabled. Propagate tag to expression in declaration, which is
1798          --  original call.
1799
1800          Call_Node := Expression (Parent (Entity (Actual)));
1801
1802       --  Ada 2005: If this is a dereference of a call to a function with a
1803       --  dispatching access-result, the tag is propagated when the dereference
1804       --  itself is expanded (see exp_ch6.adb) and there is nothing else to do.
1805
1806       elsif Nkind (Actual) = N_Explicit_Dereference
1807         and then Nkind (Original_Node (Prefix (Actual))) = N_Function_Call
1808       then
1809          return;
1810
1811       --  Only other possibilities are parenthesized or qualified expression,
1812       --  or an expander-generated unchecked conversion of a function call to
1813       --  a stream Input attribute.
1814
1815       else
1816          Call_Node := Expression (Actual);
1817       end if;
1818
1819       --  Do not set the Controlling_Argument if already set. This happens in
1820       --  the special case of _Input (see Exp_Attr, case Input).
1821
1822       if No (Controlling_Argument (Call_Node)) then
1823          Set_Controlling_Argument (Call_Node, Control);
1824       end if;
1825
1826       Arg := First_Actual (Call_Node);
1827
1828       while Present (Arg) loop
1829          if Is_Tag_Indeterminate (Arg) then
1830             Propagate_Tag (Control,  Arg);
1831          end if;
1832
1833          Next_Actual (Arg);
1834       end loop;
1835
1836       --  Expansion of dispatching calls is suppressed when VM_Target, because
1837       --  the VM back-ends directly handle the generation of dispatching calls
1838       --  and would have to undo any expansion to an indirect call.
1839
1840       if Tagged_Type_Expansion then
1841          Expand_Dispatching_Call (Call_Node);
1842
1843       --  Expansion of a dispatching call results in an indirect call, which in
1844       --  turn causes current values to be killed (see Resolve_Call), so on VM
1845       --  targets we do the call here to ensure consistent warnings between VM
1846       --  and non-VM targets.
1847
1848       else
1849          Kill_Current_Values;
1850       end if;
1851    end Propagate_Tag;
1852
1853 end Sem_Disp;