OSDN Git Service

Add NIOS2 support. Code from SourceyG++.
[pf3gnuchains/gcc-fork.git] / gcc / ada / sem_ch6.adb
1 ------------------------------------------------------------------------------
2 --                                                                          --
3 --                         GNAT COMPILER COMPONENTS                         --
4 --                                                                          --
5 --                              S E M _ C H 6                               --
6 --                                                                          --
7 --                                 B o d y                                  --
8 --                                                                          --
9 --          Copyright (C) 1992-2012, 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 Checks;   use Checks;
28 with Debug;    use Debug;
29 with Einfo;    use Einfo;
30 with Elists;   use Elists;
31 with Errout;   use Errout;
32 with Expander; use Expander;
33 with Exp_Ch6;  use Exp_Ch6;
34 with Exp_Ch7;  use Exp_Ch7;
35 with Exp_Ch9;  use Exp_Ch9;
36 with Exp_Disp; use Exp_Disp;
37 with Exp_Tss;  use Exp_Tss;
38 with Exp_Util; use Exp_Util;
39 with Fname;    use Fname;
40 with Freeze;   use Freeze;
41 with Itypes;   use Itypes;
42 with Lib.Xref; use Lib.Xref;
43 with Layout;   use Layout;
44 with Namet;    use Namet;
45 with Lib;      use Lib;
46 with Nlists;   use Nlists;
47 with Nmake;    use Nmake;
48 with Opt;      use Opt;
49 with Output;   use Output;
50 with Restrict; use Restrict;
51 with Rident;   use Rident;
52 with Rtsfind;  use Rtsfind;
53 with Sem;      use Sem;
54 with Sem_Aux;  use Sem_Aux;
55 with Sem_Cat;  use Sem_Cat;
56 with Sem_Ch3;  use Sem_Ch3;
57 with Sem_Ch4;  use Sem_Ch4;
58 with Sem_Ch5;  use Sem_Ch5;
59 with Sem_Ch8;  use Sem_Ch8;
60 with Sem_Ch10; use Sem_Ch10;
61 with Sem_Ch12; use Sem_Ch12;
62 with Sem_Ch13; use Sem_Ch13;
63 with Sem_Dim;  use Sem_Dim;
64 with Sem_Disp; use Sem_Disp;
65 with Sem_Dist; use Sem_Dist;
66 with Sem_Elim; use Sem_Elim;
67 with Sem_Eval; use Sem_Eval;
68 with Sem_Mech; use Sem_Mech;
69 with Sem_Prag; use Sem_Prag;
70 with Sem_Res;  use Sem_Res;
71 with Sem_Util; use Sem_Util;
72 with Sem_Type; use Sem_Type;
73 with Sem_Warn; use Sem_Warn;
74 with Sinput;   use Sinput;
75 with Stand;    use Stand;
76 with Sinfo;    use Sinfo;
77 with Sinfo.CN; use Sinfo.CN;
78 with Snames;   use Snames;
79 with Stringt;  use Stringt;
80 with Style;
81 with Stylesw;  use Stylesw;
82 with Targparm; use Targparm;
83 with Tbuild;   use Tbuild;
84 with Uintp;    use Uintp;
85 with Urealp;   use Urealp;
86 with Validsw;  use Validsw;
87
88 package body Sem_Ch6 is
89
90    May_Hide_Profile : Boolean := False;
91    --  This flag is used to indicate that two formals in two subprograms being
92    --  checked for conformance differ only in that one is an access parameter
93    --  while the other is of a general access type with the same designated
94    --  type. In this case, if the rest of the signatures match, a call to
95    --  either subprogram may be ambiguous, which is worth a warning. The flag
96    --  is set in Compatible_Types, and the warning emitted in
97    --  New_Overloaded_Entity.
98
99    -----------------------
100    -- Local Subprograms --
101    -----------------------
102
103    procedure Analyze_Return_Statement (N : Node_Id);
104    --  Common processing for simple and extended return statements
105
106    procedure Analyze_Function_Return (N : Node_Id);
107    --  Subsidiary to Analyze_Return_Statement. Called when the return statement
108    --  applies to a [generic] function.
109
110    procedure Analyze_Return_Type (N : Node_Id);
111    --  Subsidiary to Process_Formals: analyze subtype mark in function
112    --  specification in a context where the formals are visible and hide
113    --  outer homographs.
114
115    procedure Analyze_Subprogram_Body_Helper (N : Node_Id);
116    --  Does all the real work of Analyze_Subprogram_Body. This is split out so
117    --  that we can use RETURN but not skip the debug output at the end.
118
119    procedure Analyze_Generic_Subprogram_Body (N : Node_Id; Gen_Id : Entity_Id);
120    --  Analyze a generic subprogram body. N is the body to be analyzed, and
121    --  Gen_Id is the defining entity Id for the corresponding spec.
122
123    procedure Build_Body_To_Inline (N : Node_Id; Subp : Entity_Id);
124    --  If a subprogram has pragma Inline and inlining is active, use generic
125    --  machinery to build an unexpanded body for the subprogram. This body is
126    --  subsequently used for inline expansions at call sites. If subprogram can
127    --  be inlined (depending on size and nature of local declarations) this
128    --  function returns true. Otherwise subprogram body is treated normally.
129    --  If proper warnings are enabled and the subprogram contains a construct
130    --  that cannot be inlined, the offending construct is flagged accordingly.
131
132    function Can_Override_Operator (Subp : Entity_Id) return Boolean;
133    --  Returns true if Subp can override a predefined operator.
134
135    procedure Check_Conformance
136      (New_Id                   : Entity_Id;
137       Old_Id                   : Entity_Id;
138       Ctype                    : Conformance_Type;
139       Errmsg                   : Boolean;
140       Conforms                 : out Boolean;
141       Err_Loc                  : Node_Id := Empty;
142       Get_Inst                 : Boolean := False;
143       Skip_Controlling_Formals : Boolean := False);
144    --  Given two entities, this procedure checks that the profiles associated
145    --  with these entities meet the conformance criterion given by the third
146    --  parameter. If they conform, Conforms is set True and control returns
147    --  to the caller. If they do not conform, Conforms is set to False, and
148    --  in addition, if Errmsg is True on the call, proper messages are output
149    --  to complain about the conformance failure. If Err_Loc is non_Empty
150    --  the error messages are placed on Err_Loc, if Err_Loc is empty, then
151    --  error messages are placed on the appropriate part of the construct
152    --  denoted by New_Id. If Get_Inst is true, then this is a mode conformance
153    --  against a formal access-to-subprogram type so Get_Instance_Of must
154    --  be called.
155
156    procedure Check_Subprogram_Order (N : Node_Id);
157    --  N is the N_Subprogram_Body node for a subprogram. This routine applies
158    --  the alpha ordering rule for N if this ordering requirement applicable.
159
160    procedure Check_Returns
161      (HSS  : Node_Id;
162       Mode : Character;
163       Err  : out Boolean;
164       Proc : Entity_Id := Empty);
165    --  Called to check for missing return statements in a function body, or for
166    --  returns present in a procedure body which has No_Return set. HSS is the
167    --  handled statement sequence for the subprogram body. This procedure
168    --  checks all flow paths to make sure they either have return (Mode = 'F',
169    --  used for functions) or do not have a return (Mode = 'P', used for
170    --  No_Return procedures). The flag Err is set if there are any control
171    --  paths not explicitly terminated by a return in the function case, and is
172    --  True otherwise. Proc is the entity for the procedure case and is used
173    --  in posting the warning message.
174
175    procedure Check_Untagged_Equality (Eq_Op : Entity_Id);
176    --  In Ada 2012, a primitive equality operator on an untagged record type
177    --  must appear before the type is frozen, and have the same visibility as
178    --  that of the type. This procedure checks that this rule is met, and
179    --  otherwise emits an error on the subprogram declaration and a warning
180    --  on the earlier freeze point if it is easy to locate.
181
182    procedure Enter_Overloaded_Entity (S : Entity_Id);
183    --  This procedure makes S, a new overloaded entity, into the first visible
184    --  entity with that name.
185
186    function Is_Non_Overriding_Operation
187      (Prev_E : Entity_Id;
188       New_E  : Entity_Id) return Boolean;
189    --  Enforce the rule given in 12.3(18): a private operation in an instance
190    --  overrides an inherited operation only if the corresponding operation
191    --  was overriding in the generic. This needs to be checked for primitive
192    --  operations of types derived (in the generic unit) from formal private
193    --  or formal derived types.
194
195    procedure Make_Inequality_Operator (S : Entity_Id);
196    --  Create the declaration for an inequality operator that is implicitly
197    --  created by a user-defined equality operator that yields a boolean.
198
199    procedure May_Need_Actuals (Fun : Entity_Id);
200    --  Flag functions that can be called without parameters, i.e. those that
201    --  have no parameters, or those for which defaults exist for all parameters
202
203    procedure Process_PPCs
204      (N       : Node_Id;
205       Spec_Id : Entity_Id;
206       Body_Id : Entity_Id);
207    --  Called from Analyze[_Generic]_Subprogram_Body to deal with scanning post
208    --  conditions for the body and assembling and inserting the _postconditions
209    --  procedure. N is the node for the subprogram body and Body_Id/Spec_Id are
210    --  the entities for the body and separate spec (if there is no separate
211    --  spec, Spec_Id is Empty). Note that invariants and predicates may also
212    --  provide postconditions, and are also handled in this procedure.
213
214    procedure Set_Formal_Validity (Formal_Id : Entity_Id);
215    --  Formal_Id is an formal parameter entity. This procedure deals with
216    --  setting the proper validity status for this entity, which depends on
217    --  the kind of parameter and the validity checking mode.
218
219    ---------------------------------------------
220    -- Analyze_Abstract_Subprogram_Declaration --
221    ---------------------------------------------
222
223    procedure Analyze_Abstract_Subprogram_Declaration (N : Node_Id) is
224       Designator : constant Entity_Id :=
225                      Analyze_Subprogram_Specification (Specification (N));
226       Scop       : constant Entity_Id := Current_Scope;
227
228    begin
229       Check_SPARK_Restriction ("abstract subprogram is not allowed", N);
230
231       Generate_Definition (Designator);
232       Set_Contract (Designator, Make_Contract (Sloc (Designator)));
233       Set_Is_Abstract_Subprogram (Designator);
234       New_Overloaded_Entity (Designator);
235       Check_Delayed_Subprogram (Designator);
236
237       Set_Categorization_From_Scope (Designator, Scop);
238
239       if Ekind (Scope (Designator)) = E_Protected_Type then
240          Error_Msg_N
241            ("abstract subprogram not allowed in protected type", N);
242
243       --  Issue a warning if the abstract subprogram is neither a dispatching
244       --  operation nor an operation that overrides an inherited subprogram or
245       --  predefined operator, since this most likely indicates a mistake.
246
247       elsif Warn_On_Redundant_Constructs
248         and then not Is_Dispatching_Operation (Designator)
249         and then not Present (Overridden_Operation (Designator))
250         and then (not Is_Operator_Symbol_Name (Chars (Designator))
251                    or else Scop /= Scope (Etype (First_Formal (Designator))))
252       then
253          Error_Msg_N
254            ("?abstract subprogram is not dispatching or overriding", N);
255       end if;
256
257       Generate_Reference_To_Formals (Designator);
258       Check_Eliminated (Designator);
259
260       if Has_Aspects (N) then
261          Analyze_Aspect_Specifications (N, Designator);
262       end if;
263    end Analyze_Abstract_Subprogram_Declaration;
264
265    ---------------------------------
266    -- Analyze_Expression_Function --
267    ---------------------------------
268
269    procedure Analyze_Expression_Function (N : Node_Id) is
270       Loc      : constant Source_Ptr := Sloc (N);
271       LocX     : constant Source_Ptr := Sloc (Expression (N));
272       Expr     : constant Node_Id    := Expression (N);
273       Spec     : constant Node_Id    := Specification (N);
274
275       Def_Id :  Entity_Id;
276
277       Prev :  Entity_Id;
278       --  If the expression is a completion, Prev is the entity whose
279       --  declaration is completed. Def_Id is needed to analyze the spec.
280
281       New_Body : Node_Id;
282       New_Decl : Node_Id;
283       New_Spec : Node_Id;
284       Ret      : Node_Id;
285
286    begin
287       --  This is one of the occasions on which we transform the tree during
288       --  semantic analysis. If this is a completion, transform the expression
289       --  function into an equivalent subprogram body, and analyze it.
290
291       --  Expression functions are inlined unconditionally. The back-end will
292       --  determine whether this is possible.
293
294       Inline_Processing_Required := True;
295
296       --  Create a specification for the generated body. Types and defauts in
297       --  the profile are copies of the spec, but new entities must be created
298       --  for the unit name and the formals.
299
300       New_Spec := New_Copy_Tree (Spec);
301       Set_Defining_Unit_Name (New_Spec,
302         Make_Defining_Identifier (Sloc (Defining_Unit_Name (Spec)),
303           Chars (Defining_Unit_Name (Spec))));
304
305       if Present (Parameter_Specifications (New_Spec)) then
306          declare
307             Formal_Spec : Node_Id;
308          begin
309             Formal_Spec := First (Parameter_Specifications (New_Spec));
310             while Present (Formal_Spec) loop
311                Set_Defining_Identifier
312                  (Formal_Spec,
313                   Make_Defining_Identifier (Sloc (Formal_Spec),
314                     Chars => Chars (Defining_Identifier (Formal_Spec))));
315                Next (Formal_Spec);
316             end loop;
317          end;
318       end if;
319
320       Prev     := Current_Entity_In_Scope (Defining_Entity (Spec));
321
322       --  If there are previous overloadable entities with the same name,
323       --  check whether any of them is completed by the expression function.
324
325       if Present (Prev) and then Is_Overloadable (Prev) then
326          Def_Id   := Analyze_Subprogram_Specification (Spec);
327          Prev     := Find_Corresponding_Spec (N);
328       end if;
329
330       Ret := Make_Simple_Return_Statement (LocX, Expression (N));
331
332       New_Body :=
333         Make_Subprogram_Body (Loc,
334           Specification              => New_Spec,
335           Declarations               => Empty_List,
336           Handled_Statement_Sequence =>
337             Make_Handled_Sequence_Of_Statements (LocX,
338               Statements => New_List (Ret)));
339
340       if Present (Prev) and then Ekind (Prev) = E_Generic_Function then
341
342          --  If the expression completes a generic subprogram, we must create a
343          --  separate node for the body, because at instantiation the original
344          --  node of the generic copy must be a generic subprogram body, and
345          --  cannot be a expression function. Otherwise we just rewrite the
346          --  expression with the non-generic body.
347
348          Insert_After (N, New_Body);
349          Rewrite (N, Make_Null_Statement (Loc));
350          Set_Has_Completion (Prev, False);
351          Analyze (N);
352          Analyze (New_Body);
353          Set_Is_Inlined (Prev);
354
355       elsif Present (Prev)
356         and then Comes_From_Source (Prev)
357       then
358          Set_Has_Completion (Prev, False);
359
360          --  For navigation purposes, indicate that the function is a body
361
362          Generate_Reference (Prev, Defining_Entity (N), 'b', Force => True);
363          Rewrite (N, New_Body);
364          Analyze (N);
365
366          --  Prev is the previous entity with the same name, but it is can
367          --  be an unrelated spec that is not completed by the expression
368          --  function. In that case the relevant entity is the one in the body.
369          --  Not clear that the backend can inline it in this case ???
370
371          if Has_Completion (Prev) then
372             Set_Is_Inlined (Prev);
373
374             --  The formals of the expression function are body formals,
375             --  and do not appear in the ali file, which will only contain
376             --  references to the formals of the original subprogram spec.
377
378             declare
379                F1 : Entity_Id;
380                F2 : Entity_Id;
381
382             begin
383                F1 := First_Formal (Def_Id);
384                F2 := First_Formal (Prev);
385
386                while Present (F1) loop
387                   Set_Spec_Entity (F1, F2);
388                   Next_Formal (F1);
389                   Next_Formal (F2);
390                end loop;
391             end;
392
393          else
394             Set_Is_Inlined (Defining_Entity (New_Body));
395          end if;
396
397       --  If this is not a completion, create both a declaration and a body, so
398       --  that the expression can be inlined whenever possible.
399
400       else
401          New_Decl :=
402            Make_Subprogram_Declaration (Loc, Specification => Spec);
403
404          Rewrite (N, New_Decl);
405          Analyze (N);
406          Set_Is_Inlined (Defining_Entity (New_Decl));
407
408          --  To prevent premature freeze action, insert the new body at the end
409          --  of the current declarations, or at the end of the package spec.
410          --  However, resolve usage names now, to prevent spurious visibility
411          --  on later entities.
412
413          declare
414             Decls : List_Id            := List_Containing (N);
415             Par   : constant Node_Id   := Parent (Decls);
416             Id    : constant Entity_Id := Defining_Entity (New_Decl);
417
418          begin
419             if Nkind (Par) = N_Package_Specification
420                and then Decls = Visible_Declarations (Par)
421                and then Present (Private_Declarations (Par))
422                and then not Is_Empty_List (Private_Declarations (Par))
423             then
424                Decls := Private_Declarations (Par);
425             end if;
426
427             Insert_After (Last (Decls), New_Body);
428             Push_Scope (Id);
429             Install_Formals (Id);
430             Preanalyze_Spec_Expression (Expression  (Ret), Etype (Id));
431             End_Scope;
432          end;
433       end if;
434
435       --  If the return expression is a static constant, we suppress warning
436       --  messages on unused formals, which in most cases will be noise.
437
438       Set_Is_Trivial_Subprogram (Defining_Entity (New_Body),
439         Is_OK_Static_Expression (Expr));
440    end Analyze_Expression_Function;
441
442    ----------------------------------------
443    -- Analyze_Extended_Return_Statement  --
444    ----------------------------------------
445
446    procedure Analyze_Extended_Return_Statement (N : Node_Id) is
447    begin
448       Analyze_Return_Statement (N);
449    end Analyze_Extended_Return_Statement;
450
451    ----------------------------
452    -- Analyze_Function_Call  --
453    ----------------------------
454
455    procedure Analyze_Function_Call (N : Node_Id) is
456       P       : constant Node_Id := Name (N);
457       Actuals : constant List_Id := Parameter_Associations (N);
458       Actual  : Node_Id;
459
460    begin
461       Analyze (P);
462
463       --  A call of the form A.B (X) may be an Ada 2005 call, which is
464       --  rewritten as B (A, X). If the rewriting is successful, the call
465       --  has been analyzed and we just return.
466
467       if Nkind (P) = N_Selected_Component
468         and then Name (N) /= P
469         and then Is_Rewrite_Substitution (N)
470         and then Present (Etype (N))
471       then
472          return;
473       end if;
474
475       --  If error analyzing name, then set Any_Type as result type and return
476
477       if Etype (P) = Any_Type then
478          Set_Etype (N, Any_Type);
479          return;
480       end if;
481
482       --  Otherwise analyze the parameters
483
484       if Present (Actuals) then
485          Actual := First (Actuals);
486          while Present (Actual) loop
487             Analyze (Actual);
488             Check_Parameterless_Call (Actual);
489             Next (Actual);
490          end loop;
491       end if;
492
493       Analyze_Call (N);
494    end Analyze_Function_Call;
495
496    -----------------------------
497    -- Analyze_Function_Return --
498    -----------------------------
499
500    procedure Analyze_Function_Return (N : Node_Id) is
501       Loc        : constant Source_Ptr  := Sloc (N);
502       Stm_Entity : constant Entity_Id   := Return_Statement_Entity (N);
503       Scope_Id   : constant Entity_Id   := Return_Applies_To (Stm_Entity);
504
505       R_Type : constant Entity_Id := Etype (Scope_Id);
506       --  Function result subtype
507
508       procedure Check_Limited_Return (Expr : Node_Id);
509       --  Check the appropriate (Ada 95 or Ada 2005) rules for returning
510       --  limited types. Used only for simple return statements.
511       --  Expr is the expression returned.
512
513       procedure Check_Return_Subtype_Indication (Obj_Decl : Node_Id);
514       --  Check that the return_subtype_indication properly matches the result
515       --  subtype of the function, as required by RM-6.5(5.1/2-5.3/2).
516
517       --------------------------
518       -- Check_Limited_Return --
519       --------------------------
520
521       procedure Check_Limited_Return (Expr : Node_Id) is
522       begin
523          --  Ada 2005 (AI-318-02): Return-by-reference types have been
524          --  removed and replaced by anonymous access results. This is an
525          --  incompatibility with Ada 95. Not clear whether this should be
526          --  enforced yet or perhaps controllable with special switch. ???
527
528          --  A limited interface that is not immutably limited is OK.
529
530          if Is_Limited_Interface (R_Type)
531            and then
532              not (Is_Task_Interface (R_Type)
533                    or else Is_Protected_Interface (R_Type)
534                    or else Is_Synchronized_Interface (R_Type))
535          then
536             null;
537
538          elsif Is_Limited_Type (R_Type)
539            and then not Is_Interface (R_Type)
540            and then Comes_From_Source (N)
541            and then not In_Instance_Body
542            and then not OK_For_Limited_Init_In_05 (R_Type, Expr)
543          then
544             --  Error in Ada 2005
545
546             if Ada_Version >= Ada_2005
547               and then not Debug_Flag_Dot_L
548               and then not GNAT_Mode
549             then
550                Error_Msg_N
551                  ("(Ada 2005) cannot copy object of a limited type " &
552                   "(RM-2005 6.5(5.5/2))", Expr);
553
554                if Is_Immutably_Limited_Type (R_Type) then
555                   Error_Msg_N
556                     ("\return by reference not permitted in Ada 2005", Expr);
557                end if;
558
559             --  Warn in Ada 95 mode, to give folks a heads up about this
560             --  incompatibility.
561
562             --  In GNAT mode, this is just a warning, to allow it to be
563             --  evilly turned off. Otherwise it is a real error.
564
565             --  In a generic context, simplify the warning because it makes
566             --  no sense to discuss pass-by-reference or copy.
567
568             elsif Warn_On_Ada_2005_Compatibility or GNAT_Mode then
569                if Inside_A_Generic then
570                   Error_Msg_N
571                     ("return of limited object not permitted in Ada 2005 "
572                      & "(RM-2005 6.5(5.5/2))?", Expr);
573
574                elsif Is_Immutably_Limited_Type (R_Type) then
575                   Error_Msg_N
576                     ("return by reference not permitted in Ada 2005 "
577                      & "(RM-2005 6.5(5.5/2))?", Expr);
578                else
579                   Error_Msg_N
580                     ("cannot copy object of a limited type in Ada 2005 "
581                      & "(RM-2005 6.5(5.5/2))?", Expr);
582                end if;
583
584             --  Ada 95 mode, compatibility warnings disabled
585
586             else
587                return; --  skip continuation messages below
588             end if;
589
590             if not Inside_A_Generic then
591                Error_Msg_N
592                  ("\consider switching to return of access type", Expr);
593                Explain_Limited_Type (R_Type, Expr);
594             end if;
595          end if;
596       end Check_Limited_Return;
597
598       -------------------------------------
599       -- Check_Return_Subtype_Indication --
600       -------------------------------------
601
602       procedure Check_Return_Subtype_Indication (Obj_Decl : Node_Id) is
603          Return_Obj : constant Node_Id   := Defining_Identifier (Obj_Decl);
604
605          R_Stm_Type : constant Entity_Id := Etype (Return_Obj);
606          --  Subtype given in the extended return statement (must match R_Type)
607
608          Subtype_Ind : constant Node_Id :=
609                          Object_Definition (Original_Node (Obj_Decl));
610
611          R_Type_Is_Anon_Access :
612            constant Boolean :=
613              Ekind (R_Type) = E_Anonymous_Access_Subprogram_Type
614                or else
615              Ekind (R_Type) = E_Anonymous_Access_Protected_Subprogram_Type
616                or else
617              Ekind (R_Type) = E_Anonymous_Access_Type;
618          --  True if return type of the function is an anonymous access type
619          --  Can't we make Is_Anonymous_Access_Type in einfo ???
620
621          R_Stm_Type_Is_Anon_Access :
622            constant Boolean :=
623              Ekind (R_Stm_Type) = E_Anonymous_Access_Subprogram_Type
624                or else
625              Ekind (R_Stm_Type) = E_Anonymous_Access_Protected_Subprogram_Type
626                or else
627              Ekind (R_Stm_Type) = E_Anonymous_Access_Type;
628          --  True if type of the return object is an anonymous access type
629
630       begin
631          --  First, avoid cascaded errors
632
633          if Error_Posted (Obj_Decl) or else Error_Posted (Subtype_Ind) then
634             return;
635          end if;
636
637          --  "return access T" case; check that the return statement also has
638          --  "access T", and that the subtypes statically match:
639          --   if this is an access to subprogram the signatures must match.
640
641          if R_Type_Is_Anon_Access then
642             if R_Stm_Type_Is_Anon_Access then
643                if
644                  Ekind (Designated_Type (R_Stm_Type)) /= E_Subprogram_Type
645                then
646                   if Base_Type (Designated_Type (R_Stm_Type)) /=
647                      Base_Type (Designated_Type (R_Type))
648                     or else not Subtypes_Statically_Match (R_Stm_Type, R_Type)
649                   then
650                      Error_Msg_N
651                       ("subtype must statically match function result subtype",
652                        Subtype_Mark (Subtype_Ind));
653                   end if;
654
655                else
656                   --  For two anonymous access to subprogram types, the
657                   --  types themselves must be type conformant.
658
659                   if not Conforming_Types
660                     (R_Stm_Type, R_Type, Fully_Conformant)
661                   then
662                      Error_Msg_N
663                       ("subtype must statically match function result subtype",
664                          Subtype_Ind);
665                   end if;
666                end if;
667
668             else
669                Error_Msg_N ("must use anonymous access type", Subtype_Ind);
670             end if;
671
672          --  If the return object is of an anonymous access type, then report
673          --  an error if the function's result type is not also anonymous.
674
675          elsif R_Stm_Type_Is_Anon_Access
676            and then not R_Type_Is_Anon_Access
677          then
678             Error_Msg_N ("anonymous access not allowed for function with " &
679                          "named access result", Subtype_Ind);
680
681          --  Subtype indication case: check that the return object's type is
682          --  covered by the result type, and that the subtypes statically match
683          --  when the result subtype is constrained. Also handle record types
684          --  with unknown discriminants for which we have built the underlying
685          --  record view. Coverage is needed to allow specific-type return
686          --  objects when the result type is class-wide (see AI05-32).
687
688          elsif Covers (Base_Type (R_Type), Base_Type (R_Stm_Type))
689            or else (Is_Underlying_Record_View (Base_Type (R_Stm_Type))
690                      and then
691                        Covers
692                          (Base_Type (R_Type),
693                           Underlying_Record_View (Base_Type (R_Stm_Type))))
694          then
695             --  A null exclusion may be present on the return type, on the
696             --  function specification, on the object declaration or on the
697             --  subtype itself.
698
699             if Is_Access_Type (R_Type)
700               and then
701                (Can_Never_Be_Null (R_Type)
702                  or else Null_Exclusion_Present (Parent (Scope_Id))) /=
703                                               Can_Never_Be_Null (R_Stm_Type)
704             then
705                Error_Msg_N
706                  ("subtype must statically match function result subtype",
707                   Subtype_Ind);
708             end if;
709
710             --  AI05-103: for elementary types, subtypes must statically match
711
712             if Is_Constrained (R_Type)
713               or else Is_Access_Type (R_Type)
714             then
715                if not Subtypes_Statically_Match (R_Stm_Type, R_Type) then
716                   Error_Msg_N
717                     ("subtype must statically match function result subtype",
718                      Subtype_Ind);
719                end if;
720             end if;
721
722          elsif Etype (Base_Type (R_Type)) = R_Stm_Type
723            and then Is_Null_Extension (Base_Type (R_Type))
724          then
725             null;
726
727          else
728             Error_Msg_N
729               ("wrong type for return_subtype_indication", Subtype_Ind);
730          end if;
731       end Check_Return_Subtype_Indication;
732
733       ---------------------
734       -- Local Variables --
735       ---------------------
736
737       Expr : Node_Id;
738
739    --  Start of processing for Analyze_Function_Return
740
741    begin
742       Set_Return_Present (Scope_Id);
743
744       if Nkind (N) = N_Simple_Return_Statement then
745          Expr := Expression (N);
746
747          --  Guard against a malformed expression. The parser may have tried to
748          --  recover but the node is not analyzable.
749
750          if Nkind (Expr) = N_Error then
751             Set_Etype (Expr, Any_Type);
752             Expander_Mode_Save_And_Set (False);
753             return;
754
755          else
756             --  The resolution of a controlled [extension] aggregate associated
757             --  with a return statement creates a temporary which needs to be
758             --  finalized on function exit. Wrap the return statement inside a
759             --  block so that the finalization machinery can detect this case.
760             --  This early expansion is done only when the return statement is
761             --  not part of a handled sequence of statements.
762
763             if Nkind_In (Expr, N_Aggregate,
764                                N_Extension_Aggregate)
765               and then Needs_Finalization (R_Type)
766               and then Nkind (Parent (N)) /= N_Handled_Sequence_Of_Statements
767             then
768                Rewrite (N,
769                  Make_Block_Statement (Loc,
770                    Handled_Statement_Sequence =>
771                      Make_Handled_Sequence_Of_Statements (Loc,
772                        Statements => New_List (Relocate_Node (N)))));
773
774                Analyze (N);
775                return;
776             end if;
777
778             Analyze_And_Resolve (Expr, R_Type);
779             Check_Limited_Return (Expr);
780          end if;
781
782          --  RETURN only allowed in SPARK as the last statement in function
783
784          if Nkind (Parent (N)) /= N_Handled_Sequence_Of_Statements
785            and then
786              (Nkind (Parent (Parent (N))) /= N_Subprogram_Body
787                or else Present (Next (N)))
788          then
789             Check_SPARK_Restriction
790               ("RETURN should be the last statement in function", N);
791          end if;
792
793       else
794          Check_SPARK_Restriction ("extended RETURN is not allowed", N);
795
796          --  Analyze parts specific to extended_return_statement:
797
798          declare
799             Obj_Decl : constant Node_Id :=
800                          Last (Return_Object_Declarations (N));
801
802             HSS : constant Node_Id := Handled_Statement_Sequence (N);
803
804          begin
805             Expr := Expression (Obj_Decl);
806
807             --  Note: The check for OK_For_Limited_Init will happen in
808             --  Analyze_Object_Declaration; we treat it as a normal
809             --  object declaration.
810
811             Set_Is_Return_Object (Defining_Identifier (Obj_Decl));
812             Analyze (Obj_Decl);
813
814             Check_Return_Subtype_Indication (Obj_Decl);
815
816             if Present (HSS) then
817                Analyze (HSS);
818
819                if Present (Exception_Handlers (HSS)) then
820
821                   --  ???Has_Nested_Block_With_Handler needs to be set.
822                   --  Probably by creating an actual N_Block_Statement.
823                   --  Probably in Expand.
824
825                   null;
826                end if;
827             end if;
828
829             --  Mark the return object as referenced, since the return is an
830             --  implicit reference of the object.
831
832             Set_Referenced (Defining_Identifier (Obj_Decl));
833
834             Check_References (Stm_Entity);
835          end;
836       end if;
837
838       --  Case of Expr present
839
840       if Present (Expr)
841
842          --  Defend against previous errors
843
844         and then Nkind (Expr) /= N_Empty
845         and then Present (Etype (Expr))
846       then
847          --  Apply constraint check. Note that this is done before the implicit
848          --  conversion of the expression done for anonymous access types to
849          --  ensure correct generation of the null-excluding check associated
850          --  with null-excluding expressions found in return statements.
851
852          Apply_Constraint_Check (Expr, R_Type);
853
854          --  Ada 2005 (AI-318-02): When the result type is an anonymous access
855          --  type, apply an implicit conversion of the expression to that type
856          --  to force appropriate static and run-time accessibility checks.
857
858          if Ada_Version >= Ada_2005
859            and then Ekind (R_Type) = E_Anonymous_Access_Type
860          then
861             Rewrite (Expr, Convert_To (R_Type, Relocate_Node (Expr)));
862             Analyze_And_Resolve (Expr, R_Type);
863          end if;
864
865          --  If the result type is class-wide, then check that the return
866          --  expression's type is not declared at a deeper level than the
867          --  function (RM05-6.5(5.6/2)).
868
869          if Ada_Version >= Ada_2005
870            and then Is_Class_Wide_Type (R_Type)
871          then
872             if Type_Access_Level (Etype (Expr)) >
873                  Subprogram_Access_Level (Scope_Id)
874             then
875                Error_Msg_N
876                  ("level of return expression type is deeper than " &
877                   "class-wide function!", Expr);
878             end if;
879          end if;
880
881          --  Check incorrect use of dynamically tagged expression
882
883          if Is_Tagged_Type (R_Type) then
884             Check_Dynamically_Tagged_Expression
885               (Expr => Expr,
886                Typ  => R_Type,
887                Related_Nod => N);
888          end if;
889
890          --  ??? A real run-time accessibility check is needed in cases
891          --  involving dereferences of access parameters. For now we just
892          --  check the static cases.
893
894          if (Ada_Version < Ada_2005 or else Debug_Flag_Dot_L)
895            and then Is_Immutably_Limited_Type (Etype (Scope_Id))
896            and then Object_Access_Level (Expr) >
897                       Subprogram_Access_Level (Scope_Id)
898          then
899
900             --  Suppress the message in a generic, where the rewriting
901             --  is irrelevant.
902
903             if Inside_A_Generic then
904                null;
905
906             else
907                Rewrite (N,
908                  Make_Raise_Program_Error (Loc,
909                    Reason => PE_Accessibility_Check_Failed));
910                Analyze (N);
911
912                Error_Msg_N
913                  ("cannot return a local value by reference?", N);
914                Error_Msg_NE
915                  ("\& will be raised at run time?",
916                    N, Standard_Program_Error);
917             end if;
918          end if;
919
920          if Known_Null (Expr)
921            and then Nkind (Parent (Scope_Id)) = N_Function_Specification
922            and then Null_Exclusion_Present (Parent (Scope_Id))
923          then
924             Apply_Compile_Time_Constraint_Error
925               (N      => Expr,
926                Msg    => "(Ada 2005) null not allowed for "
927                          & "null-excluding return?",
928                Reason => CE_Null_Not_Allowed);
929          end if;
930
931          --  Apply checks suggested by AI05-0144 (dangerous order dependence)
932
933          Check_Order_Dependence;
934       end if;
935    end Analyze_Function_Return;
936
937    -------------------------------------
938    -- Analyze_Generic_Subprogram_Body --
939    -------------------------------------
940
941    procedure Analyze_Generic_Subprogram_Body
942      (N      : Node_Id;
943       Gen_Id : Entity_Id)
944    is
945       Gen_Decl : constant Node_Id     := Unit_Declaration_Node (Gen_Id);
946       Kind     : constant Entity_Kind := Ekind (Gen_Id);
947       Body_Id  : Entity_Id;
948       New_N    : Node_Id;
949       Spec     : Node_Id;
950
951    begin
952       --  Copy body and disable expansion while analyzing the generic For a
953       --  stub, do not copy the stub (which would load the proper body), this
954       --  will be done when the proper body is analyzed.
955
956       if Nkind (N) /= N_Subprogram_Body_Stub then
957          New_N := Copy_Generic_Node (N, Empty, Instantiating => False);
958          Rewrite (N, New_N);
959          Start_Generic;
960       end if;
961
962       Spec := Specification (N);
963
964       --  Within the body of the generic, the subprogram is callable, and
965       --  behaves like the corresponding non-generic unit.
966
967       Body_Id := Defining_Entity (Spec);
968
969       if Kind = E_Generic_Procedure
970         and then Nkind (Spec) /= N_Procedure_Specification
971       then
972          Error_Msg_N ("invalid body for generic procedure ", Body_Id);
973          return;
974
975       elsif Kind = E_Generic_Function
976         and then Nkind (Spec) /= N_Function_Specification
977       then
978          Error_Msg_N ("invalid body for generic function ", Body_Id);
979          return;
980       end if;
981
982       Set_Corresponding_Body (Gen_Decl, Body_Id);
983
984       if Has_Completion (Gen_Id)
985         and then Nkind (Parent (N)) /= N_Subunit
986       then
987          Error_Msg_N ("duplicate generic body", N);
988          return;
989       else
990          Set_Has_Completion (Gen_Id);
991       end if;
992
993       if Nkind (N) = N_Subprogram_Body_Stub then
994          Set_Ekind (Defining_Entity (Specification (N)), Kind);
995       else
996          Set_Corresponding_Spec (N, Gen_Id);
997       end if;
998
999       if Nkind (Parent (N)) = N_Compilation_Unit then
1000          Set_Cunit_Entity (Current_Sem_Unit, Defining_Entity (N));
1001       end if;
1002
1003       --  Make generic parameters immediately visible in the body. They are
1004       --  needed to process the formals declarations. Then make the formals
1005       --  visible in a separate step.
1006
1007       Push_Scope (Gen_Id);
1008
1009       declare
1010          E         : Entity_Id;
1011          First_Ent : Entity_Id;
1012
1013       begin
1014          First_Ent := First_Entity (Gen_Id);
1015
1016          E := First_Ent;
1017          while Present (E) and then not Is_Formal (E) loop
1018             Install_Entity (E);
1019             Next_Entity (E);
1020          end loop;
1021
1022          Set_Use (Generic_Formal_Declarations (Gen_Decl));
1023
1024          --  Now generic formals are visible, and the specification can be
1025          --  analyzed, for subsequent conformance check.
1026
1027          Body_Id := Analyze_Subprogram_Specification (Spec);
1028
1029          --  Make formal parameters visible
1030
1031          if Present (E) then
1032
1033             --  E is the first formal parameter, we loop through the formals
1034             --  installing them so that they will be visible.
1035
1036             Set_First_Entity (Gen_Id, E);
1037             while Present (E) loop
1038                Install_Entity (E);
1039                Next_Formal (E);
1040             end loop;
1041          end if;
1042
1043          --  Visible generic entity is callable within its own body
1044
1045          Set_Ekind          (Gen_Id,  Ekind (Body_Id));
1046          Set_Ekind          (Body_Id, E_Subprogram_Body);
1047          Set_Convention     (Body_Id, Convention (Gen_Id));
1048          Set_Is_Obsolescent (Body_Id, Is_Obsolescent (Gen_Id));
1049          Set_Scope          (Body_Id, Scope (Gen_Id));
1050          Check_Fully_Conformant (Body_Id, Gen_Id, Body_Id);
1051
1052          if Nkind (N) = N_Subprogram_Body_Stub then
1053
1054             --  No body to analyze, so restore state of generic unit
1055
1056             Set_Ekind (Gen_Id, Kind);
1057             Set_Ekind (Body_Id, Kind);
1058
1059             if Present (First_Ent) then
1060                Set_First_Entity (Gen_Id, First_Ent);
1061             end if;
1062
1063             End_Scope;
1064             return;
1065          end if;
1066
1067          --  If this is a compilation unit, it must be made visible explicitly,
1068          --  because the compilation of the declaration, unlike other library
1069          --  unit declarations, does not. If it is not a unit, the following
1070          --  is redundant but harmless.
1071
1072          Set_Is_Immediately_Visible (Gen_Id);
1073          Reference_Body_Formals (Gen_Id, Body_Id);
1074
1075          if Is_Child_Unit (Gen_Id) then
1076             Generate_Reference (Gen_Id, Scope (Gen_Id), 'k', False);
1077          end if;
1078
1079          Set_Actual_Subtypes (N, Current_Scope);
1080
1081          --  Deal with preconditions and postconditions. In formal verification
1082          --  mode, we keep pre- and postconditions attached to entities rather
1083          --  than inserted in the code, in order to facilitate a distinct
1084          --  treatment for them.
1085
1086          if not Alfa_Mode then
1087             Process_PPCs (N, Gen_Id, Body_Id);
1088          end if;
1089
1090          --  If the generic unit carries pre- or post-conditions, copy them
1091          --  to the original generic tree, so that they are properly added
1092          --  to any instantiation.
1093
1094          declare
1095             Orig : constant Node_Id := Original_Node (N);
1096             Cond : Node_Id;
1097
1098          begin
1099             Cond := First (Declarations (N));
1100             while Present (Cond) loop
1101                if Nkind (Cond) = N_Pragma
1102                  and then Pragma_Name (Cond) = Name_Check
1103                then
1104                   Prepend (New_Copy_Tree (Cond), Declarations (Orig));
1105
1106                elsif Nkind (Cond) = N_Pragma
1107                  and then Pragma_Name (Cond) = Name_Postcondition
1108                then
1109                   Set_Ekind (Defining_Entity (Orig), Ekind (Gen_Id));
1110                   Prepend (New_Copy_Tree (Cond), Declarations (Orig));
1111                else
1112                   exit;
1113                end if;
1114
1115                Next (Cond);
1116             end loop;
1117          end;
1118
1119          Analyze_Declarations (Declarations (N));
1120          Check_Completion;
1121          Analyze (Handled_Statement_Sequence (N));
1122
1123          Save_Global_References (Original_Node (N));
1124
1125          --  Prior to exiting the scope, include generic formals again (if any
1126          --  are present) in the set of local entities.
1127
1128          if Present (First_Ent) then
1129             Set_First_Entity (Gen_Id, First_Ent);
1130          end if;
1131
1132          Check_References (Gen_Id);
1133       end;
1134
1135       Process_End_Label (Handled_Statement_Sequence (N), 't', Current_Scope);
1136       End_Scope;
1137       Check_Subprogram_Order (N);
1138
1139       --  Outside of its body, unit is generic again
1140
1141       Set_Ekind (Gen_Id, Kind);
1142       Generate_Reference (Gen_Id, Body_Id, 'b', Set_Ref => False);
1143
1144       if Style_Check then
1145          Style.Check_Identifier (Body_Id, Gen_Id);
1146       end if;
1147
1148       End_Generic;
1149    end Analyze_Generic_Subprogram_Body;
1150
1151    -----------------------------
1152    -- Analyze_Operator_Symbol --
1153    -----------------------------
1154
1155    --  An operator symbol such as "+" or "and" may appear in context where the
1156    --  literal denotes an entity name, such as "+"(x, y) or in context when it
1157    --  is just a string, as in (conjunction = "or"). In these cases the parser
1158    --  generates this node, and the semantics does the disambiguation. Other
1159    --  such case are actuals in an instantiation, the generic unit in an
1160    --  instantiation, and pragma arguments.
1161
1162    procedure Analyze_Operator_Symbol (N : Node_Id) is
1163       Par : constant Node_Id := Parent (N);
1164
1165    begin
1166       if        (Nkind (Par) = N_Function_Call
1167                    and then N = Name (Par))
1168         or else  Nkind (Par) = N_Function_Instantiation
1169         or else (Nkind (Par) = N_Indexed_Component
1170                    and then N = Prefix (Par))
1171         or else (Nkind (Par) = N_Pragma_Argument_Association
1172                    and then not Is_Pragma_String_Literal (Par))
1173         or else  Nkind (Par) = N_Subprogram_Renaming_Declaration
1174         or else (Nkind (Par) = N_Attribute_Reference
1175                   and then Attribute_Name (Par) /= Name_Value)
1176       then
1177          Find_Direct_Name (N);
1178
1179       else
1180          Change_Operator_Symbol_To_String_Literal (N);
1181          Analyze (N);
1182       end if;
1183    end Analyze_Operator_Symbol;
1184
1185    -----------------------------------
1186    -- Analyze_Parameter_Association --
1187    -----------------------------------
1188
1189    procedure Analyze_Parameter_Association (N : Node_Id) is
1190    begin
1191       Analyze (Explicit_Actual_Parameter (N));
1192    end Analyze_Parameter_Association;
1193
1194    ----------------------------
1195    -- Analyze_Procedure_Call --
1196    ----------------------------
1197
1198    procedure Analyze_Procedure_Call (N : Node_Id) is
1199       Loc     : constant Source_Ptr := Sloc (N);
1200       P       : constant Node_Id    := Name (N);
1201       Actuals : constant List_Id    := Parameter_Associations (N);
1202       Actual  : Node_Id;
1203       New_N   : Node_Id;
1204
1205       procedure Analyze_Call_And_Resolve;
1206       --  Do Analyze and Resolve calls for procedure call
1207       --  At end, check illegal order dependence.
1208
1209       ------------------------------
1210       -- Analyze_Call_And_Resolve --
1211       ------------------------------
1212
1213       procedure Analyze_Call_And_Resolve is
1214       begin
1215          if Nkind (N) = N_Procedure_Call_Statement then
1216             Analyze_Call (N);
1217             Resolve (N, Standard_Void_Type);
1218
1219             --  Apply checks suggested by AI05-0144
1220
1221             Check_Order_Dependence;
1222
1223          else
1224             Analyze (N);
1225          end if;
1226       end Analyze_Call_And_Resolve;
1227
1228    --  Start of processing for Analyze_Procedure_Call
1229
1230    begin
1231       --  The syntactic construct: PREFIX ACTUAL_PARAMETER_PART can denote
1232       --  a procedure call or an entry call. The prefix may denote an access
1233       --  to subprogram type, in which case an implicit dereference applies.
1234       --  If the prefix is an indexed component (without implicit dereference)
1235       --  then the construct denotes a call to a member of an entire family.
1236       --  If the prefix is a simple name, it may still denote a call to a
1237       --  parameterless member of an entry family. Resolution of these various
1238       --  interpretations is delicate.
1239
1240       Analyze (P);
1241
1242       --  If this is a call of the form Obj.Op, the call may have been
1243       --  analyzed and possibly rewritten into a block, in which case
1244       --  we are done.
1245
1246       if Analyzed (N) then
1247          return;
1248       end if;
1249
1250       --  If there is an error analyzing the name (which may have been
1251       --  rewritten if the original call was in prefix notation) then error
1252       --  has been emitted already, mark node and return.
1253
1254       if Error_Posted (N)
1255         or else Etype (Name (N)) = Any_Type
1256       then
1257          Set_Etype (N, Any_Type);
1258          return;
1259       end if;
1260
1261       --  Otherwise analyze the parameters
1262
1263       if Present (Actuals) then
1264          Actual := First (Actuals);
1265
1266          while Present (Actual) loop
1267             Analyze (Actual);
1268             Check_Parameterless_Call (Actual);
1269             Next (Actual);
1270          end loop;
1271       end if;
1272
1273       --  Special processing for Elab_Spec, Elab_Body and Elab_Subp_Body calls
1274
1275       if Nkind (P) = N_Attribute_Reference
1276         and then (Attribute_Name (P) = Name_Elab_Spec
1277                    or else Attribute_Name (P) = Name_Elab_Body
1278                    or else Attribute_Name (P) = Name_Elab_Subp_Body)
1279       then
1280          if Present (Actuals) then
1281             Error_Msg_N
1282               ("no parameters allowed for this call", First (Actuals));
1283             return;
1284          end if;
1285
1286          Set_Etype (N, Standard_Void_Type);
1287          Set_Analyzed (N);
1288
1289       elsif Is_Entity_Name (P)
1290         and then Is_Record_Type (Etype (Entity (P)))
1291         and then Remote_AST_I_Dereference (P)
1292       then
1293          return;
1294
1295       elsif Is_Entity_Name (P)
1296         and then Ekind (Entity (P)) /= E_Entry_Family
1297       then
1298          if Is_Access_Type (Etype (P))
1299            and then Ekind (Designated_Type (Etype (P))) = E_Subprogram_Type
1300            and then No (Actuals)
1301            and then Comes_From_Source (N)
1302          then
1303             Error_Msg_N ("missing explicit dereference in call", N);
1304          end if;
1305
1306          Analyze_Call_And_Resolve;
1307
1308       --  If the prefix is the simple name of an entry family, this is
1309       --  a parameterless call from within the task body itself.
1310
1311       elsif Is_Entity_Name (P)
1312         and then Nkind (P) = N_Identifier
1313         and then Ekind (Entity (P)) = E_Entry_Family
1314         and then Present (Actuals)
1315         and then No (Next (First (Actuals)))
1316       then
1317          --  Can be call to parameterless entry family. What appears to be the
1318          --  sole argument is in fact the entry index. Rewrite prefix of node
1319          --  accordingly. Source representation is unchanged by this
1320          --  transformation.
1321
1322          New_N :=
1323            Make_Indexed_Component (Loc,
1324              Prefix =>
1325                Make_Selected_Component (Loc,
1326                  Prefix => New_Occurrence_Of (Scope (Entity (P)), Loc),
1327                  Selector_Name => New_Occurrence_Of (Entity (P), Loc)),
1328              Expressions => Actuals);
1329          Set_Name (N, New_N);
1330          Set_Etype (New_N, Standard_Void_Type);
1331          Set_Parameter_Associations (N, No_List);
1332          Analyze_Call_And_Resolve;
1333
1334       elsif Nkind (P) = N_Explicit_Dereference then
1335          if Ekind (Etype (P)) = E_Subprogram_Type then
1336             Analyze_Call_And_Resolve;
1337          else
1338             Error_Msg_N ("expect access to procedure in call", P);
1339          end if;
1340
1341       --  The name can be a selected component or an indexed component that
1342       --  yields an access to subprogram. Such a prefix is legal if the call
1343       --  has parameter associations.
1344
1345       elsif Is_Access_Type (Etype (P))
1346         and then Ekind (Designated_Type (Etype (P))) = E_Subprogram_Type
1347       then
1348          if Present (Actuals) then
1349             Analyze_Call_And_Resolve;
1350          else
1351             Error_Msg_N ("missing explicit dereference in call ", N);
1352          end if;
1353
1354       --  If not an access to subprogram, then the prefix must resolve to the
1355       --  name of an entry, entry family, or protected operation.
1356
1357       --  For the case of a simple entry call, P is a selected component where
1358       --  the prefix is the task and the selector name is the entry. A call to
1359       --  a protected procedure will have the same syntax. If the protected
1360       --  object contains overloaded operations, the entity may appear as a
1361       --  function, the context will select the operation whose type is Void.
1362
1363       elsif Nkind (P) = N_Selected_Component
1364         and then (Ekind (Entity (Selector_Name (P))) = E_Entry
1365                     or else
1366                   Ekind (Entity (Selector_Name (P))) = E_Procedure
1367                     or else
1368                   Ekind (Entity (Selector_Name (P))) = E_Function)
1369       then
1370          Analyze_Call_And_Resolve;
1371
1372       elsif Nkind (P) = N_Selected_Component
1373         and then Ekind (Entity (Selector_Name (P))) = E_Entry_Family
1374         and then Present (Actuals)
1375         and then No (Next (First (Actuals)))
1376       then
1377          --  Can be call to parameterless entry family. What appears to be the
1378          --  sole argument is in fact the entry index. Rewrite prefix of node
1379          --  accordingly. Source representation is unchanged by this
1380          --  transformation.
1381
1382          New_N :=
1383            Make_Indexed_Component (Loc,
1384              Prefix => New_Copy (P),
1385              Expressions => Actuals);
1386          Set_Name (N, New_N);
1387          Set_Etype (New_N, Standard_Void_Type);
1388          Set_Parameter_Associations (N, No_List);
1389          Analyze_Call_And_Resolve;
1390
1391       --  For the case of a reference to an element of an entry family, P is
1392       --  an indexed component whose prefix is a selected component (task and
1393       --  entry family), and whose index is the entry family index.
1394
1395       elsif Nkind (P) = N_Indexed_Component
1396         and then Nkind (Prefix (P)) = N_Selected_Component
1397         and then Ekind (Entity (Selector_Name (Prefix (P)))) = E_Entry_Family
1398       then
1399          Analyze_Call_And_Resolve;
1400
1401       --  If the prefix is the name of an entry family, it is a call from
1402       --  within the task body itself.
1403
1404       elsif Nkind (P) = N_Indexed_Component
1405         and then Nkind (Prefix (P)) = N_Identifier
1406         and then Ekind (Entity (Prefix (P))) = E_Entry_Family
1407       then
1408          New_N :=
1409            Make_Selected_Component (Loc,
1410              Prefix => New_Occurrence_Of (Scope (Entity (Prefix (P))), Loc),
1411              Selector_Name => New_Occurrence_Of (Entity (Prefix (P)), Loc));
1412          Rewrite (Prefix (P), New_N);
1413          Analyze (P);
1414          Analyze_Call_And_Resolve;
1415
1416       --  In Ada 2012. a qualified expression is a name, but it cannot be a
1417       --  procedure name, so the construct can only be a qualified expression.
1418
1419       elsif Nkind (P) = N_Qualified_Expression
1420         and then Ada_Version >= Ada_2012
1421       then
1422          Rewrite (N, Make_Code_Statement (Loc, Expression => P));
1423          Analyze (N);
1424
1425       --  Anything else is an error
1426
1427       else
1428          Error_Msg_N ("invalid procedure or entry call", N);
1429       end if;
1430    end Analyze_Procedure_Call;
1431
1432    ------------------------------
1433    -- Analyze_Return_Statement --
1434    ------------------------------
1435
1436    procedure Analyze_Return_Statement (N : Node_Id) is
1437
1438       pragma Assert (Nkind_In (N, N_Simple_Return_Statement,
1439                                   N_Extended_Return_Statement));
1440
1441       Returns_Object : constant Boolean :=
1442                          Nkind (N) = N_Extended_Return_Statement
1443                            or else
1444                             (Nkind (N) = N_Simple_Return_Statement
1445                               and then Present (Expression (N)));
1446       --  True if we're returning something; that is, "return <expression>;"
1447       --  or "return Result : T [:= ...]". False for "return;". Used for error
1448       --  checking: If Returns_Object is True, N should apply to a function
1449       --  body; otherwise N should apply to a procedure body, entry body,
1450       --  accept statement, or extended return statement.
1451
1452       function Find_What_It_Applies_To return Entity_Id;
1453       --  Find the entity representing the innermost enclosing body, accept
1454       --  statement, or extended return statement. If the result is a callable
1455       --  construct or extended return statement, then this will be the value
1456       --  of the Return_Applies_To attribute. Otherwise, the program is
1457       --  illegal. See RM-6.5(4/2).
1458
1459       -----------------------------
1460       -- Find_What_It_Applies_To --
1461       -----------------------------
1462
1463       function Find_What_It_Applies_To return Entity_Id is
1464          Result : Entity_Id := Empty;
1465
1466       begin
1467          --  Loop outward through the Scope_Stack, skipping blocks, loops,
1468          --  and postconditions.
1469
1470          for J in reverse 0 .. Scope_Stack.Last loop
1471             Result := Scope_Stack.Table (J).Entity;
1472             exit when not Ekind_In (Result, E_Block, E_Loop)
1473               and then Chars (Result) /= Name_uPostconditions;
1474          end loop;
1475
1476          pragma Assert (Present (Result));
1477          return Result;
1478       end Find_What_It_Applies_To;
1479
1480       --  Local declarations
1481
1482       Scope_Id   : constant Entity_Id   := Find_What_It_Applies_To;
1483       Kind       : constant Entity_Kind := Ekind (Scope_Id);
1484       Loc        : constant Source_Ptr  := Sloc (N);
1485       Stm_Entity : constant Entity_Id   :=
1486                      New_Internal_Entity
1487                        (E_Return_Statement, Current_Scope, Loc, 'R');
1488
1489    --  Start of processing for Analyze_Return_Statement
1490
1491    begin
1492       Set_Return_Statement_Entity (N, Stm_Entity);
1493
1494       Set_Etype (Stm_Entity, Standard_Void_Type);
1495       Set_Return_Applies_To (Stm_Entity, Scope_Id);
1496
1497       --  Place Return entity on scope stack, to simplify enforcement of 6.5
1498       --  (4/2): an inner return statement will apply to this extended return.
1499
1500       if Nkind (N) = N_Extended_Return_Statement then
1501          Push_Scope (Stm_Entity);
1502       end if;
1503
1504       --  Check that pragma No_Return is obeyed. Don't complain about the
1505       --  implicitly-generated return that is placed at the end.
1506
1507       if No_Return (Scope_Id) and then Comes_From_Source (N) then
1508          Error_Msg_N ("RETURN statement not allowed (No_Return)", N);
1509       end if;
1510
1511       --  Warn on any unassigned OUT parameters if in procedure
1512
1513       if Ekind (Scope_Id) = E_Procedure then
1514          Warn_On_Unassigned_Out_Parameter (N, Scope_Id);
1515       end if;
1516
1517       --  Check that functions return objects, and other things do not
1518
1519       if Kind = E_Function or else Kind = E_Generic_Function then
1520          if not Returns_Object then
1521             Error_Msg_N ("missing expression in return from function", N);
1522          end if;
1523
1524       elsif Kind = E_Procedure or else Kind = E_Generic_Procedure then
1525          if Returns_Object then
1526             Error_Msg_N ("procedure cannot return value (use function)", N);
1527          end if;
1528
1529       elsif Kind = E_Entry or else Kind = E_Entry_Family then
1530          if Returns_Object then
1531             if Is_Protected_Type (Scope (Scope_Id)) then
1532                Error_Msg_N ("entry body cannot return value", N);
1533             else
1534                Error_Msg_N ("accept statement cannot return value", N);
1535             end if;
1536          end if;
1537
1538       elsif Kind = E_Return_Statement then
1539
1540          --  We are nested within another return statement, which must be an
1541          --  extended_return_statement.
1542
1543          if Returns_Object then
1544             if Nkind (N) = N_Extended_Return_Statement then
1545                Error_Msg_N
1546                  ("extended return statement cannot be nested (use `RETURN;`)",
1547                   N);
1548
1549             --  Case of a simple return statement with a value inside extended
1550             --  return statement.
1551
1552             else
1553                Error_Msg_N
1554                  ("return nested in extended return statement cannot return " &
1555                   "value (use `RETURN;`)", N);
1556             end if;
1557          end if;
1558
1559       else
1560          Error_Msg_N ("illegal context for return statement", N);
1561       end if;
1562
1563       if Ekind_In (Kind, E_Function, E_Generic_Function) then
1564          Analyze_Function_Return (N);
1565
1566       elsif Ekind_In (Kind, E_Procedure, E_Generic_Procedure) then
1567          Set_Return_Present (Scope_Id);
1568       end if;
1569
1570       if Nkind (N) = N_Extended_Return_Statement then
1571          End_Scope;
1572       end if;
1573
1574       Kill_Current_Values (Last_Assignment_Only => True);
1575       Check_Unreachable_Code (N);
1576
1577       Analyze_Dimension (N);
1578    end Analyze_Return_Statement;
1579
1580    -------------------------------------
1581    -- Analyze_Simple_Return_Statement --
1582    -------------------------------------
1583
1584    procedure Analyze_Simple_Return_Statement (N : Node_Id) is
1585    begin
1586       if Present (Expression (N)) then
1587          Mark_Coextensions (N, Expression (N));
1588       end if;
1589
1590       Analyze_Return_Statement (N);
1591    end Analyze_Simple_Return_Statement;
1592
1593    -------------------------
1594    -- Analyze_Return_Type --
1595    -------------------------
1596
1597    procedure Analyze_Return_Type (N : Node_Id) is
1598       Designator : constant Entity_Id := Defining_Entity (N);
1599       Typ        : Entity_Id := Empty;
1600
1601    begin
1602       --  Normal case where result definition does not indicate an error
1603
1604       if Result_Definition (N) /= Error then
1605          if Nkind (Result_Definition (N)) = N_Access_Definition then
1606             Check_SPARK_Restriction
1607               ("access result is not allowed", Result_Definition (N));
1608
1609             --  Ada 2005 (AI-254): Handle anonymous access to subprograms
1610
1611             declare
1612                AD : constant Node_Id :=
1613                       Access_To_Subprogram_Definition (Result_Definition (N));
1614             begin
1615                if Present (AD) and then Protected_Present (AD) then
1616                   Typ := Replace_Anonymous_Access_To_Protected_Subprogram (N);
1617                else
1618                   Typ := Access_Definition (N, Result_Definition (N));
1619                end if;
1620             end;
1621
1622             Set_Parent (Typ, Result_Definition (N));
1623             Set_Is_Local_Anonymous_Access (Typ);
1624             Set_Etype (Designator, Typ);
1625
1626             --  Ada 2005 (AI-231): Ensure proper usage of null exclusion
1627
1628             Null_Exclusion_Static_Checks (N);
1629
1630          --  Subtype_Mark case
1631
1632          else
1633             Find_Type (Result_Definition (N));
1634             Typ := Entity (Result_Definition (N));
1635             Set_Etype (Designator, Typ);
1636
1637             --  Unconstrained array as result is not allowed in SPARK
1638
1639             if Is_Array_Type (Typ)
1640               and then not Is_Constrained (Typ)
1641             then
1642                Check_SPARK_Restriction
1643                  ("returning an unconstrained array is not allowed",
1644                   Result_Definition (N));
1645             end if;
1646
1647             --  Ada 2005 (AI-231): Ensure proper usage of null exclusion
1648
1649             Null_Exclusion_Static_Checks (N);
1650
1651             --  If a null exclusion is imposed on the result type, then create
1652             --  a null-excluding itype (an access subtype) and use it as the
1653             --  function's Etype. Note that the null exclusion checks are done
1654             --  right before this, because they don't get applied to types that
1655             --  do not come from source.
1656
1657             if Is_Access_Type (Typ)
1658               and then Null_Exclusion_Present (N)
1659             then
1660                Set_Etype  (Designator,
1661                  Create_Null_Excluding_Itype
1662                   (T           => Typ,
1663                    Related_Nod => N,
1664                    Scope_Id    => Scope (Current_Scope)));
1665
1666                --  The new subtype must be elaborated before use because
1667                --  it is visible outside of the function. However its base
1668                --  type may not be frozen yet, so the reference that will
1669                --  force elaboration must be attached to the freezing of
1670                --  the base type.
1671
1672                --  If the return specification appears on a proper body,
1673                --  the subtype will have been created already on the spec.
1674
1675                if Is_Frozen (Typ) then
1676                   if Nkind (Parent (N)) = N_Subprogram_Body
1677                     and then Nkind (Parent (Parent (N))) = N_Subunit
1678                   then
1679                      null;
1680                   else
1681                      Build_Itype_Reference (Etype (Designator), Parent (N));
1682                   end if;
1683
1684                else
1685                   Ensure_Freeze_Node (Typ);
1686
1687                   declare
1688                      IR : constant Node_Id := Make_Itype_Reference (Sloc (N));
1689                   begin
1690                      Set_Itype (IR, Etype (Designator));
1691                      Append_Freeze_Actions (Typ, New_List (IR));
1692                   end;
1693                end if;
1694
1695             else
1696                Set_Etype (Designator, Typ);
1697             end if;
1698
1699             if Ekind (Typ) = E_Incomplete_Type
1700               and then Is_Value_Type (Typ)
1701             then
1702                null;
1703
1704             elsif Ekind (Typ) = E_Incomplete_Type
1705               or else (Is_Class_Wide_Type (Typ)
1706                          and then
1707                            Ekind (Root_Type (Typ)) = E_Incomplete_Type)
1708             then
1709                --  AI05-0151: Tagged incomplete types are allowed in all formal
1710                --  parts. Untagged incomplete types are not allowed in bodies.
1711
1712                if Ada_Version >= Ada_2012 then
1713                   if Is_Tagged_Type (Typ) then
1714                      null;
1715
1716                   elsif Nkind_In (Parent (Parent (N)),
1717                      N_Accept_Statement,
1718                      N_Entry_Body,
1719                      N_Subprogram_Body)
1720                   then
1721                      Error_Msg_NE
1722                        ("invalid use of untagged incomplete type&",
1723                           Designator, Typ);
1724                   end if;
1725
1726                   --  The type must be completed in the current package. This
1727                   --  is checked at the end of the package declaraton, when
1728                   --  Taft-amendment types are identified. If the return type
1729                   --  is class-wide, there is no required check, the type can
1730                   --  be a bona fide TAT.
1731
1732                   if Ekind (Scope (Current_Scope)) = E_Package
1733                     and then In_Private_Part (Scope (Current_Scope))
1734                     and then not Is_Class_Wide_Type (Typ)
1735                   then
1736                      Append_Elmt (Designator, Private_Dependents (Typ));
1737                   end if;
1738
1739                else
1740                   Error_Msg_NE
1741                     ("invalid use of incomplete type&", Designator, Typ);
1742                end if;
1743             end if;
1744          end if;
1745
1746       --  Case where result definition does indicate an error
1747
1748       else
1749          Set_Etype (Designator, Any_Type);
1750       end if;
1751    end Analyze_Return_Type;
1752
1753    -----------------------------
1754    -- Analyze_Subprogram_Body --
1755    -----------------------------
1756
1757    procedure Analyze_Subprogram_Body (N : Node_Id) is
1758       Loc       : constant Source_Ptr := Sloc (N);
1759       Body_Spec : constant Node_Id    := Specification (N);
1760       Body_Id   : constant Entity_Id  := Defining_Entity (Body_Spec);
1761
1762    begin
1763       if Debug_Flag_C then
1764          Write_Str ("==> subprogram body ");
1765          Write_Name (Chars (Body_Id));
1766          Write_Str (" from ");
1767          Write_Location (Loc);
1768          Write_Eol;
1769          Indent;
1770       end if;
1771
1772       Trace_Scope (N, Body_Id, " Analyze subprogram: ");
1773
1774       --  The real work is split out into the helper, so it can do "return;"
1775       --  without skipping the debug output:
1776
1777       Analyze_Subprogram_Body_Helper (N);
1778
1779       if Debug_Flag_C then
1780          Outdent;
1781          Write_Str ("<== subprogram body ");
1782          Write_Name (Chars (Body_Id));
1783          Write_Str (" from ");
1784          Write_Location (Loc);
1785          Write_Eol;
1786       end if;
1787    end Analyze_Subprogram_Body;
1788
1789    ------------------------------------
1790    -- Analyze_Subprogram_Body_Helper --
1791    ------------------------------------
1792
1793    --  This procedure is called for regular subprogram bodies, generic bodies,
1794    --  and for subprogram stubs of both kinds. In the case of stubs, only the
1795    --  specification matters, and is used to create a proper declaration for
1796    --  the subprogram, or to perform conformance checks.
1797
1798    procedure Analyze_Subprogram_Body_Helper (N : Node_Id) is
1799       Loc          : constant Source_Ptr := Sloc (N);
1800       Body_Deleted : constant Boolean    := False;
1801       Body_Spec    : constant Node_Id    := Specification (N);
1802       Body_Id      : Entity_Id           := Defining_Entity (Body_Spec);
1803       Prev_Id      : constant Entity_Id  := Current_Entity_In_Scope (Body_Id);
1804       Conformant   : Boolean;
1805       HSS          : Node_Id;
1806       P_Ent        : Entity_Id;
1807       Prot_Typ     : Entity_Id := Empty;
1808       Spec_Id      : Entity_Id;
1809       Spec_Decl    : Node_Id   := Empty;
1810
1811       Last_Real_Spec_Entity : Entity_Id := Empty;
1812       --  When we analyze a separate spec, the entity chain ends up containing
1813       --  the formals, as well as any itypes generated during analysis of the
1814       --  default expressions for parameters, or the arguments of associated
1815       --  precondition/postcondition pragmas (which are analyzed in the context
1816       --  of the spec since they have visibility on formals).
1817       --
1818       --  These entities belong with the spec and not the body. However we do
1819       --  the analysis of the body in the context of the spec (again to obtain
1820       --  visibility to the formals), and all the entities generated during
1821       --  this analysis end up also chained to the entity chain of the spec.
1822       --  But they really belong to the body, and there is circuitry to move
1823       --  them from the spec to the body.
1824       --
1825       --  However, when we do this move, we don't want to move the real spec
1826       --  entities (first para above) to the body. The Last_Real_Spec_Entity
1827       --  variable points to the last real spec entity, so we only move those
1828       --  chained beyond that point. It is initialized to Empty to deal with
1829       --  the case where there is no separate spec.
1830
1831       procedure Check_Anonymous_Return;
1832       --  Ada 2005: if a function returns an access type that denotes a task,
1833       --  or a type that contains tasks, we must create a master entity for
1834       --  the anonymous type, which typically will be used in an allocator
1835       --  in the body of the function.
1836
1837       procedure Check_Inline_Pragma (Spec : in out Node_Id);
1838       --  Look ahead to recognize a pragma that may appear after the body.
1839       --  If there is a previous spec, check that it appears in the same
1840       --  declarative part. If the pragma is Inline_Always, perform inlining
1841       --  unconditionally, otherwise only if Front_End_Inlining is requested.
1842       --  If the body acts as a spec, and inlining is required, we create a
1843       --  subprogram declaration for it, in order to attach the body to inline.
1844       --  If pragma does not appear after the body, check whether there is
1845       --  an inline pragma before any local declarations.
1846
1847       procedure Check_Missing_Return;
1848       --  Checks for a function with a no return statements, and also performs
1849       --  the warning checks implemented by Check_Returns. In formal mode, also
1850       --  verify that a function ends with a RETURN and that a procedure does
1851       --  not contain any RETURN.
1852
1853       function Disambiguate_Spec return Entity_Id;
1854       --  When a primitive is declared between the private view and the full
1855       --  view of a concurrent type which implements an interface, a special
1856       --  mechanism is used to find the corresponding spec of the primitive
1857       --  body.
1858
1859       procedure Exchange_Limited_Views (Subp_Id : Entity_Id);
1860       --  Ada 2012 (AI05-0151): Detect whether the profile of Subp_Id contains
1861       --  incomplete types coming from a limited context and swap their limited
1862       --  views with the non-limited ones.
1863
1864       function Is_Private_Concurrent_Primitive
1865         (Subp_Id : Entity_Id) return Boolean;
1866       --  Determine whether subprogram Subp_Id is a primitive of a concurrent
1867       --  type that implements an interface and has a private view.
1868
1869       procedure Set_Trivial_Subprogram (N : Node_Id);
1870       --  Sets the Is_Trivial_Subprogram flag in both spec and body of the
1871       --  subprogram whose body is being analyzed. N is the statement node
1872       --  causing the flag to be set, if the following statement is a return
1873       --  of an entity, we mark the entity as set in source to suppress any
1874       --  warning on the stylized use of function stubs with a dummy return.
1875
1876       procedure Verify_Overriding_Indicator;
1877       --  If there was a previous spec, the entity has been entered in the
1878       --  current scope previously. If the body itself carries an overriding
1879       --  indicator, check that it is consistent with the known status of the
1880       --  entity.
1881
1882       ----------------------------
1883       -- Check_Anonymous_Return --
1884       ----------------------------
1885
1886       procedure Check_Anonymous_Return is
1887          Decl : Node_Id;
1888          Par  : Node_Id;
1889          Scop : Entity_Id;
1890
1891       begin
1892          if Present (Spec_Id) then
1893             Scop := Spec_Id;
1894          else
1895             Scop := Body_Id;
1896          end if;
1897
1898          if Ekind (Scop) = E_Function
1899            and then Ekind (Etype (Scop)) = E_Anonymous_Access_Type
1900            and then not Is_Thunk (Scop)
1901            and then (Has_Task (Designated_Type (Etype (Scop)))
1902                       or else
1903                        (Is_Class_Wide_Type (Designated_Type (Etype (Scop)))
1904                           and then
1905                         Is_Limited_Record (Designated_Type (Etype (Scop)))))
1906            and then Expander_Active
1907
1908             --  Avoid cases with no tasking support
1909
1910            and then RTE_Available (RE_Current_Master)
1911            and then not Restriction_Active (No_Task_Hierarchy)
1912          then
1913             Decl :=
1914               Make_Object_Declaration (Loc,
1915                 Defining_Identifier =>
1916                   Make_Defining_Identifier (Loc, Name_uMaster),
1917                 Constant_Present => True,
1918                 Object_Definition =>
1919                   New_Reference_To (RTE (RE_Master_Id), Loc),
1920                 Expression =>
1921                   Make_Explicit_Dereference (Loc,
1922                     New_Reference_To (RTE (RE_Current_Master), Loc)));
1923
1924             if Present (Declarations (N)) then
1925                Prepend (Decl, Declarations (N));
1926             else
1927                Set_Declarations (N, New_List (Decl));
1928             end if;
1929
1930             Set_Master_Id (Etype (Scop), Defining_Identifier (Decl));
1931             Set_Has_Master_Entity (Scop);
1932
1933             --  Now mark the containing scope as a task master
1934
1935             Par := N;
1936             while Nkind (Par) /= N_Compilation_Unit loop
1937                Par := Parent (Par);
1938                pragma Assert (Present (Par));
1939
1940                --  If we fall off the top, we are at the outer level, and
1941                --  the environment task is our effective master, so nothing
1942                --  to mark.
1943
1944                if Nkind_In
1945                    (Par, N_Task_Body, N_Block_Statement, N_Subprogram_Body)
1946                then
1947                   Set_Is_Task_Master (Par, True);
1948                   exit;
1949                end if;
1950             end loop;
1951          end if;
1952       end Check_Anonymous_Return;
1953
1954       -------------------------
1955       -- Check_Inline_Pragma --
1956       -------------------------
1957
1958       procedure Check_Inline_Pragma (Spec : in out Node_Id) is
1959          Prag  : Node_Id;
1960          Plist : List_Id;
1961
1962          function Is_Inline_Pragma (N : Node_Id) return Boolean;
1963          --  True when N is a pragma Inline or Inline_Always that applies
1964          --  to this subprogram.
1965
1966          -----------------------
1967          --  Is_Inline_Pragma --
1968          -----------------------
1969
1970          function Is_Inline_Pragma (N : Node_Id) return Boolean is
1971          begin
1972             return
1973               Nkind (N) = N_Pragma
1974                 and then
1975                    (Pragma_Name (N) = Name_Inline_Always
1976                      or else
1977                       (Front_End_Inlining
1978                         and then Pragma_Name (N) = Name_Inline))
1979                 and then
1980                    Chars
1981                      (Expression (First (Pragma_Argument_Associations (N))))
1982                         = Chars (Body_Id);
1983          end Is_Inline_Pragma;
1984
1985       --  Start of processing for Check_Inline_Pragma
1986
1987       begin
1988          if not Expander_Active then
1989             return;
1990          end if;
1991
1992          if Is_List_Member (N)
1993            and then Present (Next (N))
1994            and then Is_Inline_Pragma (Next (N))
1995          then
1996             Prag := Next (N);
1997
1998          elsif Nkind (N) /= N_Subprogram_Body_Stub
1999            and then Present (Declarations (N))
2000            and then Is_Inline_Pragma (First (Declarations (N)))
2001          then
2002             Prag := First (Declarations (N));
2003
2004          else
2005             Prag := Empty;
2006          end if;
2007
2008          if Present (Prag) then
2009             if Present (Spec_Id) then
2010                if In_Same_List (N, Unit_Declaration_Node (Spec_Id)) then
2011                   Analyze (Prag);
2012                end if;
2013
2014             else
2015                --  Create a subprogram declaration, to make treatment uniform
2016
2017                declare
2018                   Subp : constant Entity_Id :=
2019                            Make_Defining_Identifier (Loc, Chars (Body_Id));
2020                   Decl : constant Node_Id :=
2021                            Make_Subprogram_Declaration (Loc,
2022                              Specification =>
2023                                New_Copy_Tree (Specification (N)));
2024
2025                begin
2026                   Set_Defining_Unit_Name (Specification (Decl), Subp);
2027
2028                   if Present (First_Formal (Body_Id)) then
2029                      Plist := Copy_Parameter_List (Body_Id);
2030                      Set_Parameter_Specifications
2031                        (Specification (Decl), Plist);
2032                   end if;
2033
2034                   Insert_Before (N, Decl);
2035                   Analyze (Decl);
2036                   Analyze (Prag);
2037                   Set_Has_Pragma_Inline (Subp);
2038
2039                   if Pragma_Name (Prag) = Name_Inline_Always then
2040                      Set_Is_Inlined (Subp);
2041                      Set_Has_Pragma_Inline_Always (Subp);
2042                   end if;
2043
2044                   Spec := Subp;
2045                end;
2046             end if;
2047          end if;
2048       end Check_Inline_Pragma;
2049
2050       --------------------------
2051       -- Check_Missing_Return --
2052       --------------------------
2053
2054       procedure Check_Missing_Return is
2055          Id          : Entity_Id;
2056          Missing_Ret : Boolean;
2057
2058       begin
2059          if Nkind (Body_Spec) = N_Function_Specification then
2060             if Present (Spec_Id) then
2061                Id := Spec_Id;
2062             else
2063                Id := Body_Id;
2064             end if;
2065
2066             if Return_Present (Id) then
2067                Check_Returns (HSS, 'F', Missing_Ret);
2068
2069                if Missing_Ret then
2070                   Set_Has_Missing_Return (Id);
2071                end if;
2072
2073             elsif (Is_Generic_Subprogram (Id)
2074                      or else not Is_Machine_Code_Subprogram (Id))
2075               and then not Body_Deleted
2076             then
2077                Error_Msg_N ("missing RETURN statement in function body", N);
2078             end if;
2079
2080          --  If procedure with No_Return, check returns
2081
2082          elsif Nkind (Body_Spec) = N_Procedure_Specification
2083            and then Present (Spec_Id)
2084            and then No_Return (Spec_Id)
2085          then
2086             Check_Returns (HSS, 'P', Missing_Ret, Spec_Id);
2087          end if;
2088
2089          --  Special checks in SPARK mode
2090
2091          if Nkind (Body_Spec) = N_Function_Specification then
2092
2093             --  In SPARK mode, last statement of a function should be a return
2094
2095             declare
2096                Stat : constant Node_Id := Last_Source_Statement (HSS);
2097             begin
2098                if Present (Stat)
2099                  and then not Nkind_In (Stat, N_Simple_Return_Statement,
2100                                               N_Extended_Return_Statement)
2101                then
2102                   Check_SPARK_Restriction
2103                     ("last statement in function should be RETURN", Stat);
2104                end if;
2105             end;
2106
2107          --  In SPARK mode, verify that a procedure has no return
2108
2109          elsif Nkind (Body_Spec) = N_Procedure_Specification then
2110             if Present (Spec_Id) then
2111                Id := Spec_Id;
2112             else
2113                Id := Body_Id;
2114             end if;
2115
2116             --  Would be nice to point to return statement here, can we
2117             --  borrow the Check_Returns procedure here ???
2118
2119             if Return_Present (Id) then
2120                Check_SPARK_Restriction
2121                  ("procedure should not have RETURN", N);
2122             end if;
2123          end if;
2124       end Check_Missing_Return;
2125
2126       -----------------------
2127       -- Disambiguate_Spec --
2128       -----------------------
2129
2130       function Disambiguate_Spec return Entity_Id is
2131          Priv_Spec : Entity_Id;
2132          Spec_N    : Entity_Id;
2133
2134          procedure Replace_Types (To_Corresponding : Boolean);
2135          --  Depending on the flag, replace the type of formal parameters of
2136          --  Body_Id if it is a concurrent type implementing interfaces with
2137          --  the corresponding record type or the other way around.
2138
2139          procedure Replace_Types (To_Corresponding : Boolean) is
2140             Formal     : Entity_Id;
2141             Formal_Typ : Entity_Id;
2142
2143          begin
2144             Formal := First_Formal (Body_Id);
2145             while Present (Formal) loop
2146                Formal_Typ := Etype (Formal);
2147
2148                if Is_Class_Wide_Type (Formal_Typ) then
2149                   Formal_Typ := Root_Type (Formal_Typ);
2150                end if;
2151
2152                --  From concurrent type to corresponding record
2153
2154                if To_Corresponding then
2155                   if Is_Concurrent_Type (Formal_Typ)
2156                     and then Present (Corresponding_Record_Type (Formal_Typ))
2157                     and then Present (Interfaces (
2158                                Corresponding_Record_Type (Formal_Typ)))
2159                   then
2160                      Set_Etype (Formal,
2161                        Corresponding_Record_Type (Formal_Typ));
2162                   end if;
2163
2164                --  From corresponding record to concurrent type
2165
2166                else
2167                   if Is_Concurrent_Record_Type (Formal_Typ)
2168                     and then Present (Interfaces (Formal_Typ))
2169                   then
2170                      Set_Etype (Formal,
2171                        Corresponding_Concurrent_Type (Formal_Typ));
2172                   end if;
2173                end if;
2174
2175                Next_Formal (Formal);
2176             end loop;
2177          end Replace_Types;
2178
2179       --  Start of processing for Disambiguate_Spec
2180
2181       begin
2182          --  Try to retrieve the specification of the body as is. All error
2183          --  messages are suppressed because the body may not have a spec in
2184          --  its current state.
2185
2186          Spec_N := Find_Corresponding_Spec (N, False);
2187
2188          --  It is possible that this is the body of a primitive declared
2189          --  between a private and a full view of a concurrent type. The
2190          --  controlling parameter of the spec carries the concurrent type,
2191          --  not the corresponding record type as transformed by Analyze_
2192          --  Subprogram_Specification. In such cases, we undo the change
2193          --  made by the analysis of the specification and try to find the
2194          --  spec again.
2195
2196          --  Note that wrappers already have their corresponding specs and
2197          --  bodies set during their creation, so if the candidate spec is
2198          --  a wrapper, then we definitely need to swap all types to their
2199          --  original concurrent status.
2200
2201          if No (Spec_N)
2202            or else Is_Primitive_Wrapper (Spec_N)
2203          then
2204             --  Restore all references of corresponding record types to the
2205             --  original concurrent types.
2206
2207             Replace_Types (To_Corresponding => False);
2208             Priv_Spec := Find_Corresponding_Spec (N, False);
2209
2210             --  The current body truly belongs to a primitive declared between
2211             --  a private and a full view. We leave the modified body as is,
2212             --  and return the true spec.
2213
2214             if Present (Priv_Spec)
2215               and then Is_Private_Primitive (Priv_Spec)
2216             then
2217                return Priv_Spec;
2218             end if;
2219
2220             --  In case that this is some sort of error, restore the original
2221             --  state of the body.
2222
2223             Replace_Types (To_Corresponding => True);
2224          end if;
2225
2226          return Spec_N;
2227       end Disambiguate_Spec;
2228
2229       ----------------------------
2230       -- Exchange_Limited_Views --
2231       ----------------------------
2232
2233       procedure Exchange_Limited_Views (Subp_Id : Entity_Id) is
2234          procedure Detect_And_Exchange (Id : Entity_Id);
2235          --  Determine whether Id's type denotes an incomplete type associated
2236          --  with a limited with clause and exchange the limited view with the
2237          --  non-limited one.
2238
2239          -------------------------
2240          -- Detect_And_Exchange --
2241          -------------------------
2242
2243          procedure Detect_And_Exchange (Id : Entity_Id) is
2244             Typ : constant Entity_Id := Etype (Id);
2245
2246          begin
2247             if Ekind (Typ) = E_Incomplete_Type
2248               and then From_With_Type (Typ)
2249               and then Present (Non_Limited_View (Typ))
2250             then
2251                Set_Etype (Id, Non_Limited_View (Typ));
2252             end if;
2253          end Detect_And_Exchange;
2254
2255          --  Local variables
2256
2257          Formal : Entity_Id;
2258
2259       --  Start of processing for Exchange_Limited_Views
2260
2261       begin
2262          if No (Subp_Id) then
2263             return;
2264
2265          --  Do not process subprogram bodies as they already use the non-
2266          --  limited view of types.
2267
2268          elsif not Ekind_In (Subp_Id, E_Function, E_Procedure) then
2269             return;
2270          end if;
2271
2272          --  Examine all formals and swap views when applicable
2273
2274          Formal := First_Formal (Subp_Id);
2275          while Present (Formal) loop
2276             Detect_And_Exchange (Formal);
2277
2278             Next_Formal (Formal);
2279          end loop;
2280
2281          --  Process the return type of a function
2282
2283          if Ekind (Subp_Id) = E_Function then
2284             Detect_And_Exchange (Subp_Id);
2285          end if;
2286       end Exchange_Limited_Views;
2287
2288       -------------------------------------
2289       -- Is_Private_Concurrent_Primitive --
2290       -------------------------------------
2291
2292       function Is_Private_Concurrent_Primitive
2293         (Subp_Id : Entity_Id) return Boolean
2294       is
2295          Formal_Typ : Entity_Id;
2296
2297       begin
2298          if Present (First_Formal (Subp_Id)) then
2299             Formal_Typ := Etype (First_Formal (Subp_Id));
2300
2301             if Is_Concurrent_Record_Type (Formal_Typ) then
2302                if Is_Class_Wide_Type (Formal_Typ) then
2303                   Formal_Typ := Root_Type (Formal_Typ);
2304                end if;
2305
2306                Formal_Typ := Corresponding_Concurrent_Type (Formal_Typ);
2307             end if;
2308
2309             --  The type of the first formal is a concurrent tagged type with
2310             --  a private view.
2311
2312             return
2313               Is_Concurrent_Type (Formal_Typ)
2314                 and then Is_Tagged_Type (Formal_Typ)
2315                 and then Has_Private_Declaration (Formal_Typ);
2316          end if;
2317
2318          return False;
2319       end Is_Private_Concurrent_Primitive;
2320
2321       ----------------------------
2322       -- Set_Trivial_Subprogram --
2323       ----------------------------
2324
2325       procedure Set_Trivial_Subprogram (N : Node_Id) is
2326          Nxt : constant Node_Id := Next (N);
2327
2328       begin
2329          Set_Is_Trivial_Subprogram (Body_Id);
2330
2331          if Present (Spec_Id) then
2332             Set_Is_Trivial_Subprogram (Spec_Id);
2333          end if;
2334
2335          if Present (Nxt)
2336            and then Nkind (Nxt) = N_Simple_Return_Statement
2337            and then No (Next (Nxt))
2338            and then Present (Expression (Nxt))
2339            and then Is_Entity_Name (Expression (Nxt))
2340          then
2341             Set_Never_Set_In_Source (Entity (Expression (Nxt)), False);
2342          end if;
2343       end Set_Trivial_Subprogram;
2344
2345       ---------------------------------
2346       -- Verify_Overriding_Indicator --
2347       ---------------------------------
2348
2349       procedure Verify_Overriding_Indicator is
2350       begin
2351          if Must_Override (Body_Spec) then
2352             if Nkind (Spec_Id) = N_Defining_Operator_Symbol
2353               and then  Operator_Matches_Spec (Spec_Id, Spec_Id)
2354             then
2355                null;
2356
2357             elsif not Present (Overridden_Operation (Spec_Id)) then
2358                Error_Msg_NE
2359                  ("subprogram& is not overriding", Body_Spec, Spec_Id);
2360             end if;
2361
2362          elsif Must_Not_Override (Body_Spec) then
2363             if Present (Overridden_Operation (Spec_Id)) then
2364                Error_Msg_NE
2365                  ("subprogram& overrides inherited operation",
2366                   Body_Spec, Spec_Id);
2367
2368             elsif Nkind (Spec_Id) = N_Defining_Operator_Symbol
2369               and then  Operator_Matches_Spec (Spec_Id, Spec_Id)
2370             then
2371                Error_Msg_NE
2372                  ("subprogram & overrides predefined operator ",
2373                     Body_Spec, Spec_Id);
2374
2375             --  If this is not a primitive operation or protected subprogram,
2376             --  then the overriding indicator is altogether illegal.
2377
2378             elsif not Is_Primitive (Spec_Id)
2379               and then Ekind (Scope (Spec_Id)) /= E_Protected_Type
2380             then
2381                Error_Msg_N
2382                  ("overriding indicator only allowed " &
2383                   "if subprogram is primitive",
2384                   Body_Spec);
2385             end if;
2386
2387          elsif Style_Check
2388            and then Present (Overridden_Operation (Spec_Id))
2389          then
2390             pragma Assert (Unit_Declaration_Node (Body_Id) = N);
2391             Style.Missing_Overriding (N, Body_Id);
2392
2393          elsif Style_Check
2394            and then Can_Override_Operator (Spec_Id)
2395            and then not Is_Predefined_File_Name
2396                           (Unit_File_Name (Get_Source_Unit (Spec_Id)))
2397          then
2398             pragma Assert (Unit_Declaration_Node (Body_Id) = N);
2399             Style.Missing_Overriding (N, Body_Id);
2400          end if;
2401       end Verify_Overriding_Indicator;
2402
2403    --  Start of processing for Analyze_Subprogram_Body_Helper
2404
2405    begin
2406       --  Generic subprograms are handled separately. They always have a
2407       --  generic specification. Determine whether current scope has a
2408       --  previous declaration.
2409
2410       --  If the subprogram body is defined within an instance of the same
2411       --  name, the instance appears as a package renaming, and will be hidden
2412       --  within the subprogram.
2413
2414       if Present (Prev_Id)
2415         and then not Is_Overloadable (Prev_Id)
2416         and then (Nkind (Parent (Prev_Id)) /= N_Package_Renaming_Declaration
2417                    or else Comes_From_Source (Prev_Id))
2418       then
2419          if Is_Generic_Subprogram (Prev_Id) then
2420             Spec_Id := Prev_Id;
2421             Set_Is_Compilation_Unit (Body_Id, Is_Compilation_Unit (Spec_Id));
2422             Set_Is_Child_Unit       (Body_Id, Is_Child_Unit       (Spec_Id));
2423
2424             Analyze_Generic_Subprogram_Body (N, Spec_Id);
2425
2426             if Nkind (N) = N_Subprogram_Body then
2427                HSS := Handled_Statement_Sequence (N);
2428                Check_Missing_Return;
2429             end if;
2430
2431             return;
2432
2433          else
2434             --  Previous entity conflicts with subprogram name. Attempting to
2435             --  enter name will post error.
2436
2437             Enter_Name (Body_Id);
2438             return;
2439          end if;
2440
2441       --  Non-generic case, find the subprogram declaration, if one was seen,
2442       --  or enter new overloaded entity in the current scope. If the
2443       --  Current_Entity is the Body_Id itself, the unit is being analyzed as
2444       --  part of the context of one of its subunits. No need to redo the
2445       --  analysis.
2446
2447       elsif Prev_Id = Body_Id
2448         and then Has_Completion (Body_Id)
2449       then
2450          return;
2451
2452       else
2453          Body_Id := Analyze_Subprogram_Specification (Body_Spec);
2454
2455          if Nkind (N) = N_Subprogram_Body_Stub
2456            or else No (Corresponding_Spec (N))
2457          then
2458             if Is_Private_Concurrent_Primitive (Body_Id) then
2459                Spec_Id := Disambiguate_Spec;
2460             else
2461                Spec_Id := Find_Corresponding_Spec (N);
2462             end if;
2463
2464             --  If this is a duplicate body, no point in analyzing it
2465
2466             if Error_Posted (N) then
2467                return;
2468             end if;
2469
2470             --  A subprogram body should cause freezing of its own declaration,
2471             --  but if there was no previous explicit declaration, then the
2472             --  subprogram will get frozen too late (there may be code within
2473             --  the body that depends on the subprogram having been frozen,
2474             --  such as uses of extra formals), so we force it to be frozen
2475             --  here. Same holds if the body and spec are compilation units.
2476             --  Finally, if the return type is an anonymous access to protected
2477             --  subprogram, it must be frozen before the body because its
2478             --  expansion has generated an equivalent type that is used when
2479             --  elaborating the body.
2480
2481             --  An exception in the case of Ada 2012, AI05-177: The bodies
2482             --  created for expression functions do not freeze.
2483
2484             if No (Spec_Id)
2485               and then Nkind (Original_Node (N)) /= N_Expression_Function
2486             then
2487                Freeze_Before (N, Body_Id);
2488
2489             elsif Nkind (Parent (N)) = N_Compilation_Unit then
2490                Freeze_Before (N, Spec_Id);
2491
2492             elsif Is_Access_Subprogram_Type (Etype (Body_Id)) then
2493                Freeze_Before (N, Etype (Body_Id));
2494             end if;
2495
2496          else
2497             Spec_Id := Corresponding_Spec (N);
2498          end if;
2499       end if;
2500
2501       --  Do not inline any subprogram that contains nested subprograms, since
2502       --  the backend inlining circuit seems to generate uninitialized
2503       --  references in this case. We know this happens in the case of front
2504       --  end ZCX support, but it also appears it can happen in other cases as
2505       --  well. The backend often rejects attempts to inline in the case of
2506       --  nested procedures anyway, so little if anything is lost by this.
2507       --  Note that this is test is for the benefit of the back-end. There is
2508       --  a separate test for front-end inlining that also rejects nested
2509       --  subprograms.
2510
2511       --  Do not do this test if errors have been detected, because in some
2512       --  error cases, this code blows up, and we don't need it anyway if
2513       --  there have been errors, since we won't get to the linker anyway.
2514
2515       if Comes_From_Source (Body_Id)
2516         and then Serious_Errors_Detected = 0
2517       then
2518          P_Ent := Body_Id;
2519          loop
2520             P_Ent := Scope (P_Ent);
2521             exit when No (P_Ent) or else P_Ent = Standard_Standard;
2522
2523             if Is_Subprogram (P_Ent) then
2524                Set_Is_Inlined (P_Ent, False);
2525
2526                if Comes_From_Source (P_Ent)
2527                  and then Has_Pragma_Inline (P_Ent)
2528                then
2529                   Cannot_Inline
2530                     ("cannot inline& (nested subprogram)?",
2531                      N, P_Ent);
2532                end if;
2533             end if;
2534          end loop;
2535       end if;
2536
2537       Check_Inline_Pragma (Spec_Id);
2538
2539       --  Deal with special case of a fully private operation in the body of
2540       --  the protected type. We must create a declaration for the subprogram,
2541       --  in order to attach the protected subprogram that will be used in
2542       --  internal calls. We exclude compiler generated bodies from the
2543       --  expander since the issue does not arise for those cases.
2544
2545       if No (Spec_Id)
2546         and then Comes_From_Source (N)
2547         and then Is_Protected_Type (Current_Scope)
2548       then
2549          Spec_Id := Build_Private_Protected_Declaration (N);
2550       end if;
2551
2552       --  If a separate spec is present, then deal with freezing issues
2553
2554       if Present (Spec_Id) then
2555          Spec_Decl := Unit_Declaration_Node (Spec_Id);
2556          Verify_Overriding_Indicator;
2557
2558          --  In general, the spec will be frozen when we start analyzing the
2559          --  body. However, for internally generated operations, such as
2560          --  wrapper functions for inherited operations with controlling
2561          --  results, the spec may not have been frozen by the time we expand
2562          --  the freeze actions that include the bodies. In particular, extra
2563          --  formals for accessibility or for return-in-place may need to be
2564          --  generated. Freeze nodes, if any, are inserted before the current
2565          --  body. These freeze actions are also needed in ASIS mode to enable
2566          --  the proper back-annotations.
2567
2568          if not Is_Frozen (Spec_Id)
2569            and then (Expander_Active or ASIS_Mode)
2570          then
2571             --  Force the generation of its freezing node to ensure proper
2572             --  management of access types in the backend.
2573
2574             --  This is definitely needed for some cases, but it is not clear
2575             --  why, to be investigated further???
2576
2577             Set_Has_Delayed_Freeze (Spec_Id);
2578             Freeze_Before (N, Spec_Id);
2579          end if;
2580       end if;
2581
2582       --  Mark presence of postcondition procedure in current scope and mark
2583       --  the procedure itself as needing debug info. The latter is important
2584       --  when analyzing decision coverage (for example, for MC/DC coverage).
2585
2586       if Chars (Body_Id) = Name_uPostconditions then
2587          Set_Has_Postconditions (Current_Scope);
2588          Set_Debug_Info_Needed (Body_Id);
2589       end if;
2590
2591       --  Place subprogram on scope stack, and make formals visible. If there
2592       --  is a spec, the visible entity remains that of the spec.
2593
2594       if Present (Spec_Id) then
2595          Generate_Reference (Spec_Id, Body_Id, 'b', Set_Ref => False);
2596
2597          if Is_Child_Unit (Spec_Id) then
2598             Generate_Reference (Spec_Id, Scope (Spec_Id), 'k', False);
2599          end if;
2600
2601          if Style_Check then
2602             Style.Check_Identifier (Body_Id, Spec_Id);
2603          end if;
2604
2605          Set_Is_Compilation_Unit (Body_Id, Is_Compilation_Unit (Spec_Id));
2606          Set_Is_Child_Unit       (Body_Id, Is_Child_Unit       (Spec_Id));
2607
2608          if Is_Abstract_Subprogram (Spec_Id) then
2609             Error_Msg_N ("an abstract subprogram cannot have a body", N);
2610             return;
2611
2612          else
2613             Set_Convention (Body_Id, Convention (Spec_Id));
2614             Set_Has_Completion (Spec_Id);
2615
2616             if Is_Protected_Type (Scope (Spec_Id)) then
2617                Prot_Typ := Scope (Spec_Id);
2618             end if;
2619
2620             --  If this is a body generated for a renaming, do not check for
2621             --  full conformance. The check is redundant, because the spec of
2622             --  the body is a copy of the spec in the renaming declaration,
2623             --  and the test can lead to spurious errors on nested defaults.
2624
2625             if Present (Spec_Decl)
2626               and then not Comes_From_Source (N)
2627               and then
2628                 (Nkind (Original_Node (Spec_Decl)) =
2629                                         N_Subprogram_Renaming_Declaration
2630                    or else (Present (Corresponding_Body (Spec_Decl))
2631                               and then
2632                                 Nkind (Unit_Declaration_Node
2633                                         (Corresponding_Body (Spec_Decl))) =
2634                                            N_Subprogram_Renaming_Declaration))
2635             then
2636                Conformant := True;
2637
2638             --  Conversely, the spec may have been generated for specless body
2639             --  with an inline pragma.
2640
2641             elsif Comes_From_Source (N)
2642               and then not Comes_From_Source (Spec_Id)
2643               and then Has_Pragma_Inline (Spec_Id)
2644             then
2645                Conformant := True;
2646
2647             else
2648                Check_Conformance
2649                  (Body_Id, Spec_Id,
2650                   Fully_Conformant, True, Conformant, Body_Id);
2651             end if;
2652
2653             --  If the body is not fully conformant, we have to decide if we
2654             --  should analyze it or not. If it has a really messed up profile
2655             --  then we probably should not analyze it, since we will get too
2656             --  many bogus messages.
2657
2658             --  Our decision is to go ahead in the non-fully conformant case
2659             --  only if it is at least mode conformant with the spec. Note
2660             --  that the call to Check_Fully_Conformant has issued the proper
2661             --  error messages to complain about the lack of conformance.
2662
2663             if not Conformant
2664               and then not Mode_Conformant (Body_Id, Spec_Id)
2665             then
2666                return;
2667             end if;
2668          end if;
2669
2670          if Spec_Id /= Body_Id then
2671             Reference_Body_Formals (Spec_Id, Body_Id);
2672          end if;
2673
2674          if Nkind (N) /= N_Subprogram_Body_Stub then
2675             Set_Corresponding_Spec (N, Spec_Id);
2676
2677             --  Ada 2005 (AI-345): If the operation is a primitive operation
2678             --  of a concurrent type, the type of the first parameter has been
2679             --  replaced with the corresponding record, which is the proper
2680             --  run-time structure to use. However, within the body there may
2681             --  be uses of the formals that depend on primitive operations
2682             --  of the type (in particular calls in prefixed form) for which
2683             --  we need the original concurrent type. The operation may have
2684             --  several controlling formals, so the replacement must be done
2685             --  for all of them.
2686
2687             if Comes_From_Source (Spec_Id)
2688               and then Present (First_Entity (Spec_Id))
2689               and then Ekind (Etype (First_Entity (Spec_Id))) = E_Record_Type
2690               and then Is_Tagged_Type (Etype (First_Entity (Spec_Id)))
2691               and then
2692                 Present (Interfaces (Etype (First_Entity (Spec_Id))))
2693               and then
2694                 Present
2695                   (Corresponding_Concurrent_Type
2696                      (Etype (First_Entity (Spec_Id))))
2697             then
2698                declare
2699                   Typ  : constant Entity_Id := Etype (First_Entity (Spec_Id));
2700                   Form : Entity_Id;
2701
2702                begin
2703                   Form := First_Formal (Spec_Id);
2704                   while Present (Form) loop
2705                      if Etype (Form) = Typ then
2706                         Set_Etype (Form, Corresponding_Concurrent_Type (Typ));
2707                      end if;
2708
2709                      Next_Formal (Form);
2710                   end loop;
2711                end;
2712             end if;
2713
2714             --  Make the formals visible, and place subprogram on scope stack.
2715             --  This is also the point at which we set Last_Real_Spec_Entity
2716             --  to mark the entities which will not be moved to the body.
2717
2718             Install_Formals (Spec_Id);
2719             Last_Real_Spec_Entity := Last_Entity (Spec_Id);
2720             Push_Scope (Spec_Id);
2721
2722             --  Make sure that the subprogram is immediately visible. For
2723             --  child units that have no separate spec this is indispensable.
2724             --  Otherwise it is safe albeit redundant.
2725
2726             Set_Is_Immediately_Visible (Spec_Id);
2727          end if;
2728
2729          Set_Corresponding_Body (Unit_Declaration_Node (Spec_Id), Body_Id);
2730          Set_Ekind (Body_Id, E_Subprogram_Body);
2731          Set_Scope (Body_Id, Scope (Spec_Id));
2732          Set_Is_Obsolescent (Body_Id, Is_Obsolescent (Spec_Id));
2733
2734       --  Case of subprogram body with no previous spec
2735
2736       else
2737          --  Check for style warning required
2738
2739          if Style_Check
2740
2741            --  Only apply check for source level subprograms for which checks
2742            --  have not been suppressed.
2743
2744            and then Comes_From_Source (Body_Id)
2745            and then not Suppress_Style_Checks (Body_Id)
2746
2747            --  No warnings within an instance
2748
2749            and then not In_Instance
2750
2751            --  No warnings for expression functions
2752
2753            and then Nkind (Original_Node (N)) /= N_Expression_Function
2754          then
2755             Style.Body_With_No_Spec (N);
2756          end if;
2757
2758          New_Overloaded_Entity (Body_Id);
2759
2760          if Nkind (N) /= N_Subprogram_Body_Stub then
2761             Set_Acts_As_Spec (N);
2762             Generate_Definition (Body_Id);
2763             Set_Contract (Body_Id, Make_Contract (Sloc (Body_Id)));
2764             Generate_Reference
2765               (Body_Id, Body_Id, 'b', Set_Ref => False, Force => True);
2766             Install_Formals (Body_Id);
2767             Push_Scope (Body_Id);
2768          end if;
2769
2770          --  For stubs and bodies with no previous spec, generate references to
2771          --  formals.
2772
2773          Generate_Reference_To_Formals (Body_Id);
2774       end if;
2775
2776       --  If the return type is an anonymous access type whose designated type
2777       --  is the limited view of a class-wide type and the non-limited view is
2778       --  available, update the return type accordingly.
2779
2780       if Ada_Version >= Ada_2005
2781         and then Comes_From_Source (N)
2782       then
2783          declare
2784             Etyp : Entity_Id;
2785             Rtyp : Entity_Id;
2786
2787          begin
2788             Rtyp := Etype (Current_Scope);
2789
2790             if Ekind (Rtyp) = E_Anonymous_Access_Type then
2791                Etyp := Directly_Designated_Type (Rtyp);
2792
2793                if Is_Class_Wide_Type (Etyp)
2794                  and then From_With_Type (Etyp)
2795                then
2796                   Set_Directly_Designated_Type
2797                     (Etype (Current_Scope), Available_View (Etyp));
2798                end if;
2799             end if;
2800          end;
2801       end if;
2802
2803       --  If this is the proper body of a stub, we must verify that the stub
2804       --  conforms to the body, and to the previous spec if one was present.
2805       --  We know already that the body conforms to that spec. This test is
2806       --  only required for subprograms that come from source.
2807
2808       if Nkind (Parent (N)) = N_Subunit
2809         and then Comes_From_Source (N)
2810         and then not Error_Posted (Body_Id)
2811         and then Nkind (Corresponding_Stub (Parent (N))) =
2812                                                 N_Subprogram_Body_Stub
2813       then
2814          declare
2815             Old_Id : constant Entity_Id :=
2816                        Defining_Entity
2817                          (Specification (Corresponding_Stub (Parent (N))));
2818
2819             Conformant : Boolean := False;
2820
2821          begin
2822             if No (Spec_Id) then
2823                Check_Fully_Conformant (Body_Id, Old_Id);
2824
2825             else
2826                Check_Conformance
2827                  (Body_Id, Old_Id, Fully_Conformant, False, Conformant);
2828
2829                if not Conformant then
2830
2831                   --  The stub was taken to be a new declaration. Indicate that
2832                   --  it lacks a body.
2833
2834                   Set_Has_Completion (Old_Id, False);
2835                end if;
2836             end if;
2837          end;
2838       end if;
2839
2840       Set_Has_Completion (Body_Id);
2841       Check_Eliminated (Body_Id);
2842
2843       if Nkind (N) = N_Subprogram_Body_Stub then
2844          return;
2845
2846       elsif Present (Spec_Id)
2847         and then Expander_Active
2848         and then
2849           (Has_Pragma_Inline_Always (Spec_Id)
2850              or else (Has_Pragma_Inline (Spec_Id) and Front_End_Inlining))
2851       then
2852          Build_Body_To_Inline (N, Spec_Id);
2853       end if;
2854
2855       --  Ada 2005 (AI-262): In library subprogram bodies, after the analysis
2856       --  of the specification we have to install the private withed units.
2857       --  This holds for child units as well.
2858
2859       if Is_Compilation_Unit (Body_Id)
2860         or else Nkind (Parent (N)) = N_Compilation_Unit
2861       then
2862          Install_Private_With_Clauses (Body_Id);
2863       end if;
2864
2865       Check_Anonymous_Return;
2866
2867       --  Set the Protected_Formal field of each extra formal of the protected
2868       --  subprogram to reference the corresponding extra formal of the
2869       --  subprogram that implements it. For regular formals this occurs when
2870       --  the protected subprogram's declaration is expanded, but the extra
2871       --  formals don't get created until the subprogram is frozen. We need to
2872       --  do this before analyzing the protected subprogram's body so that any
2873       --  references to the original subprogram's extra formals will be changed
2874       --  refer to the implementing subprogram's formals (see Expand_Formal).
2875
2876       if Present (Spec_Id)
2877         and then Is_Protected_Type (Scope (Spec_Id))
2878         and then Present (Protected_Body_Subprogram (Spec_Id))
2879       then
2880          declare
2881             Impl_Subp       : constant Entity_Id :=
2882                                 Protected_Body_Subprogram (Spec_Id);
2883             Prot_Ext_Formal : Entity_Id := Extra_Formals (Spec_Id);
2884             Impl_Ext_Formal : Entity_Id := Extra_Formals (Impl_Subp);
2885          begin
2886             while Present (Prot_Ext_Formal) loop
2887                pragma Assert (Present (Impl_Ext_Formal));
2888                Set_Protected_Formal (Prot_Ext_Formal, Impl_Ext_Formal);
2889                Next_Formal_With_Extras (Prot_Ext_Formal);
2890                Next_Formal_With_Extras (Impl_Ext_Formal);
2891             end loop;
2892          end;
2893       end if;
2894
2895       --  Now we can go on to analyze the body
2896
2897       HSS := Handled_Statement_Sequence (N);
2898       Set_Actual_Subtypes (N, Current_Scope);
2899
2900       --  Deal with preconditions and postconditions. In formal verification
2901       --  mode, we keep pre- and postconditions attached to entities rather
2902       --  than inserted in the code, in order to facilitate a distinct
2903       --  treatment for them.
2904
2905       if not Alfa_Mode then
2906          Process_PPCs (N, Spec_Id, Body_Id);
2907       end if;
2908
2909       --  Add a declaration for the Protection object, renaming declarations
2910       --  for discriminals and privals and finally a declaration for the entry
2911       --  family index (if applicable). This form of early expansion is done
2912       --  when the Expander is active because Install_Private_Data_Declarations
2913       --  references entities which were created during regular expansion. The
2914       --  body may be the rewritting of an expression function, and we need to
2915       --  verify that the original node is in the source.
2916
2917       if Full_Expander_Active
2918         and then Comes_From_Source (Original_Node (N))
2919         and then Present (Prot_Typ)
2920         and then Present (Spec_Id)
2921         and then not Is_Eliminated (Spec_Id)
2922       then
2923          Install_Private_Data_Declarations
2924            (Sloc (N), Spec_Id, Prot_Typ, N, Declarations (N));
2925       end if;
2926
2927       --  Ada 2012 (AI05-0151): Incomplete types coming from a limited context
2928       --  may now appear in parameter and result profiles. Since the analysis
2929       --  of a subprogram body may use the parameter and result profile of the
2930       --  spec, swap any limited views with their non-limited counterpart.
2931
2932       if Ada_Version >= Ada_2012 then
2933          Exchange_Limited_Views (Spec_Id);
2934       end if;
2935
2936       --  Analyze the declarations (this call will analyze the precondition
2937       --  Check pragmas we prepended to the list, as well as the declaration
2938       --  of the _Postconditions procedure).
2939
2940       Analyze_Declarations (Declarations (N));
2941
2942       --  Check completion, and analyze the statements
2943
2944       Check_Completion;
2945       Inspect_Deferred_Constant_Completion (Declarations (N));
2946       Analyze (HSS);
2947
2948       --  Deal with end of scope processing for the body
2949
2950       Process_End_Label (HSS, 't', Current_Scope);
2951       End_Scope;
2952       Check_Subprogram_Order (N);
2953       Set_Analyzed (Body_Id);
2954
2955       --  If we have a separate spec, then the analysis of the declarations
2956       --  caused the entities in the body to be chained to the spec id, but
2957       --  we want them chained to the body id. Only the formal parameters
2958       --  end up chained to the spec id in this case.
2959
2960       if Present (Spec_Id) then
2961
2962          --  We must conform to the categorization of our spec
2963
2964          Validate_Categorization_Dependency (N, Spec_Id);
2965
2966          --  And if this is a child unit, the parent units must conform
2967
2968          if Is_Child_Unit (Spec_Id) then
2969             Validate_Categorization_Dependency
2970               (Unit_Declaration_Node (Spec_Id), Spec_Id);
2971          end if;
2972
2973          --  Here is where we move entities from the spec to the body
2974
2975          --  Case where there are entities that stay with the spec
2976
2977          if Present (Last_Real_Spec_Entity) then
2978
2979             --  No body entities (happens when the only real spec entities come
2980             --  from precondition and postcondition pragmas).
2981
2982             if No (Last_Entity (Body_Id)) then
2983                Set_First_Entity
2984                  (Body_Id, Next_Entity (Last_Real_Spec_Entity));
2985
2986             --  Body entities present (formals), so chain stuff past them
2987
2988             else
2989                Set_Next_Entity
2990                  (Last_Entity (Body_Id), Next_Entity (Last_Real_Spec_Entity));
2991             end if;
2992
2993             Set_Next_Entity (Last_Real_Spec_Entity, Empty);
2994             Set_Last_Entity (Body_Id, Last_Entity (Spec_Id));
2995             Set_Last_Entity (Spec_Id, Last_Real_Spec_Entity);
2996
2997          --  Case where there are no spec entities, in this case there can be
2998          --  no body entities either, so just move everything.
2999
3000          else
3001             pragma Assert (No (Last_Entity (Body_Id)));
3002             Set_First_Entity (Body_Id, First_Entity (Spec_Id));
3003             Set_Last_Entity  (Body_Id, Last_Entity (Spec_Id));
3004             Set_First_Entity (Spec_Id, Empty);
3005             Set_Last_Entity  (Spec_Id, Empty);
3006          end if;
3007       end if;
3008
3009       Check_Missing_Return;
3010
3011       --  Now we are going to check for variables that are never modified in
3012       --  the body of the procedure. But first we deal with a special case
3013       --  where we want to modify this check. If the body of the subprogram
3014       --  starts with a raise statement or its equivalent, or if the body
3015       --  consists entirely of a null statement, then it is pretty obvious
3016       --  that it is OK to not reference the parameters. For example, this
3017       --  might be the following common idiom for a stubbed function:
3018       --  statement of the procedure raises an exception. In particular this
3019       --  deals with the common idiom of a stubbed function, which might
3020       --  appear as something like:
3021
3022       --     function F (A : Integer) return Some_Type;
3023       --        X : Some_Type;
3024       --     begin
3025       --        raise Program_Error;
3026       --        return X;
3027       --     end F;
3028
3029       --  Here the purpose of X is simply to satisfy the annoying requirement
3030       --  in Ada that there be at least one return, and we certainly do not
3031       --  want to go posting warnings on X that it is not initialized! On
3032       --  the other hand, if X is entirely unreferenced that should still
3033       --  get a warning.
3034
3035       --  What we do is to detect these cases, and if we find them, flag the
3036       --  subprogram as being Is_Trivial_Subprogram and then use that flag to
3037       --  suppress unwanted warnings. For the case of the function stub above
3038       --  we have a special test to set X as apparently assigned to suppress
3039       --  the warning.
3040
3041       declare
3042          Stm : Node_Id;
3043
3044       begin
3045          --  Skip initial labels (for one thing this occurs when we are in
3046          --  front end ZCX mode, but in any case it is irrelevant), and also
3047          --  initial Push_xxx_Error_Label nodes, which are also irrelevant.
3048
3049          Stm := First (Statements (HSS));
3050          while Nkind (Stm) = N_Label
3051            or else Nkind (Stm) in N_Push_xxx_Label
3052          loop
3053             Next (Stm);
3054          end loop;
3055
3056          --  Do the test on the original statement before expansion
3057
3058          declare
3059             Ostm : constant Node_Id := Original_Node (Stm);
3060
3061          begin
3062             --  If explicit raise statement, turn on flag
3063
3064             if Nkind (Ostm) = N_Raise_Statement then
3065                Set_Trivial_Subprogram (Stm);
3066
3067             --  If null statement, and no following statements, turn on flag
3068
3069             elsif Nkind (Stm) = N_Null_Statement
3070               and then Comes_From_Source (Stm)
3071               and then No (Next (Stm))
3072             then
3073                Set_Trivial_Subprogram (Stm);
3074
3075             --  Check for explicit call cases which likely raise an exception
3076
3077             elsif Nkind (Ostm) = N_Procedure_Call_Statement then
3078                if Is_Entity_Name (Name (Ostm)) then
3079                   declare
3080                      Ent : constant Entity_Id := Entity (Name (Ostm));
3081
3082                   begin
3083                      --  If the procedure is marked No_Return, then likely it
3084                      --  raises an exception, but in any case it is not coming
3085                      --  back here, so turn on the flag.
3086
3087                      if Present (Ent)
3088                        and then Ekind (Ent) = E_Procedure
3089                        and then No_Return (Ent)
3090                      then
3091                         Set_Trivial_Subprogram (Stm);
3092                      end if;
3093                   end;
3094                end if;
3095             end if;
3096          end;
3097       end;
3098
3099       --  Check for variables that are never modified
3100
3101       declare
3102          E1, E2 : Entity_Id;
3103
3104       begin
3105          --  If there is a separate spec, then transfer Never_Set_In_Source
3106          --  flags from out parameters to the corresponding entities in the
3107          --  body. The reason we do that is we want to post error flags on
3108          --  the body entities, not the spec entities.
3109
3110          if Present (Spec_Id) then
3111             E1 := First_Entity (Spec_Id);
3112             while Present (E1) loop
3113                if Ekind (E1) = E_Out_Parameter then
3114                   E2 := First_Entity (Body_Id);
3115                   while Present (E2) loop
3116                      exit when Chars (E1) = Chars (E2);
3117                      Next_Entity (E2);
3118                   end loop;
3119
3120                   if Present (E2) then
3121                      Set_Never_Set_In_Source (E2, Never_Set_In_Source (E1));
3122                   end if;
3123                end if;
3124
3125                Next_Entity (E1);
3126             end loop;
3127          end if;
3128
3129          --  Check references in body unless it was deleted. Note that the
3130          --  check of Body_Deleted here is not just for efficiency, it is
3131          --  necessary to avoid junk warnings on formal parameters.
3132
3133          if not Body_Deleted then
3134             Check_References (Body_Id);
3135          end if;
3136       end;
3137    end Analyze_Subprogram_Body_Helper;
3138
3139    ------------------------------------
3140    -- Analyze_Subprogram_Declaration --
3141    ------------------------------------
3142
3143    procedure Analyze_Subprogram_Declaration (N : Node_Id) is
3144       Loc        : constant Source_Ptr := Sloc (N);
3145       Scop       : constant Entity_Id  := Current_Scope;
3146       Designator : Entity_Id;
3147       Form       : Node_Id;
3148       Null_Body  : Node_Id := Empty;
3149
3150    --  Start of processing for Analyze_Subprogram_Declaration
3151
3152    begin
3153       --  Null procedures are not allowed in SPARK
3154
3155       if Nkind (Specification (N)) = N_Procedure_Specification
3156         and then Null_Present (Specification (N))
3157       then
3158          Check_SPARK_Restriction ("null procedure is not allowed", N);
3159       end if;
3160
3161       --  For a null procedure, capture the profile before analysis, for
3162       --  expansion at the freeze point and at each point of call. The body
3163       --  will only be used if the procedure has preconditions. In that case
3164       --  the body is analyzed at the freeze point.
3165
3166       if Nkind (Specification (N)) = N_Procedure_Specification
3167         and then Null_Present (Specification (N))
3168         and then Expander_Active
3169       then
3170          Null_Body :=
3171            Make_Subprogram_Body (Loc,
3172              Specification =>
3173                New_Copy_Tree (Specification (N)),
3174              Declarations =>
3175                New_List,
3176              Handled_Statement_Sequence =>
3177                Make_Handled_Sequence_Of_Statements (Loc,
3178                  Statements => New_List (Make_Null_Statement (Loc))));
3179
3180          --  Create new entities for body and formals
3181
3182          Set_Defining_Unit_Name (Specification (Null_Body),
3183            Make_Defining_Identifier (Loc, Chars (Defining_Entity (N))));
3184
3185          Form := First (Parameter_Specifications (Specification (Null_Body)));
3186          while Present (Form) loop
3187             Set_Defining_Identifier (Form,
3188               Make_Defining_Identifier (Loc,
3189                 Chars (Defining_Identifier (Form))));
3190
3191             --  Resolve the types of the formals now, because the freeze point
3192             --  may appear in a different context, e.g. an instantiation.
3193
3194             if Nkind (Parameter_Type (Form)) /= N_Access_Definition then
3195                Find_Type (Parameter_Type (Form));
3196
3197             elsif
3198               No (Access_To_Subprogram_Definition (Parameter_Type (Form)))
3199             then
3200                Find_Type (Subtype_Mark (Parameter_Type (Form)));
3201
3202             else
3203
3204                --  the case of a null procedure with a formal that is an
3205                --  access_to_subprogram type, and that is used as an actual
3206                --  in an instantiation is left to the enthusiastic reader.
3207
3208                null;
3209             end if;
3210
3211             Next (Form);
3212          end loop;
3213
3214          if Is_Protected_Type (Current_Scope) then
3215             Error_Msg_N ("protected operation cannot be a null procedure", N);
3216          end if;
3217       end if;
3218
3219       Designator := Analyze_Subprogram_Specification (Specification (N));
3220
3221       --  A reference may already have been generated for the unit name, in
3222       --  which case the following call is redundant. However it is needed for
3223       --  declarations that are the rewriting of an expression function.
3224
3225       Generate_Definition (Designator);
3226
3227       if Debug_Flag_C then
3228          Write_Str ("==> subprogram spec ");
3229          Write_Name (Chars (Designator));
3230          Write_Str (" from ");
3231          Write_Location (Sloc (N));
3232          Write_Eol;
3233          Indent;
3234       end if;
3235
3236       if Nkind (Specification (N)) = N_Procedure_Specification
3237         and then Null_Present (Specification (N))
3238       then
3239          Set_Has_Completion (Designator);
3240
3241          --  Null procedures are always inlined, but generic formal subprograms
3242          --  which appear as such in the internal instance of formal packages,
3243          --  need no completion and are not marked Inline.
3244
3245          if Present (Null_Body)
3246            and then Nkind (N) /= N_Formal_Concrete_Subprogram_Declaration
3247          then
3248             Set_Corresponding_Body (N, Defining_Entity (Null_Body));
3249             Set_Body_To_Inline (N, Null_Body);
3250             Set_Is_Inlined (Designator);
3251          end if;
3252       end if;
3253
3254       Validate_RCI_Subprogram_Declaration (N);
3255       New_Overloaded_Entity (Designator);
3256       Check_Delayed_Subprogram (Designator);
3257
3258       --  If the type of the first formal of the current subprogram is a
3259       --  nongeneric tagged private type, mark the subprogram as being a
3260       --  private primitive. Ditto if this is a function with controlling
3261       --  result, and the return type is currently private. In both cases,
3262       --  the type of the controlling argument or result must be in the
3263       --  current scope for the operation to be primitive.
3264
3265       if Has_Controlling_Result (Designator)
3266         and then Is_Private_Type (Etype (Designator))
3267         and then Scope (Etype (Designator)) = Current_Scope
3268         and then not Is_Generic_Actual_Type (Etype (Designator))
3269       then
3270          Set_Is_Private_Primitive (Designator);
3271
3272       elsif Present (First_Formal (Designator)) then
3273          declare
3274             Formal_Typ : constant Entity_Id :=
3275                            Etype (First_Formal (Designator));
3276          begin
3277             Set_Is_Private_Primitive (Designator,
3278               Is_Tagged_Type (Formal_Typ)
3279                 and then Scope (Formal_Typ) = Current_Scope
3280                 and then Is_Private_Type (Formal_Typ)
3281                 and then not Is_Generic_Actual_Type (Formal_Typ));
3282          end;
3283       end if;
3284
3285       --  Ada 2005 (AI-251): Abstract interface primitives must be abstract
3286       --  or null.
3287
3288       if Ada_Version >= Ada_2005
3289         and then Comes_From_Source (N)
3290         and then Is_Dispatching_Operation (Designator)
3291       then
3292          declare
3293             E    : Entity_Id;
3294             Etyp : Entity_Id;
3295
3296          begin
3297             if Has_Controlling_Result (Designator) then
3298                Etyp := Etype (Designator);
3299
3300             else
3301                E := First_Entity (Designator);
3302                while Present (E)
3303                  and then Is_Formal (E)
3304                  and then not Is_Controlling_Formal (E)
3305                loop
3306                   Next_Entity (E);
3307                end loop;
3308
3309                Etyp := Etype (E);
3310             end if;
3311
3312             if Is_Access_Type (Etyp) then
3313                Etyp := Directly_Designated_Type (Etyp);
3314             end if;
3315
3316             if Is_Interface (Etyp)
3317               and then not Is_Abstract_Subprogram (Designator)
3318               and then not (Ekind (Designator) = E_Procedure
3319                               and then Null_Present (Specification (N)))
3320             then
3321                Error_Msg_Name_1 := Chars (Defining_Entity (N));
3322
3323                --  Specialize error message based on procedures vs. functions,
3324                --  since functions can't be null subprograms.
3325
3326                if Ekind (Designator) = E_Procedure then
3327                   Error_Msg_N
3328                     ("interface procedure % must be abstract or null", N);
3329                else
3330                   Error_Msg_N ("interface function % must be abstract", N);
3331                end if;
3332             end if;
3333          end;
3334       end if;
3335
3336       --  What is the following code for, it used to be
3337
3338       --  ???   Set_Suppress_Elaboration_Checks
3339       --  ???     (Designator, Elaboration_Checks_Suppressed (Designator));
3340
3341       --  The following seems equivalent, but a bit dubious
3342
3343       if Elaboration_Checks_Suppressed (Designator) then
3344          Set_Kill_Elaboration_Checks (Designator);
3345       end if;
3346
3347       if Scop /= Standard_Standard
3348         and then not Is_Child_Unit (Designator)
3349       then
3350          Set_Categorization_From_Scope (Designator, Scop);
3351       else
3352          --  For a compilation unit, check for library-unit pragmas
3353
3354          Push_Scope (Designator);
3355          Set_Categorization_From_Pragmas (N);
3356          Validate_Categorization_Dependency (N, Designator);
3357          Pop_Scope;
3358       end if;
3359
3360       --  For a compilation unit, set body required. This flag will only be
3361       --  reset if a valid Import or Interface pragma is processed later on.
3362
3363       if Nkind (Parent (N)) = N_Compilation_Unit then
3364          Set_Body_Required (Parent (N), True);
3365
3366          if Ada_Version >= Ada_2005
3367            and then Nkind (Specification (N)) = N_Procedure_Specification
3368            and then Null_Present (Specification (N))
3369          then
3370             Error_Msg_N
3371               ("null procedure cannot be declared at library level", N);
3372          end if;
3373       end if;
3374
3375       Generate_Reference_To_Formals (Designator);
3376       Check_Eliminated (Designator);
3377
3378       if Debug_Flag_C then
3379          Outdent;
3380          Write_Str ("<== subprogram spec ");
3381          Write_Name (Chars (Designator));
3382          Write_Str (" from ");
3383          Write_Location (Sloc (N));
3384          Write_Eol;
3385       end if;
3386
3387       if Is_Protected_Type (Current_Scope) then
3388
3389          --  Indicate that this is a protected operation, because it may be
3390          --  used in subsequent declarations within the protected type.
3391
3392          Set_Convention (Designator, Convention_Protected);
3393       end if;
3394
3395       List_Inherited_Pre_Post_Aspects (Designator);
3396
3397       if Has_Aspects (N) then
3398          Analyze_Aspect_Specifications (N, Designator);
3399       end if;
3400    end Analyze_Subprogram_Declaration;
3401
3402    --------------------------------------
3403    -- Analyze_Subprogram_Specification --
3404    --------------------------------------
3405
3406    --  Reminder: N here really is a subprogram specification (not a subprogram
3407    --  declaration). This procedure is called to analyze the specification in
3408    --  both subprogram bodies and subprogram declarations (specs).
3409
3410    function Analyze_Subprogram_Specification (N : Node_Id) return Entity_Id is
3411       Designator : constant Entity_Id := Defining_Entity (N);
3412       Formals    : constant List_Id   := Parameter_Specifications (N);
3413
3414    --  Start of processing for Analyze_Subprogram_Specification
3415
3416    begin
3417       --  User-defined operator is not allowed in SPARK, except as a renaming
3418
3419       if Nkind (Defining_Unit_Name (N)) = N_Defining_Operator_Symbol
3420         and then Nkind (Parent (N)) /= N_Subprogram_Renaming_Declaration
3421       then
3422          Check_SPARK_Restriction ("user-defined operator is not allowed", N);
3423       end if;
3424
3425       --  Proceed with analysis. Do not emit a cross-reference entry if the
3426       --  specification comes from an expression function, because it may be
3427       --  the completion of a previous declaration. It is is not, the cross-
3428       --  reference entry will be emitted for the new subprogram declaration.
3429
3430       if Nkind (Parent (N)) /= N_Expression_Function then
3431          Generate_Definition (Designator);
3432       end if;
3433
3434       Set_Contract (Designator, Make_Contract (Sloc (Designator)));
3435
3436       if Nkind (N) = N_Function_Specification then
3437          Set_Ekind (Designator, E_Function);
3438          Set_Mechanism (Designator, Default_Mechanism);
3439       else
3440          Set_Ekind (Designator, E_Procedure);
3441          Set_Etype (Designator, Standard_Void_Type);
3442       end if;
3443
3444       --  Introduce new scope for analysis of the formals and the return type
3445
3446       Set_Scope (Designator, Current_Scope);
3447
3448       if Present (Formals) then
3449          Push_Scope (Designator);
3450          Process_Formals (Formals, N);
3451
3452          --  Ada 2005 (AI-345): If this is an overriding operation of an
3453          --  inherited interface operation, and the controlling type is
3454          --  a synchronized type, replace the type with its corresponding
3455          --  record, to match the proper signature of an overriding operation.
3456          --  Same processing for an access parameter whose designated type is
3457          --  derived from a synchronized interface.
3458
3459          if Ada_Version >= Ada_2005 then
3460             declare
3461                Formal     : Entity_Id;
3462                Formal_Typ : Entity_Id;
3463                Rec_Typ    : Entity_Id;
3464                Desig_Typ  : Entity_Id;
3465
3466             begin
3467                Formal := First_Formal (Designator);
3468                while Present (Formal) loop
3469                   Formal_Typ := Etype (Formal);
3470
3471                   if Is_Concurrent_Type (Formal_Typ)
3472                     and then Present (Corresponding_Record_Type (Formal_Typ))
3473                   then
3474                      Rec_Typ := Corresponding_Record_Type (Formal_Typ);
3475
3476                      if Present (Interfaces (Rec_Typ)) then
3477                         Set_Etype (Formal, Rec_Typ);
3478                      end if;
3479
3480                   elsif Ekind (Formal_Typ) = E_Anonymous_Access_Type then
3481                      Desig_Typ := Designated_Type (Formal_Typ);
3482
3483                      if Is_Concurrent_Type (Desig_Typ)
3484                        and then Present (Corresponding_Record_Type (Desig_Typ))
3485                      then
3486                         Rec_Typ := Corresponding_Record_Type (Desig_Typ);
3487
3488                         if Present (Interfaces (Rec_Typ)) then
3489                            Set_Directly_Designated_Type (Formal_Typ, Rec_Typ);
3490                         end if;
3491                      end if;
3492                   end if;
3493
3494                   Next_Formal (Formal);
3495                end loop;
3496             end;
3497          end if;
3498
3499          End_Scope;
3500
3501       --  The subprogram scope is pushed and popped around the processing of
3502       --  the return type for consistency with call above to Process_Formals
3503       --  (which itself can call Analyze_Return_Type), and to ensure that any
3504       --  itype created for the return type will be associated with the proper
3505       --  scope.
3506
3507       elsif Nkind (N) = N_Function_Specification then
3508          Push_Scope (Designator);
3509          Analyze_Return_Type (N);
3510          End_Scope;
3511       end if;
3512
3513       --  Function case
3514
3515       if Nkind (N) = N_Function_Specification then
3516
3517          --  Deal with operator symbol case
3518
3519          if Nkind (Designator) = N_Defining_Operator_Symbol then
3520             Valid_Operator_Definition (Designator);
3521          end if;
3522
3523          May_Need_Actuals (Designator);
3524
3525          --  Ada 2005 (AI-251): If the return type is abstract, verify that
3526          --  the subprogram is abstract also. This does not apply to renaming
3527          --  declarations, where abstractness is inherited, and to subprogram
3528          --  bodies generated for stream operations, which become renamings as
3529          --  bodies.
3530
3531          --  In case of primitives associated with abstract interface types
3532          --  the check is applied later (see Analyze_Subprogram_Declaration).
3533
3534          if not Nkind_In (Original_Node (Parent (N)),
3535                             N_Subprogram_Renaming_Declaration,
3536                             N_Abstract_Subprogram_Declaration,
3537                             N_Formal_Abstract_Subprogram_Declaration)
3538          then
3539             if Is_Abstract_Type (Etype (Designator))
3540               and then not Is_Interface (Etype (Designator))
3541             then
3542                Error_Msg_N
3543                  ("function that returns abstract type must be abstract", N);
3544
3545             --  Ada 2012 (AI-0073): Extend this test to subprograms with an
3546             --  access result whose designated type is abstract.
3547
3548             elsif Nkind (Result_Definition (N)) = N_Access_Definition
3549               and then
3550                 not Is_Class_Wide_Type (Designated_Type (Etype (Designator)))
3551               and then Is_Abstract_Type (Designated_Type (Etype (Designator)))
3552               and then Ada_Version >= Ada_2012
3553             then
3554                Error_Msg_N ("function whose access result designates "
3555                  & "abstract type must be abstract", N);
3556             end if;
3557          end if;
3558       end if;
3559
3560       return Designator;
3561    end Analyze_Subprogram_Specification;
3562
3563    --------------------------
3564    -- Build_Body_To_Inline --
3565    --------------------------
3566
3567    procedure Build_Body_To_Inline (N : Node_Id; Subp : Entity_Id) is
3568       Decl            : constant Node_Id := Unit_Declaration_Node (Subp);
3569       Original_Body   : Node_Id;
3570       Body_To_Analyze : Node_Id;
3571       Max_Size        : constant := 10;
3572       Stat_Count      : Integer := 0;
3573
3574       function Has_Excluded_Declaration (Decls : List_Id) return Boolean;
3575       --  Check for declarations that make inlining not worthwhile
3576
3577       function Has_Excluded_Statement   (Stats : List_Id) return Boolean;
3578       --  Check for statements that make inlining not worthwhile: any tasking
3579       --  statement, nested at any level. Keep track of total number of
3580       --  elementary statements, as a measure of acceptable size.
3581
3582       function Has_Pending_Instantiation return Boolean;
3583       --  If some enclosing body contains instantiations that appear before the
3584       --  corresponding generic body, the enclosing body has a freeze node so
3585       --  that it can be elaborated after the generic itself. This might
3586       --  conflict with subsequent inlinings, so that it is unsafe to try to
3587       --  inline in such a case.
3588
3589       function Has_Single_Return return Boolean;
3590       --  In general we cannot inline functions that return unconstrained type.
3591       --  However, we can handle such functions if all return statements return
3592       --  a local variable that is the only declaration in the body of the
3593       --  function. In that case the call can be replaced by that local
3594       --  variable as is done for other inlined calls.
3595
3596       procedure Remove_Pragmas;
3597       --  A pragma Unreferenced or pragma Unmodified that mentions a formal
3598       --  parameter has no meaning when the body is inlined and the formals
3599       --  are rewritten. Remove it from body to inline. The analysis of the
3600       --  non-inlined body will handle the pragma properly.
3601
3602       function Uses_Secondary_Stack (Bod : Node_Id) return Boolean;
3603       --  If the body of the subprogram includes a call that returns an
3604       --  unconstrained type, the secondary stack is involved, and it
3605       --  is not worth inlining.
3606
3607       ------------------------------
3608       -- Has_Excluded_Declaration --
3609       ------------------------------
3610
3611       function Has_Excluded_Declaration (Decls : List_Id) return Boolean is
3612          D : Node_Id;
3613
3614          function Is_Unchecked_Conversion (D : Node_Id) return Boolean;
3615          --  Nested subprograms make a given body ineligible for inlining, but
3616          --  we make an exception for instantiations of unchecked conversion.
3617          --  The body has not been analyzed yet, so check the name, and verify
3618          --  that the visible entity with that name is the predefined unit.
3619
3620          -----------------------------
3621          -- Is_Unchecked_Conversion --
3622          -----------------------------
3623
3624          function Is_Unchecked_Conversion (D : Node_Id) return Boolean is
3625             Id   : constant Node_Id := Name (D);
3626             Conv : Entity_Id;
3627
3628          begin
3629             if Nkind (Id) = N_Identifier
3630               and then Chars (Id) = Name_Unchecked_Conversion
3631             then
3632                Conv := Current_Entity (Id);
3633
3634             elsif Nkind_In (Id, N_Selected_Component, N_Expanded_Name)
3635               and then Chars (Selector_Name (Id)) = Name_Unchecked_Conversion
3636             then
3637                Conv := Current_Entity (Selector_Name (Id));
3638             else
3639                return False;
3640             end if;
3641
3642             return Present (Conv)
3643               and then Is_Predefined_File_Name
3644                          (Unit_File_Name (Get_Source_Unit (Conv)))
3645               and then Is_Intrinsic_Subprogram (Conv);
3646          end Is_Unchecked_Conversion;
3647
3648       --  Start of processing for Has_Excluded_Declaration
3649
3650       begin
3651          D := First (Decls);
3652          while Present (D) loop
3653             if (Nkind (D) = N_Function_Instantiation
3654                   and then not Is_Unchecked_Conversion (D))
3655               or else Nkind_In (D, N_Protected_Type_Declaration,
3656                                    N_Package_Declaration,
3657                                    N_Package_Instantiation,
3658                                    N_Subprogram_Body,
3659                                    N_Procedure_Instantiation,
3660                                    N_Task_Type_Declaration)
3661             then
3662                Cannot_Inline
3663                  ("cannot inline & (non-allowed declaration)?", D, Subp);
3664                return True;
3665             end if;
3666
3667             Next (D);
3668          end loop;
3669
3670          return False;
3671       end Has_Excluded_Declaration;
3672
3673       ----------------------------
3674       -- Has_Excluded_Statement --
3675       ----------------------------
3676
3677       function Has_Excluded_Statement (Stats : List_Id) return Boolean is
3678          S : Node_Id;
3679          E : Node_Id;
3680
3681       begin
3682          S := First (Stats);
3683          while Present (S) loop
3684             Stat_Count := Stat_Count + 1;
3685
3686             if Nkind_In (S, N_Abort_Statement,
3687                             N_Asynchronous_Select,
3688                             N_Conditional_Entry_Call,
3689                             N_Delay_Relative_Statement,
3690                             N_Delay_Until_Statement,
3691                             N_Selective_Accept,
3692                             N_Timed_Entry_Call)
3693             then
3694                Cannot_Inline
3695                  ("cannot inline & (non-allowed statement)?", S, Subp);
3696                return True;
3697
3698             elsif Nkind (S) = N_Block_Statement then
3699                if Present (Declarations (S))
3700                  and then Has_Excluded_Declaration (Declarations (S))
3701                then
3702                   return True;
3703
3704                elsif Present (Handled_Statement_Sequence (S))
3705                   and then
3706                     (Present
3707                       (Exception_Handlers (Handled_Statement_Sequence (S)))
3708                      or else
3709                        Has_Excluded_Statement
3710                          (Statements (Handled_Statement_Sequence (S))))
3711                then
3712                   return True;
3713                end if;
3714
3715             elsif Nkind (S) = N_Case_Statement then
3716                E := First (Alternatives (S));
3717                while Present (E) loop
3718                   if Has_Excluded_Statement (Statements (E)) then
3719                      return True;
3720                   end if;
3721
3722                   Next (E);
3723                end loop;
3724
3725             elsif Nkind (S) = N_If_Statement then
3726                if Has_Excluded_Statement (Then_Statements (S)) then
3727                   return True;
3728                end if;
3729
3730                if Present (Elsif_Parts (S)) then
3731                   E := First (Elsif_Parts (S));
3732                   while Present (E) loop
3733                      if Has_Excluded_Statement (Then_Statements (E)) then
3734                         return True;
3735                      end if;
3736                      Next (E);
3737                   end loop;
3738                end if;
3739
3740                if Present (Else_Statements (S))
3741                  and then Has_Excluded_Statement (Else_Statements (S))
3742                then
3743                   return True;
3744                end if;
3745
3746             elsif Nkind (S) = N_Loop_Statement
3747               and then Has_Excluded_Statement (Statements (S))
3748             then
3749                return True;
3750
3751             elsif Nkind (S) = N_Extended_Return_Statement then
3752                if Has_Excluded_Statement
3753                   (Statements (Handled_Statement_Sequence (S)))
3754                  or else Present
3755                    (Exception_Handlers (Handled_Statement_Sequence (S)))
3756                then
3757                   return True;
3758                end if;
3759             end if;
3760
3761             Next (S);
3762          end loop;
3763
3764          return False;
3765       end Has_Excluded_Statement;
3766
3767       -------------------------------
3768       -- Has_Pending_Instantiation --
3769       -------------------------------
3770
3771       function Has_Pending_Instantiation return Boolean is
3772          S : Entity_Id;
3773
3774       begin
3775          S := Current_Scope;
3776          while Present (S) loop
3777             if Is_Compilation_Unit (S)
3778               or else Is_Child_Unit (S)
3779             then
3780                return False;
3781
3782             elsif Ekind (S) = E_Package
3783               and then Has_Forward_Instantiation (S)
3784             then
3785                return True;
3786             end if;
3787
3788             S := Scope (S);
3789          end loop;
3790
3791          return False;
3792       end Has_Pending_Instantiation;
3793
3794       ------------------------
3795       --  Has_Single_Return --
3796       ------------------------
3797
3798       function Has_Single_Return return Boolean is
3799          Return_Statement : Node_Id := Empty;
3800
3801          function Check_Return (N : Node_Id) return Traverse_Result;
3802
3803          ------------------
3804          -- Check_Return --
3805          ------------------
3806
3807          function Check_Return (N : Node_Id) return Traverse_Result is
3808          begin
3809             if Nkind (N) = N_Simple_Return_Statement then
3810                if Present (Expression (N))
3811                  and then Is_Entity_Name (Expression (N))
3812                then
3813                   if No (Return_Statement) then
3814                      Return_Statement := N;
3815                      return OK;
3816
3817                   elsif Chars (Expression (N)) =
3818                         Chars (Expression (Return_Statement))
3819                   then
3820                      return OK;
3821
3822                   else
3823                      return Abandon;
3824                   end if;
3825
3826                --  A return statement within an extended return is a noop
3827                --  after inlining.
3828
3829                elsif No (Expression (N))
3830                  and then Nkind (Parent (Parent (N))) =
3831                  N_Extended_Return_Statement
3832                then
3833                   return OK;
3834
3835                else
3836                   --  Expression has wrong form
3837
3838                   return Abandon;
3839                end if;
3840
3841             --  We can only inline a build-in-place function if
3842             --  it has a single extended return.
3843
3844             elsif Nkind (N) = N_Extended_Return_Statement then
3845                if No (Return_Statement) then
3846                   Return_Statement := N;
3847                   return OK;
3848
3849                else
3850                   return Abandon;
3851                end if;
3852
3853             else
3854                return OK;
3855             end if;
3856          end Check_Return;
3857
3858          function Check_All_Returns is new Traverse_Func (Check_Return);
3859
3860       --  Start of processing for Has_Single_Return
3861
3862       begin
3863          if Check_All_Returns (N) /= OK then
3864             return False;
3865
3866          elsif Nkind (Return_Statement) = N_Extended_Return_Statement then
3867             return True;
3868
3869          else
3870             return Present (Declarations (N))
3871               and then Present (First (Declarations (N)))
3872               and then Chars (Expression (Return_Statement)) =
3873                  Chars (Defining_Identifier (First (Declarations (N))));
3874          end if;
3875       end Has_Single_Return;
3876
3877       --------------------
3878       -- Remove_Pragmas --
3879       --------------------
3880
3881       procedure Remove_Pragmas is
3882          Decl : Node_Id;
3883          Nxt  : Node_Id;
3884
3885       begin
3886          Decl := First (Declarations (Body_To_Analyze));
3887          while Present (Decl) loop
3888             Nxt := Next (Decl);
3889
3890             if Nkind (Decl) = N_Pragma
3891               and then (Pragma_Name (Decl) = Name_Unreferenced
3892                           or else
3893                         Pragma_Name (Decl) = Name_Unmodified)
3894             then
3895                Remove (Decl);
3896             end if;
3897
3898             Decl := Nxt;
3899          end loop;
3900       end Remove_Pragmas;
3901
3902       --------------------------
3903       -- Uses_Secondary_Stack --
3904       --------------------------
3905
3906       function Uses_Secondary_Stack (Bod : Node_Id) return Boolean is
3907          function Check_Call (N : Node_Id) return Traverse_Result;
3908          --  Look for function calls that return an unconstrained type
3909
3910          ----------------
3911          -- Check_Call --
3912          ----------------
3913
3914          function Check_Call (N : Node_Id) return Traverse_Result is
3915          begin
3916             if Nkind (N) = N_Function_Call
3917               and then Is_Entity_Name (Name (N))
3918               and then Is_Composite_Type (Etype (Entity (Name (N))))
3919               and then not Is_Constrained (Etype (Entity (Name (N))))
3920             then
3921                Cannot_Inline
3922                  ("cannot inline & (call returns unconstrained type)?",
3923                     N, Subp);
3924                return Abandon;
3925             else
3926                return OK;
3927             end if;
3928          end Check_Call;
3929
3930          function Check_Calls is new Traverse_Func (Check_Call);
3931
3932       begin
3933          return Check_Calls (Bod) = Abandon;
3934       end Uses_Secondary_Stack;
3935
3936    --  Start of processing for Build_Body_To_Inline
3937
3938    begin
3939       --  Return immediately if done already
3940
3941       if Nkind (Decl) = N_Subprogram_Declaration
3942         and then Present (Body_To_Inline (Decl))
3943       then
3944          return;
3945
3946       --  Functions that return unconstrained composite types require
3947       --  secondary stack handling, and cannot currently be inlined, unless
3948       --  all return statements return a local variable that is the first
3949       --  local declaration in the body.
3950
3951       elsif Ekind (Subp) = E_Function
3952         and then not Is_Scalar_Type (Etype (Subp))
3953         and then not Is_Access_Type (Etype (Subp))
3954         and then not Is_Constrained (Etype (Subp))
3955       then
3956          if not Has_Single_Return then
3957             Cannot_Inline
3958               ("cannot inline & (unconstrained return type)?", N, Subp);
3959             return;
3960          end if;
3961
3962       --  Ditto for functions that return controlled types, where controlled
3963       --  actions interfere in complex ways with inlining.
3964
3965       elsif Ekind (Subp) = E_Function
3966         and then Needs_Finalization (Etype (Subp))
3967       then
3968          Cannot_Inline
3969            ("cannot inline & (controlled return type)?", N, Subp);
3970          return;
3971       end if;
3972
3973       if Present (Declarations (N))
3974         and then Has_Excluded_Declaration (Declarations (N))
3975       then
3976          return;
3977       end if;
3978
3979       if Present (Handled_Statement_Sequence (N)) then
3980          if Present (Exception_Handlers (Handled_Statement_Sequence (N))) then
3981             Cannot_Inline
3982               ("cannot inline& (exception handler)?",
3983                First (Exception_Handlers (Handled_Statement_Sequence (N))),
3984                Subp);
3985             return;
3986          elsif
3987            Has_Excluded_Statement
3988              (Statements (Handled_Statement_Sequence (N)))
3989          then
3990             return;
3991          end if;
3992       end if;
3993
3994       --  We do not inline a subprogram  that is too large, unless it is
3995       --  marked Inline_Always. This pragma does not suppress the other
3996       --  checks on inlining (forbidden declarations, handlers, etc).
3997
3998       if Stat_Count > Max_Size
3999         and then not Has_Pragma_Inline_Always (Subp)
4000       then
4001          Cannot_Inline ("cannot inline& (body too large)?", N, Subp);
4002          return;
4003       end if;
4004
4005       if Has_Pending_Instantiation then
4006          Cannot_Inline
4007            ("cannot inline& (forward instance within enclosing body)?",
4008              N, Subp);
4009          return;
4010       end if;
4011
4012       --  Within an instance, the body to inline must be treated as a nested
4013       --  generic, so that the proper global references are preserved.
4014
4015       --  Note that we do not do this at the library level, because it is not
4016       --  needed, and furthermore this causes trouble if front end inlining
4017       --  is activated (-gnatN).
4018
4019       if In_Instance and then Scope (Current_Scope) /= Standard_Standard then
4020          Save_Env (Scope (Current_Scope), Scope (Current_Scope));
4021          Original_Body := Copy_Generic_Node (N, Empty, True);
4022       else
4023          Original_Body := Copy_Separate_Tree (N);
4024       end if;
4025
4026       --  We need to capture references to the formals in order to substitute
4027       --  the actuals at the point of inlining, i.e. instantiation. To treat
4028       --  the formals as globals to the body to inline, we nest it within
4029       --  a dummy parameterless subprogram, declared within the real one.
4030       --  To avoid generating an internal name (which is never public, and
4031       --  which affects serial numbers of other generated names), we use
4032       --  an internal symbol that cannot conflict with user declarations.
4033
4034       Set_Parameter_Specifications (Specification (Original_Body), No_List);
4035       Set_Defining_Unit_Name
4036         (Specification (Original_Body),
4037           Make_Defining_Identifier (Sloc (N), Name_uParent));
4038       Set_Corresponding_Spec (Original_Body, Empty);
4039
4040       Body_To_Analyze := Copy_Generic_Node (Original_Body, Empty, False);
4041
4042       --  Set return type of function, which is also global and does not need
4043       --  to be resolved.
4044
4045       if Ekind (Subp) = E_Function then
4046          Set_Result_Definition (Specification (Body_To_Analyze),
4047            New_Occurrence_Of (Etype (Subp), Sloc (N)));
4048       end if;
4049
4050       if No (Declarations (N)) then
4051          Set_Declarations (N, New_List (Body_To_Analyze));
4052       else
4053          Append (Body_To_Analyze, Declarations (N));
4054       end if;
4055
4056       Expander_Mode_Save_And_Set (False);
4057       Remove_Pragmas;
4058
4059       Analyze (Body_To_Analyze);
4060       Push_Scope (Defining_Entity (Body_To_Analyze));
4061       Save_Global_References (Original_Body);
4062       End_Scope;
4063       Remove (Body_To_Analyze);
4064
4065       Expander_Mode_Restore;
4066
4067       --  Restore environment if previously saved
4068
4069       if In_Instance and then Scope (Current_Scope) /= Standard_Standard then
4070          Restore_Env;
4071       end if;
4072
4073       --  If secondary stk used there is no point in inlining. We have
4074       --  already issued the warning in this case, so nothing to do.
4075
4076       if Uses_Secondary_Stack (Body_To_Analyze) then
4077          return;
4078       end if;
4079
4080       Set_Body_To_Inline (Decl, Original_Body);
4081       Set_Ekind (Defining_Entity (Original_Body), Ekind (Subp));
4082       Set_Is_Inlined (Subp);
4083    end Build_Body_To_Inline;
4084
4085    -------------------
4086    -- Cannot_Inline --
4087    -------------------
4088
4089    procedure Cannot_Inline (Msg : String; N : Node_Id; Subp : Entity_Id) is
4090    begin
4091       --  Do not emit warning if this is a predefined unit which is not the
4092       --  main unit. With validity checks enabled, some predefined subprograms
4093       --  may contain nested subprograms and become ineligible for inlining.
4094
4095       if Is_Predefined_File_Name (Unit_File_Name (Get_Source_Unit (Subp)))
4096         and then not In_Extended_Main_Source_Unit (Subp)
4097       then
4098          null;
4099
4100       elsif Has_Pragma_Inline_Always (Subp) then
4101
4102          --  Remove last character (question mark) to make this into an error,
4103          --  because the Inline_Always pragma cannot be obeyed.
4104
4105          Error_Msg_NE (Msg (Msg'First .. Msg'Last - 1), N, Subp);
4106
4107       elsif Ineffective_Inline_Warnings then
4108          Error_Msg_NE (Msg, N, Subp);
4109       end if;
4110    end Cannot_Inline;
4111
4112    -----------------------
4113    -- Check_Conformance --
4114    -----------------------
4115
4116    procedure Check_Conformance
4117      (New_Id                   : Entity_Id;
4118       Old_Id                   : Entity_Id;
4119       Ctype                    : Conformance_Type;
4120       Errmsg                   : Boolean;
4121       Conforms                 : out Boolean;
4122       Err_Loc                  : Node_Id := Empty;
4123       Get_Inst                 : Boolean := False;
4124       Skip_Controlling_Formals : Boolean := False)
4125    is
4126       procedure Conformance_Error (Msg : String; N : Node_Id := New_Id);
4127       --  Sets Conforms to False. If Errmsg is False, then that's all it does.
4128       --  If Errmsg is True, then processing continues to post an error message
4129       --  for conformance error on given node. Two messages are output. The
4130       --  first message points to the previous declaration with a general "no
4131       --  conformance" message. The second is the detailed reason, supplied as
4132       --  Msg. The parameter N provide information for a possible & insertion
4133       --  in the message, and also provides the location for posting the
4134       --  message in the absence of a specified Err_Loc location.
4135
4136       -----------------------
4137       -- Conformance_Error --
4138       -----------------------
4139
4140       procedure Conformance_Error (Msg : String; N : Node_Id := New_Id) is
4141          Enode : Node_Id;
4142
4143       begin
4144          Conforms := False;
4145
4146          if Errmsg then
4147             if No (Err_Loc) then
4148                Enode := N;
4149             else
4150                Enode := Err_Loc;
4151             end if;
4152
4153             Error_Msg_Sloc := Sloc (Old_Id);
4154
4155             case Ctype is
4156                when Type_Conformant =>
4157                   Error_Msg_N -- CODEFIX
4158                     ("not type conformant with declaration#!", Enode);
4159
4160                when Mode_Conformant =>
4161                   if Nkind (Parent (Old_Id)) = N_Full_Type_Declaration then
4162                      Error_Msg_N
4163                        ("not mode conformant with operation inherited#!",
4164                          Enode);
4165                   else
4166                      Error_Msg_N
4167                        ("not mode conformant with declaration#!", Enode);
4168                   end if;
4169
4170                when Subtype_Conformant =>
4171                   if Nkind (Parent (Old_Id)) = N_Full_Type_Declaration then
4172                      Error_Msg_N
4173                        ("not subtype conformant with operation inherited#!",
4174                          Enode);
4175                   else
4176                      Error_Msg_N
4177                        ("not subtype conformant with declaration#!", Enode);
4178                   end if;
4179
4180                when Fully_Conformant =>
4181                   if Nkind (Parent (Old_Id)) = N_Full_Type_Declaration then
4182                      Error_Msg_N -- CODEFIX
4183                        ("not fully conformant with operation inherited#!",
4184                          Enode);
4185                   else
4186                      Error_Msg_N -- CODEFIX
4187                        ("not fully conformant with declaration#!", Enode);
4188                   end if;
4189             end case;
4190
4191             Error_Msg_NE (Msg, Enode, N);
4192          end if;
4193       end Conformance_Error;
4194
4195       --  Local Variables
4196
4197       Old_Type           : constant Entity_Id := Etype (Old_Id);
4198       New_Type           : constant Entity_Id := Etype (New_Id);
4199       Old_Formal         : Entity_Id;
4200       New_Formal         : Entity_Id;
4201       Access_Types_Match : Boolean;
4202       Old_Formal_Base    : Entity_Id;
4203       New_Formal_Base    : Entity_Id;
4204
4205    --  Start of processing for Check_Conformance
4206
4207    begin
4208       Conforms := True;
4209
4210       --  We need a special case for operators, since they don't appear
4211       --  explicitly.
4212
4213       if Ctype = Type_Conformant then
4214          if Ekind (New_Id) = E_Operator
4215            and then Operator_Matches_Spec (New_Id, Old_Id)
4216          then
4217             return;
4218          end if;
4219       end if;
4220
4221       --  If both are functions/operators, check return types conform
4222
4223       if Old_Type /= Standard_Void_Type
4224         and then New_Type /= Standard_Void_Type
4225       then
4226
4227          --  If we are checking interface conformance we omit controlling
4228          --  arguments and result, because we are only checking the conformance
4229          --  of the remaining parameters.
4230
4231          if Has_Controlling_Result (Old_Id)
4232            and then Has_Controlling_Result (New_Id)
4233            and then Skip_Controlling_Formals
4234          then
4235             null;
4236
4237          elsif not Conforming_Types (Old_Type, New_Type, Ctype, Get_Inst) then
4238             Conformance_Error ("\return type does not match!", New_Id);
4239             return;
4240          end if;
4241
4242          --  Ada 2005 (AI-231): In case of anonymous access types check the
4243          --  null-exclusion and access-to-constant attributes match.
4244
4245          if Ada_Version >= Ada_2005
4246            and then Ekind (Etype (Old_Type)) = E_Anonymous_Access_Type
4247            and then
4248              (Can_Never_Be_Null (Old_Type)
4249                 /= Can_Never_Be_Null (New_Type)
4250               or else Is_Access_Constant (Etype (Old_Type))
4251                         /= Is_Access_Constant (Etype (New_Type)))
4252          then
4253             Conformance_Error ("\return type does not match!", New_Id);
4254             return;
4255          end if;
4256
4257       --  If either is a function/operator and the other isn't, error
4258
4259       elsif Old_Type /= Standard_Void_Type
4260         or else New_Type /= Standard_Void_Type
4261       then
4262          Conformance_Error ("\functions can only match functions!", New_Id);
4263          return;
4264       end if;
4265
4266       --  In subtype conformant case, conventions must match (RM 6.3.1(16)).
4267       --  If this is a renaming as body, refine error message to indicate that
4268       --  the conflict is with the original declaration. If the entity is not
4269       --  frozen, the conventions don't have to match, the one of the renamed
4270       --  entity is inherited.
4271
4272       if Ctype >= Subtype_Conformant then
4273          if Convention (Old_Id) /= Convention (New_Id) then
4274
4275             if not Is_Frozen (New_Id) then
4276                null;
4277
4278             elsif Present (Err_Loc)
4279               and then Nkind (Err_Loc) = N_Subprogram_Renaming_Declaration
4280               and then Present (Corresponding_Spec (Err_Loc))
4281             then
4282                Error_Msg_Name_1 := Chars (New_Id);
4283                Error_Msg_Name_2 :=
4284                  Name_Ada + Convention_Id'Pos (Convention (New_Id));
4285                Conformance_Error ("\prior declaration for% has convention %!");
4286
4287             else
4288                Conformance_Error ("\calling conventions do not match!");
4289             end if;
4290
4291             return;
4292
4293          elsif Is_Formal_Subprogram (Old_Id)
4294            or else Is_Formal_Subprogram (New_Id)
4295          then
4296             Conformance_Error ("\formal subprograms not allowed!");
4297             return;
4298          end if;
4299       end if;
4300
4301       --  Deal with parameters
4302
4303       --  Note: we use the entity information, rather than going directly
4304       --  to the specification in the tree. This is not only simpler, but
4305       --  absolutely necessary for some cases of conformance tests between
4306       --  operators, where the declaration tree simply does not exist!
4307
4308       Old_Formal := First_Formal (Old_Id);
4309       New_Formal := First_Formal (New_Id);
4310       while Present (Old_Formal) and then Present (New_Formal) loop
4311          if Is_Controlling_Formal (Old_Formal)
4312            and then Is_Controlling_Formal (New_Formal)
4313            and then Skip_Controlling_Formals
4314          then
4315             --  The controlling formals will have different types when
4316             --  comparing an interface operation with its match, but both
4317             --  or neither must be access parameters.
4318
4319             if Is_Access_Type (Etype (Old_Formal))
4320                  =
4321                Is_Access_Type (Etype (New_Formal))
4322             then
4323                goto Skip_Controlling_Formal;
4324             else
4325                Conformance_Error
4326                  ("\access parameter does not match!", New_Formal);
4327             end if;
4328          end if;
4329
4330          if Ctype = Fully_Conformant then
4331
4332             --  Names must match. Error message is more accurate if we do
4333             --  this before checking that the types of the formals match.
4334
4335             if Chars (Old_Formal) /= Chars (New_Formal) then
4336                Conformance_Error ("\name & does not match!", New_Formal);
4337
4338                --  Set error posted flag on new formal as well to stop
4339                --  junk cascaded messages in some cases.
4340
4341                Set_Error_Posted (New_Formal);
4342                return;
4343             end if;
4344
4345             --  Null exclusion must match
4346
4347             if Null_Exclusion_Present (Parent (Old_Formal))
4348                  /=
4349                Null_Exclusion_Present (Parent (New_Formal))
4350             then
4351                --  Only give error if both come from source. This should be
4352                --  investigated some time, since it should not be needed ???
4353
4354                if Comes_From_Source (Old_Formal)
4355                     and then
4356                   Comes_From_Source (New_Formal)
4357                then
4358                   Conformance_Error
4359                     ("\null exclusion for & does not match", New_Formal);
4360
4361                   --  Mark error posted on the new formal to avoid duplicated
4362                   --  complaint about types not matching.
4363
4364                   Set_Error_Posted (New_Formal);
4365                end if;
4366             end if;
4367          end if;
4368
4369          --  Ada 2005 (AI-423): Possible access [sub]type and itype match. This
4370          --  case occurs whenever a subprogram is being renamed and one of its
4371          --  parameters imposes a null exclusion. For example:
4372
4373          --     type T is null record;
4374          --     type Acc_T is access T;
4375          --     subtype Acc_T_Sub is Acc_T;
4376
4377          --     procedure P     (Obj : not null Acc_T_Sub);  --  itype
4378          --     procedure Ren_P (Obj :          Acc_T_Sub)   --  subtype
4379          --       renames P;
4380
4381          Old_Formal_Base := Etype (Old_Formal);
4382          New_Formal_Base := Etype (New_Formal);
4383
4384          if Get_Inst then
4385             Old_Formal_Base := Get_Instance_Of (Old_Formal_Base);
4386             New_Formal_Base := Get_Instance_Of (New_Formal_Base);
4387          end if;
4388
4389          Access_Types_Match := Ada_Version >= Ada_2005
4390
4391             --  Ensure that this rule is only applied when New_Id is a
4392             --  renaming of Old_Id.
4393
4394            and then Nkind (Parent (Parent (New_Id))) =
4395                       N_Subprogram_Renaming_Declaration
4396            and then Nkind (Name (Parent (Parent (New_Id)))) in N_Has_Entity
4397            and then Present (Entity (Name (Parent (Parent (New_Id)))))
4398            and then Entity (Name (Parent (Parent (New_Id)))) = Old_Id
4399
4400             --  Now handle the allowed access-type case
4401
4402            and then Is_Access_Type (Old_Formal_Base)
4403            and then Is_Access_Type (New_Formal_Base)
4404
4405             --  The type kinds must match. The only exception occurs with
4406             --  multiple generics of the form:
4407
4408             --   generic                    generic
4409             --     type F is private;         type A is private;
4410             --     type F_Ptr is access F;    type A_Ptr is access A;
4411             --     with proc F_P (X : F_Ptr); with proc A_P (X : A_Ptr);
4412             --   package F_Pack is ...      package A_Pack is
4413             --                                package F_Inst is
4414             --                                  new F_Pack (A, A_Ptr, A_P);
4415
4416             --  When checking for conformance between the parameters of A_P
4417             --  and F_P, the type kinds of F_Ptr and A_Ptr will not match
4418             --  because the compiler has transformed A_Ptr into a subtype of
4419             --  F_Ptr. We catch this case in the code below.
4420
4421            and then (Ekind (Old_Formal_Base) = Ekind (New_Formal_Base)
4422                   or else
4423                     (Is_Generic_Type (Old_Formal_Base)
4424                        and then Is_Generic_Type (New_Formal_Base)
4425                        and then Is_Internal (New_Formal_Base)
4426                        and then Etype (Etype (New_Formal_Base)) =
4427                                   Old_Formal_Base))
4428            and then Directly_Designated_Type (Old_Formal_Base) =
4429                       Directly_Designated_Type (New_Formal_Base)
4430            and then ((Is_Itype (Old_Formal_Base)
4431                        and then Can_Never_Be_Null (Old_Formal_Base))
4432                     or else
4433                      (Is_Itype (New_Formal_Base)
4434                        and then Can_Never_Be_Null (New_Formal_Base)));
4435
4436          --  Types must always match. In the visible part of an instance,
4437          --  usual overloading rules for dispatching operations apply, and
4438          --  we check base types (not the actual subtypes).
4439
4440          if In_Instance_Visible_Part
4441            and then Is_Dispatching_Operation (New_Id)
4442          then
4443             if not Conforming_Types
4444                      (T1       => Base_Type (Etype (Old_Formal)),
4445                       T2       => Base_Type (Etype (New_Formal)),
4446                       Ctype    => Ctype,
4447                       Get_Inst => Get_Inst)
4448                and then not Access_Types_Match
4449             then
4450                Conformance_Error ("\type of & does not match!", New_Formal);
4451                return;
4452             end if;
4453
4454          elsif not Conforming_Types
4455                      (T1       => Old_Formal_Base,
4456                       T2       => New_Formal_Base,
4457                       Ctype    => Ctype,
4458                       Get_Inst => Get_Inst)
4459            and then not Access_Types_Match
4460          then
4461             --  Don't give error message if old type is Any_Type. This test
4462             --  avoids some cascaded errors, e.g. in case of a bad spec.
4463
4464             if Errmsg and then Old_Formal_Base = Any_Type then
4465                Conforms := False;
4466             else
4467                Conformance_Error ("\type of & does not match!", New_Formal);
4468             end if;
4469
4470             return;
4471          end if;
4472
4473          --  For mode conformance, mode must match
4474
4475          if Ctype >= Mode_Conformant then
4476             if Parameter_Mode (Old_Formal) /= Parameter_Mode (New_Formal) then
4477                if not Ekind_In (New_Id, E_Function, E_Procedure)
4478                  or else not Is_Primitive_Wrapper (New_Id)
4479                then
4480                   Conformance_Error ("\mode of & does not match!", New_Formal);
4481
4482                else
4483                   declare
4484                      T : constant  Entity_Id := Find_Dispatching_Type (New_Id);
4485                   begin
4486                      if Is_Protected_Type
4487                           (Corresponding_Concurrent_Type (T))
4488                      then
4489                         Error_Msg_PT (T, New_Id);
4490                      else
4491                         Conformance_Error
4492                           ("\mode of & does not match!", New_Formal);
4493                      end if;
4494                   end;
4495                end if;
4496
4497                return;
4498
4499             --  Part of mode conformance for access types is having the same
4500             --  constant modifier.
4501
4502             elsif Access_Types_Match
4503               and then Is_Access_Constant (Old_Formal_Base) /=
4504                        Is_Access_Constant (New_Formal_Base)
4505             then
4506                Conformance_Error
4507                  ("\constant modifier does not match!", New_Formal);
4508                return;
4509             end if;
4510          end if;
4511
4512          if Ctype >= Subtype_Conformant then
4513
4514             --  Ada 2005 (AI-231): In case of anonymous access types check
4515             --  the null-exclusion and access-to-constant attributes must
4516             --  match. For null exclusion, we test the types rather than the
4517             --  formals themselves, since the attribute is only set reliably
4518             --  on the formals in the Ada 95 case, and we exclude the case
4519             --  where Old_Formal is marked as controlling, to avoid errors
4520             --  when matching completing bodies with dispatching declarations
4521             --  (access formals in the bodies aren't marked Can_Never_Be_Null).
4522
4523             if Ada_Version >= Ada_2005
4524               and then Ekind (Etype (Old_Formal)) = E_Anonymous_Access_Type
4525               and then Ekind (Etype (New_Formal)) = E_Anonymous_Access_Type
4526               and then
4527                 ((Can_Never_Be_Null (Etype (Old_Formal)) /=
4528                   Can_Never_Be_Null (Etype (New_Formal))
4529                     and then
4530                       not Is_Controlling_Formal (Old_Formal))
4531                    or else
4532                  Is_Access_Constant (Etype (Old_Formal)) /=
4533                  Is_Access_Constant (Etype (New_Formal)))
4534
4535               --  Do not complain if error already posted on New_Formal. This
4536               --  avoids some redundant error messages.
4537
4538               and then not Error_Posted (New_Formal)
4539             then
4540                --  It is allowed to omit the null-exclusion in case of stream
4541                --  attribute subprograms. We recognize stream subprograms
4542                --  through their TSS-generated suffix.
4543
4544                declare
4545                   TSS_Name : constant TSS_Name_Type := Get_TSS_Name (New_Id);
4546                begin
4547                   if TSS_Name /= TSS_Stream_Read
4548                     and then TSS_Name /= TSS_Stream_Write
4549                     and then TSS_Name /= TSS_Stream_Input
4550                     and then TSS_Name /= TSS_Stream_Output
4551                   then
4552                      Conformance_Error
4553                        ("\type of & does not match!", New_Formal);
4554                      return;
4555                   end if;
4556                end;
4557             end if;
4558          end if;
4559
4560          --  Full conformance checks
4561
4562          if Ctype = Fully_Conformant then
4563
4564             --  We have checked already that names match
4565
4566             if Parameter_Mode (Old_Formal) = E_In_Parameter then
4567
4568                --  Check default expressions for in parameters
4569
4570                declare
4571                   NewD : constant Boolean :=
4572                            Present (Default_Value (New_Formal));
4573                   OldD : constant Boolean :=
4574                            Present (Default_Value (Old_Formal));
4575                begin
4576                   if NewD or OldD then
4577
4578                      --  The old default value has been analyzed because the
4579                      --  current full declaration will have frozen everything
4580                      --  before. The new default value has not been analyzed,
4581                      --  so analyze it now before we check for conformance.
4582
4583                      if NewD then
4584                         Push_Scope (New_Id);
4585                         Preanalyze_Spec_Expression
4586                           (Default_Value (New_Formal), Etype (New_Formal));
4587                         End_Scope;
4588                      end if;
4589
4590                      if not (NewD and OldD)
4591                        or else not Fully_Conformant_Expressions
4592                                     (Default_Value (Old_Formal),
4593                                      Default_Value (New_Formal))
4594                      then
4595                         Conformance_Error
4596                           ("\default expression for & does not match!",
4597                            New_Formal);
4598                         return;
4599                      end if;
4600                   end if;
4601                end;
4602             end if;
4603          end if;
4604
4605          --  A couple of special checks for Ada 83 mode. These checks are
4606          --  skipped if either entity is an operator in package Standard,
4607          --  or if either old or new instance is not from the source program.
4608
4609          if Ada_Version = Ada_83
4610            and then Sloc (Old_Id) > Standard_Location
4611            and then Sloc (New_Id) > Standard_Location
4612            and then Comes_From_Source (Old_Id)
4613            and then Comes_From_Source (New_Id)
4614          then
4615             declare
4616                Old_Param : constant Node_Id := Declaration_Node (Old_Formal);
4617                New_Param : constant Node_Id := Declaration_Node (New_Formal);
4618
4619             begin
4620                --  Explicit IN must be present or absent in both cases. This
4621                --  test is required only in the full conformance case.
4622
4623                if In_Present (Old_Param) /= In_Present (New_Param)
4624                  and then Ctype = Fully_Conformant
4625                then
4626                   Conformance_Error
4627                     ("\(Ada 83) IN must appear in both declarations",
4628                      New_Formal);
4629                   return;
4630                end if;
4631
4632                --  Grouping (use of comma in param lists) must be the same
4633                --  This is where we catch a misconformance like:
4634
4635                --    A, B : Integer
4636                --    A : Integer; B : Integer
4637
4638                --  which are represented identically in the tree except
4639                --  for the setting of the flags More_Ids and Prev_Ids.
4640
4641                if More_Ids (Old_Param) /= More_Ids (New_Param)
4642                  or else Prev_Ids (Old_Param) /= Prev_Ids (New_Param)
4643                then
4644                   Conformance_Error
4645                     ("\grouping of & does not match!", New_Formal);
4646                   return;
4647                end if;
4648             end;
4649          end if;
4650
4651          --  This label is required when skipping controlling formals
4652
4653          <<Skip_Controlling_Formal>>
4654
4655          Next_Formal (Old_Formal);
4656          Next_Formal (New_Formal);
4657       end loop;
4658
4659       if Present (Old_Formal) then
4660          Conformance_Error ("\too few parameters!");
4661          return;
4662
4663       elsif Present (New_Formal) then
4664          Conformance_Error ("\too many parameters!", New_Formal);
4665          return;
4666       end if;
4667    end Check_Conformance;
4668
4669    -----------------------
4670    -- Check_Conventions --
4671    -----------------------
4672
4673    procedure Check_Conventions (Typ : Entity_Id) is
4674       Ifaces_List : Elist_Id;
4675
4676       procedure Check_Convention (Op : Entity_Id);
4677       --  Verify that the convention of inherited dispatching operation Op is
4678       --  consistent among all subprograms it overrides. In order to minimize
4679       --  the search, Search_From is utilized to designate a specific point in
4680       --  the list rather than iterating over the whole list once more.
4681
4682       ----------------------
4683       -- Check_Convention --
4684       ----------------------
4685
4686       procedure Check_Convention (Op : Entity_Id) is
4687          Iface_Elmt      : Elmt_Id;
4688          Iface_Prim_Elmt : Elmt_Id;
4689          Iface_Prim      : Entity_Id;
4690
4691       begin
4692          Iface_Elmt := First_Elmt (Ifaces_List);
4693          while Present (Iface_Elmt) loop
4694             Iface_Prim_Elmt :=
4695                First_Elmt (Primitive_Operations (Node (Iface_Elmt)));
4696             while Present (Iface_Prim_Elmt) loop
4697                Iface_Prim := Node (Iface_Prim_Elmt);
4698
4699                if Is_Interface_Conformant (Typ, Iface_Prim, Op)
4700                  and then Convention (Iface_Prim) /= Convention (Op)
4701                then
4702                   Error_Msg_N
4703                     ("inconsistent conventions in primitive operations", Typ);
4704
4705                   Error_Msg_Name_1 := Chars (Op);
4706                   Error_Msg_Name_2 := Get_Convention_Name (Convention (Op));
4707                   Error_Msg_Sloc   := Sloc (Op);
4708
4709                   if Comes_From_Source (Op) or else No (Alias (Op)) then
4710                      if not Present (Overridden_Operation (Op)) then
4711                         Error_Msg_N ("\\primitive % defined #", Typ);
4712                      else
4713                         Error_Msg_N
4714                           ("\\overriding operation % with " &
4715                            "convention % defined #", Typ);
4716                      end if;
4717
4718                   else pragma Assert (Present (Alias (Op)));
4719                      Error_Msg_Sloc := Sloc (Alias (Op));
4720                      Error_Msg_N
4721                        ("\\inherited operation % with " &
4722                         "convention % defined #", Typ);
4723                   end if;
4724
4725                   Error_Msg_Name_1 := Chars (Op);
4726                   Error_Msg_Name_2 :=
4727                     Get_Convention_Name (Convention (Iface_Prim));
4728                   Error_Msg_Sloc := Sloc (Iface_Prim);
4729                   Error_Msg_N
4730                     ("\\overridden operation % with " &
4731                      "convention % defined #", Typ);
4732
4733                   --  Avoid cascading errors
4734
4735                   return;
4736                end if;
4737
4738                Next_Elmt (Iface_Prim_Elmt);
4739             end loop;
4740
4741             Next_Elmt (Iface_Elmt);
4742          end loop;
4743       end Check_Convention;
4744
4745       --  Local variables
4746
4747       Prim_Op      : Entity_Id;
4748       Prim_Op_Elmt : Elmt_Id;
4749
4750    --  Start of processing for Check_Conventions
4751
4752    begin
4753       if not Has_Interfaces (Typ) then
4754          return;
4755       end if;
4756
4757       Collect_Interfaces (Typ, Ifaces_List);
4758
4759       --  The algorithm checks every overriding dispatching operation against
4760       --  all the corresponding overridden dispatching operations, detecting
4761       --  differences in conventions.
4762
4763       Prim_Op_Elmt := First_Elmt (Primitive_Operations (Typ));
4764       while Present (Prim_Op_Elmt) loop
4765          Prim_Op := Node (Prim_Op_Elmt);
4766
4767          --  A small optimization: skip the predefined dispatching operations
4768          --  since they always have the same convention.
4769
4770          if not Is_Predefined_Dispatching_Operation (Prim_Op) then
4771             Check_Convention (Prim_Op);
4772          end if;
4773
4774          Next_Elmt (Prim_Op_Elmt);
4775       end loop;
4776    end Check_Conventions;
4777
4778    ------------------------------
4779    -- Check_Delayed_Subprogram --
4780    ------------------------------
4781
4782    procedure Check_Delayed_Subprogram (Designator : Entity_Id) is
4783       F : Entity_Id;
4784
4785       procedure Possible_Freeze (T : Entity_Id);
4786       --  T is the type of either a formal parameter or of the return type.
4787       --  If T is not yet frozen and needs a delayed freeze, then the
4788       --  subprogram itself must be delayed. If T is the limited view of an
4789       --  incomplete type the subprogram must be frozen as well, because
4790       --  T may depend on local types that have not been frozen yet.
4791
4792       ---------------------
4793       -- Possible_Freeze --
4794       ---------------------
4795
4796       procedure Possible_Freeze (T : Entity_Id) is
4797       begin
4798          if Has_Delayed_Freeze (T) and then not Is_Frozen (T) then
4799             Set_Has_Delayed_Freeze (Designator);
4800
4801          elsif Is_Access_Type (T)
4802            and then Has_Delayed_Freeze (Designated_Type (T))
4803            and then not Is_Frozen (Designated_Type (T))
4804          then
4805             Set_Has_Delayed_Freeze (Designator);
4806
4807          elsif Ekind (T) = E_Incomplete_Type and then From_With_Type (T) then
4808             Set_Has_Delayed_Freeze (Designator);
4809
4810          --  AI05-0151: In Ada 2012, Incomplete types can appear in the profile
4811          --  of a subprogram or entry declaration.
4812
4813          elsif Ekind (T) = E_Incomplete_Type
4814            and then Ada_Version >= Ada_2012
4815          then
4816             Set_Has_Delayed_Freeze (Designator);
4817          end if;
4818
4819       end Possible_Freeze;
4820
4821    --  Start of processing for Check_Delayed_Subprogram
4822
4823    begin
4824       --  All subprograms, including abstract subprograms, may need a freeze
4825       --  node if some formal type or the return type needs one.
4826
4827       Possible_Freeze (Etype (Designator));
4828       Possible_Freeze (Base_Type (Etype (Designator))); -- needed ???
4829
4830       --  Need delayed freeze if any of the formal types themselves need
4831       --  a delayed freeze and are not yet frozen.
4832
4833       F := First_Formal (Designator);
4834       while Present (F) loop
4835          Possible_Freeze (Etype (F));
4836          Possible_Freeze (Base_Type (Etype (F))); -- needed ???
4837          Next_Formal (F);
4838       end loop;
4839
4840       --  Mark functions that return by reference. Note that it cannot be
4841       --  done for delayed_freeze subprograms because the underlying
4842       --  returned type may not be known yet (for private types)
4843
4844       if not Has_Delayed_Freeze (Designator)
4845         and then Expander_Active
4846       then
4847          declare
4848             Typ  : constant Entity_Id := Etype (Designator);
4849             Utyp : constant Entity_Id := Underlying_Type (Typ);
4850
4851          begin
4852             if Is_Immutably_Limited_Type (Typ) then
4853                Set_Returns_By_Ref (Designator);
4854
4855             elsif Present (Utyp) and then CW_Or_Has_Controlled_Part (Utyp) then
4856                Set_Returns_By_Ref (Designator);
4857             end if;
4858          end;
4859       end if;
4860    end Check_Delayed_Subprogram;
4861
4862    ------------------------------------
4863    -- Check_Discriminant_Conformance --
4864    ------------------------------------
4865
4866    procedure Check_Discriminant_Conformance
4867      (N        : Node_Id;
4868       Prev     : Entity_Id;
4869       Prev_Loc : Node_Id)
4870    is
4871       Old_Discr      : Entity_Id := First_Discriminant (Prev);
4872       New_Discr      : Node_Id   := First (Discriminant_Specifications (N));
4873       New_Discr_Id   : Entity_Id;
4874       New_Discr_Type : Entity_Id;
4875
4876       procedure Conformance_Error (Msg : String; N : Node_Id);
4877       --  Post error message for conformance error on given node. Two messages
4878       --  are output. The first points to the previous declaration with a
4879       --  general "no conformance" message. The second is the detailed reason,
4880       --  supplied as Msg. The parameter N provide information for a possible
4881       --  & insertion in the message.
4882
4883       -----------------------
4884       -- Conformance_Error --
4885       -----------------------
4886
4887       procedure Conformance_Error (Msg : String; N : Node_Id) is
4888       begin
4889          Error_Msg_Sloc := Sloc (Prev_Loc);
4890          Error_Msg_N -- CODEFIX
4891            ("not fully conformant with declaration#!", N);
4892          Error_Msg_NE (Msg, N, N);
4893       end Conformance_Error;
4894
4895    --  Start of processing for Check_Discriminant_Conformance
4896
4897    begin
4898       while Present (Old_Discr) and then Present (New_Discr) loop
4899
4900          New_Discr_Id := Defining_Identifier (New_Discr);
4901
4902          --  The subtype mark of the discriminant on the full type has not
4903          --  been analyzed so we do it here. For an access discriminant a new
4904          --  type is created.
4905
4906          if Nkind (Discriminant_Type (New_Discr)) = N_Access_Definition then
4907             New_Discr_Type :=
4908               Access_Definition (N, Discriminant_Type (New_Discr));
4909
4910          else
4911             Analyze (Discriminant_Type (New_Discr));
4912             New_Discr_Type := Etype (Discriminant_Type (New_Discr));
4913
4914             --  Ada 2005: if the discriminant definition carries a null
4915             --  exclusion, create an itype to check properly for consistency
4916             --  with partial declaration.
4917
4918             if Is_Access_Type (New_Discr_Type)
4919                  and then Null_Exclusion_Present (New_Discr)
4920             then
4921                New_Discr_Type :=
4922                  Create_Null_Excluding_Itype
4923                    (T           => New_Discr_Type,
4924                     Related_Nod => New_Discr,
4925                     Scope_Id    => Current_Scope);
4926             end if;
4927          end if;
4928
4929          if not Conforming_Types
4930                   (Etype (Old_Discr), New_Discr_Type, Fully_Conformant)
4931          then
4932             Conformance_Error ("type of & does not match!", New_Discr_Id);
4933             return;
4934          else
4935             --  Treat the new discriminant as an occurrence of the old one,
4936             --  for navigation purposes, and fill in some semantic
4937             --  information, for completeness.
4938
4939             Generate_Reference (Old_Discr, New_Discr_Id, 'r');
4940             Set_Etype (New_Discr_Id, Etype (Old_Discr));
4941             Set_Scope (New_Discr_Id, Scope (Old_Discr));
4942          end if;
4943
4944          --  Names must match
4945
4946          if Chars (Old_Discr) /= Chars (Defining_Identifier (New_Discr)) then
4947             Conformance_Error ("name & does not match!", New_Discr_Id);
4948             return;
4949          end if;
4950
4951          --  Default expressions must match
4952
4953          declare
4954             NewD : constant Boolean :=
4955                      Present (Expression (New_Discr));
4956             OldD : constant Boolean :=
4957                      Present (Expression (Parent (Old_Discr)));
4958
4959          begin
4960             if NewD or OldD then
4961
4962                --  The old default value has been analyzed and expanded,
4963                --  because the current full declaration will have frozen
4964                --  everything before. The new default values have not been
4965                --  expanded, so expand now to check conformance.
4966
4967                if NewD then
4968                   Preanalyze_Spec_Expression
4969                     (Expression (New_Discr), New_Discr_Type);
4970                end if;
4971
4972                if not (NewD and OldD)
4973                  or else not Fully_Conformant_Expressions
4974                               (Expression (Parent (Old_Discr)),
4975                                Expression (New_Discr))
4976
4977                then
4978                   Conformance_Error
4979                     ("default expression for & does not match!",
4980                      New_Discr_Id);
4981                   return;
4982                end if;
4983             end if;
4984          end;
4985
4986          --  In Ada 83 case, grouping must match: (A,B : X) /= (A : X; B : X)
4987
4988          if Ada_Version = Ada_83 then
4989             declare
4990                Old_Disc : constant Node_Id := Declaration_Node (Old_Discr);
4991
4992             begin
4993                --  Grouping (use of comma in param lists) must be the same
4994                --  This is where we catch a misconformance like:
4995
4996                --    A, B : Integer
4997                --    A : Integer; B : Integer
4998
4999                --  which are represented identically in the tree except
5000                --  for the setting of the flags More_Ids and Prev_Ids.
5001
5002                if More_Ids (Old_Disc) /= More_Ids (New_Discr)
5003                  or else Prev_Ids (Old_Disc) /= Prev_Ids (New_Discr)
5004                then
5005                   Conformance_Error
5006                     ("grouping of & does not match!", New_Discr_Id);
5007                   return;
5008                end if;
5009             end;
5010          end if;
5011
5012          Next_Discriminant (Old_Discr);
5013          Next (New_Discr);
5014       end loop;
5015
5016       if Present (Old_Discr) then
5017          Conformance_Error ("too few discriminants!", Defining_Identifier (N));
5018          return;
5019
5020       elsif Present (New_Discr) then
5021          Conformance_Error
5022            ("too many discriminants!", Defining_Identifier (New_Discr));
5023          return;
5024       end if;
5025    end Check_Discriminant_Conformance;
5026
5027    ----------------------------
5028    -- Check_Fully_Conformant --
5029    ----------------------------
5030
5031    procedure Check_Fully_Conformant
5032      (New_Id  : Entity_Id;
5033       Old_Id  : Entity_Id;
5034       Err_Loc : Node_Id := Empty)
5035    is
5036       Result : Boolean;
5037       pragma Warnings (Off, Result);
5038    begin
5039       Check_Conformance
5040         (New_Id, Old_Id, Fully_Conformant, True, Result, Err_Loc);
5041    end Check_Fully_Conformant;
5042
5043    ---------------------------
5044    -- Check_Mode_Conformant --
5045    ---------------------------
5046
5047    procedure Check_Mode_Conformant
5048      (New_Id   : Entity_Id;
5049       Old_Id   : Entity_Id;
5050       Err_Loc  : Node_Id := Empty;
5051       Get_Inst : Boolean := False)
5052    is
5053       Result : Boolean;
5054       pragma Warnings (Off, Result);
5055    begin
5056       Check_Conformance
5057         (New_Id, Old_Id, Mode_Conformant, True, Result, Err_Loc, Get_Inst);
5058    end Check_Mode_Conformant;
5059
5060    --------------------------------
5061    -- Check_Overriding_Indicator --
5062    --------------------------------
5063
5064    procedure Check_Overriding_Indicator
5065      (Subp            : Entity_Id;
5066       Overridden_Subp : Entity_Id;
5067       Is_Primitive    : Boolean)
5068    is
5069       Decl : Node_Id;
5070       Spec : Node_Id;
5071
5072    begin
5073       --  No overriding indicator for literals
5074
5075       if Ekind (Subp) = E_Enumeration_Literal then
5076          return;
5077
5078       elsif Ekind (Subp) = E_Entry then
5079          Decl := Parent (Subp);
5080
5081          --  No point in analyzing a malformed operator
5082
5083       elsif Nkind (Subp) = N_Defining_Operator_Symbol
5084         and then Error_Posted (Subp)
5085       then
5086          return;
5087
5088       else
5089          Decl := Unit_Declaration_Node (Subp);
5090       end if;
5091
5092       if Nkind_In (Decl, N_Subprogram_Body,
5093                          N_Subprogram_Body_Stub,
5094                          N_Subprogram_Declaration,
5095                          N_Abstract_Subprogram_Declaration,
5096                          N_Subprogram_Renaming_Declaration)
5097       then
5098          Spec := Specification (Decl);
5099
5100       elsif Nkind (Decl) = N_Entry_Declaration then
5101          Spec := Decl;
5102
5103       else
5104          return;
5105       end if;
5106
5107       --  The overriding operation is type conformant with the overridden one,
5108       --  but the names of the formals are not required to match. If the names
5109       --  appear permuted in the overriding operation, this is a possible
5110       --  source of confusion that is worth diagnosing. Controlling formals
5111       --  often carry names that reflect the type, and it is not worthwhile
5112       --  requiring that their names match.
5113
5114       if Present (Overridden_Subp)
5115         and then Nkind (Subp) /= N_Defining_Operator_Symbol
5116       then
5117          declare
5118             Form1 : Entity_Id;
5119             Form2 : Entity_Id;
5120
5121          begin
5122             Form1 := First_Formal (Subp);
5123             Form2 := First_Formal (Overridden_Subp);
5124
5125             --  If the overriding operation is a synchronized operation, skip
5126             --  the first parameter of the overridden operation, which is
5127             --  implicit in the new one. If the operation is declared in the
5128             --  body it is not primitive and all formals must match.
5129
5130             if Is_Concurrent_Type (Scope (Subp))
5131               and then Is_Tagged_Type (Scope (Subp))
5132               and then not Has_Completion (Scope (Subp))
5133             then
5134                Form2 := Next_Formal (Form2);
5135             end if;
5136
5137             if Present (Form1) then
5138                Form1 := Next_Formal (Form1);
5139                Form2 := Next_Formal (Form2);
5140             end if;
5141
5142             while Present (Form1) loop
5143                if not Is_Controlling_Formal (Form1)
5144                  and then Present (Next_Formal (Form2))
5145                  and then Chars (Form1) = Chars (Next_Formal (Form2))
5146                then
5147                   Error_Msg_Node_2 := Alias (Overridden_Subp);
5148                   Error_Msg_Sloc := Sloc (Error_Msg_Node_2);
5149                   Error_Msg_NE
5150                     ("& does not match corresponding formal of&#",
5151                      Form1, Form1);
5152                   exit;
5153                end if;
5154
5155                Next_Formal (Form1);
5156                Next_Formal (Form2);
5157             end loop;
5158          end;
5159       end if;
5160
5161       --  If there is an overridden subprogram, then check that there is no
5162       --  "not overriding" indicator, and mark the subprogram as overriding.
5163       --  This is not done if the overridden subprogram is marked as hidden,
5164       --  which can occur for the case of inherited controlled operations
5165       --  (see Derive_Subprogram), unless the inherited subprogram's parent
5166       --  subprogram is not itself hidden. (Note: This condition could probably
5167       --  be simplified, leaving out the testing for the specific controlled
5168       --  cases, but it seems safer and clearer this way, and echoes similar
5169       --  special-case tests of this kind in other places.)
5170
5171       if Present (Overridden_Subp)
5172         and then (not Is_Hidden (Overridden_Subp)
5173                    or else
5174                      ((Chars (Overridden_Subp) = Name_Initialize
5175                          or else
5176                        Chars (Overridden_Subp) = Name_Adjust
5177                          or else
5178                        Chars (Overridden_Subp) = Name_Finalize)
5179                       and then Present (Alias (Overridden_Subp))
5180                       and then not Is_Hidden (Alias (Overridden_Subp))))
5181       then
5182          if Must_Not_Override (Spec) then
5183             Error_Msg_Sloc := Sloc (Overridden_Subp);
5184
5185             if Ekind (Subp) = E_Entry then
5186                Error_Msg_NE
5187                  ("entry & overrides inherited operation #", Spec, Subp);
5188             else
5189                Error_Msg_NE
5190                  ("subprogram & overrides inherited operation #", Spec, Subp);
5191             end if;
5192
5193          --  Special-case to fix a GNAT oddity: Limited_Controlled is declared
5194          --  as an extension of Root_Controlled, and thus has a useless Adjust
5195          --  operation. This operation should not be inherited by other limited
5196          --  controlled types. An explicit Adjust for them is not overriding.
5197
5198          elsif Must_Override (Spec)
5199            and then Chars (Overridden_Subp) = Name_Adjust
5200            and then Is_Limited_Type (Etype (First_Formal (Subp)))
5201            and then Present (Alias (Overridden_Subp))
5202            and then
5203              Is_Predefined_File_Name
5204                (Unit_File_Name (Get_Source_Unit (Alias (Overridden_Subp))))
5205          then
5206             Error_Msg_NE ("subprogram & is not overriding", Spec, Subp);
5207
5208          elsif Is_Subprogram (Subp) then
5209             if Is_Init_Proc (Subp) then
5210                null;
5211
5212             elsif No (Overridden_Operation (Subp)) then
5213
5214                --  For entities generated by Derive_Subprograms the overridden
5215                --  operation is the inherited primitive (which is available
5216                --  through the attribute alias)
5217
5218                if (Is_Dispatching_Operation (Subp)
5219                     or else Is_Dispatching_Operation (Overridden_Subp))
5220                  and then not Comes_From_Source (Overridden_Subp)
5221                  and then Find_Dispatching_Type (Overridden_Subp) =
5222                           Find_Dispatching_Type (Subp)
5223                  and then Present (Alias (Overridden_Subp))
5224                  and then Comes_From_Source (Alias (Overridden_Subp))
5225                then
5226                   Set_Overridden_Operation (Subp, Alias (Overridden_Subp));
5227
5228                else
5229                   Set_Overridden_Operation (Subp, Overridden_Subp);
5230                end if;
5231             end if;
5232          end if;
5233
5234          --  If primitive flag is set or this is a protected operation, then
5235          --  the operation is overriding at the point of its declaration, so
5236          --  warn if necessary. Otherwise it may have been declared before the
5237          --  operation it overrides and no check is required.
5238
5239          if Style_Check
5240            and then not Must_Override (Spec)
5241            and then (Is_Primitive
5242                       or else Ekind (Scope (Subp)) = E_Protected_Type)
5243          then
5244             Style.Missing_Overriding (Decl, Subp);
5245          end if;
5246
5247       --  If Subp is an operator, it may override a predefined operation, if
5248       --  it is defined in the same scope as the type to which it applies.
5249       --  In that case Overridden_Subp is empty because of our implicit
5250       --  representation for predefined operators. We have to check whether the
5251       --  signature of Subp matches that of a predefined operator. Note that
5252       --  first argument provides the name of the operator, and the second
5253       --  argument the signature that may match that of a standard operation.
5254       --  If the indicator is overriding, then the operator must match a
5255       --  predefined signature, because we know already that there is no
5256       --  explicit overridden operation.
5257
5258       elsif Nkind (Subp) = N_Defining_Operator_Symbol then
5259          if Must_Not_Override (Spec) then
5260
5261             --  If this is not a primitive or a protected subprogram, then
5262             --  "not overriding" is illegal.
5263
5264             if not Is_Primitive
5265               and then Ekind (Scope (Subp)) /= E_Protected_Type
5266             then
5267                Error_Msg_N
5268                  ("overriding indicator only allowed "
5269                   & "if subprogram is primitive", Subp);
5270
5271             elsif Can_Override_Operator (Subp) then
5272                Error_Msg_NE
5273                  ("subprogram& overrides predefined operator ", Spec, Subp);
5274             end if;
5275
5276          elsif Must_Override (Spec) then
5277             if No (Overridden_Operation (Subp))
5278               and then not Can_Override_Operator (Subp)
5279             then
5280                Error_Msg_NE ("subprogram & is not overriding", Spec, Subp);
5281             end if;
5282
5283          elsif not Error_Posted (Subp)
5284            and then Style_Check
5285            and then Can_Override_Operator (Subp)
5286            and then
5287              not Is_Predefined_File_Name
5288                    (Unit_File_Name (Get_Source_Unit (Subp)))
5289          then
5290             --  If style checks are enabled, indicate that the indicator is
5291             --  missing. However, at the point of declaration, the type of
5292             --  which this is a primitive operation may be private, in which
5293             --  case the indicator would be premature.
5294
5295             if Has_Private_Declaration (Etype (Subp))
5296               or else Has_Private_Declaration (Etype (First_Formal (Subp)))
5297             then
5298                null;
5299             else
5300                Style.Missing_Overriding (Decl, Subp);
5301             end if;
5302          end if;
5303
5304       elsif Must_Override (Spec) then
5305          if Ekind (Subp) = E_Entry then
5306             Error_Msg_NE ("entry & is not overriding", Spec, Subp);
5307          else
5308             Error_Msg_NE ("subprogram & is not overriding", Spec, Subp);
5309          end if;
5310
5311       --  If the operation is marked "not overriding" and it's not primitive
5312       --  then an error is issued, unless this is an operation of a task or
5313       --  protected type (RM05-8.3.1(3/2-4/2)). Error cases where "overriding"
5314       --  has been specified have already been checked above.
5315
5316       elsif Must_Not_Override (Spec)
5317         and then not Is_Primitive
5318         and then Ekind (Subp) /= E_Entry
5319         and then Ekind (Scope (Subp)) /= E_Protected_Type
5320       then
5321          Error_Msg_N
5322            ("overriding indicator only allowed if subprogram is primitive",
5323             Subp);
5324          return;
5325       end if;
5326    end Check_Overriding_Indicator;
5327
5328    -------------------
5329    -- Check_Returns --
5330    -------------------
5331
5332    --  Note: this procedure needs to know far too much about how the expander
5333    --  messes with exceptions. The use of the flag Exception_Junk and the
5334    --  incorporation of knowledge of Exp_Ch11.Expand_Local_Exception_Handlers
5335    --  works, but is not very clean. It would be better if the expansion
5336    --  routines would leave Original_Node working nicely, and we could use
5337    --  Original_Node here to ignore all the peculiar expander messing ???
5338
5339    procedure Check_Returns
5340      (HSS  : Node_Id;
5341       Mode : Character;
5342       Err  : out Boolean;
5343       Proc : Entity_Id := Empty)
5344    is
5345       Handler : Node_Id;
5346
5347       procedure Check_Statement_Sequence (L : List_Id);
5348       --  Internal recursive procedure to check a list of statements for proper
5349       --  termination by a return statement (or a transfer of control or a
5350       --  compound statement that is itself internally properly terminated).
5351
5352       ------------------------------
5353       -- Check_Statement_Sequence --
5354       ------------------------------
5355
5356       procedure Check_Statement_Sequence (L : List_Id) is
5357          Last_Stm : Node_Id;
5358          Stm      : Node_Id;
5359          Kind     : Node_Kind;
5360
5361          Raise_Exception_Call : Boolean;
5362          --  Set True if statement sequence terminated by Raise_Exception call
5363          --  or a Reraise_Occurrence call.
5364
5365       begin
5366          Raise_Exception_Call := False;
5367
5368          --  Get last real statement
5369
5370          Last_Stm := Last (L);
5371
5372          --  Deal with digging out exception handler statement sequences that
5373          --  have been transformed by the local raise to goto optimization.
5374          --  See Exp_Ch11.Expand_Local_Exception_Handlers for details. If this
5375          --  optimization has occurred, we are looking at something like:
5376
5377          --  begin
5378          --     original stmts in block
5379
5380          --  exception            \
5381          --     when excep1 =>     |
5382          --        goto L1;        | omitted if No_Exception_Propagation
5383          --     when excep2 =>     |
5384          --        goto L2;       /
5385          --  end;
5386
5387          --  goto L3;      -- skip handler when exception not raised
5388
5389          --  <<L1>>        -- target label for local exception
5390          --     begin
5391          --        estmts1
5392          --     end;
5393
5394          --     goto L3;
5395
5396          --  <<L2>>
5397          --     begin
5398          --        estmts2
5399          --     end;
5400
5401          --  <<L3>>
5402
5403          --  and what we have to do is to dig out the estmts1 and estmts2
5404          --  sequences (which were the original sequences of statements in
5405          --  the exception handlers) and check them.
5406
5407          if Nkind (Last_Stm) = N_Label
5408            and then Exception_Junk (Last_Stm)
5409          then
5410             Stm := Last_Stm;
5411             loop
5412                Prev (Stm);
5413                exit when No (Stm);
5414                exit when Nkind (Stm) /= N_Block_Statement;
5415                exit when not Exception_Junk (Stm);
5416                Prev (Stm);
5417                exit when No (Stm);
5418                exit when Nkind (Stm) /= N_Label;
5419                exit when not Exception_Junk (Stm);
5420                Check_Statement_Sequence
5421                  (Statements (Handled_Statement_Sequence (Next (Stm))));
5422
5423                Prev (Stm);
5424                Last_Stm := Stm;
5425                exit when No (Stm);
5426                exit when Nkind (Stm) /= N_Goto_Statement;
5427                exit when not Exception_Junk (Stm);
5428             end loop;
5429          end if;
5430
5431          --  Don't count pragmas
5432
5433          while Nkind (Last_Stm) = N_Pragma
5434
5435          --  Don't count call to SS_Release (can happen after Raise_Exception)
5436
5437            or else
5438              (Nkind (Last_Stm) = N_Procedure_Call_Statement
5439                 and then
5440               Nkind (Name (Last_Stm)) = N_Identifier
5441                 and then
5442               Is_RTE (Entity (Name (Last_Stm)), RE_SS_Release))
5443
5444          --  Don't count exception junk
5445
5446            or else
5447              (Nkind_In (Last_Stm, N_Goto_Statement,
5448                                    N_Label,
5449                                    N_Object_Declaration)
5450                 and then Exception_Junk (Last_Stm))
5451            or else Nkind (Last_Stm) in N_Push_xxx_Label
5452            or else Nkind (Last_Stm) in N_Pop_xxx_Label
5453          loop
5454             Prev (Last_Stm);
5455          end loop;
5456
5457          --  Here we have the "real" last statement
5458
5459          Kind := Nkind (Last_Stm);
5460
5461          --  Transfer of control, OK. Note that in the No_Return procedure
5462          --  case, we already diagnosed any explicit return statements, so
5463          --  we can treat them as OK in this context.
5464
5465          if Is_Transfer (Last_Stm) then
5466             return;
5467
5468          --  Check cases of explicit non-indirect procedure calls
5469
5470          elsif Kind = N_Procedure_Call_Statement
5471            and then Is_Entity_Name (Name (Last_Stm))
5472          then
5473             --  Check call to Raise_Exception procedure which is treated
5474             --  specially, as is a call to Reraise_Occurrence.
5475
5476             --  We suppress the warning in these cases since it is likely that
5477             --  the programmer really does not expect to deal with the case
5478             --  of Null_Occurrence, and thus would find a warning about a
5479             --  missing return curious, and raising Program_Error does not
5480             --  seem such a bad behavior if this does occur.
5481
5482             --  Note that in the Ada 2005 case for Raise_Exception, the actual
5483             --  behavior will be to raise Constraint_Error (see AI-329).
5484
5485             if Is_RTE (Entity (Name (Last_Stm)), RE_Raise_Exception)
5486                  or else
5487                Is_RTE (Entity (Name (Last_Stm)), RE_Reraise_Occurrence)
5488             then
5489                Raise_Exception_Call := True;
5490
5491                --  For Raise_Exception call, test first argument, if it is
5492                --  an attribute reference for a 'Identity call, then we know
5493                --  that the call cannot possibly return.
5494
5495                declare
5496                   Arg : constant Node_Id :=
5497                           Original_Node (First_Actual (Last_Stm));
5498                begin
5499                   if Nkind (Arg) = N_Attribute_Reference
5500                     and then Attribute_Name (Arg) = Name_Identity
5501                   then
5502                      return;
5503                   end if;
5504                end;
5505             end if;
5506
5507          --  If statement, need to look inside if there is an else and check
5508          --  each constituent statement sequence for proper termination.
5509
5510          elsif Kind = N_If_Statement
5511            and then Present (Else_Statements (Last_Stm))
5512          then
5513             Check_Statement_Sequence (Then_Statements (Last_Stm));
5514             Check_Statement_Sequence (Else_Statements (Last_Stm));
5515
5516             if Present (Elsif_Parts (Last_Stm)) then
5517                declare
5518                   Elsif_Part : Node_Id := First (Elsif_Parts (Last_Stm));
5519
5520                begin
5521                   while Present (Elsif_Part) loop
5522                      Check_Statement_Sequence (Then_Statements (Elsif_Part));
5523                      Next (Elsif_Part);
5524                   end loop;
5525                end;
5526             end if;
5527
5528             return;
5529
5530          --  Case statement, check each case for proper termination
5531
5532          elsif Kind = N_Case_Statement then
5533             declare
5534                Case_Alt : Node_Id;
5535             begin
5536                Case_Alt := First_Non_Pragma (Alternatives (Last_Stm));
5537                while Present (Case_Alt) loop
5538                   Check_Statement_Sequence (Statements (Case_Alt));
5539                   Next_Non_Pragma (Case_Alt);
5540                end loop;
5541             end;
5542
5543             return;
5544
5545          --  Block statement, check its handled sequence of statements
5546
5547          elsif Kind = N_Block_Statement then
5548             declare
5549                Err1 : Boolean;
5550
5551             begin
5552                Check_Returns
5553                  (Handled_Statement_Sequence (Last_Stm), Mode, Err1);
5554
5555                if Err1 then
5556                   Err := True;
5557                end if;
5558
5559                return;
5560             end;
5561
5562          --  Loop statement. If there is an iteration scheme, we can definitely
5563          --  fall out of the loop. Similarly if there is an exit statement, we
5564          --  can fall out. In either case we need a following return.
5565
5566          elsif Kind = N_Loop_Statement then
5567             if Present (Iteration_Scheme (Last_Stm))
5568               or else Has_Exit (Entity (Identifier (Last_Stm)))
5569             then
5570                null;
5571
5572             --  A loop with no exit statement or iteration scheme is either
5573             --  an infinite loop, or it has some other exit (raise/return).
5574             --  In either case, no warning is required.
5575
5576             else
5577                return;
5578             end if;
5579
5580          --  Timed entry call, check entry call and delay alternatives
5581
5582          --  Note: in expanded code, the timed entry call has been converted
5583          --  to a set of expanded statements on which the check will work
5584          --  correctly in any case.
5585
5586          elsif Kind = N_Timed_Entry_Call then
5587             declare
5588                ECA : constant Node_Id := Entry_Call_Alternative (Last_Stm);
5589                DCA : constant Node_Id := Delay_Alternative      (Last_Stm);
5590
5591             begin
5592                --  If statement sequence of entry call alternative is missing,
5593                --  then we can definitely fall through, and we post the error
5594                --  message on the entry call alternative itself.
5595
5596                if No (Statements (ECA)) then
5597                   Last_Stm := ECA;
5598
5599                --  If statement sequence of delay alternative is missing, then
5600                --  we can definitely fall through, and we post the error
5601                --  message on the delay alternative itself.
5602
5603                --  Note: if both ECA and DCA are missing the return, then we
5604                --  post only one message, should be enough to fix the bugs.
5605                --  If not we will get a message next time on the DCA when the
5606                --  ECA is fixed!
5607
5608                elsif No (Statements (DCA)) then
5609                   Last_Stm := DCA;
5610
5611                --  Else check both statement sequences
5612
5613                else
5614                   Check_Statement_Sequence (Statements (ECA));
5615                   Check_Statement_Sequence (Statements (DCA));
5616                   return;
5617                end if;
5618             end;
5619
5620          --  Conditional entry call, check entry call and else part
5621
5622          --  Note: in expanded code, the conditional entry call has been
5623          --  converted to a set of expanded statements on which the check
5624          --  will work correctly in any case.
5625
5626          elsif Kind = N_Conditional_Entry_Call then
5627             declare
5628                ECA : constant Node_Id := Entry_Call_Alternative (Last_Stm);
5629
5630             begin
5631                --  If statement sequence of entry call alternative is missing,
5632                --  then we can definitely fall through, and we post the error
5633                --  message on the entry call alternative itself.
5634
5635                if No (Statements (ECA)) then
5636                   Last_Stm := ECA;
5637
5638                --  Else check statement sequence and else part
5639
5640                else
5641                   Check_Statement_Sequence (Statements (ECA));
5642                   Check_Statement_Sequence (Else_Statements (Last_Stm));
5643                   return;
5644                end if;
5645             end;
5646          end if;
5647
5648          --  If we fall through, issue appropriate message
5649
5650          if Mode = 'F' then
5651             if not Raise_Exception_Call then
5652                Error_Msg_N
5653                  ("?RETURN statement missing following this statement!",
5654                   Last_Stm);
5655                Error_Msg_N
5656                  ("\?Program_Error may be raised at run time!",
5657                   Last_Stm);
5658             end if;
5659
5660             --  Note: we set Err even though we have not issued a warning
5661             --  because we still have a case of a missing return. This is
5662             --  an extremely marginal case, probably will never be noticed
5663             --  but we might as well get it right.
5664
5665             Err := True;
5666
5667          --  Otherwise we have the case of a procedure marked No_Return
5668
5669          else
5670             if not Raise_Exception_Call then
5671                Error_Msg_N
5672                  ("?implied return after this statement " &
5673                   "will raise Program_Error",
5674                   Last_Stm);
5675                Error_Msg_NE
5676                  ("\?procedure & is marked as No_Return!",
5677                   Last_Stm, Proc);
5678             end if;
5679
5680             declare
5681                RE : constant Node_Id :=
5682                       Make_Raise_Program_Error (Sloc (Last_Stm),
5683                         Reason => PE_Implicit_Return);
5684             begin
5685                Insert_After (Last_Stm, RE);
5686                Analyze (RE);
5687             end;
5688          end if;
5689       end Check_Statement_Sequence;
5690
5691    --  Start of processing for Check_Returns
5692
5693    begin
5694       Err := False;
5695       Check_Statement_Sequence (Statements (HSS));
5696
5697       if Present (Exception_Handlers (HSS)) then
5698          Handler := First_Non_Pragma (Exception_Handlers (HSS));
5699          while Present (Handler) loop
5700             Check_Statement_Sequence (Statements (Handler));
5701             Next_Non_Pragma (Handler);
5702          end loop;
5703       end if;
5704    end Check_Returns;
5705
5706    -------------------------------
5707    -- Check_Subprogram_Contract --
5708    -------------------------------
5709
5710    procedure Check_Subprogram_Contract (Spec_Id : Entity_Id) is
5711
5712       --  Code is currently commented out as, in some cases, it causes crashes
5713       --  because Direct_Primitive_Operations is not available for a private
5714       --  type. This may cause more warnings to be issued than necessary. See
5715       --  below for the intended use of this variable. ???
5716
5717 --        Inherited : constant Subprogram_List :=
5718 --                      Inherited_Subprograms (Spec_Id);
5719 --        --  List of subprograms inherited by this subprogram
5720
5721       Last_Postcondition : Node_Id := Empty;
5722       --  Last postcondition on the subprogram, or else Empty if either no
5723       --  postcondition or only inherited postconditions.
5724
5725       Attribute_Result_Mentioned : Boolean := False;
5726       --  Whether attribute 'Result is mentioned in a postcondition
5727
5728       Post_State_Mentioned : Boolean := False;
5729       --  Whether some expression mentioned in a postcondition can have a
5730       --  different value in the post-state than in the pre-state.
5731
5732       function Check_Attr_Result (N : Node_Id) return Traverse_Result;
5733       --  Check if N is a reference to the attribute 'Result, and if so set
5734       --  Attribute_Result_Mentioned and return Abandon. Otherwise return OK.
5735
5736       function Check_Post_State (N : Node_Id) return Traverse_Result;
5737       --  Check whether the value of evaluating N can be different in the
5738       --  post-state, compared to the same evaluation in the pre-state, and
5739       --  if so set Post_State_Mentioned and return Abandon. Return Skip on
5740       --  reference to attribute 'Old, in order to ignore its prefix, which
5741       --  is precisely evaluated in the pre-state. Otherwise return OK.
5742
5743       procedure Process_Post_Conditions (Spec : Node_Id; Class : Boolean);
5744       --  This processes the Spec_PPC_List from Spec, processing any
5745       --  postconditions from the list. If Class is True, then only
5746       --  postconditions marked with Class_Present are considered. The
5747       --  caller has checked that Spec_PPC_List is non-Empty.
5748
5749       function Find_Attribute_Result is new Traverse_Func (Check_Attr_Result);
5750
5751       function Find_Post_State is new Traverse_Func (Check_Post_State);
5752
5753       -----------------------
5754       -- Check_Attr_Result --
5755       -----------------------
5756
5757       function Check_Attr_Result (N : Node_Id) return Traverse_Result is
5758       begin
5759          if Nkind (N) = N_Attribute_Reference
5760            and then Get_Attribute_Id (Attribute_Name (N)) = Attribute_Result
5761          then
5762             Attribute_Result_Mentioned := True;
5763             return Abandon;
5764          else
5765             return OK;
5766          end if;
5767       end Check_Attr_Result;
5768
5769       ----------------------
5770       -- Check_Post_State --
5771       ----------------------
5772
5773       function Check_Post_State (N : Node_Id) return Traverse_Result is
5774          Found : Boolean := False;
5775
5776       begin
5777          case Nkind (N) is
5778             when N_Function_Call        |
5779                  N_Explicit_Dereference =>
5780                Found := True;
5781
5782             when N_Identifier    |
5783                  N_Expanded_Name =>
5784
5785                declare
5786                   E : constant Entity_Id := Entity (N);
5787
5788                begin
5789                   --  ???Quantified expressions get analyzed later, so E can
5790                   --  be empty at this point. In this case, we suppress the
5791                   --  warning, just in case E is assignable. It seems better to
5792                   --  have false negatives than false positives. At some point,
5793                   --  we should make the warning more accurate, either by
5794                   --  analyzing quantified expressions earlier, or moving
5795                   --  this processing later.
5796
5797                   if No (E)
5798                     or else
5799                       (Is_Entity_Name (N)
5800                         and then Ekind (E) in Assignable_Kind)
5801                   then
5802                      Found := True;
5803                   end if;
5804                end;
5805
5806             when N_Attribute_Reference =>
5807                case Get_Attribute_Id (Attribute_Name (N)) is
5808                   when Attribute_Old =>
5809                      return Skip;
5810                   when Attribute_Result =>
5811                      Found := True;
5812                   when others =>
5813                      null;
5814                end case;
5815
5816             when others =>
5817                null;
5818          end case;
5819
5820          if Found then
5821             Post_State_Mentioned := True;
5822             return Abandon;
5823          else
5824             return OK;
5825          end if;
5826       end Check_Post_State;
5827
5828       -----------------------------
5829       -- Process_Post_Conditions --
5830       -----------------------------
5831
5832       procedure Process_Post_Conditions
5833         (Spec  : Node_Id;
5834          Class : Boolean)
5835       is
5836          Prag    : Node_Id;
5837          Arg     : Node_Id;
5838          Ignored : Traverse_Final_Result;
5839          pragma Unreferenced (Ignored);
5840
5841       begin
5842          Prag := Spec_PPC_List (Contract (Spec));
5843
5844          loop
5845             Arg := First (Pragma_Argument_Associations (Prag));
5846
5847             --  Since pre- and post-conditions are listed in reverse order, the
5848             --  first postcondition in the list is the last in the source.
5849
5850             if Pragma_Name (Prag) = Name_Postcondition
5851               and then not Class
5852               and then No (Last_Postcondition)
5853             then
5854                Last_Postcondition := Prag;
5855             end if;
5856
5857             --  For functions, look for presence of 'Result in postcondition
5858
5859             if Ekind_In (Spec_Id, E_Function, E_Generic_Function) then
5860                Ignored := Find_Attribute_Result (Arg);
5861             end if;
5862
5863             --  For each individual non-inherited postcondition, look for
5864             --  presence of an expression that could be evaluated differently
5865             --  in post-state.
5866
5867             if Pragma_Name (Prag) = Name_Postcondition
5868               and then not Class
5869             then
5870                Post_State_Mentioned := False;
5871                Ignored := Find_Post_State (Arg);
5872
5873                if not Post_State_Mentioned then
5874                   Error_Msg_N ("?postcondition refers only to pre-state",
5875                                Prag);
5876                end if;
5877             end if;
5878
5879             Prag := Next_Pragma (Prag);
5880             exit when No (Prag);
5881          end loop;
5882       end Process_Post_Conditions;
5883
5884    --  Start of processing for Check_Subprogram_Contract
5885
5886    begin
5887       if not Warn_On_Suspicious_Contract then
5888          return;
5889       end if;
5890
5891       if Present (Spec_PPC_List (Contract (Spec_Id))) then
5892          Process_Post_Conditions (Spec_Id, Class => False);
5893       end if;
5894
5895       --  Process inherited postconditions
5896
5897       --  Code is currently commented out as, in some cases, it causes crashes
5898       --  because Direct_Primitive_Operations is not available for a private
5899       --  type. This may cause more warnings to be issued than necessary. ???
5900
5901 --        for J in Inherited'Range loop
5902 --           if Present (Spec_PPC_List (Contract (Inherited (J)))) then
5903 --              Process_Post_Conditions (Inherited (J), Class => True);
5904 --           end if;
5905 --        end loop;
5906
5907       --  Issue warning for functions whose postcondition does not mention
5908       --  'Result after all postconditions have been processed.
5909
5910       if Ekind_In (Spec_Id, E_Function, E_Generic_Function)
5911         and then Present (Last_Postcondition)
5912         and then not Attribute_Result_Mentioned
5913       then
5914          Error_Msg_N ("?function postcondition does not mention result",
5915                       Last_Postcondition);
5916       end if;
5917    end Check_Subprogram_Contract;
5918
5919    ----------------------------
5920    -- Check_Subprogram_Order --
5921    ----------------------------
5922
5923    procedure Check_Subprogram_Order (N : Node_Id) is
5924
5925       function Subprogram_Name_Greater (S1, S2 : String) return Boolean;
5926       --  This is used to check if S1 > S2 in the sense required by this test,
5927       --  for example nameab < namec, but name2 < name10.
5928
5929       -----------------------------
5930       -- Subprogram_Name_Greater --
5931       -----------------------------
5932
5933       function Subprogram_Name_Greater (S1, S2 : String) return Boolean is
5934          L1, L2 : Positive;
5935          N1, N2 : Natural;
5936
5937       begin
5938          --  Remove trailing numeric parts
5939
5940          L1 := S1'Last;
5941          while S1 (L1) in '0' .. '9' loop
5942             L1 := L1 - 1;
5943          end loop;
5944
5945          L2 := S2'Last;
5946          while S2 (L2) in '0' .. '9' loop
5947             L2 := L2 - 1;
5948          end loop;
5949
5950          --  If non-numeric parts non-equal, that's decisive
5951
5952          if S1 (S1'First .. L1) < S2 (S2'First .. L2) then
5953             return False;
5954
5955          elsif S1 (S1'First .. L1) > S2 (S2'First .. L2) then
5956             return True;
5957
5958          --  If non-numeric parts equal, compare suffixed numeric parts. Note
5959          --  that a missing suffix is treated as numeric zero in this test.
5960
5961          else
5962             N1 := 0;
5963             while L1 < S1'Last loop
5964                L1 := L1 + 1;
5965                N1 := N1 * 10 + Character'Pos (S1 (L1)) - Character'Pos ('0');
5966             end loop;
5967
5968             N2 := 0;
5969             while L2 < S2'Last loop
5970                L2 := L2 + 1;
5971                N2 := N2 * 10 + Character'Pos (S2 (L2)) - Character'Pos ('0');
5972             end loop;
5973
5974             return N1 > N2;
5975          end if;
5976       end Subprogram_Name_Greater;
5977
5978    --  Start of processing for Check_Subprogram_Order
5979
5980    begin
5981       --  Check body in alpha order if this is option
5982
5983       if Style_Check
5984         and then Style_Check_Order_Subprograms
5985         and then Nkind (N) = N_Subprogram_Body
5986         and then Comes_From_Source (N)
5987         and then In_Extended_Main_Source_Unit (N)
5988       then
5989          declare
5990             LSN : String_Ptr
5991                     renames Scope_Stack.Table
5992                               (Scope_Stack.Last).Last_Subprogram_Name;
5993
5994             Body_Id : constant Entity_Id :=
5995                         Defining_Entity (Specification (N));
5996
5997          begin
5998             Get_Decoded_Name_String (Chars (Body_Id));
5999
6000             if LSN /= null then
6001                if Subprogram_Name_Greater
6002                     (LSN.all, Name_Buffer (1 .. Name_Len))
6003                then
6004                   Style.Subprogram_Not_In_Alpha_Order (Body_Id);
6005                end if;
6006
6007                Free (LSN);
6008             end if;
6009
6010             LSN := new String'(Name_Buffer (1 .. Name_Len));
6011          end;
6012       end if;
6013    end Check_Subprogram_Order;
6014
6015    ------------------------------
6016    -- Check_Subtype_Conformant --
6017    ------------------------------
6018
6019    procedure Check_Subtype_Conformant
6020      (New_Id                   : Entity_Id;
6021       Old_Id                   : Entity_Id;
6022       Err_Loc                  : Node_Id := Empty;
6023       Skip_Controlling_Formals : Boolean := False)
6024    is
6025       Result : Boolean;
6026       pragma Warnings (Off, Result);
6027    begin
6028       Check_Conformance
6029         (New_Id, Old_Id, Subtype_Conformant, True, Result, Err_Loc,
6030          Skip_Controlling_Formals => Skip_Controlling_Formals);
6031    end Check_Subtype_Conformant;
6032
6033    ---------------------------
6034    -- Check_Type_Conformant --
6035    ---------------------------
6036
6037    procedure Check_Type_Conformant
6038      (New_Id  : Entity_Id;
6039       Old_Id  : Entity_Id;
6040       Err_Loc : Node_Id := Empty)
6041    is
6042       Result : Boolean;
6043       pragma Warnings (Off, Result);
6044    begin
6045       Check_Conformance
6046         (New_Id, Old_Id, Type_Conformant, True, Result, Err_Loc);
6047    end Check_Type_Conformant;
6048
6049    ---------------------------
6050    -- Can_Override_Operator --
6051    ---------------------------
6052
6053    function Can_Override_Operator (Subp : Entity_Id) return Boolean is
6054       Typ : Entity_Id;
6055    begin
6056       if Nkind (Subp) /= N_Defining_Operator_Symbol then
6057          return False;
6058
6059       else
6060          Typ := Base_Type (Etype (First_Formal (Subp)));
6061
6062          return Operator_Matches_Spec (Subp, Subp)
6063            and then Scope (Subp) = Scope (Typ)
6064            and then not Is_Class_Wide_Type (Typ);
6065       end if;
6066    end Can_Override_Operator;
6067
6068    ----------------------
6069    -- Conforming_Types --
6070    ----------------------
6071
6072    function Conforming_Types
6073      (T1       : Entity_Id;
6074       T2       : Entity_Id;
6075       Ctype    : Conformance_Type;
6076       Get_Inst : Boolean := False) return Boolean
6077    is
6078       Type_1 : Entity_Id := T1;
6079       Type_2 : Entity_Id := T2;
6080       Are_Anonymous_Access_To_Subprogram_Types : Boolean := False;
6081
6082       function Base_Types_Match (T1, T2 : Entity_Id) return Boolean;
6083       --  If neither T1 nor T2 are generic actual types, or if they are in
6084       --  different scopes (e.g. parent and child instances), then verify that
6085       --  the base types are equal. Otherwise T1 and T2 must be on the same
6086       --  subtype chain. The whole purpose of this procedure is to prevent
6087       --  spurious ambiguities in an instantiation that may arise if two
6088       --  distinct generic types are instantiated with the same actual.
6089
6090       function Find_Designated_Type (T : Entity_Id) return Entity_Id;
6091       --  An access parameter can designate an incomplete type. If the
6092       --  incomplete type is the limited view of a type from a limited_
6093       --  with_clause, check whether the non-limited view is available. If
6094       --  it is a (non-limited) incomplete type, get the full view.
6095
6096       function Matches_Limited_With_View (T1, T2 : Entity_Id) return Boolean;
6097       --  Returns True if and only if either T1 denotes a limited view of T2
6098       --  or T2 denotes a limited view of T1. This can arise when the limited
6099       --  with view of a type is used in a subprogram declaration and the
6100       --  subprogram body is in the scope of a regular with clause for the
6101       --  same unit. In such a case, the two type entities can be considered
6102       --  identical for purposes of conformance checking.
6103
6104       ----------------------
6105       -- Base_Types_Match --
6106       ----------------------
6107
6108       function Base_Types_Match (T1, T2 : Entity_Id) return Boolean is
6109       begin
6110          if T1 = T2 then
6111             return True;
6112
6113          elsif Base_Type (T1) = Base_Type (T2) then
6114
6115             --  The following is too permissive. A more precise test should
6116             --  check that the generic actual is an ancestor subtype of the
6117             --  other ???.
6118
6119             return not Is_Generic_Actual_Type (T1)
6120               or else not Is_Generic_Actual_Type (T2)
6121               or else Scope (T1) /= Scope (T2);
6122
6123          else
6124             return False;
6125          end if;
6126       end Base_Types_Match;
6127
6128       --------------------------
6129       -- Find_Designated_Type --
6130       --------------------------
6131
6132       function Find_Designated_Type (T : Entity_Id) return Entity_Id is
6133          Desig : Entity_Id;
6134
6135       begin
6136          Desig := Directly_Designated_Type (T);
6137
6138          if Ekind (Desig) = E_Incomplete_Type then
6139
6140             --  If regular incomplete type, get full view if available
6141
6142             if Present (Full_View (Desig)) then
6143                Desig := Full_View (Desig);
6144
6145             --  If limited view of a type, get non-limited view if available,
6146             --  and check again for a regular incomplete type.
6147
6148             elsif Present (Non_Limited_View (Desig)) then
6149                Desig := Get_Full_View (Non_Limited_View (Desig));
6150             end if;
6151          end if;
6152
6153          return Desig;
6154       end Find_Designated_Type;
6155
6156       -------------------------------
6157       -- Matches_Limited_With_View --
6158       -------------------------------
6159
6160       function Matches_Limited_With_View (T1, T2 : Entity_Id) return Boolean is
6161       begin
6162          --  In some cases a type imported through a limited_with clause, and
6163          --  its nonlimited view are both visible, for example in an anonymous
6164          --  access-to-class-wide type in a formal. Both entities designate the
6165          --  same type.
6166
6167          if From_With_Type (T1)
6168            and then T2 = Available_View (T1)
6169          then
6170             return True;
6171
6172          elsif From_With_Type (T2)
6173            and then T1 = Available_View (T2)
6174          then
6175             return True;
6176
6177          elsif From_With_Type (T1)
6178            and then From_With_Type (T2)
6179            and then Available_View (T1) = Available_View (T2)
6180          then
6181             return True;
6182
6183          else
6184             return False;
6185          end if;
6186       end Matches_Limited_With_View;
6187
6188    --  Start of processing for Conforming_Types
6189
6190    begin
6191       --  The context is an instance association for a formal
6192       --  access-to-subprogram type; the formal parameter types require
6193       --  mapping because they may denote other formal parameters of the
6194       --  generic unit.
6195
6196       if Get_Inst then
6197          Type_1 := Get_Instance_Of (T1);
6198          Type_2 := Get_Instance_Of (T2);
6199       end if;
6200
6201       --  If one of the types is a view of the other introduced by a limited
6202       --  with clause, treat these as conforming for all purposes.
6203
6204       if Matches_Limited_With_View (T1, T2) then
6205          return True;
6206
6207       elsif Base_Types_Match (Type_1, Type_2) then
6208          return Ctype <= Mode_Conformant
6209            or else Subtypes_Statically_Match (Type_1, Type_2);
6210
6211       elsif Is_Incomplete_Or_Private_Type (Type_1)
6212         and then Present (Full_View (Type_1))
6213         and then Base_Types_Match (Full_View (Type_1), Type_2)
6214       then
6215          return Ctype <= Mode_Conformant
6216            or else Subtypes_Statically_Match (Full_View (Type_1), Type_2);
6217
6218       elsif Ekind (Type_2) = E_Incomplete_Type
6219         and then Present (Full_View (Type_2))
6220         and then Base_Types_Match (Type_1, Full_View (Type_2))
6221       then
6222          return Ctype <= Mode_Conformant
6223            or else Subtypes_Statically_Match (Type_1, Full_View (Type_2));
6224
6225       elsif Is_Private_Type (Type_2)
6226         and then In_Instance
6227         and then Present (Full_View (Type_2))
6228         and then Base_Types_Match (Type_1, Full_View (Type_2))
6229       then
6230          return Ctype <= Mode_Conformant
6231            or else Subtypes_Statically_Match (Type_1, Full_View (Type_2));
6232       end if;
6233
6234       --  Ada 2005 (AI-254): Anonymous access-to-subprogram types must be
6235       --  treated recursively because they carry a signature.
6236
6237       Are_Anonymous_Access_To_Subprogram_Types :=
6238         Ekind (Type_1) = Ekind (Type_2)
6239           and then
6240             (Ekind (Type_1) = E_Anonymous_Access_Subprogram_Type
6241              or else
6242                Ekind (Type_1) = E_Anonymous_Access_Protected_Subprogram_Type);
6243
6244       --  Test anonymous access type case. For this case, static subtype
6245       --  matching is required for mode conformance (RM 6.3.1(15)). We check
6246       --  the base types because we may have built internal subtype entities
6247       --  to handle null-excluding types (see Process_Formals).
6248
6249       if (Ekind (Base_Type (Type_1)) = E_Anonymous_Access_Type
6250             and then
6251           Ekind (Base_Type (Type_2)) = E_Anonymous_Access_Type)
6252         or else Are_Anonymous_Access_To_Subprogram_Types -- Ada 2005 (AI-254)
6253       then
6254          declare
6255             Desig_1 : Entity_Id;
6256             Desig_2 : Entity_Id;
6257
6258          begin
6259             --  In Ada 2005, access constant indicators must match for
6260             --  subtype conformance.
6261
6262             if Ada_Version >= Ada_2005
6263               and then Ctype >= Subtype_Conformant
6264               and then
6265                 Is_Access_Constant (Type_1) /= Is_Access_Constant (Type_2)
6266             then
6267                return False;
6268             end if;
6269
6270             Desig_1 := Find_Designated_Type (Type_1);
6271             Desig_2 := Find_Designated_Type (Type_2);
6272
6273             --  If the context is an instance association for a formal
6274             --  access-to-subprogram type; formal access parameter designated
6275             --  types require mapping because they may denote other formal
6276             --  parameters of the generic unit.
6277
6278             if Get_Inst then
6279                Desig_1 := Get_Instance_Of (Desig_1);
6280                Desig_2 := Get_Instance_Of (Desig_2);
6281             end if;
6282
6283             --  It is possible for a Class_Wide_Type to be introduced for an
6284             --  incomplete type, in which case there is a separate class_ wide
6285             --  type for the full view. The types conform if their Etypes
6286             --  conform, i.e. one may be the full view of the other. This can
6287             --  only happen in the context of an access parameter, other uses
6288             --  of an incomplete Class_Wide_Type are illegal.
6289
6290             if Is_Class_Wide_Type (Desig_1)
6291                  and then
6292                Is_Class_Wide_Type (Desig_2)
6293             then
6294                return
6295                  Conforming_Types
6296                    (Etype (Base_Type (Desig_1)),
6297                     Etype (Base_Type (Desig_2)), Ctype);
6298
6299             elsif Are_Anonymous_Access_To_Subprogram_Types then
6300                if Ada_Version < Ada_2005 then
6301                   return Ctype = Type_Conformant
6302                     or else
6303                       Subtypes_Statically_Match (Desig_1, Desig_2);
6304
6305                --  We must check the conformance of the signatures themselves
6306
6307                else
6308                   declare
6309                      Conformant : Boolean;
6310                   begin
6311                      Check_Conformance
6312                        (Desig_1, Desig_2, Ctype, False, Conformant);
6313                      return Conformant;
6314                   end;
6315                end if;
6316
6317             else
6318                return Base_Type (Desig_1) = Base_Type (Desig_2)
6319                 and then (Ctype = Type_Conformant
6320                             or else
6321                           Subtypes_Statically_Match (Desig_1, Desig_2));
6322             end if;
6323          end;
6324
6325       --  Otherwise definitely no match
6326
6327       else
6328          if ((Ekind (Type_1) = E_Anonymous_Access_Type
6329                and then Is_Access_Type (Type_2))
6330             or else (Ekind (Type_2) = E_Anonymous_Access_Type
6331                        and then Is_Access_Type (Type_1)))
6332            and then
6333              Conforming_Types
6334                (Designated_Type (Type_1), Designated_Type (Type_2), Ctype)
6335          then
6336             May_Hide_Profile := True;
6337          end if;
6338
6339          return False;
6340       end if;
6341    end Conforming_Types;
6342
6343    --------------------------
6344    -- Create_Extra_Formals --
6345    --------------------------
6346
6347    procedure Create_Extra_Formals (E : Entity_Id) is
6348       Formal      : Entity_Id;
6349       First_Extra : Entity_Id := Empty;
6350       Last_Extra  : Entity_Id;
6351       Formal_Type : Entity_Id;
6352       P_Formal    : Entity_Id := Empty;
6353
6354       function Add_Extra_Formal
6355         (Assoc_Entity : Entity_Id;
6356          Typ          : Entity_Id;
6357          Scope        : Entity_Id;
6358          Suffix       : String) return Entity_Id;
6359       --  Add an extra formal to the current list of formals and extra formals.
6360       --  The extra formal is added to the end of the list of extra formals,
6361       --  and also returned as the result. These formals are always of mode IN.
6362       --  The new formal has the type Typ, is declared in Scope, and its name
6363       --  is given by a concatenation of the name of Assoc_Entity and Suffix.
6364       --  The following suffixes are currently used. They should not be changed
6365       --  without coordinating with CodePeer, which makes use of these to
6366       --  provide better messages.
6367
6368       --  O denotes the Constrained bit.
6369       --  L denotes the accessibility level.
6370       --  BIP_xxx denotes an extra formal for a build-in-place function. See
6371       --  the full list in exp_ch6.BIP_Formal_Kind.
6372
6373       ----------------------
6374       -- Add_Extra_Formal --
6375       ----------------------
6376
6377       function Add_Extra_Formal
6378         (Assoc_Entity : Entity_Id;
6379          Typ          : Entity_Id;
6380          Scope        : Entity_Id;
6381          Suffix       : String) return Entity_Id
6382       is
6383          EF : constant Entity_Id :=
6384                 Make_Defining_Identifier (Sloc (Assoc_Entity),
6385                   Chars  => New_External_Name (Chars (Assoc_Entity),
6386                                                Suffix => Suffix));
6387
6388       begin
6389          --  A little optimization. Never generate an extra formal for the
6390          --  _init operand of an initialization procedure, since it could
6391          --  never be used.
6392
6393          if Chars (Formal) = Name_uInit then
6394             return Empty;
6395          end if;
6396
6397          Set_Ekind           (EF, E_In_Parameter);
6398          Set_Actual_Subtype  (EF, Typ);
6399          Set_Etype           (EF, Typ);
6400          Set_Scope           (EF, Scope);
6401          Set_Mechanism       (EF, Default_Mechanism);
6402          Set_Formal_Validity (EF);
6403
6404          if No (First_Extra) then
6405             First_Extra := EF;
6406             Set_Extra_Formals (Scope, First_Extra);
6407          end if;
6408
6409          if Present (Last_Extra) then
6410             Set_Extra_Formal (Last_Extra, EF);
6411          end if;
6412
6413          Last_Extra := EF;
6414
6415          return EF;
6416       end Add_Extra_Formal;
6417
6418    --  Start of processing for Create_Extra_Formals
6419
6420    begin
6421       --  We never generate extra formals if expansion is not active
6422       --  because we don't need them unless we are generating code.
6423
6424       if not Expander_Active then
6425          return;
6426       end if;
6427
6428       --  If this is a derived subprogram then the subtypes of the parent
6429       --  subprogram's formal parameters will be used to determine the need
6430       --  for extra formals.
6431
6432       if Is_Overloadable (E) and then Present (Alias (E)) then
6433          P_Formal := First_Formal (Alias (E));
6434       end if;
6435
6436       Last_Extra := Empty;
6437       Formal := First_Formal (E);
6438       while Present (Formal) loop
6439          Last_Extra := Formal;
6440          Next_Formal (Formal);
6441       end loop;
6442
6443       --  If Extra_formals were already created, don't do it again. This
6444       --  situation may arise for subprogram types created as part of
6445       --  dispatching calls (see Expand_Dispatching_Call)
6446
6447       if Present (Last_Extra) and then
6448         Present (Extra_Formal (Last_Extra))
6449       then
6450          return;
6451       end if;
6452
6453       --  If the subprogram is a predefined dispatching subprogram then don't
6454       --  generate any extra constrained or accessibility level formals. In
6455       --  general we suppress these for internal subprograms (by not calling
6456       --  Freeze_Subprogram and Create_Extra_Formals at all), but internally
6457       --  generated stream attributes do get passed through because extra
6458       --  build-in-place formals are needed in some cases (limited 'Input).
6459
6460       if Is_Predefined_Internal_Operation (E) then
6461          goto Test_For_Func_Result_Extras;
6462       end if;
6463
6464       Formal := First_Formal (E);
6465       while Present (Formal) loop
6466
6467          --  Create extra formal for supporting the attribute 'Constrained.
6468          --  The case of a private type view without discriminants also
6469          --  requires the extra formal if the underlying type has defaulted
6470          --  discriminants.
6471
6472          if Ekind (Formal) /= E_In_Parameter then
6473             if Present (P_Formal) then
6474                Formal_Type := Etype (P_Formal);
6475             else
6476                Formal_Type := Etype (Formal);
6477             end if;
6478
6479             --  Do not produce extra formals for Unchecked_Union parameters.
6480             --  Jump directly to the end of the loop.
6481
6482             if Is_Unchecked_Union (Base_Type (Formal_Type)) then
6483                goto Skip_Extra_Formal_Generation;
6484             end if;
6485
6486             if not Has_Discriminants (Formal_Type)
6487               and then Ekind (Formal_Type) in Private_Kind
6488               and then Present (Underlying_Type (Formal_Type))
6489             then
6490                Formal_Type := Underlying_Type (Formal_Type);
6491             end if;
6492
6493             --  Suppress the extra formal if formal's subtype is constrained or
6494             --  indefinite, or we're compiling for Ada 2012 and the underlying
6495             --  type is tagged and limited. In Ada 2012, a limited tagged type
6496             --  can have defaulted discriminants, but 'Constrained is required
6497             --  to return True, so the formal is never needed (see AI05-0214).
6498             --  Note that this ensures consistency of calling sequences for
6499             --  dispatching operations when some types in a class have defaults
6500             --  on discriminants and others do not (and requiring the extra
6501             --  formal would introduce distributed overhead).
6502
6503             if Has_Discriminants (Formal_Type)
6504               and then not Is_Constrained (Formal_Type)
6505               and then not Is_Indefinite_Subtype (Formal_Type)
6506               and then (Ada_Version < Ada_2012
6507                          or else
6508                            not (Is_Tagged_Type (Underlying_Type (Formal_Type))
6509                                  and then Is_Limited_Type (Formal_Type)))
6510             then
6511                Set_Extra_Constrained
6512                  (Formal, Add_Extra_Formal (Formal, Standard_Boolean, E, "O"));
6513             end if;
6514          end if;
6515
6516          --  Create extra formal for supporting accessibility checking. This
6517          --  is done for both anonymous access formals and formals of named
6518          --  access types that are marked as controlling formals. The latter
6519          --  case can occur when Expand_Dispatching_Call creates a subprogram
6520          --  type and substitutes the types of access-to-class-wide actuals
6521          --  for the anonymous access-to-specific-type of controlling formals.
6522          --  Base_Type is applied because in cases where there is a null
6523          --  exclusion the formal may have an access subtype.
6524
6525          --  This is suppressed if we specifically suppress accessibility
6526          --  checks at the package level for either the subprogram, or the
6527          --  package in which it resides. However, we do not suppress it
6528          --  simply if the scope has accessibility checks suppressed, since
6529          --  this could cause trouble when clients are compiled with a
6530          --  different suppression setting. The explicit checks at the
6531          --  package level are safe from this point of view.
6532
6533          if (Ekind (Base_Type (Etype (Formal))) = E_Anonymous_Access_Type
6534               or else (Is_Controlling_Formal (Formal)
6535                         and then Is_Access_Type (Base_Type (Etype (Formal)))))
6536            and then not
6537              (Explicit_Suppress (E, Accessibility_Check)
6538                or else
6539               Explicit_Suppress (Scope (E), Accessibility_Check))
6540            and then
6541              (No (P_Formal)
6542                or else Present (Extra_Accessibility (P_Formal)))
6543          then
6544             Set_Extra_Accessibility
6545               (Formal, Add_Extra_Formal (Formal, Standard_Natural, E, "L"));
6546          end if;
6547
6548          --  This label is required when skipping extra formal generation for
6549          --  Unchecked_Union parameters.
6550
6551          <<Skip_Extra_Formal_Generation>>
6552
6553          if Present (P_Formal) then
6554             Next_Formal (P_Formal);
6555          end if;
6556
6557          Next_Formal (Formal);
6558       end loop;
6559
6560       <<Test_For_Func_Result_Extras>>
6561
6562       --  Ada 2012 (AI05-234): "the accessibility level of the result of a
6563       --  function call is ... determined by the point of call ...".
6564
6565       if Needs_Result_Accessibility_Level (E) then
6566          Set_Extra_Accessibility_Of_Result
6567            (E, Add_Extra_Formal (E, Standard_Natural, E, "L"));
6568       end if;
6569
6570       --  Ada 2005 (AI-318-02): In the case of build-in-place functions, add
6571       --  appropriate extra formals. See type Exp_Ch6.BIP_Formal_Kind.
6572
6573       if Ada_Version >= Ada_2005 and then Is_Build_In_Place_Function (E) then
6574          declare
6575             Result_Subt : constant Entity_Id := Etype (E);
6576             Full_Subt   : constant Entity_Id := Available_View (Result_Subt);
6577             Formal_Typ  : Entity_Id;
6578
6579             Discard : Entity_Id;
6580             pragma Warnings (Off, Discard);
6581
6582          begin
6583             --  In the case of functions with unconstrained result subtypes,
6584             --  add a 4-state formal indicating whether the return object is
6585             --  allocated by the caller (1), or should be allocated by the
6586             --  callee on the secondary stack (2), in the global heap (3), or
6587             --  in a user-defined storage pool (4). For the moment we just use
6588             --  Natural for the type of this formal. Note that this formal
6589             --  isn't usually needed in the case where the result subtype is
6590             --  constrained, but it is needed when the function has a tagged
6591             --  result, because generally such functions can be called in a
6592             --  dispatching context and such calls must be handled like calls
6593             --  to a class-wide function.
6594
6595             if Needs_BIP_Alloc_Form (E) then
6596                Discard :=
6597                  Add_Extra_Formal
6598                    (E, Standard_Natural,
6599                     E, BIP_Formal_Suffix (BIP_Alloc_Form));
6600
6601                --  Add BIP_Storage_Pool, in case BIP_Alloc_Form indicates to
6602                --  use a user-defined pool. This formal is not added on
6603                --  .NET/JVM/ZFP as those targets do not support pools.
6604
6605                if VM_Target = No_VM
6606                  and then RTE_Available (RE_Root_Storage_Pool_Ptr)
6607                then
6608                   Discard :=
6609                     Add_Extra_Formal
6610                       (E, RTE (RE_Root_Storage_Pool_Ptr),
6611                        E, BIP_Formal_Suffix (BIP_Storage_Pool));
6612                end if;
6613             end if;
6614
6615             --  In the case of functions whose result type needs finalization,
6616             --  add an extra formal which represents the finalization master.
6617
6618             if Needs_BIP_Finalization_Master (E) then
6619                Discard :=
6620                  Add_Extra_Formal
6621                    (E, RTE (RE_Finalization_Master_Ptr),
6622                     E, BIP_Formal_Suffix (BIP_Finalization_Master));
6623             end if;
6624
6625             --  When the result type contains tasks, add two extra formals: the
6626             --  master of the tasks to be created, and the caller's activation
6627             --  chain.
6628
6629             if Has_Task (Full_Subt) then
6630                Discard :=
6631                  Add_Extra_Formal
6632                    (E, RTE (RE_Master_Id),
6633                     E, BIP_Formal_Suffix (BIP_Task_Master));
6634                Discard :=
6635                  Add_Extra_Formal
6636                    (E, RTE (RE_Activation_Chain_Access),
6637                     E, BIP_Formal_Suffix (BIP_Activation_Chain));
6638             end if;
6639
6640             --  All build-in-place functions get an extra formal that will be
6641             --  passed the address of the return object within the caller.
6642
6643             Formal_Typ :=
6644               Create_Itype (E_Anonymous_Access_Type, E, Scope_Id => Scope (E));
6645
6646             Set_Directly_Designated_Type (Formal_Typ, Result_Subt);
6647             Set_Etype (Formal_Typ, Formal_Typ);
6648             Set_Depends_On_Private
6649               (Formal_Typ, Has_Private_Component (Formal_Typ));
6650             Set_Is_Public (Formal_Typ, Is_Public (Scope (Formal_Typ)));
6651             Set_Is_Access_Constant (Formal_Typ, False);
6652
6653             --  Ada 2005 (AI-50217): Propagate the attribute that indicates
6654             --  the designated type comes from the limited view (for back-end
6655             --  purposes).
6656
6657             Set_From_With_Type (Formal_Typ, From_With_Type (Result_Subt));
6658
6659             Layout_Type (Formal_Typ);
6660
6661             Discard :=
6662               Add_Extra_Formal
6663                 (E, Formal_Typ, E, BIP_Formal_Suffix (BIP_Object_Access));
6664          end;
6665       end if;
6666    end Create_Extra_Formals;
6667
6668    -----------------------------
6669    -- Enter_Overloaded_Entity --
6670    -----------------------------
6671
6672    procedure Enter_Overloaded_Entity (S : Entity_Id) is
6673       E   : Entity_Id := Current_Entity_In_Scope (S);
6674       C_E : Entity_Id := Current_Entity (S);
6675
6676    begin
6677       if Present (E) then
6678          Set_Has_Homonym (E);
6679          Set_Has_Homonym (S);
6680       end if;
6681
6682       Set_Is_Immediately_Visible (S);
6683       Set_Scope (S, Current_Scope);
6684
6685       --  Chain new entity if front of homonym in current scope, so that
6686       --  homonyms are contiguous.
6687
6688       if Present (E)
6689         and then E /= C_E
6690       then
6691          while Homonym (C_E) /= E loop
6692             C_E := Homonym (C_E);
6693          end loop;
6694
6695          Set_Homonym (C_E, S);
6696
6697       else
6698          E := C_E;
6699          Set_Current_Entity (S);
6700       end if;
6701
6702       Set_Homonym (S, E);
6703
6704       Append_Entity (S, Current_Scope);
6705       Set_Public_Status (S);
6706
6707       if Debug_Flag_E then
6708          Write_Str ("New overloaded entity chain: ");
6709          Write_Name (Chars (S));
6710
6711          E := S;
6712          while Present (E) loop
6713             Write_Str (" "); Write_Int (Int (E));
6714             E := Homonym (E);
6715          end loop;
6716
6717          Write_Eol;
6718       end if;
6719
6720       --  Generate warning for hiding
6721
6722       if Warn_On_Hiding
6723         and then Comes_From_Source (S)
6724         and then In_Extended_Main_Source_Unit (S)
6725       then
6726          E := S;
6727          loop
6728             E := Homonym (E);
6729             exit when No (E);
6730
6731             --  Warn unless genuine overloading. Do not emit warning on
6732             --  hiding predefined operators in Standard (these are either an
6733             --  (artifact of our implicit declarations, or simple noise) but
6734             --  keep warning on a operator defined on a local subtype, because
6735             --  of the real danger that different operators may be applied in
6736             --  various parts of the program.
6737
6738             --  Note that if E and S have the same scope, there is never any
6739             --  hiding. Either the two conflict, and the program is illegal,
6740             --  or S is overriding an implicit inherited subprogram.
6741
6742             if Scope (E) /= Scope (S)
6743                   and then (not Is_Overloadable (E)
6744                              or else Subtype_Conformant (E, S))
6745                   and then (Is_Immediately_Visible (E)
6746                               or else
6747                             Is_Potentially_Use_Visible (S))
6748             then
6749                if Scope (E) /= Standard_Standard then
6750                   Error_Msg_Sloc := Sloc (E);
6751                   Error_Msg_N ("declaration of & hides one#?", S);
6752
6753                elsif Nkind (S) = N_Defining_Operator_Symbol
6754                  and then
6755                    Scope (Base_Type (Etype (First_Formal (S)))) /= Scope (S)
6756                then
6757                   Error_Msg_N
6758                     ("declaration of & hides predefined operator?", S);
6759                end if;
6760             end if;
6761          end loop;
6762       end if;
6763    end Enter_Overloaded_Entity;
6764
6765    -----------------------------
6766    -- Check_Untagged_Equality --
6767    -----------------------------
6768
6769    procedure Check_Untagged_Equality (Eq_Op : Entity_Id) is
6770       Typ      : constant Entity_Id := Etype (First_Formal (Eq_Op));
6771       Decl     : constant Node_Id   := Unit_Declaration_Node (Eq_Op);
6772       Obj_Decl : Node_Id;
6773
6774    begin
6775       if Nkind (Decl) = N_Subprogram_Declaration
6776         and then Is_Record_Type (Typ)
6777         and then not Is_Tagged_Type (Typ)
6778       then
6779          --  If the type is not declared in a package, or if we are in the
6780          --  body of the package or in some other scope, the new operation is
6781          --  not primitive, and therefore legal, though suspicious. If the
6782          --  type is a generic actual (sub)type, the operation is not primitive
6783          --  either because the base type is declared elsewhere.
6784
6785          if Is_Frozen (Typ) then
6786             if Ekind (Scope (Typ)) /= E_Package
6787               or else Scope (Typ) /= Current_Scope
6788             then
6789                null;
6790
6791             elsif Is_Generic_Actual_Type (Typ) then
6792                null;
6793
6794             elsif In_Package_Body (Scope (Typ)) then
6795                Error_Msg_NE
6796                  ("equality operator must be declared "
6797                    & "before type& is frozen", Eq_Op, Typ);
6798                Error_Msg_N
6799                  ("\move declaration to package spec", Eq_Op);
6800
6801             else
6802                Error_Msg_NE
6803                  ("equality operator must be declared "
6804                    & "before type& is frozen", Eq_Op, Typ);
6805
6806                Obj_Decl := Next (Parent (Typ));
6807                while Present (Obj_Decl)
6808                  and then Obj_Decl /= Decl
6809                loop
6810                   if Nkind (Obj_Decl) = N_Object_Declaration
6811                     and then Etype (Defining_Identifier (Obj_Decl)) = Typ
6812                   then
6813                      Error_Msg_NE ("type& is frozen by declaration?",
6814                         Obj_Decl, Typ);
6815                      Error_Msg_N
6816                        ("\an equality operator cannot be declared after this "
6817                          & "point (RM 4.5.2 (9.8)) (Ada 2012))?", Obj_Decl);
6818                      exit;
6819                   end if;
6820
6821                   Next (Obj_Decl);
6822                end loop;
6823             end if;
6824
6825          elsif not In_Same_List (Parent (Typ), Decl)
6826            and then not Is_Limited_Type (Typ)
6827          then
6828
6829             --  This makes it illegal to have a primitive equality declared in
6830             --  the private part if the type is visible.
6831
6832             Error_Msg_N ("equality operator appears too late", Eq_Op);
6833          end if;
6834       end if;
6835    end Check_Untagged_Equality;
6836
6837    -----------------------------
6838    -- Find_Corresponding_Spec --
6839    -----------------------------
6840
6841    function Find_Corresponding_Spec
6842      (N          : Node_Id;
6843       Post_Error : Boolean := True) return Entity_Id
6844    is
6845       Spec       : constant Node_Id   := Specification (N);
6846       Designator : constant Entity_Id := Defining_Entity (Spec);
6847
6848       E : Entity_Id;
6849
6850    begin
6851       E := Current_Entity (Designator);
6852       while Present (E) loop
6853
6854          --  We are looking for a matching spec. It must have the same scope,
6855          --  and the same name, and either be type conformant, or be the case
6856          --  of a library procedure spec and its body (which belong to one
6857          --  another regardless of whether they are type conformant or not).
6858
6859          if Scope (E) = Current_Scope then
6860             if Current_Scope = Standard_Standard
6861               or else (Ekind (E) = Ekind (Designator)
6862                          and then Type_Conformant (E, Designator))
6863             then
6864                --  Within an instantiation, we know that spec and body are
6865                --  subtype conformant, because they were subtype conformant
6866                --  in the generic. We choose the subtype-conformant entity
6867                --  here as well, to resolve spurious ambiguities in the
6868                --  instance that were not present in the generic (i.e. when
6869                --  two different types are given the same actual). If we are
6870                --  looking for a spec to match a body, full conformance is
6871                --  expected.
6872
6873                if In_Instance then
6874                   Set_Convention (Designator, Convention (E));
6875
6876                   --  Skip past subprogram bodies and subprogram renamings that
6877                   --  may appear to have a matching spec, but that aren't fully
6878                   --  conformant with it. That can occur in cases where an
6879                   --  actual type causes unrelated homographs in the instance.
6880
6881                   if Nkind_In (N, N_Subprogram_Body,
6882                                   N_Subprogram_Renaming_Declaration)
6883                     and then Present (Homonym (E))
6884                     and then not Fully_Conformant (Designator, E)
6885                   then
6886                      goto Next_Entity;
6887
6888                   elsif not Subtype_Conformant (Designator, E) then
6889                      goto Next_Entity;
6890                   end if;
6891                end if;
6892
6893                --  Ada 2012 (AI05-0165): For internally generated bodies of
6894                --  null procedures locate the internally generated spec. We
6895                --  enforce mode conformance since a tagged type may inherit
6896                --  from interfaces several null primitives which differ only
6897                --  in the mode of the formals.
6898
6899                if not (Comes_From_Source (E))
6900                  and then Is_Null_Procedure (E)
6901                  and then not Mode_Conformant (Designator, E)
6902                then
6903                   null;
6904
6905                elsif not Has_Completion (E) then
6906                   if Nkind (N) /= N_Subprogram_Body_Stub then
6907                      Set_Corresponding_Spec (N, E);
6908                   end if;
6909
6910                   Set_Has_Completion (E);
6911                   return E;
6912
6913                elsif Nkind (Parent (N)) = N_Subunit then
6914
6915                   --  If this is the proper body of a subunit, the completion
6916                   --  flag is set when analyzing the stub.
6917
6918                   return E;
6919
6920                --  If E is an internal function with a controlling result
6921                --  that was created for an operation inherited by a null
6922                --  extension, it may be overridden by a body without a previous
6923                --  spec (one more reason why these should be shunned). In that
6924                --  case remove the generated body if present, because the
6925                --  current one is the explicit overriding.
6926
6927                elsif Ekind (E) = E_Function
6928                  and then Ada_Version >= Ada_2005
6929                  and then not Comes_From_Source (E)
6930                  and then Has_Controlling_Result (E)
6931                  and then Is_Null_Extension (Etype (E))
6932                  and then Comes_From_Source (Spec)
6933                then
6934                   Set_Has_Completion (E, False);
6935
6936                   if Expander_Active
6937                     and then Nkind (Parent (E)) = N_Function_Specification
6938                   then
6939                      Remove
6940                        (Unit_Declaration_Node
6941                           (Corresponding_Body (Unit_Declaration_Node (E))));
6942
6943                      return E;
6944
6945                   --  If expansion is disabled, or if the wrapper function has
6946                   --  not been generated yet, this a late body overriding an
6947                   --  inherited operation, or it is an overriding by some other
6948                   --  declaration before the controlling result is frozen. In
6949                   --  either case this is a declaration of a new entity.
6950
6951                   else
6952                      return Empty;
6953                   end if;
6954
6955                --  If the body already exists, then this is an error unless
6956                --  the previous declaration is the implicit declaration of a
6957                --  derived subprogram. It is also legal for an instance to
6958                --  contain type conformant overloadable declarations (but the
6959                --  generic declaration may not), per 8.3(26/2).
6960
6961                elsif No (Alias (E))
6962                  and then not Is_Intrinsic_Subprogram (E)
6963                  and then not In_Instance
6964                  and then Post_Error
6965                then
6966                   Error_Msg_Sloc := Sloc (E);
6967
6968                   if Is_Imported (E) then
6969                      Error_Msg_NE
6970                       ("body not allowed for imported subprogram & declared#",
6971                         N, E);
6972                   else
6973                      Error_Msg_NE ("duplicate body for & declared#", N, E);
6974                   end if;
6975                end if;
6976
6977             --  Child units cannot be overloaded, so a conformance mismatch
6978             --  between body and a previous spec is an error.
6979
6980             elsif Is_Child_Unit (E)
6981               and then
6982                 Nkind (Unit_Declaration_Node (Designator)) = N_Subprogram_Body
6983               and then
6984                 Nkind (Parent (Unit_Declaration_Node (Designator))) =
6985                   N_Compilation_Unit
6986               and then Post_Error
6987             then
6988                Error_Msg_N
6989                  ("body of child unit does not match previous declaration", N);
6990             end if;
6991          end if;
6992
6993          <<Next_Entity>>
6994             E := Homonym (E);
6995       end loop;
6996
6997       --  On exit, we know that no previous declaration of subprogram exists
6998
6999       return Empty;
7000    end Find_Corresponding_Spec;
7001
7002    ----------------------
7003    -- Fully_Conformant --
7004    ----------------------
7005
7006    function Fully_Conformant (New_Id, Old_Id : Entity_Id) return Boolean is
7007       Result : Boolean;
7008    begin
7009       Check_Conformance (New_Id, Old_Id, Fully_Conformant, False, Result);
7010       return Result;
7011    end Fully_Conformant;
7012
7013    ----------------------------------
7014    -- Fully_Conformant_Expressions --
7015    ----------------------------------
7016
7017    function Fully_Conformant_Expressions
7018      (Given_E1 : Node_Id;
7019       Given_E2 : Node_Id) return Boolean
7020    is
7021       E1 : constant Node_Id := Original_Node (Given_E1);
7022       E2 : constant Node_Id := Original_Node (Given_E2);
7023       --  We always test conformance on original nodes, since it is possible
7024       --  for analysis and/or expansion to make things look as though they
7025       --  conform when they do not, e.g. by converting 1+2 into 3.
7026
7027       function FCE (Given_E1, Given_E2 : Node_Id) return Boolean
7028         renames Fully_Conformant_Expressions;
7029
7030       function FCL (L1, L2 : List_Id) return Boolean;
7031       --  Compare elements of two lists for conformance. Elements have to
7032       --  be conformant, and actuals inserted as default parameters do not
7033       --  match explicit actuals with the same value.
7034
7035       function FCO (Op_Node, Call_Node : Node_Id) return Boolean;
7036       --  Compare an operator node with a function call
7037
7038       ---------
7039       -- FCL --
7040       ---------
7041
7042       function FCL (L1, L2 : List_Id) return Boolean is
7043          N1, N2 : Node_Id;
7044
7045       begin
7046          if L1 = No_List then
7047             N1 := Empty;
7048          else
7049             N1 := First (L1);
7050          end if;
7051
7052          if L2 = No_List then
7053             N2 := Empty;
7054          else
7055             N2 := First (L2);
7056          end if;
7057
7058          --  Compare two lists, skipping rewrite insertions (we want to
7059          --  compare the original trees, not the expanded versions!)
7060
7061          loop
7062             if Is_Rewrite_Insertion (N1) then
7063                Next (N1);
7064             elsif Is_Rewrite_Insertion (N2) then
7065                Next (N2);
7066             elsif No (N1) then
7067                return No (N2);
7068             elsif No (N2) then
7069                return False;
7070             elsif not FCE (N1, N2) then
7071                return False;
7072             else
7073                Next (N1);
7074                Next (N2);
7075             end if;
7076          end loop;
7077       end FCL;
7078
7079       ---------
7080       -- FCO --
7081       ---------
7082
7083       function FCO (Op_Node, Call_Node : Node_Id) return Boolean is
7084          Actuals : constant List_Id := Parameter_Associations (Call_Node);
7085          Act     : Node_Id;
7086
7087       begin
7088          if No (Actuals)
7089             or else Entity (Op_Node) /= Entity (Name (Call_Node))
7090          then
7091             return False;
7092
7093          else
7094             Act := First (Actuals);
7095
7096             if Nkind (Op_Node) in N_Binary_Op then
7097                if not FCE (Left_Opnd (Op_Node), Act) then
7098                   return False;
7099                end if;
7100
7101                Next (Act);
7102             end if;
7103
7104             return Present (Act)
7105               and then FCE (Right_Opnd (Op_Node), Act)
7106               and then No (Next (Act));
7107          end if;
7108       end FCO;
7109
7110    --  Start of processing for Fully_Conformant_Expressions
7111
7112    begin
7113       --  Non-conformant if paren count does not match. Note: if some idiot
7114       --  complains that we don't do this right for more than 3 levels of
7115       --  parentheses, they will be treated with the respect they deserve!
7116
7117       if Paren_Count (E1) /= Paren_Count (E2) then
7118          return False;
7119
7120       --  If same entities are referenced, then they are conformant even if
7121       --  they have different forms (RM 8.3.1(19-20)).
7122
7123       elsif Is_Entity_Name (E1) and then Is_Entity_Name (E2) then
7124          if Present (Entity (E1)) then
7125             return Entity (E1) = Entity (E2)
7126               or else (Chars (Entity (E1)) = Chars (Entity (E2))
7127                         and then Ekind (Entity (E1)) = E_Discriminant
7128                         and then Ekind (Entity (E2)) = E_In_Parameter);
7129
7130          elsif Nkind (E1) = N_Expanded_Name
7131            and then Nkind (E2) = N_Expanded_Name
7132            and then Nkind (Selector_Name (E1)) = N_Character_Literal
7133            and then Nkind (Selector_Name (E2)) = N_Character_Literal
7134          then
7135             return Chars (Selector_Name (E1)) = Chars (Selector_Name (E2));
7136
7137          else
7138             --  Identifiers in component associations don't always have
7139             --  entities, but their names must conform.
7140
7141             return Nkind  (E1) = N_Identifier
7142               and then Nkind (E2) = N_Identifier
7143               and then Chars (E1) = Chars (E2);
7144          end if;
7145
7146       elsif Nkind (E1) = N_Character_Literal
7147         and then Nkind (E2) = N_Expanded_Name
7148       then
7149          return Nkind (Selector_Name (E2)) = N_Character_Literal
7150            and then Chars (E1) = Chars (Selector_Name (E2));
7151
7152       elsif Nkind (E2) = N_Character_Literal
7153         and then Nkind (E1) = N_Expanded_Name
7154       then
7155          return Nkind (Selector_Name (E1)) = N_Character_Literal
7156            and then Chars (E2) = Chars (Selector_Name (E1));
7157
7158       elsif Nkind (E1) in N_Op
7159         and then Nkind (E2) = N_Function_Call
7160       then
7161          return FCO (E1, E2);
7162
7163       elsif Nkind (E2) in N_Op
7164         and then Nkind (E1) = N_Function_Call
7165       then
7166          return FCO (E2, E1);
7167
7168       --  Otherwise we must have the same syntactic entity
7169
7170       elsif Nkind (E1) /= Nkind (E2) then
7171          return False;
7172
7173       --  At this point, we specialize by node type
7174
7175       else
7176          case Nkind (E1) is
7177
7178             when N_Aggregate =>
7179                return
7180                  FCL (Expressions (E1), Expressions (E2))
7181                    and then
7182                  FCL (Component_Associations (E1),
7183                       Component_Associations (E2));
7184
7185             when N_Allocator =>
7186                if Nkind (Expression (E1)) = N_Qualified_Expression
7187                     or else
7188                   Nkind (Expression (E2)) = N_Qualified_Expression
7189                then
7190                   return FCE (Expression (E1), Expression (E2));
7191
7192                --  Check that the subtype marks and any constraints
7193                --  are conformant
7194
7195                else
7196                   declare
7197                      Indic1 : constant Node_Id := Expression (E1);
7198                      Indic2 : constant Node_Id := Expression (E2);
7199                      Elt1   : Node_Id;
7200                      Elt2   : Node_Id;
7201
7202                   begin
7203                      if Nkind (Indic1) /= N_Subtype_Indication then
7204                         return
7205                           Nkind (Indic2) /= N_Subtype_Indication
7206                             and then Entity (Indic1) = Entity (Indic2);
7207
7208                      elsif Nkind (Indic2) /= N_Subtype_Indication then
7209                         return
7210                           Nkind (Indic1) /= N_Subtype_Indication
7211                             and then Entity (Indic1) = Entity (Indic2);
7212
7213                      else
7214                         if Entity (Subtype_Mark (Indic1)) /=
7215                           Entity (Subtype_Mark (Indic2))
7216                         then
7217                            return False;
7218                         end if;
7219
7220                         Elt1 := First (Constraints (Constraint (Indic1)));
7221                         Elt2 := First (Constraints (Constraint (Indic2)));
7222                         while Present (Elt1) and then Present (Elt2) loop
7223                            if not FCE (Elt1, Elt2) then
7224                               return False;
7225                            end if;
7226
7227                            Next (Elt1);
7228                            Next (Elt2);
7229                         end loop;
7230
7231                         return True;
7232                      end if;
7233                   end;
7234                end if;
7235
7236             when N_Attribute_Reference =>
7237                return
7238                  Attribute_Name (E1) = Attribute_Name (E2)
7239                    and then FCL (Expressions (E1), Expressions (E2));
7240
7241             when N_Binary_Op =>
7242                return
7243                  Entity (E1) = Entity (E2)
7244                    and then FCE (Left_Opnd  (E1), Left_Opnd  (E2))
7245                    and then FCE (Right_Opnd (E1), Right_Opnd (E2));
7246
7247             when N_Short_Circuit | N_Membership_Test =>
7248                return
7249                  FCE (Left_Opnd  (E1), Left_Opnd  (E2))
7250                    and then
7251                  FCE (Right_Opnd (E1), Right_Opnd (E2));
7252
7253             when N_Case_Expression =>
7254                declare
7255                   Alt1 : Node_Id;
7256                   Alt2 : Node_Id;
7257
7258                begin
7259                   if not FCE (Expression (E1), Expression (E2)) then
7260                      return False;
7261
7262                   else
7263                      Alt1 := First (Alternatives (E1));
7264                      Alt2 := First (Alternatives (E2));
7265                      loop
7266                         if Present (Alt1) /= Present (Alt2) then
7267                            return False;
7268                         elsif No (Alt1) then
7269                            return True;
7270                         end if;
7271
7272                         if not FCE (Expression (Alt1), Expression (Alt2))
7273                           or else not FCL (Discrete_Choices (Alt1),
7274                                            Discrete_Choices (Alt2))
7275                         then
7276                            return False;
7277                         end if;
7278
7279                         Next (Alt1);
7280                         Next (Alt2);
7281                      end loop;
7282                   end if;
7283                end;
7284
7285             when N_Character_Literal =>
7286                return
7287                  Char_Literal_Value (E1) = Char_Literal_Value (E2);
7288
7289             when N_Component_Association =>
7290                return
7291                  FCL (Choices (E1), Choices (E2))
7292                    and then
7293                  FCE (Expression (E1), Expression (E2));
7294
7295             when N_Conditional_Expression =>
7296                return
7297                  FCL (Expressions (E1), Expressions (E2));
7298
7299             when N_Explicit_Dereference =>
7300                return
7301                  FCE (Prefix (E1), Prefix (E2));
7302
7303             when N_Extension_Aggregate =>
7304                return
7305                  FCL (Expressions (E1), Expressions (E2))
7306                    and then Null_Record_Present (E1) =
7307                             Null_Record_Present (E2)
7308                    and then FCL (Component_Associations (E1),
7309                                Component_Associations (E2));
7310
7311             when N_Function_Call =>
7312                return
7313                  FCE (Name (E1), Name (E2))
7314                    and then
7315                  FCL (Parameter_Associations (E1),
7316                       Parameter_Associations (E2));
7317
7318             when N_Indexed_Component =>
7319                return
7320                  FCE (Prefix (E1), Prefix (E2))
7321                    and then
7322                  FCL (Expressions (E1), Expressions (E2));
7323
7324             when N_Integer_Literal =>
7325                return (Intval (E1) = Intval (E2));
7326
7327             when N_Null =>
7328                return True;
7329
7330             when N_Operator_Symbol =>
7331                return
7332                  Chars (E1) = Chars (E2);
7333
7334             when N_Others_Choice =>
7335                return True;
7336
7337             when N_Parameter_Association =>
7338                return
7339                  Chars (Selector_Name (E1))  = Chars (Selector_Name (E2))
7340                    and then FCE (Explicit_Actual_Parameter (E1),
7341                                  Explicit_Actual_Parameter (E2));
7342
7343             when N_Qualified_Expression =>
7344                return
7345                  FCE (Subtype_Mark (E1), Subtype_Mark (E2))
7346                    and then
7347                  FCE (Expression (E1), Expression (E2));
7348
7349             when N_Quantified_Expression =>
7350                if not FCE (Condition (E1), Condition (E2)) then
7351                   return False;
7352                end if;
7353
7354                if Present (Loop_Parameter_Specification (E1))
7355                  and then Present (Loop_Parameter_Specification (E2))
7356                then
7357                   declare
7358                      L1 : constant Node_Id :=
7359                        Loop_Parameter_Specification (E1);
7360                      L2 : constant Node_Id :=
7361                        Loop_Parameter_Specification (E2);
7362
7363                   begin
7364                      return
7365                        Reverse_Present (L1) = Reverse_Present (L2)
7366                          and then
7367                            FCE (Defining_Identifier (L1),
7368                                 Defining_Identifier (L2))
7369                          and then
7370                            FCE (Discrete_Subtype_Definition (L1),
7371                                 Discrete_Subtype_Definition (L2));
7372                   end;
7373
7374                else   --  quantified expression with an iterator
7375                   declare
7376                      I1 : constant Node_Id := Iterator_Specification (E1);
7377                      I2 : constant Node_Id := Iterator_Specification (E2);
7378
7379                   begin
7380                      return
7381                        FCE (Defining_Identifier (I1),
7382                             Defining_Identifier (I2))
7383                        and then
7384                          Of_Present (I1) = Of_Present (I2)
7385                        and then
7386                          Reverse_Present (I1) = Reverse_Present (I2)
7387                        and then FCE (Name (I1), Name (I2))
7388                        and then FCE (Subtype_Indication (I1),
7389                                       Subtype_Indication (I2));
7390                   end;
7391                end if;
7392
7393             when N_Range =>
7394                return
7395                  FCE (Low_Bound (E1), Low_Bound (E2))
7396                    and then
7397                  FCE (High_Bound (E1), High_Bound (E2));
7398
7399             when N_Real_Literal =>
7400                return (Realval (E1) = Realval (E2));
7401
7402             when N_Selected_Component =>
7403                return
7404                  FCE (Prefix (E1), Prefix (E2))
7405                    and then
7406                  FCE (Selector_Name (E1), Selector_Name (E2));
7407
7408             when N_Slice =>
7409                return
7410                  FCE (Prefix (E1), Prefix (E2))
7411                    and then
7412                  FCE (Discrete_Range (E1), Discrete_Range (E2));
7413
7414             when N_String_Literal =>
7415                declare
7416                   S1 : constant String_Id := Strval (E1);
7417                   S2 : constant String_Id := Strval (E2);
7418                   L1 : constant Nat       := String_Length (S1);
7419                   L2 : constant Nat       := String_Length (S2);
7420
7421                begin
7422                   if L1 /= L2 then
7423                      return False;
7424
7425                   else
7426                      for J in 1 .. L1 loop
7427                         if Get_String_Char (S1, J) /=
7428                            Get_String_Char (S2, J)
7429                         then
7430                            return False;
7431                         end if;
7432                      end loop;
7433
7434                      return True;
7435                   end if;
7436                end;
7437
7438             when N_Type_Conversion =>
7439                return
7440                  FCE (Subtype_Mark (E1), Subtype_Mark (E2))
7441                    and then
7442                  FCE (Expression (E1), Expression (E2));
7443
7444             when N_Unary_Op =>
7445                return
7446                  Entity (E1) = Entity (E2)
7447                    and then
7448                  FCE (Right_Opnd (E1), Right_Opnd (E2));
7449
7450             when N_Unchecked_Type_Conversion =>
7451                return
7452                  FCE (Subtype_Mark (E1), Subtype_Mark (E2))
7453                    and then
7454                  FCE (Expression (E1), Expression (E2));
7455
7456             --  All other node types cannot appear in this context. Strictly
7457             --  we should raise a fatal internal error. Instead we just ignore
7458             --  the nodes. This means that if anyone makes a mistake in the
7459             --  expander and mucks an expression tree irretrievably, the
7460             --  result will be a failure to detect a (probably very obscure)
7461             --  case of non-conformance, which is better than bombing on some
7462             --  case where two expressions do in fact conform.
7463
7464             when others =>
7465                return True;
7466
7467          end case;
7468       end if;
7469    end Fully_Conformant_Expressions;
7470
7471    ----------------------------------------
7472    -- Fully_Conformant_Discrete_Subtypes --
7473    ----------------------------------------
7474
7475    function Fully_Conformant_Discrete_Subtypes
7476      (Given_S1 : Node_Id;
7477       Given_S2 : Node_Id) return Boolean
7478    is
7479       S1 : constant Node_Id := Original_Node (Given_S1);
7480       S2 : constant Node_Id := Original_Node (Given_S2);
7481
7482       function Conforming_Bounds (B1, B2 : Node_Id) return Boolean;
7483       --  Special-case for a bound given by a discriminant, which in the body
7484       --  is replaced with the discriminal of the enclosing type.
7485
7486       function Conforming_Ranges (R1, R2 : Node_Id) return Boolean;
7487       --  Check both bounds
7488
7489       -----------------------
7490       -- Conforming_Bounds --
7491       -----------------------
7492
7493       function Conforming_Bounds (B1, B2 : Node_Id) return Boolean is
7494       begin
7495          if Is_Entity_Name (B1)
7496            and then Is_Entity_Name (B2)
7497            and then Ekind (Entity (B1)) = E_Discriminant
7498          then
7499             return Chars (B1) = Chars (B2);
7500
7501          else
7502             return Fully_Conformant_Expressions (B1, B2);
7503          end if;
7504       end Conforming_Bounds;
7505
7506       -----------------------
7507       -- Conforming_Ranges --
7508       -----------------------
7509
7510       function Conforming_Ranges (R1, R2 : Node_Id) return Boolean is
7511       begin
7512          return
7513            Conforming_Bounds (Low_Bound (R1), Low_Bound (R2))
7514              and then
7515            Conforming_Bounds (High_Bound (R1), High_Bound (R2));
7516       end Conforming_Ranges;
7517
7518    --  Start of processing for Fully_Conformant_Discrete_Subtypes
7519
7520    begin
7521       if Nkind (S1) /= Nkind (S2) then
7522          return False;
7523
7524       elsif Is_Entity_Name (S1) then
7525          return Entity (S1) = Entity (S2);
7526
7527       elsif Nkind (S1) = N_Range then
7528          return Conforming_Ranges (S1, S2);
7529
7530       elsif Nkind (S1) = N_Subtype_Indication then
7531          return
7532             Entity (Subtype_Mark (S1)) = Entity (Subtype_Mark (S2))
7533               and then
7534             Conforming_Ranges
7535               (Range_Expression (Constraint (S1)),
7536                Range_Expression (Constraint (S2)));
7537       else
7538          return True;
7539       end if;
7540    end Fully_Conformant_Discrete_Subtypes;
7541
7542    --------------------
7543    -- Install_Entity --
7544    --------------------
7545
7546    procedure Install_Entity (E : Entity_Id) is
7547       Prev : constant Entity_Id := Current_Entity (E);
7548    begin
7549       Set_Is_Immediately_Visible (E);
7550       Set_Current_Entity (E);
7551       Set_Homonym (E, Prev);
7552    end Install_Entity;
7553
7554    ---------------------
7555    -- Install_Formals --
7556    ---------------------
7557
7558    procedure Install_Formals (Id : Entity_Id) is
7559       F : Entity_Id;
7560    begin
7561       F := First_Formal (Id);
7562       while Present (F) loop
7563          Install_Entity (F);
7564          Next_Formal (F);
7565       end loop;
7566    end Install_Formals;
7567
7568    -----------------------------
7569    -- Is_Interface_Conformant --
7570    -----------------------------
7571
7572    function Is_Interface_Conformant
7573      (Tagged_Type : Entity_Id;
7574       Iface_Prim  : Entity_Id;
7575       Prim        : Entity_Id) return Boolean
7576    is
7577       Iface : constant Entity_Id := Find_Dispatching_Type (Iface_Prim);
7578       Typ   : constant Entity_Id := Find_Dispatching_Type (Prim);
7579
7580       function Controlling_Formal (Prim : Entity_Id) return Entity_Id;
7581       --  Return the controlling formal of Prim
7582
7583       ------------------------
7584       -- Controlling_Formal --
7585       ------------------------
7586
7587       function Controlling_Formal (Prim : Entity_Id) return Entity_Id is
7588          E : Entity_Id := First_Entity (Prim);
7589
7590       begin
7591          while Present (E) loop
7592             if Is_Formal (E) and then Is_Controlling_Formal (E) then
7593                return E;
7594             end if;
7595
7596             Next_Entity (E);
7597          end loop;
7598
7599          return Empty;
7600       end Controlling_Formal;
7601
7602       --  Local variables
7603
7604       Iface_Ctrl_F : constant Entity_Id := Controlling_Formal (Iface_Prim);
7605       Prim_Ctrl_F  : constant Entity_Id := Controlling_Formal (Prim);
7606
7607    --  Start of processing for Is_Interface_Conformant
7608
7609    begin
7610       pragma Assert (Is_Subprogram (Iface_Prim)
7611         and then Is_Subprogram (Prim)
7612         and then Is_Dispatching_Operation (Iface_Prim)
7613         and then Is_Dispatching_Operation (Prim));
7614
7615       pragma Assert (Is_Interface (Iface)
7616         or else (Present (Alias (Iface_Prim))
7617                    and then
7618                      Is_Interface
7619                        (Find_Dispatching_Type (Ultimate_Alias (Iface_Prim)))));
7620
7621       if Prim = Iface_Prim
7622         or else not Is_Subprogram (Prim)
7623         or else Ekind (Prim) /= Ekind (Iface_Prim)
7624         or else not Is_Dispatching_Operation (Prim)
7625         or else Scope (Prim) /= Scope (Tagged_Type)
7626         or else No (Typ)
7627         or else Base_Type (Typ) /= Tagged_Type
7628         or else not Primitive_Names_Match (Iface_Prim, Prim)
7629       then
7630          return False;
7631
7632       --  The mode of the controlling formals must match
7633
7634       elsif Present (Iface_Ctrl_F)
7635          and then Present (Prim_Ctrl_F)
7636          and then Ekind (Iface_Ctrl_F) /= Ekind (Prim_Ctrl_F)
7637       then
7638          return False;
7639
7640       --  Case of a procedure, or a function whose result type matches the
7641       --  result type of the interface primitive, or a function that has no
7642       --  controlling result (I or access I).
7643
7644       elsif Ekind (Iface_Prim) = E_Procedure
7645         or else Etype (Prim) = Etype (Iface_Prim)
7646         or else not Has_Controlling_Result (Prim)
7647       then
7648          return Type_Conformant
7649                   (Iface_Prim, Prim, Skip_Controlling_Formals => True);
7650
7651       --  Case of a function returning an interface, or an access to one.
7652       --  Check that the return types correspond.
7653
7654       elsif Implements_Interface (Typ, Iface) then
7655          if (Ekind (Etype (Prim)) = E_Anonymous_Access_Type)
7656               /=
7657             (Ekind (Etype (Iface_Prim)) = E_Anonymous_Access_Type)
7658          then
7659             return False;
7660          else
7661             return
7662               Type_Conformant (Prim, Iface_Prim,
7663                 Skip_Controlling_Formals => True);
7664          end if;
7665
7666       else
7667          return False;
7668       end if;
7669    end Is_Interface_Conformant;
7670
7671    ---------------------------------
7672    -- Is_Non_Overriding_Operation --
7673    ---------------------------------
7674
7675    function Is_Non_Overriding_Operation
7676      (Prev_E : Entity_Id;
7677       New_E  : Entity_Id) return Boolean
7678    is
7679       Formal : Entity_Id;
7680       F_Typ  : Entity_Id;
7681       G_Typ  : Entity_Id := Empty;
7682
7683       function Get_Generic_Parent_Type (F_Typ : Entity_Id) return Entity_Id;
7684       --  If F_Type is a derived type associated with a generic actual subtype,
7685       --  then return its Generic_Parent_Type attribute, else return Empty.
7686
7687       function Types_Correspond
7688         (P_Type : Entity_Id;
7689          N_Type : Entity_Id) return Boolean;
7690       --  Returns true if and only if the types (or designated types in the
7691       --  case of anonymous access types) are the same or N_Type is derived
7692       --  directly or indirectly from P_Type.
7693
7694       -----------------------------
7695       -- Get_Generic_Parent_Type --
7696       -----------------------------
7697
7698       function Get_Generic_Parent_Type (F_Typ : Entity_Id) return Entity_Id is
7699          G_Typ : Entity_Id;
7700          Defn  : Node_Id;
7701          Indic : Node_Id;
7702
7703       begin
7704          if Is_Derived_Type (F_Typ)
7705            and then Nkind (Parent (F_Typ)) = N_Full_Type_Declaration
7706          then
7707             --  The tree must be traversed to determine the parent subtype in
7708             --  the generic unit, which unfortunately isn't always available
7709             --  via semantic attributes. ??? (Note: The use of Original_Node
7710             --  is needed for cases where a full derived type has been
7711             --  rewritten.)
7712
7713             Defn := Type_Definition (Original_Node (Parent (F_Typ)));
7714             if Nkind (Defn) = N_Derived_Type_Definition then
7715                Indic := Subtype_Indication (Defn);
7716
7717                if Nkind (Indic) = N_Subtype_Indication then
7718                   G_Typ := Entity (Subtype_Mark (Indic));
7719                else
7720                   G_Typ := Entity (Indic);
7721                end if;
7722
7723                if Nkind (Parent (G_Typ)) = N_Subtype_Declaration
7724                  and then Present (Generic_Parent_Type (Parent (G_Typ)))
7725                then
7726                   return Generic_Parent_Type (Parent (G_Typ));
7727                end if;
7728             end if;
7729          end if;
7730
7731          return Empty;
7732       end Get_Generic_Parent_Type;
7733
7734       ----------------------
7735       -- Types_Correspond --
7736       ----------------------
7737
7738       function Types_Correspond
7739         (P_Type : Entity_Id;
7740          N_Type : Entity_Id) return Boolean
7741       is
7742          Prev_Type : Entity_Id := Base_Type (P_Type);
7743          New_Type  : Entity_Id := Base_Type (N_Type);
7744
7745       begin
7746          if Ekind (Prev_Type) = E_Anonymous_Access_Type then
7747             Prev_Type := Designated_Type (Prev_Type);
7748          end if;
7749
7750          if Ekind (New_Type) = E_Anonymous_Access_Type then
7751             New_Type := Designated_Type (New_Type);
7752          end if;
7753
7754          if Prev_Type = New_Type then
7755             return True;
7756
7757          elsif not Is_Class_Wide_Type (New_Type) then
7758             while Etype (New_Type) /= New_Type loop
7759                New_Type := Etype (New_Type);
7760                if New_Type = Prev_Type then
7761                   return True;
7762                end if;
7763             end loop;
7764          end if;
7765          return False;
7766       end Types_Correspond;
7767
7768    --  Start of processing for Is_Non_Overriding_Operation
7769
7770    begin
7771       --  In the case where both operations are implicit derived subprograms
7772       --  then neither overrides the other. This can only occur in certain
7773       --  obscure cases (e.g., derivation from homographs created in a generic
7774       --  instantiation).
7775
7776       if Present (Alias (Prev_E)) and then Present (Alias (New_E)) then
7777          return True;
7778
7779       elsif Ekind (Current_Scope) = E_Package
7780         and then Is_Generic_Instance (Current_Scope)
7781         and then In_Private_Part (Current_Scope)
7782         and then Comes_From_Source (New_E)
7783       then
7784          --  We examine the formals and result type of the inherited operation,
7785          --  to determine whether their type is derived from (the instance of)
7786          --  a generic type. The first such formal or result type is the one
7787          --  tested.
7788
7789          Formal := First_Formal (Prev_E);
7790          while Present (Formal) loop
7791             F_Typ := Base_Type (Etype (Formal));
7792
7793             if Ekind (F_Typ) = E_Anonymous_Access_Type then
7794                F_Typ := Designated_Type (F_Typ);
7795             end if;
7796
7797             G_Typ := Get_Generic_Parent_Type (F_Typ);
7798             exit when Present (G_Typ);
7799
7800             Next_Formal (Formal);
7801          end loop;
7802
7803          if No (G_Typ) and then Ekind (Prev_E) = E_Function then
7804             G_Typ := Get_Generic_Parent_Type (Base_Type (Etype (Prev_E)));
7805          end if;
7806
7807          if No (G_Typ) then
7808             return False;
7809          end if;
7810
7811          --  If the generic type is a private type, then the original operation
7812          --  was not overriding in the generic, because there was no primitive
7813          --  operation to override.
7814
7815          if Nkind (Parent (G_Typ)) = N_Formal_Type_Declaration
7816            and then Nkind (Formal_Type_Definition (Parent (G_Typ))) =
7817                       N_Formal_Private_Type_Definition
7818          then
7819             return True;
7820
7821          --  The generic parent type is the ancestor of a formal derived
7822          --  type declaration. We need to check whether it has a primitive
7823          --  operation that should be overridden by New_E in the generic.
7824
7825          else
7826             declare
7827                P_Formal : Entity_Id;
7828                N_Formal : Entity_Id;
7829                P_Typ    : Entity_Id;
7830                N_Typ    : Entity_Id;
7831                P_Prim   : Entity_Id;
7832                Prim_Elt : Elmt_Id := First_Elmt (Primitive_Operations (G_Typ));
7833
7834             begin
7835                while Present (Prim_Elt) loop
7836                   P_Prim := Node (Prim_Elt);
7837
7838                   if Chars (P_Prim) = Chars (New_E)
7839                     and then Ekind (P_Prim) = Ekind (New_E)
7840                   then
7841                      P_Formal := First_Formal (P_Prim);
7842                      N_Formal := First_Formal (New_E);
7843                      while Present (P_Formal) and then Present (N_Formal) loop
7844                         P_Typ := Etype (P_Formal);
7845                         N_Typ := Etype (N_Formal);
7846
7847                         if not Types_Correspond (P_Typ, N_Typ) then
7848                            exit;
7849                         end if;
7850
7851                         Next_Entity (P_Formal);
7852                         Next_Entity (N_Formal);
7853                      end loop;
7854
7855                      --  Found a matching primitive operation belonging to the
7856                      --  formal ancestor type, so the new subprogram is
7857                      --  overriding.
7858
7859                      if No (P_Formal)
7860                        and then No (N_Formal)
7861                        and then (Ekind (New_E) /= E_Function
7862                                   or else
7863                                  Types_Correspond
7864                                    (Etype (P_Prim), Etype (New_E)))
7865                      then
7866                         return False;
7867                      end if;
7868                   end if;
7869
7870                   Next_Elmt (Prim_Elt);
7871                end loop;
7872
7873                --  If no match found, then the new subprogram does not
7874                --  override in the generic (nor in the instance).
7875
7876                --  If the type in question is not abstract, and the subprogram
7877                --  is, this will be an error if the new operation is in the
7878                --  private part of the instance. Emit a warning now, which will
7879                --  make the subsequent error message easier to understand.
7880
7881                if not Is_Abstract_Type (F_Typ)
7882                  and then Is_Abstract_Subprogram (Prev_E)
7883                  and then In_Private_Part (Current_Scope)
7884                then
7885                   Error_Msg_Node_2 := F_Typ;
7886                   Error_Msg_NE
7887                     ("private operation& in generic unit does not override " &
7888                      "any primitive operation of& (RM 12.3 (18))?",
7889                      New_E, New_E);
7890                end if;
7891
7892                return True;
7893             end;
7894          end if;
7895       else
7896          return False;
7897       end if;
7898    end Is_Non_Overriding_Operation;
7899
7900    -------------------------------------
7901    -- List_Inherited_Pre_Post_Aspects --
7902    -------------------------------------
7903
7904    procedure List_Inherited_Pre_Post_Aspects (E : Entity_Id) is
7905    begin
7906       if Opt.List_Inherited_Aspects
7907         and then (Is_Subprogram (E) or else Is_Generic_Subprogram (E))
7908       then
7909          declare
7910             Inherited : constant Subprogram_List :=
7911                           Inherited_Subprograms (E);
7912             P         : Node_Id;
7913
7914          begin
7915             for J in Inherited'Range loop
7916                P := Spec_PPC_List (Contract (Inherited (J)));
7917
7918                while Present (P) loop
7919                   Error_Msg_Sloc := Sloc (P);
7920
7921                   if Class_Present (P) and then not Split_PPC (P) then
7922                      if Pragma_Name (P) = Name_Precondition then
7923                         Error_Msg_N
7924                           ("?info: & inherits `Pre''Class` aspect from #", E);
7925                      else
7926                         Error_Msg_N
7927                           ("?info: & inherits `Post''Class` aspect from #", E);
7928                      end if;
7929                   end if;
7930
7931                   P := Next_Pragma (P);
7932                end loop;
7933             end loop;
7934          end;
7935       end if;
7936    end List_Inherited_Pre_Post_Aspects;
7937
7938    ------------------------------
7939    -- Make_Inequality_Operator --
7940    ------------------------------
7941
7942    --  S is the defining identifier of an equality operator. We build a
7943    --  subprogram declaration with the right signature. This operation is
7944    --  intrinsic, because it is always expanded as the negation of the
7945    --  call to the equality function.
7946
7947    procedure Make_Inequality_Operator (S : Entity_Id) is
7948       Loc     : constant Source_Ptr := Sloc (S);
7949       Decl    : Node_Id;
7950       Formals : List_Id;
7951       Op_Name : Entity_Id;
7952
7953       FF : constant Entity_Id := First_Formal (S);
7954       NF : constant Entity_Id := Next_Formal (FF);
7955
7956    begin
7957       --  Check that equality was properly defined, ignore call if not
7958
7959       if No (NF) then
7960          return;
7961       end if;
7962
7963       declare
7964          A : constant Entity_Id :=
7965                Make_Defining_Identifier (Sloc (FF),
7966                  Chars => Chars (FF));
7967
7968          B : constant Entity_Id :=
7969                Make_Defining_Identifier (Sloc (NF),
7970                  Chars => Chars (NF));
7971
7972       begin
7973          Op_Name := Make_Defining_Operator_Symbol (Loc, Name_Op_Ne);
7974
7975          Formals := New_List (
7976            Make_Parameter_Specification (Loc,
7977              Defining_Identifier => A,
7978              Parameter_Type      =>
7979                New_Reference_To (Etype (First_Formal (S)),
7980                  Sloc (Etype (First_Formal (S))))),
7981
7982            Make_Parameter_Specification (Loc,
7983              Defining_Identifier => B,
7984              Parameter_Type      =>
7985                New_Reference_To (Etype (Next_Formal (First_Formal (S))),
7986                  Sloc (Etype (Next_Formal (First_Formal (S)))))));
7987
7988          Decl :=
7989            Make_Subprogram_Declaration (Loc,
7990              Specification =>
7991                Make_Function_Specification (Loc,
7992                  Defining_Unit_Name       => Op_Name,
7993                  Parameter_Specifications => Formals,
7994                  Result_Definition        =>
7995                    New_Reference_To (Standard_Boolean, Loc)));
7996
7997          --  Insert inequality right after equality if it is explicit or after
7998          --  the derived type when implicit. These entities are created only
7999          --  for visibility purposes, and eventually replaced in the course of
8000          --  expansion, so they do not need to be attached to the tree and seen
8001          --  by the back-end. Keeping them internal also avoids spurious
8002          --  freezing problems. The declaration is inserted in the tree for
8003          --  analysis, and removed afterwards. If the equality operator comes
8004          --  from an explicit declaration, attach the inequality immediately
8005          --  after. Else the equality is inherited from a derived type
8006          --  declaration, so insert inequality after that declaration.
8007
8008          if No (Alias (S)) then
8009             Insert_After (Unit_Declaration_Node (S), Decl);
8010          elsif Is_List_Member (Parent (S)) then
8011             Insert_After (Parent (S), Decl);
8012          else
8013             Insert_After (Parent (Etype (First_Formal (S))), Decl);
8014          end if;
8015
8016          Mark_Rewrite_Insertion (Decl);
8017          Set_Is_Intrinsic_Subprogram (Op_Name);
8018          Analyze (Decl);
8019          Remove (Decl);
8020          Set_Has_Completion (Op_Name);
8021          Set_Corresponding_Equality (Op_Name, S);
8022          Set_Is_Abstract_Subprogram (Op_Name, Is_Abstract_Subprogram (S));
8023       end;
8024    end Make_Inequality_Operator;
8025
8026    ----------------------
8027    -- May_Need_Actuals --
8028    ----------------------
8029
8030    procedure May_Need_Actuals (Fun : Entity_Id) is
8031       F : Entity_Id;
8032       B : Boolean;
8033
8034    begin
8035       F := First_Formal (Fun);
8036       B := True;
8037       while Present (F) loop
8038          if No (Default_Value (F)) then
8039             B := False;
8040             exit;
8041          end if;
8042
8043          Next_Formal (F);
8044       end loop;
8045
8046       Set_Needs_No_Actuals (Fun, B);
8047    end May_Need_Actuals;
8048
8049    ---------------------
8050    -- Mode_Conformant --
8051    ---------------------
8052
8053    function Mode_Conformant (New_Id, Old_Id : Entity_Id) return Boolean is
8054       Result : Boolean;
8055    begin
8056       Check_Conformance (New_Id, Old_Id, Mode_Conformant, False, Result);
8057       return Result;
8058    end Mode_Conformant;
8059
8060    ---------------------------
8061    -- New_Overloaded_Entity --
8062    ---------------------------
8063
8064    procedure New_Overloaded_Entity
8065      (S            : Entity_Id;
8066       Derived_Type : Entity_Id := Empty)
8067    is
8068       Overridden_Subp : Entity_Id := Empty;
8069       --  Set if the current scope has an operation that is type-conformant
8070       --  with S, and becomes hidden by S.
8071
8072       Is_Primitive_Subp : Boolean;
8073       --  Set to True if the new subprogram is primitive
8074
8075       E : Entity_Id;
8076       --  Entity that S overrides
8077
8078       Prev_Vis : Entity_Id := Empty;
8079       --  Predecessor of E in Homonym chain
8080
8081       procedure Check_For_Primitive_Subprogram
8082         (Is_Primitive  : out Boolean;
8083          Is_Overriding : Boolean := False);
8084       --  If the subprogram being analyzed is a primitive operation of the type
8085       --  of a formal or result, set the Has_Primitive_Operations flag on the
8086       --  type, and set Is_Primitive to True (otherwise set to False). Set the
8087       --  corresponding flag on the entity itself for later use.
8088
8089       procedure Check_Synchronized_Overriding
8090         (Def_Id          : Entity_Id;
8091          Overridden_Subp : out Entity_Id);
8092       --  First determine if Def_Id is an entry or a subprogram either defined
8093       --  in the scope of a task or protected type, or is a primitive of such
8094       --  a type. Check whether Def_Id overrides a subprogram of an interface
8095       --  implemented by the synchronized type, return the overridden entity
8096       --  or Empty.
8097
8098       function Is_Private_Declaration (E : Entity_Id) return Boolean;
8099       --  Check that E is declared in the private part of the current package,
8100       --  or in the package body, where it may hide a previous declaration.
8101       --  We can't use In_Private_Part by itself because this flag is also
8102       --  set when freezing entities, so we must examine the place of the
8103       --  declaration in the tree, and recognize wrapper packages as well.
8104
8105       function Is_Overriding_Alias
8106         (Old_E : Entity_Id;
8107          New_E : Entity_Id) return Boolean;
8108       --  Check whether new subprogram and old subprogram are both inherited
8109       --  from subprograms that have distinct dispatch table entries. This can
8110       --  occur with derivations from instances with accidental homonyms.
8111       --  The function is conservative given that the converse is only true
8112       --  within instances that contain accidental overloadings.
8113
8114       ------------------------------------
8115       -- Check_For_Primitive_Subprogram --
8116       ------------------------------------
8117
8118       procedure Check_For_Primitive_Subprogram
8119         (Is_Primitive  : out Boolean;
8120          Is_Overriding : Boolean := False)
8121       is
8122          Formal : Entity_Id;
8123          F_Typ  : Entity_Id;
8124          B_Typ  : Entity_Id;
8125
8126          function Visible_Part_Type (T : Entity_Id) return Boolean;
8127          --  Returns true if T is declared in the visible part of the current
8128          --  package scope; otherwise returns false. Assumes that T is declared
8129          --  in a package.
8130
8131          procedure Check_Private_Overriding (T : Entity_Id);
8132          --  Checks that if a primitive abstract subprogram of a visible
8133          --  abstract type is declared in a private part, then it must override
8134          --  an abstract subprogram declared in the visible part. Also checks
8135          --  that if a primitive function with a controlling result is declared
8136          --  in a private part, then it must override a function declared in
8137          --  the visible part.
8138
8139          ------------------------------
8140          -- Check_Private_Overriding --
8141          ------------------------------
8142
8143          procedure Check_Private_Overriding (T : Entity_Id) is
8144          begin
8145             if Is_Package_Or_Generic_Package (Current_Scope)
8146               and then In_Private_Part (Current_Scope)
8147               and then Visible_Part_Type (T)
8148               and then not In_Instance
8149             then
8150                if Is_Abstract_Type (T)
8151                  and then Is_Abstract_Subprogram (S)
8152                  and then (not Is_Overriding
8153                             or else not Is_Abstract_Subprogram (E))
8154                then
8155                   Error_Msg_N
8156                     ("abstract subprograms must be visible "
8157                      & "(RM 3.9.3(10))!", S);
8158
8159                elsif Ekind (S) = E_Function
8160                  and then not Is_Overriding
8161                then
8162                   if Is_Tagged_Type (T)
8163                     and then T = Base_Type (Etype (S))
8164                   then
8165                      Error_Msg_N
8166                        ("private function with tagged result must"
8167                         & " override visible-part function", S);
8168                      Error_Msg_N
8169                        ("\move subprogram to the visible part"
8170                         & " (RM 3.9.3(10))", S);
8171
8172                   --  AI05-0073: extend this test to the case of a function
8173                   --  with a controlling access result.
8174
8175                   elsif Ekind (Etype (S)) = E_Anonymous_Access_Type
8176                     and then Is_Tagged_Type (Designated_Type (Etype (S)))
8177                     and then
8178                       not Is_Class_Wide_Type (Designated_Type (Etype (S)))
8179                     and then Ada_Version >= Ada_2012
8180                   then
8181                      Error_Msg_N
8182                        ("private function with controlling access result "
8183                           & "must override visible-part function", S);
8184                      Error_Msg_N
8185                        ("\move subprogram to the visible part"
8186                           & " (RM 3.9.3(10))", S);
8187                   end if;
8188                end if;
8189             end if;
8190          end Check_Private_Overriding;
8191
8192          -----------------------
8193          -- Visible_Part_Type --
8194          -----------------------
8195
8196          function Visible_Part_Type (T : Entity_Id) return Boolean is
8197             P : constant Node_Id := Unit_Declaration_Node (Scope (T));
8198             N : Node_Id;
8199
8200          begin
8201             --  If the entity is a private type, then it must be declared in a
8202             --  visible part.
8203
8204             if Ekind (T) in Private_Kind then
8205                return True;
8206             end if;
8207
8208             --  Otherwise, we traverse the visible part looking for its
8209             --  corresponding declaration. We cannot use the declaration
8210             --  node directly because in the private part the entity of a
8211             --  private type is the one in the full view, which does not
8212             --  indicate that it is the completion of something visible.
8213
8214             N := First (Visible_Declarations (Specification (P)));
8215             while Present (N) loop
8216                if Nkind (N) = N_Full_Type_Declaration
8217                  and then Present (Defining_Identifier (N))
8218                  and then T = Defining_Identifier (N)
8219                then
8220                   return True;
8221
8222                elsif Nkind_In (N, N_Private_Type_Declaration,
8223                                   N_Private_Extension_Declaration)
8224                  and then Present (Defining_Identifier (N))
8225                  and then T = Full_View (Defining_Identifier (N))
8226                then
8227                   return True;
8228                end if;
8229
8230                Next (N);
8231             end loop;
8232
8233             return False;
8234          end Visible_Part_Type;
8235
8236       --  Start of processing for Check_For_Primitive_Subprogram
8237
8238       begin
8239          Is_Primitive := False;
8240
8241          if not Comes_From_Source (S) then
8242             null;
8243
8244          --  If subprogram is at library level, it is not primitive operation
8245
8246          elsif Current_Scope = Standard_Standard then
8247             null;
8248
8249          elsif (Is_Package_Or_Generic_Package (Current_Scope)
8250                  and then not In_Package_Body (Current_Scope))
8251            or else Is_Overriding
8252          then
8253             --  For function, check return type
8254
8255             if Ekind (S) = E_Function then
8256                if Ekind (Etype (S)) = E_Anonymous_Access_Type then
8257                   F_Typ := Designated_Type (Etype (S));
8258                else
8259                   F_Typ := Etype (S);
8260                end if;
8261
8262                B_Typ := Base_Type (F_Typ);
8263
8264                if Scope (B_Typ) = Current_Scope
8265                  and then not Is_Class_Wide_Type (B_Typ)
8266                  and then not Is_Generic_Type (B_Typ)
8267                then
8268                   Is_Primitive := True;
8269                   Set_Has_Primitive_Operations (B_Typ);
8270                   Set_Is_Primitive (S);
8271                   Check_Private_Overriding (B_Typ);
8272                end if;
8273             end if;
8274
8275             --  For all subprograms, check formals
8276
8277             Formal := First_Formal (S);
8278             while Present (Formal) loop
8279                if Ekind (Etype (Formal)) = E_Anonymous_Access_Type then
8280                   F_Typ := Designated_Type (Etype (Formal));
8281                else
8282                   F_Typ := Etype (Formal);
8283                end if;
8284
8285                B_Typ := Base_Type (F_Typ);
8286
8287                if Ekind (B_Typ) = E_Access_Subtype then
8288                   B_Typ := Base_Type (B_Typ);
8289                end if;
8290
8291                if Scope (B_Typ) = Current_Scope
8292                  and then not Is_Class_Wide_Type (B_Typ)
8293                  and then not Is_Generic_Type (B_Typ)
8294                then
8295                   Is_Primitive := True;
8296                   Set_Is_Primitive (S);
8297                   Set_Has_Primitive_Operations (B_Typ);
8298                   Check_Private_Overriding (B_Typ);
8299                end if;
8300
8301                Next_Formal (Formal);
8302             end loop;
8303          end if;
8304       end Check_For_Primitive_Subprogram;
8305
8306       -----------------------------------
8307       -- Check_Synchronized_Overriding --
8308       -----------------------------------
8309
8310       procedure Check_Synchronized_Overriding
8311         (Def_Id          : Entity_Id;
8312          Overridden_Subp : out Entity_Id)
8313       is
8314          Ifaces_List : Elist_Id;
8315          In_Scope    : Boolean;
8316          Typ         : Entity_Id;
8317
8318          function Matches_Prefixed_View_Profile
8319            (Prim_Params  : List_Id;
8320             Iface_Params : List_Id) return Boolean;
8321          --  Determine whether a subprogram's parameter profile Prim_Params
8322          --  matches that of a potentially overridden interface subprogram
8323          --  Iface_Params. Also determine if the type of first parameter of
8324          --  Iface_Params is an implemented interface.
8325
8326          -----------------------------------
8327          -- Matches_Prefixed_View_Profile --
8328          -----------------------------------
8329
8330          function Matches_Prefixed_View_Profile
8331            (Prim_Params  : List_Id;
8332             Iface_Params : List_Id) return Boolean
8333          is
8334             Iface_Id     : Entity_Id;
8335             Iface_Param  : Node_Id;
8336             Iface_Typ    : Entity_Id;
8337             Prim_Id      : Entity_Id;
8338             Prim_Param   : Node_Id;
8339             Prim_Typ     : Entity_Id;
8340
8341             function Is_Implemented
8342               (Ifaces_List : Elist_Id;
8343                Iface       : Entity_Id) return Boolean;
8344             --  Determine if Iface is implemented by the current task or
8345             --  protected type.
8346
8347             --------------------
8348             -- Is_Implemented --
8349             --------------------
8350
8351             function Is_Implemented
8352               (Ifaces_List : Elist_Id;
8353                Iface       : Entity_Id) return Boolean
8354             is
8355                Iface_Elmt : Elmt_Id;
8356
8357             begin
8358                Iface_Elmt := First_Elmt (Ifaces_List);
8359                while Present (Iface_Elmt) loop
8360                   if Node (Iface_Elmt) = Iface then
8361                      return True;
8362                   end if;
8363
8364                   Next_Elmt (Iface_Elmt);
8365                end loop;
8366
8367                return False;
8368             end Is_Implemented;
8369
8370          --  Start of processing for Matches_Prefixed_View_Profile
8371
8372          begin
8373             Iface_Param := First (Iface_Params);
8374             Iface_Typ   := Etype (Defining_Identifier (Iface_Param));
8375
8376             if Is_Access_Type (Iface_Typ) then
8377                Iface_Typ := Designated_Type (Iface_Typ);
8378             end if;
8379
8380             Prim_Param := First (Prim_Params);
8381
8382             --  The first parameter of the potentially overridden subprogram
8383             --  must be an interface implemented by Prim.
8384
8385             if not Is_Interface (Iface_Typ)
8386               or else not Is_Implemented (Ifaces_List, Iface_Typ)
8387             then
8388                return False;
8389             end if;
8390
8391             --  The checks on the object parameters are done, move onto the
8392             --  rest of the parameters.
8393
8394             if not In_Scope then
8395                Prim_Param := Next (Prim_Param);
8396             end if;
8397
8398             Iface_Param := Next (Iface_Param);
8399             while Present (Iface_Param) and then Present (Prim_Param) loop
8400                Iface_Id  := Defining_Identifier (Iface_Param);
8401                Iface_Typ := Find_Parameter_Type (Iface_Param);
8402
8403                Prim_Id  := Defining_Identifier (Prim_Param);
8404                Prim_Typ := Find_Parameter_Type (Prim_Param);
8405
8406                if Ekind (Iface_Typ) = E_Anonymous_Access_Type
8407                  and then Ekind (Prim_Typ) = E_Anonymous_Access_Type
8408                  and then Is_Concurrent_Type (Designated_Type (Prim_Typ))
8409                then
8410                   Iface_Typ := Designated_Type (Iface_Typ);
8411                   Prim_Typ := Designated_Type (Prim_Typ);
8412                end if;
8413
8414                --  Case of multiple interface types inside a parameter profile
8415
8416                --     (Obj_Param : in out Iface; ...; Param : Iface)
8417
8418                --  If the interface type is implemented, then the matching type
8419                --  in the primitive should be the implementing record type.
8420
8421                if Ekind (Iface_Typ) = E_Record_Type
8422                  and then Is_Interface (Iface_Typ)
8423                  and then Is_Implemented (Ifaces_List, Iface_Typ)
8424                then
8425                   if Prim_Typ /= Typ then
8426                      return False;
8427                   end if;
8428
8429                --  The two parameters must be both mode and subtype conformant
8430
8431                elsif Ekind (Iface_Id) /= Ekind (Prim_Id)
8432                  or else not
8433                    Conforming_Types (Iface_Typ, Prim_Typ, Subtype_Conformant)
8434                then
8435                   return False;
8436                end if;
8437
8438                Next (Iface_Param);
8439                Next (Prim_Param);
8440             end loop;
8441
8442             --  One of the two lists contains more parameters than the other
8443
8444             if Present (Iface_Param) or else Present (Prim_Param) then
8445                return False;
8446             end if;
8447
8448             return True;
8449          end Matches_Prefixed_View_Profile;
8450
8451       --  Start of processing for Check_Synchronized_Overriding
8452
8453       begin
8454          Overridden_Subp := Empty;
8455
8456          --  Def_Id must be an entry or a subprogram. We should skip predefined
8457          --  primitives internally generated by the frontend; however at this
8458          --  stage predefined primitives are still not fully decorated. As a
8459          --  minor optimization we skip here internally generated subprograms.
8460
8461          if (Ekind (Def_Id) /= E_Entry
8462               and then Ekind (Def_Id) /= E_Function
8463               and then Ekind (Def_Id) /= E_Procedure)
8464            or else not Comes_From_Source (Def_Id)
8465          then
8466             return;
8467          end if;
8468
8469          --  Search for the concurrent declaration since it contains the list
8470          --  of all implemented interfaces. In this case, the subprogram is
8471          --  declared within the scope of a protected or a task type.
8472
8473          if Present (Scope (Def_Id))
8474            and then Is_Concurrent_Type (Scope (Def_Id))
8475            and then not Is_Generic_Actual_Type (Scope (Def_Id))
8476          then
8477             Typ := Scope (Def_Id);
8478             In_Scope := True;
8479
8480          --  The enclosing scope is not a synchronized type and the subprogram
8481          --  has no formals.
8482
8483          elsif No (First_Formal (Def_Id)) then
8484             return;
8485
8486          --  The subprogram has formals and hence it may be a primitive of a
8487          --  concurrent type.
8488
8489          else
8490             Typ := Etype (First_Formal (Def_Id));
8491
8492             if Is_Access_Type (Typ) then
8493                Typ := Directly_Designated_Type (Typ);
8494             end if;
8495
8496             if Is_Concurrent_Type (Typ)
8497               and then not Is_Generic_Actual_Type (Typ)
8498             then
8499                In_Scope := False;
8500
8501             --  This case occurs when the concurrent type is declared within
8502             --  a generic unit. As a result the corresponding record has been
8503             --  built and used as the type of the first formal, we just have
8504             --  to retrieve the corresponding concurrent type.
8505
8506             elsif Is_Concurrent_Record_Type (Typ)
8507               and then not Is_Class_Wide_Type (Typ)
8508               and then Present (Corresponding_Concurrent_Type (Typ))
8509             then
8510                Typ := Corresponding_Concurrent_Type (Typ);
8511                In_Scope := False;
8512
8513             else
8514                return;
8515             end if;
8516          end if;
8517
8518          --  There is no overriding to check if is an inherited operation in a
8519          --  type derivation on for a generic actual.
8520
8521          Collect_Interfaces (Typ, Ifaces_List);
8522
8523          if Is_Empty_Elmt_List (Ifaces_List) then
8524             return;
8525          end if;
8526
8527          --  Determine whether entry or subprogram Def_Id overrides a primitive
8528          --  operation that belongs to one of the interfaces in Ifaces_List.
8529
8530          declare
8531             Candidate : Entity_Id := Empty;
8532             Hom       : Entity_Id := Empty;
8533             Iface_Typ : Entity_Id;
8534             Subp      : Entity_Id := Empty;
8535
8536          begin
8537             --  Traverse the homonym chain, looking for a potentially
8538             --  overridden subprogram that belongs to an implemented
8539             --  interface.
8540
8541             Hom := Current_Entity_In_Scope (Def_Id);
8542             while Present (Hom) loop
8543                Subp := Hom;
8544
8545                if Subp = Def_Id
8546                  or else not Is_Overloadable (Subp)
8547                  or else not Is_Primitive (Subp)
8548                  or else not Is_Dispatching_Operation (Subp)
8549                  or else not Present (Find_Dispatching_Type (Subp))
8550                  or else not Is_Interface (Find_Dispatching_Type (Subp))
8551                then
8552                   null;
8553
8554                --  Entries and procedures can override abstract or null
8555                --  interface procedures.
8556
8557                elsif (Ekind (Def_Id) = E_Procedure
8558                         or else Ekind (Def_Id) = E_Entry)
8559                  and then Ekind (Subp) = E_Procedure
8560                  and then Matches_Prefixed_View_Profile
8561                             (Parameter_Specifications (Parent (Def_Id)),
8562                              Parameter_Specifications (Parent (Subp)))
8563                then
8564                   Candidate := Subp;
8565
8566                   --  For an overridden subprogram Subp, check whether the mode
8567                   --  of its first parameter is correct depending on the kind
8568                   --  of synchronized type.
8569
8570                   declare
8571                      Formal : constant Node_Id := First_Formal (Candidate);
8572
8573                   begin
8574                      --  In order for an entry or a protected procedure to
8575                      --  override, the first parameter of the overridden
8576                      --  routine must be of mode "out", "in out" or
8577                      --  access-to-variable.
8578
8579                      if (Ekind (Candidate) = E_Entry
8580                          or else Ekind (Candidate) = E_Procedure)
8581                        and then Is_Protected_Type (Typ)
8582                        and then Ekind (Formal) /= E_In_Out_Parameter
8583                        and then Ekind (Formal) /= E_Out_Parameter
8584                        and then Nkind (Parameter_Type (Parent (Formal)))
8585                                   /= N_Access_Definition
8586                      then
8587                         null;
8588
8589                      --  All other cases are OK since a task entry or routine
8590                      --  does not have a restriction on the mode of the first
8591                      --  parameter of the overridden interface routine.
8592
8593                      else
8594                         Overridden_Subp := Candidate;
8595                         return;
8596                      end if;
8597                   end;
8598
8599                --  Functions can override abstract interface functions
8600
8601                elsif Ekind (Def_Id) = E_Function
8602                  and then Ekind (Subp) = E_Function
8603                  and then Matches_Prefixed_View_Profile
8604                             (Parameter_Specifications (Parent (Def_Id)),
8605                              Parameter_Specifications (Parent (Subp)))
8606                  and then Etype (Result_Definition (Parent (Def_Id))) =
8607                           Etype (Result_Definition (Parent (Subp)))
8608                then
8609                   Overridden_Subp := Subp;
8610                   return;
8611                end if;
8612
8613                Hom := Homonym (Hom);
8614             end loop;
8615
8616             --  After examining all candidates for overriding, we are left with
8617             --  the best match which is a mode incompatible interface routine.
8618             --  Do not emit an error if the Expander is active since this error
8619             --  will be detected later on after all concurrent types are
8620             --  expanded and all wrappers are built. This check is meant for
8621             --  spec-only compilations.
8622
8623             if Present (Candidate) and then not Expander_Active then
8624                Iface_Typ :=
8625                  Find_Parameter_Type (Parent (First_Formal (Candidate)));
8626
8627                --  Def_Id is primitive of a protected type, declared inside the
8628                --  type, and the candidate is primitive of a limited or
8629                --  synchronized interface.
8630
8631                if In_Scope
8632                  and then Is_Protected_Type (Typ)
8633                  and then
8634                    (Is_Limited_Interface (Iface_Typ)
8635                      or else Is_Protected_Interface (Iface_Typ)
8636                      or else Is_Synchronized_Interface (Iface_Typ)
8637                      or else Is_Task_Interface (Iface_Typ))
8638                then
8639                   Error_Msg_PT (Parent (Typ), Candidate);
8640                end if;
8641             end if;
8642
8643             Overridden_Subp := Candidate;
8644             return;
8645          end;
8646       end Check_Synchronized_Overriding;
8647
8648       ----------------------------
8649       -- Is_Private_Declaration --
8650       ----------------------------
8651
8652       function Is_Private_Declaration (E : Entity_Id) return Boolean is
8653          Priv_Decls : List_Id;
8654          Decl       : constant Node_Id := Unit_Declaration_Node (E);
8655
8656       begin
8657          if Is_Package_Or_Generic_Package (Current_Scope)
8658            and then In_Private_Part (Current_Scope)
8659          then
8660             Priv_Decls :=
8661               Private_Declarations
8662                 (Specification (Unit_Declaration_Node (Current_Scope)));
8663
8664             return In_Package_Body (Current_Scope)
8665               or else
8666                 (Is_List_Member (Decl)
8667                   and then List_Containing (Decl) = Priv_Decls)
8668               or else (Nkind (Parent (Decl)) = N_Package_Specification
8669                         and then not
8670                           Is_Compilation_Unit
8671                             (Defining_Entity (Parent (Decl)))
8672                         and then List_Containing (Parent (Parent (Decl))) =
8673                                                                 Priv_Decls);
8674          else
8675             return False;
8676          end if;
8677       end Is_Private_Declaration;
8678
8679       --------------------------
8680       -- Is_Overriding_Alias --
8681       --------------------------
8682
8683       function Is_Overriding_Alias
8684         (Old_E : Entity_Id;
8685          New_E : Entity_Id) return Boolean
8686       is
8687          AO : constant Entity_Id := Alias (Old_E);
8688          AN : constant Entity_Id := Alias (New_E);
8689
8690       begin
8691          return Scope (AO) /= Scope (AN)
8692            or else No (DTC_Entity (AO))
8693            or else No (DTC_Entity (AN))
8694            or else DT_Position (AO) = DT_Position (AN);
8695       end Is_Overriding_Alias;
8696
8697    --  Start of processing for New_Overloaded_Entity
8698
8699    begin
8700       --  We need to look for an entity that S may override. This must be a
8701       --  homonym in the current scope, so we look for the first homonym of
8702       --  S in the current scope as the starting point for the search.
8703
8704       E := Current_Entity_In_Scope (S);
8705
8706       --  Ada 2005 (AI-251): Derivation of abstract interface primitives.
8707       --  They are directly added to the list of primitive operations of
8708       --  Derived_Type, unless this is a rederivation in the private part
8709       --  of an operation that was already derived in the visible part of
8710       --  the current package.
8711
8712       if Ada_Version >= Ada_2005
8713         and then Present (Derived_Type)
8714         and then Present (Alias (S))
8715         and then Is_Dispatching_Operation (Alias (S))
8716         and then Present (Find_Dispatching_Type (Alias (S)))
8717         and then Is_Interface (Find_Dispatching_Type (Alias (S)))
8718       then
8719          --  For private types, when the full-view is processed we propagate to
8720          --  the full view the non-overridden entities whose attribute "alias"
8721          --  references an interface primitive. These entities were added by
8722          --  Derive_Subprograms to ensure that interface primitives are
8723          --  covered.
8724
8725          --  Inside_Freeze_Actions is non zero when S corresponds with an
8726          --  internal entity that links an interface primitive with its
8727          --  covering primitive through attribute Interface_Alias (see
8728          --  Add_Internal_Interface_Entities).
8729
8730          if Inside_Freezing_Actions = 0
8731            and then Is_Package_Or_Generic_Package (Current_Scope)
8732            and then In_Private_Part (Current_Scope)
8733            and then Nkind (Parent (E)) = N_Private_Extension_Declaration
8734            and then Nkind (Parent (S)) = N_Full_Type_Declaration
8735            and then Full_View (Defining_Identifier (Parent (E)))
8736                       = Defining_Identifier (Parent (S))
8737            and then Alias (E) = Alias (S)
8738          then
8739             Check_Operation_From_Private_View (S, E);
8740             Set_Is_Dispatching_Operation (S);
8741
8742          --  Common case
8743
8744          else
8745             Enter_Overloaded_Entity (S);
8746             Check_Dispatching_Operation (S, Empty);
8747             Check_For_Primitive_Subprogram (Is_Primitive_Subp);
8748          end if;
8749
8750          return;
8751       end if;
8752
8753       --  If there is no homonym then this is definitely not overriding
8754
8755       if No (E) then
8756          Enter_Overloaded_Entity (S);
8757          Check_Dispatching_Operation (S, Empty);
8758          Check_For_Primitive_Subprogram (Is_Primitive_Subp);
8759
8760          --  If subprogram has an explicit declaration, check whether it
8761          --  has an overriding indicator.
8762
8763          if Comes_From_Source (S) then
8764             Check_Synchronized_Overriding (S, Overridden_Subp);
8765
8766             --  (Ada 2012: AI05-0125-1): If S is a dispatching operation then
8767             --  it may have overridden some hidden inherited primitive. Update
8768             --  Overridden_Subp to avoid spurious errors when checking the
8769             --  overriding indicator.
8770
8771             if Ada_Version >= Ada_2012
8772               and then No (Overridden_Subp)
8773               and then Is_Dispatching_Operation (S)
8774               and then Present (Overridden_Operation (S))
8775             then
8776                Overridden_Subp := Overridden_Operation (S);
8777             end if;
8778
8779             Check_Overriding_Indicator
8780               (S, Overridden_Subp, Is_Primitive => Is_Primitive_Subp);
8781          end if;
8782
8783       --  If there is a homonym that is not overloadable, then we have an
8784       --  error, except for the special cases checked explicitly below.
8785
8786       elsif not Is_Overloadable (E) then
8787
8788          --  Check for spurious conflict produced by a subprogram that has the
8789          --  same name as that of the enclosing generic package. The conflict
8790          --  occurs within an instance, between the subprogram and the renaming
8791          --  declaration for the package. After the subprogram, the package
8792          --  renaming declaration becomes hidden.
8793
8794          if Ekind (E) = E_Package
8795            and then Present (Renamed_Object (E))
8796            and then Renamed_Object (E) = Current_Scope
8797            and then Nkind (Parent (Renamed_Object (E))) =
8798                                                      N_Package_Specification
8799            and then Present (Generic_Parent (Parent (Renamed_Object (E))))
8800          then
8801             Set_Is_Hidden (E);
8802             Set_Is_Immediately_Visible (E, False);
8803             Enter_Overloaded_Entity (S);
8804             Set_Homonym (S, Homonym (E));
8805             Check_Dispatching_Operation (S, Empty);
8806             Check_Overriding_Indicator (S, Empty, Is_Primitive => False);
8807
8808          --  If the subprogram is implicit it is hidden by the previous
8809          --  declaration. However if it is dispatching, it must appear in the
8810          --  dispatch table anyway, because it can be dispatched to even if it
8811          --  cannot be called directly.
8812
8813          elsif Present (Alias (S)) and then not Comes_From_Source (S) then
8814             Set_Scope (S, Current_Scope);
8815
8816             if Is_Dispatching_Operation (Alias (S)) then
8817                Check_Dispatching_Operation (S, Empty);
8818             end if;
8819
8820             return;
8821
8822          else
8823             Error_Msg_Sloc := Sloc (E);
8824
8825             --  Generate message, with useful additional warning if in generic
8826
8827             if Is_Generic_Unit (E) then
8828                Error_Msg_N ("previous generic unit cannot be overloaded", S);
8829                Error_Msg_N ("\& conflicts with declaration#", S);
8830             else
8831                Error_Msg_N ("& conflicts with declaration#", S);
8832             end if;
8833
8834             return;
8835          end if;
8836
8837       --  E exists and is overloadable
8838
8839       else
8840          Check_Synchronized_Overriding (S, Overridden_Subp);
8841
8842          --  Loop through E and its homonyms to determine if any of them is
8843          --  the candidate for overriding by S.
8844
8845          while Present (E) loop
8846
8847             --  Definitely not interesting if not in the current scope
8848
8849             if Scope (E) /= Current_Scope then
8850                null;
8851
8852             --  Ada 2012 (AI05-0165): For internally generated bodies of
8853             --  null procedures locate the internally generated spec. We
8854             --  enforce mode conformance since a tagged type may inherit
8855             --  from interfaces several null primitives which differ only
8856             --  in the mode of the formals.
8857
8858             elsif not Comes_From_Source (S)
8859               and then Is_Null_Procedure (S)
8860               and then not Mode_Conformant (E, S)
8861             then
8862                null;
8863
8864             --  Check if we have type conformance
8865
8866             elsif Type_Conformant (E, S) then
8867
8868                --  If the old and new entities have the same profile and one
8869                --  is not the body of the other, then this is an error, unless
8870                --  one of them is implicitly declared.
8871
8872                --  There are some cases when both can be implicit, for example
8873                --  when both a literal and a function that overrides it are
8874                --  inherited in a derivation, or when an inherited operation
8875                --  of a tagged full type overrides the inherited operation of
8876                --  a private extension. Ada 83 had a special rule for the
8877                --  literal case. In Ada 95, the later implicit operation hides
8878                --  the former, and the literal is always the former. In the
8879                --  odd case where both are derived operations declared at the
8880                --  same point, both operations should be declared, and in that
8881                --  case we bypass the following test and proceed to the next
8882                --  part. This can only occur for certain obscure cases in
8883                --  instances, when an operation on a type derived from a formal
8884                --  private type does not override a homograph inherited from
8885                --  the actual. In subsequent derivations of such a type, the
8886                --  DT positions of these operations remain distinct, if they
8887                --  have been set.
8888
8889                if Present (Alias (S))
8890                  and then (No (Alias (E))
8891                             or else Comes_From_Source (E)
8892                             or else Is_Abstract_Subprogram (S)
8893                             or else
8894                               (Is_Dispatching_Operation (E)
8895                                  and then Is_Overriding_Alias (E, S)))
8896                  and then Ekind (E) /= E_Enumeration_Literal
8897                then
8898                   --  When an derived operation is overloaded it may be due to
8899                   --  the fact that the full view of a private extension
8900                   --  re-inherits. It has to be dealt with.
8901
8902                   if Is_Package_Or_Generic_Package (Current_Scope)
8903                     and then In_Private_Part (Current_Scope)
8904                   then
8905                      Check_Operation_From_Private_View (S, E);
8906                   end if;
8907
8908                   --  In any case the implicit operation remains hidden by the
8909                   --  existing declaration, which is overriding. Indicate that
8910                   --  E overrides the operation from which S is inherited.
8911
8912                   if Present (Alias (S)) then
8913                      Set_Overridden_Operation (E, Alias (S));
8914                   else
8915                      Set_Overridden_Operation (E, S);
8916                   end if;
8917
8918                   if Comes_From_Source (E) then
8919                      Check_Overriding_Indicator (E, S, Is_Primitive => False);
8920                   end if;
8921
8922                   return;
8923
8924                --  Within an instance, the renaming declarations for actual
8925                --  subprograms may become ambiguous, but they do not hide each
8926                --  other.
8927
8928                elsif Ekind (E) /= E_Entry
8929                  and then not Comes_From_Source (E)
8930                  and then not Is_Generic_Instance (E)
8931                  and then (Present (Alias (E))
8932                             or else Is_Intrinsic_Subprogram (E))
8933                  and then (not In_Instance
8934                             or else No (Parent (E))
8935                             or else Nkind (Unit_Declaration_Node (E)) /=
8936                                       N_Subprogram_Renaming_Declaration)
8937                then
8938                   --  A subprogram child unit is not allowed to override an
8939                   --  inherited subprogram (10.1.1(20)).
8940
8941                   if Is_Child_Unit (S) then
8942                      Error_Msg_N
8943                        ("child unit overrides inherited subprogram in parent",
8944                         S);
8945                      return;
8946                   end if;
8947
8948                   if Is_Non_Overriding_Operation (E, S) then
8949                      Enter_Overloaded_Entity (S);
8950
8951                      if No (Derived_Type)
8952                        or else Is_Tagged_Type (Derived_Type)
8953                      then
8954                         Check_Dispatching_Operation (S, Empty);
8955                      end if;
8956
8957                      return;
8958                   end if;
8959
8960                   --  E is a derived operation or an internal operator which
8961                   --  is being overridden. Remove E from further visibility.
8962                   --  Furthermore, if E is a dispatching operation, it must be
8963                   --  replaced in the list of primitive operations of its type
8964                   --  (see Override_Dispatching_Operation).
8965
8966                   Overridden_Subp := E;
8967
8968                   declare
8969                      Prev : Entity_Id;
8970
8971                   begin
8972                      Prev := First_Entity (Current_Scope);
8973                      while Present (Prev)
8974                        and then Next_Entity (Prev) /= E
8975                      loop
8976                         Next_Entity (Prev);
8977                      end loop;
8978
8979                      --  It is possible for E to be in the current scope and
8980                      --  yet not in the entity chain. This can only occur in a
8981                      --  generic context where E is an implicit concatenation
8982                      --  in the formal part, because in a generic body the
8983                      --  entity chain starts with the formals.
8984
8985                      pragma Assert
8986                        (Present (Prev) or else Chars (E) = Name_Op_Concat);
8987
8988                      --  E must be removed both from the entity_list of the
8989                      --  current scope, and from the visibility chain
8990
8991                      if Debug_Flag_E then
8992                         Write_Str ("Override implicit operation ");
8993                         Write_Int (Int (E));
8994                         Write_Eol;
8995                      end if;
8996
8997                      --  If E is a predefined concatenation, it stands for four
8998                      --  different operations. As a result, a single explicit
8999                      --  declaration does not hide it. In a possible ambiguous
9000                      --  situation, Disambiguate chooses the user-defined op,
9001                      --  so it is correct to retain the previous internal one.
9002
9003                      if Chars (E) /= Name_Op_Concat
9004                        or else Ekind (E) /= E_Operator
9005                      then
9006                         --  For nondispatching derived operations that are
9007                         --  overridden by a subprogram declared in the private
9008                         --  part of a package, we retain the derived subprogram
9009                         --  but mark it as not immediately visible. If the
9010                         --  derived operation was declared in the visible part
9011                         --  then this ensures that it will still be visible
9012                         --  outside the package with the proper signature
9013                         --  (calls from outside must also be directed to this
9014                         --  version rather than the overriding one, unlike the
9015                         --  dispatching case). Calls from inside the package
9016                         --  will still resolve to the overriding subprogram
9017                         --  since the derived one is marked as not visible
9018                         --  within the package.
9019
9020                         --  If the private operation is dispatching, we achieve
9021                         --  the overriding by keeping the implicit operation
9022                         --  but setting its alias to be the overriding one. In
9023                         --  this fashion the proper body is executed in all
9024                         --  cases, but the original signature is used outside
9025                         --  of the package.
9026
9027                         --  If the overriding is not in the private part, we
9028                         --  remove the implicit operation altogether.
9029
9030                         if Is_Private_Declaration (S) then
9031                            if not Is_Dispatching_Operation (E) then
9032                               Set_Is_Immediately_Visible (E, False);
9033                            else
9034                               --  Work done in Override_Dispatching_Operation,
9035                               --  so nothing else needs to be done here.
9036
9037                               null;
9038                            end if;
9039
9040                         else
9041                            --  Find predecessor of E in Homonym chain
9042
9043                            if E = Current_Entity (E) then
9044                               Prev_Vis := Empty;
9045                            else
9046                               Prev_Vis := Current_Entity (E);
9047                               while Homonym (Prev_Vis) /= E loop
9048                                  Prev_Vis := Homonym (Prev_Vis);
9049                               end loop;
9050                            end if;
9051
9052                            if Prev_Vis /= Empty then
9053
9054                               --  Skip E in the visibility chain
9055
9056                               Set_Homonym (Prev_Vis, Homonym (E));
9057
9058                            else
9059                               Set_Name_Entity_Id (Chars (E), Homonym (E));
9060                            end if;
9061
9062                            Set_Next_Entity (Prev, Next_Entity (E));
9063
9064                            if No (Next_Entity (Prev)) then
9065                               Set_Last_Entity (Current_Scope, Prev);
9066                            end if;
9067                         end if;
9068                      end if;
9069
9070                      Enter_Overloaded_Entity (S);
9071
9072                      --  For entities generated by Derive_Subprograms the
9073                      --  overridden operation is the inherited primitive
9074                      --  (which is available through the attribute alias).
9075
9076                      if not (Comes_From_Source (E))
9077                        and then Is_Dispatching_Operation (E)
9078                        and then Find_Dispatching_Type (E) =
9079                                 Find_Dispatching_Type (S)
9080                        and then Present (Alias (E))
9081                        and then Comes_From_Source (Alias (E))
9082                      then
9083                         Set_Overridden_Operation (S, Alias (E));
9084
9085                      --  Normal case of setting entity as overridden
9086
9087                      --  Note: Static_Initialization and Overridden_Operation
9088                      --  attributes use the same field in subprogram entities.
9089                      --  Static_Initialization is only defined for internal
9090                      --  initialization procedures, where Overridden_Operation
9091                      --  is irrelevant. Therefore the setting of this attribute
9092                      --  must check whether the target is an init_proc.
9093
9094                      elsif not Is_Init_Proc (S) then
9095                         Set_Overridden_Operation (S, E);
9096                      end if;
9097
9098                      Check_Overriding_Indicator (S, E, Is_Primitive => True);
9099
9100                      --  If S is a user-defined subprogram or a null procedure
9101                      --  expanded to override an inherited null procedure, or a
9102                      --  predefined dispatching primitive then indicate that E
9103                      --  overrides the operation from which S is inherited.
9104
9105                      if Comes_From_Source (S)
9106                        or else
9107                          (Present (Parent (S))
9108                            and then
9109                              Nkind (Parent (S)) = N_Procedure_Specification
9110                            and then
9111                              Null_Present (Parent (S)))
9112                        or else
9113                          (Present (Alias (E))
9114                            and then
9115                              Is_Predefined_Dispatching_Operation (Alias (E)))
9116                      then
9117                         if Present (Alias (E)) then
9118                            Set_Overridden_Operation (S, Alias (E));
9119                         end if;
9120                      end if;
9121
9122                      if Is_Dispatching_Operation (E) then
9123
9124                         --  An overriding dispatching subprogram inherits the
9125                         --  convention of the overridden subprogram (AI-117).
9126
9127                         Set_Convention (S, Convention (E));
9128                         Check_Dispatching_Operation (S, E);
9129
9130                      else
9131                         Check_Dispatching_Operation (S, Empty);
9132                      end if;
9133
9134                      Check_For_Primitive_Subprogram
9135                        (Is_Primitive_Subp, Is_Overriding => True);
9136                      goto Check_Inequality;
9137                   end;
9138
9139                --  Apparent redeclarations in instances can occur when two
9140                --  formal types get the same actual type. The subprograms in
9141                --  in the instance are legal,  even if not callable from the
9142                --  outside. Calls from within are disambiguated elsewhere.
9143                --  For dispatching operations in the visible part, the usual
9144                --  rules apply, and operations with the same profile are not
9145                --  legal (B830001).
9146
9147                elsif (In_Instance_Visible_Part
9148                        and then not Is_Dispatching_Operation (E))
9149                  or else In_Instance_Not_Visible
9150                then
9151                   null;
9152
9153                --  Here we have a real error (identical profile)
9154
9155                else
9156                   Error_Msg_Sloc := Sloc (E);
9157
9158                   --  Avoid cascaded errors if the entity appears in
9159                   --  subsequent calls.
9160
9161                   Set_Scope (S, Current_Scope);
9162
9163                   --  Generate error, with extra useful warning for the case
9164                   --  of a generic instance with no completion.
9165
9166                   if Is_Generic_Instance (S)
9167                     and then not Has_Completion (E)
9168                   then
9169                      Error_Msg_N
9170                        ("instantiation cannot provide body for&", S);
9171                      Error_Msg_N ("\& conflicts with declaration#", S);
9172                   else
9173                      Error_Msg_N ("& conflicts with declaration#", S);
9174                   end if;
9175
9176                   return;
9177                end if;
9178
9179             else
9180                --  If one subprogram has an access parameter and the other
9181                --  a parameter of an access type, calls to either might be
9182                --  ambiguous. Verify that parameters match except for the
9183                --  access parameter.
9184
9185                if May_Hide_Profile then
9186                   declare
9187                      F1 : Entity_Id;
9188                      F2 : Entity_Id;
9189
9190                   begin
9191                      F1 := First_Formal (S);
9192                      F2 := First_Formal (E);
9193                      while Present (F1) and then Present (F2) loop
9194                         if Is_Access_Type (Etype (F1)) then
9195                            if not Is_Access_Type (Etype (F2))
9196                               or else not Conforming_Types
9197                                 (Designated_Type (Etype (F1)),
9198                                  Designated_Type (Etype (F2)),
9199                                  Type_Conformant)
9200                            then
9201                               May_Hide_Profile := False;
9202                            end if;
9203
9204                         elsif
9205                           not Conforming_Types
9206                             (Etype (F1), Etype (F2), Type_Conformant)
9207                         then
9208                            May_Hide_Profile := False;
9209                         end if;
9210
9211                         Next_Formal (F1);
9212                         Next_Formal (F2);
9213                      end loop;
9214
9215                      if May_Hide_Profile
9216                        and then No (F1)
9217                        and then No (F2)
9218                      then
9219                         Error_Msg_NE ("calls to& may be ambiguous?", S, S);
9220                      end if;
9221                   end;
9222                end if;
9223             end if;
9224
9225             E := Homonym (E);
9226          end loop;
9227
9228          --  On exit, we know that S is a new entity
9229
9230          Enter_Overloaded_Entity (S);
9231          Check_For_Primitive_Subprogram (Is_Primitive_Subp);
9232          Check_Overriding_Indicator
9233            (S, Overridden_Subp, Is_Primitive => Is_Primitive_Subp);
9234
9235          --  Overloading is not allowed in SPARK, except for operators
9236
9237          if Nkind (S) /= N_Defining_Operator_Symbol then
9238             Error_Msg_Sloc := Sloc (Homonym (S));
9239             Check_SPARK_Restriction
9240               ("overloading not allowed with entity#", S);
9241          end if;
9242
9243          --  If S is a derived operation for an untagged type then by
9244          --  definition it's not a dispatching operation (even if the parent
9245          --  operation was dispatching), so Check_Dispatching_Operation is not
9246          --  called in that case.
9247
9248          if No (Derived_Type)
9249            or else Is_Tagged_Type (Derived_Type)
9250          then
9251             Check_Dispatching_Operation (S, Empty);
9252          end if;
9253       end if;
9254
9255       --  If this is a user-defined equality operator that is not a derived
9256       --  subprogram, create the corresponding inequality. If the operation is
9257       --  dispatching, the expansion is done elsewhere, and we do not create
9258       --  an explicit inequality operation.
9259
9260       <<Check_Inequality>>
9261          if Chars (S) = Name_Op_Eq
9262            and then Etype (S) = Standard_Boolean
9263            and then Present (Parent (S))
9264            and then not Is_Dispatching_Operation (S)
9265          then
9266             Make_Inequality_Operator (S);
9267
9268             if Ada_Version >= Ada_2012 then
9269                Check_Untagged_Equality (S);
9270             end if;
9271          end if;
9272    end New_Overloaded_Entity;
9273
9274    ---------------------
9275    -- Process_Formals --
9276    ---------------------
9277
9278    procedure Process_Formals
9279      (T           : List_Id;
9280       Related_Nod : Node_Id)
9281    is
9282       Param_Spec  : Node_Id;
9283       Formal      : Entity_Id;
9284       Formal_Type : Entity_Id;
9285       Default     : Node_Id;
9286       Ptype       : Entity_Id;
9287
9288       Num_Out_Params  : Nat       := 0;
9289       First_Out_Param : Entity_Id := Empty;
9290       --  Used for setting Is_Only_Out_Parameter
9291
9292       function Designates_From_With_Type (Typ : Entity_Id) return Boolean;
9293       --  Determine whether an access type designates a type coming from a
9294       --  limited view.
9295
9296       function Is_Class_Wide_Default (D : Node_Id) return Boolean;
9297       --  Check whether the default has a class-wide type. After analysis the
9298       --  default has the type of the formal, so we must also check explicitly
9299       --  for an access attribute.
9300
9301       -------------------------------
9302       -- Designates_From_With_Type --
9303       -------------------------------
9304
9305       function Designates_From_With_Type (Typ : Entity_Id) return Boolean is
9306          Desig : Entity_Id := Typ;
9307
9308       begin
9309          if Is_Access_Type (Desig) then
9310             Desig := Directly_Designated_Type (Desig);
9311          end if;
9312
9313          if Is_Class_Wide_Type (Desig) then
9314             Desig := Root_Type (Desig);
9315          end if;
9316
9317          return
9318            Ekind (Desig) = E_Incomplete_Type
9319              and then From_With_Type (Desig);
9320       end Designates_From_With_Type;
9321
9322       ---------------------------
9323       -- Is_Class_Wide_Default --
9324       ---------------------------
9325
9326       function Is_Class_Wide_Default (D : Node_Id) return Boolean is
9327       begin
9328          return Is_Class_Wide_Type (Designated_Type (Etype (D)))
9329            or else (Nkind (D) =  N_Attribute_Reference
9330                      and then Attribute_Name (D) = Name_Access
9331                      and then Is_Class_Wide_Type (Etype (Prefix (D))));
9332       end Is_Class_Wide_Default;
9333
9334    --  Start of processing for Process_Formals
9335
9336    begin
9337       --  In order to prevent premature use of the formals in the same formal
9338       --  part, the Ekind is left undefined until all default expressions are
9339       --  analyzed. The Ekind is established in a separate loop at the end.
9340
9341       Param_Spec := First (T);
9342       while Present (Param_Spec) loop
9343          Formal := Defining_Identifier (Param_Spec);
9344          Set_Never_Set_In_Source (Formal, True);
9345          Enter_Name (Formal);
9346
9347          --  Case of ordinary parameters
9348
9349          if Nkind (Parameter_Type (Param_Spec)) /= N_Access_Definition then
9350             Find_Type (Parameter_Type (Param_Spec));
9351             Ptype := Parameter_Type (Param_Spec);
9352
9353             if Ptype = Error then
9354                goto Continue;
9355             end if;
9356
9357             Formal_Type := Entity (Ptype);
9358
9359             if Is_Incomplete_Type (Formal_Type)
9360               or else
9361                (Is_Class_Wide_Type (Formal_Type)
9362                   and then Is_Incomplete_Type (Root_Type (Formal_Type)))
9363             then
9364                --  Ada 2005 (AI-326): Tagged incomplete types allowed in
9365                --  primitive operations, as long as their completion is
9366                --  in the same declarative part. If in the private part
9367                --  this means that the type cannot be a Taft-amendment type.
9368                --  Check is done on package exit. For access to subprograms,
9369                --  the use is legal for Taft-amendment types.
9370
9371                if Is_Tagged_Type (Formal_Type) then
9372                   if Ekind (Scope (Current_Scope)) = E_Package
9373                     and then not From_With_Type (Formal_Type)
9374                     and then not Is_Class_Wide_Type (Formal_Type)
9375                   then
9376                      if not Nkind_In
9377                        (Parent (T), N_Access_Function_Definition,
9378                                     N_Access_Procedure_Definition)
9379                      then
9380                         Append_Elmt
9381                           (Current_Scope,
9382                              Private_Dependents (Base_Type (Formal_Type)));
9383
9384                         --  Freezing is delayed to ensure that Register_Prim
9385                         --  will get called for this operation, which is needed
9386                         --  in cases where static dispatch tables aren't built.
9387                         --  (Note that the same is done for controlling access
9388                         --  parameter cases in function Access_Definition.)
9389
9390                         Set_Has_Delayed_Freeze (Current_Scope);
9391                      end if;
9392                   end if;
9393
9394                --  Special handling of Value_Type for CIL case
9395
9396                elsif Is_Value_Type (Formal_Type) then
9397                   null;
9398
9399                elsif not Nkind_In (Parent (T), N_Access_Function_Definition,
9400                                                N_Access_Procedure_Definition)
9401                then
9402                   --  AI05-0151: Tagged incomplete types are allowed in all
9403                   --  formal parts. Untagged incomplete types are not allowed
9404                   --  in bodies.
9405
9406                   if Ada_Version >= Ada_2012 then
9407                      if Is_Tagged_Type (Formal_Type) then
9408                         null;
9409
9410                      elsif Nkind_In (Parent (Parent (T)), N_Accept_Statement,
9411                                                           N_Entry_Body,
9412                                                           N_Subprogram_Body)
9413                      then
9414                         Error_Msg_NE
9415                           ("invalid use of untagged incomplete type&",
9416                            Ptype, Formal_Type);
9417                      end if;
9418
9419                   else
9420                      Error_Msg_NE
9421                        ("invalid use of incomplete type&",
9422                         Param_Spec, Formal_Type);
9423
9424                      --  Further checks on the legality of incomplete types
9425                      --  in formal parts are delayed until the freeze point
9426                      --  of the enclosing subprogram or access to subprogram.
9427                   end if;
9428                end if;
9429
9430             elsif Ekind (Formal_Type) = E_Void then
9431                Error_Msg_NE
9432                  ("premature use of&",
9433                   Parameter_Type (Param_Spec), Formal_Type);
9434             end if;
9435
9436             --  Ada 2012 (AI-142): Handle aliased parameters
9437
9438             if Ada_Version >= Ada_2012
9439               and then Aliased_Present (Param_Spec)
9440             then
9441                Set_Is_Aliased (Formal);
9442             end if;
9443
9444             --  Ada 2005 (AI-231): Create and decorate an internal subtype
9445             --  declaration corresponding to the null-excluding type of the
9446             --  formal in the enclosing scope. Finally, replace the parameter
9447             --  type of the formal with the internal subtype.
9448
9449             if Ada_Version >= Ada_2005
9450               and then Null_Exclusion_Present (Param_Spec)
9451             then
9452                if not Is_Access_Type (Formal_Type) then
9453                   Error_Msg_N
9454                     ("`NOT NULL` allowed only for an access type", Param_Spec);
9455
9456                else
9457                   if Can_Never_Be_Null (Formal_Type)
9458                     and then Comes_From_Source (Related_Nod)
9459                   then
9460                      Error_Msg_NE
9461                        ("`NOT NULL` not allowed (& already excludes null)",
9462                         Param_Spec, Formal_Type);
9463                   end if;
9464
9465                   Formal_Type :=
9466                     Create_Null_Excluding_Itype
9467                       (T           => Formal_Type,
9468                        Related_Nod => Related_Nod,
9469                        Scope_Id    => Scope (Current_Scope));
9470
9471                   --  If the designated type of the itype is an itype we
9472                   --  decorate it with the Has_Delayed_Freeze attribute to
9473                   --  avoid problems with the backend.
9474
9475                   --  Example:
9476                   --     type T is access procedure;
9477                   --     procedure Op (O : not null T);
9478
9479                   if Is_Itype (Directly_Designated_Type (Formal_Type)) then
9480                      Set_Has_Delayed_Freeze (Formal_Type);
9481                   end if;
9482                end if;
9483             end if;
9484
9485          --  An access formal type
9486
9487          else
9488             Formal_Type :=
9489               Access_Definition (Related_Nod, Parameter_Type (Param_Spec));
9490
9491             --  No need to continue if we already notified errors
9492
9493             if not Present (Formal_Type) then
9494                return;
9495             end if;
9496
9497             --  Ada 2005 (AI-254)
9498
9499             declare
9500                AD : constant Node_Id :=
9501                       Access_To_Subprogram_Definition
9502                         (Parameter_Type (Param_Spec));
9503             begin
9504                if Present (AD) and then Protected_Present (AD) then
9505                   Formal_Type :=
9506                     Replace_Anonymous_Access_To_Protected_Subprogram
9507                       (Param_Spec);
9508                end if;
9509             end;
9510          end if;
9511
9512          Set_Etype (Formal, Formal_Type);
9513
9514          --  Deal with default expression if present
9515
9516          Default := Expression (Param_Spec);
9517
9518          if Present (Default) then
9519             Check_SPARK_Restriction
9520               ("default expression is not allowed", Default);
9521
9522             if Out_Present (Param_Spec) then
9523                Error_Msg_N
9524                  ("default initialization only allowed for IN parameters",
9525                   Param_Spec);
9526             end if;
9527
9528             --  Do the special preanalysis of the expression (see section on
9529             --  "Handling of Default Expressions" in the spec of package Sem).
9530
9531             Preanalyze_Spec_Expression (Default, Formal_Type);
9532
9533             --  An access to constant cannot be the default for
9534             --  an access parameter that is an access to variable.
9535
9536             if Ekind (Formal_Type) = E_Anonymous_Access_Type
9537               and then not Is_Access_Constant (Formal_Type)
9538               and then Is_Access_Type (Etype (Default))
9539               and then Is_Access_Constant (Etype (Default))
9540             then
9541                Error_Msg_N
9542                  ("formal that is access to variable cannot be initialized " &
9543                     "with an access-to-constant expression", Default);
9544             end if;
9545
9546             --  Check that the designated type of an access parameter's default
9547             --  is not a class-wide type unless the parameter's designated type
9548             --  is also class-wide.
9549
9550             if Ekind (Formal_Type) = E_Anonymous_Access_Type
9551               and then not Designates_From_With_Type (Formal_Type)
9552               and then Is_Class_Wide_Default (Default)
9553               and then not Is_Class_Wide_Type (Designated_Type (Formal_Type))
9554             then
9555                Error_Msg_N
9556                  ("access to class-wide expression not allowed here", Default);
9557             end if;
9558
9559             --  Check incorrect use of dynamically tagged expressions
9560
9561             if Is_Tagged_Type (Formal_Type) then
9562                Check_Dynamically_Tagged_Expression
9563                  (Expr        => Default,
9564                   Typ         => Formal_Type,
9565                   Related_Nod => Default);
9566             end if;
9567          end if;
9568
9569          --  Ada 2005 (AI-231): Static checks
9570
9571          if Ada_Version >= Ada_2005
9572            and then Is_Access_Type (Etype (Formal))
9573            and then Can_Never_Be_Null (Etype (Formal))
9574          then
9575             Null_Exclusion_Static_Checks (Param_Spec);
9576          end if;
9577
9578       <<Continue>>
9579          Next (Param_Spec);
9580       end loop;
9581
9582       --  If this is the formal part of a function specification, analyze the
9583       --  subtype mark in the context where the formals are visible but not
9584       --  yet usable, and may hide outer homographs.
9585
9586       if Nkind (Related_Nod) = N_Function_Specification then
9587          Analyze_Return_Type (Related_Nod);
9588       end if;
9589
9590       --  Now set the kind (mode) of each formal
9591
9592       Param_Spec := First (T);
9593       while Present (Param_Spec) loop
9594          Formal := Defining_Identifier (Param_Spec);
9595          Set_Formal_Mode (Formal);
9596
9597          if Ekind (Formal) = E_In_Parameter then
9598             Set_Default_Value (Formal, Expression (Param_Spec));
9599
9600             if Present (Expression (Param_Spec)) then
9601                Default :=  Expression (Param_Spec);
9602
9603                if Is_Scalar_Type (Etype (Default)) then
9604                   if Nkind (Parameter_Type (Param_Spec)) /=
9605                                               N_Access_Definition
9606                   then
9607                      Formal_Type := Entity (Parameter_Type (Param_Spec));
9608                   else
9609                      Formal_Type :=
9610                        Access_Definition
9611                          (Related_Nod, Parameter_Type (Param_Spec));
9612                   end if;
9613
9614                   Apply_Scalar_Range_Check (Default, Formal_Type);
9615                end if;
9616             end if;
9617
9618          elsif Ekind (Formal) = E_Out_Parameter then
9619             Num_Out_Params := Num_Out_Params + 1;
9620
9621             if Num_Out_Params = 1 then
9622                First_Out_Param := Formal;
9623             end if;
9624
9625          elsif Ekind (Formal) = E_In_Out_Parameter then
9626             Num_Out_Params := Num_Out_Params + 1;
9627          end if;
9628
9629          --  Skip remaining processing if formal type was in error
9630
9631          if Etype (Formal) = Any_Type or else Error_Posted (Formal) then
9632             goto Next_Parameter;
9633          end if;
9634
9635          --  Force call by reference if aliased
9636
9637          if Is_Aliased (Formal) then
9638             Set_Mechanism (Formal, By_Reference);
9639
9640             --  Warn if user asked this to be passed by copy
9641
9642             if Convention (Formal_Type) = Convention_Ada_Pass_By_Copy then
9643                Error_Msg_N
9644                  ("?cannot pass aliased parameter & by copy", Formal);
9645             end if;
9646
9647          --  Force mechanism if type has Convention Ada_Pass_By_Ref/Copy
9648
9649          elsif Convention (Formal_Type) = Convention_Ada_Pass_By_Copy then
9650             Set_Mechanism (Formal, By_Copy);
9651
9652          elsif Convention (Formal_Type) = Convention_Ada_Pass_By_Reference then
9653             Set_Mechanism (Formal, By_Reference);
9654          end if;
9655
9656       <<Next_Parameter>>
9657          Next (Param_Spec);
9658       end loop;
9659
9660       if Present (First_Out_Param) and then Num_Out_Params = 1 then
9661          Set_Is_Only_Out_Parameter (First_Out_Param);
9662       end if;
9663    end Process_Formals;
9664
9665    ------------------
9666    -- Process_PPCs --
9667    ------------------
9668
9669    procedure Process_PPCs
9670      (N       : Node_Id;
9671       Spec_Id : Entity_Id;
9672       Body_Id : Entity_Id)
9673    is
9674       Loc   : constant Source_Ptr := Sloc (N);
9675       Prag  : Node_Id;
9676       Parms : List_Id;
9677
9678       Designator : Entity_Id;
9679       --  Subprogram designator, set from Spec_Id if present, else Body_Id
9680
9681       Precond : Node_Id := Empty;
9682       --  Set non-Empty if we prepend precondition to the declarations. This
9683       --  is used to hook up inherited preconditions (adding the condition
9684       --  expression with OR ELSE, and adding the message).
9685
9686       Inherited_Precond : Node_Id;
9687       --  Precondition inherited from parent subprogram
9688
9689       Inherited : constant Subprogram_List :=
9690                      Inherited_Subprograms (Spec_Id);
9691       --  List of subprograms inherited by this subprogram
9692
9693       Plist : List_Id := No_List;
9694       --  List of generated postconditions
9695
9696       function Grab_PPC (Pspec : Entity_Id := Empty) return Node_Id;
9697       --  Prag contains an analyzed precondition or postcondition pragma. This
9698       --  function copies the pragma, changes it to the corresponding Check
9699       --  pragma and returns the Check pragma as the result. If Pspec is non-
9700       --  empty, this is the case of inheriting a PPC, where we must change
9701       --  references to parameters of the inherited subprogram to point to the
9702       --  corresponding parameters of the current subprogram.
9703
9704       function Invariants_Or_Predicates_Present return Boolean;
9705       --  Determines if any invariants or predicates are present for any OUT
9706       --  or IN OUT parameters of the subprogram, or (for a function) if the
9707       --  return value has an invariant.
9708
9709       function Is_Public_Subprogram_For (T : Entity_Id) return Boolean;
9710       --  T is the entity for a private type for which invariants are defined.
9711       --  This function returns True if the procedure corresponding to the
9712       --  value of Designator is a public procedure from the point of view of
9713       --  this type (i.e. its spec is in the visible part of the package that
9714       --  contains the declaration of the private type). A True value means
9715       --  that an invariant check is required (for an IN OUT parameter, or
9716       --  the returned value of a function.
9717
9718       --------------
9719       -- Grab_PPC --
9720       --------------
9721
9722       function Grab_PPC (Pspec : Entity_Id := Empty) return Node_Id is
9723          Nam : constant Name_Id := Pragma_Name (Prag);
9724          Map : Elist_Id;
9725          CP  : Node_Id;
9726
9727       begin
9728          --  Prepare map if this is the case where we have to map entities of
9729          --  arguments in the overridden subprogram to corresponding entities
9730          --  of the current subprogram.
9731
9732          if No (Pspec) then
9733             Map := No_Elist;
9734
9735          else
9736             declare
9737                PF : Entity_Id;
9738                CF : Entity_Id;
9739
9740             begin
9741                Map := New_Elmt_List;
9742                PF := First_Formal (Pspec);
9743                CF := First_Formal (Designator);
9744                while Present (PF) loop
9745                   Append_Elmt (PF, Map);
9746                   Append_Elmt (CF, Map);
9747                   Next_Formal (PF);
9748                   Next_Formal (CF);
9749                end loop;
9750             end;
9751          end if;
9752
9753          --  Now we can copy the tree, doing any required substitutions
9754
9755          CP := New_Copy_Tree (Prag, Map => Map, New_Scope => Current_Scope);
9756
9757          --  Set Analyzed to false, since we want to reanalyze the check
9758          --  procedure. Note that it is only at the outer level that we
9759          --  do this fiddling, for the spec cases, the already preanalyzed
9760          --  parameters are not affected.
9761
9762          Set_Analyzed (CP, False);
9763
9764          --  We also make sure Comes_From_Source is False for the copy
9765
9766          Set_Comes_From_Source (CP, False);
9767
9768          --  For a postcondition pragma within a generic, preserve the pragma
9769          --  for later expansion.
9770
9771          if Nam = Name_Postcondition
9772            and then not Expander_Active
9773          then
9774             return CP;
9775          end if;
9776
9777          --  Change copy of pragma into corresponding pragma Check
9778
9779          Prepend_To (Pragma_Argument_Associations (CP),
9780            Make_Pragma_Argument_Association (Sloc (Prag),
9781              Expression => Make_Identifier (Loc, Nam)));
9782          Set_Pragma_Identifier (CP, Make_Identifier (Sloc (Prag), Name_Check));
9783
9784          --  If this is inherited case and the current message starts with
9785          --  "failed p", we change it to "failed inherited p...".
9786
9787          if Present (Pspec) then
9788             declare
9789                Msg : constant Node_Id :=
9790                        Last (Pragma_Argument_Associations (CP));
9791
9792             begin
9793                if Chars (Msg) = Name_Message then
9794                   String_To_Name_Buffer (Strval (Expression (Msg)));
9795
9796                   if Name_Buffer (1 .. 8) = "failed p" then
9797                      Insert_Str_In_Name_Buffer ("inherited ", 8);
9798                      Set_Strval
9799                        (Expression (Last (Pragma_Argument_Associations (CP))),
9800                         String_From_Name_Buffer);
9801                   end if;
9802                end if;
9803             end;
9804          end if;
9805
9806          --  Return the check pragma
9807
9808          return CP;
9809       end Grab_PPC;
9810
9811       --------------------------------------
9812       -- Invariants_Or_Predicates_Present --
9813       --------------------------------------
9814
9815       function Invariants_Or_Predicates_Present return Boolean is
9816          Formal : Entity_Id;
9817
9818       begin
9819          --  Check function return result
9820
9821          if Ekind (Designator) /= E_Procedure
9822            and then Has_Invariants (Etype (Designator))
9823          then
9824             return True;
9825          end if;
9826
9827          --  Check parameters
9828
9829          Formal := First_Formal (Designator);
9830          while Present (Formal) loop
9831             if Ekind (Formal) /= E_In_Parameter
9832               and then
9833                 (Has_Invariants (Etype (Formal))
9834                   or else Present (Predicate_Function (Etype (Formal))))
9835             then
9836                return True;
9837             end if;
9838
9839             Next_Formal (Formal);
9840          end loop;
9841
9842          return False;
9843       end Invariants_Or_Predicates_Present;
9844
9845       ------------------------------
9846       -- Is_Public_Subprogram_For --
9847       ------------------------------
9848
9849       --  The type T is a private type, its declaration is therefore in
9850       --  the list of public declarations of some package. The test for a
9851       --  public subprogram is that its declaration is in this same list
9852       --  of declarations for the same package (note that all the public
9853       --  declarations are in one list, and all the private declarations
9854       --  in another, so this deals with the public/private distinction).
9855
9856       function Is_Public_Subprogram_For (T : Entity_Id) return Boolean is
9857          DD : constant Node_Id := Unit_Declaration_Node (Designator);
9858          --  The subprogram declaration for the subprogram in question
9859
9860          TL : constant List_Id :=
9861                 Visible_Declarations
9862                   (Specification (Unit_Declaration_Node (Scope (T))));
9863          --  The list of declarations containing the private declaration of
9864          --  the type. We know it is a private type, so we know its scope is
9865          --  the package in question, and we know it must be in the visible
9866          --  declarations of this package.
9867
9868       begin
9869          --  If the subprogram declaration is not a list member, it must be
9870          --  an Init_Proc, in which case we want to consider it to be a
9871          --  public subprogram, since we do get initializations to deal with.
9872
9873          if not Is_List_Member (DD) then
9874             return True;
9875
9876          --  Otherwise we test whether the subprogram is declared in the
9877          --  visible declarations of the package containing the type.
9878
9879          else
9880             return TL = List_Containing (DD);
9881          end if;
9882       end Is_Public_Subprogram_For;
9883
9884    --  Start of processing for Process_PPCs
9885
9886    begin
9887       --  Capture designator from spec if present, else from body
9888
9889       if Present (Spec_Id) then
9890          Designator := Spec_Id;
9891       else
9892          Designator := Body_Id;
9893       end if;
9894
9895       --  Grab preconditions from spec
9896
9897       if Present (Spec_Id) then
9898
9899          --  Loop through PPC pragmas from spec. Note that preconditions from
9900          --  the body will be analyzed and converted when we scan the body
9901          --  declarations below.
9902
9903          Prag := Spec_PPC_List (Contract (Spec_Id));
9904          while Present (Prag) loop
9905             if Pragma_Name (Prag) = Name_Precondition then
9906
9907                --  For Pre (or Precondition pragma), we simply prepend the
9908                --  pragma to the list of declarations right away so that it
9909                --  will be executed at the start of the procedure. Note that
9910                --  this processing reverses the order of the list, which is
9911                --  what we want since new entries were chained to the head of
9912                --  the list. There can be more than one precondition when we
9913                --  use pragma Precondition.
9914
9915                if not Class_Present (Prag) then
9916                   Prepend (Grab_PPC, Declarations (N));
9917
9918                --  For Pre'Class there can only be one pragma, and we save
9919                --  it in Precond for now. We will add inherited Pre'Class
9920                --  stuff before inserting this pragma in the declarations.
9921                else
9922                   Precond := Grab_PPC;
9923                end if;
9924             end if;
9925
9926             Prag := Next_Pragma (Prag);
9927          end loop;
9928
9929          --  Now deal with inherited preconditions
9930
9931          for J in Inherited'Range loop
9932             Prag := Spec_PPC_List (Contract (Inherited (J)));
9933
9934             while Present (Prag) loop
9935                if Pragma_Name (Prag) = Name_Precondition
9936                  and then Class_Present (Prag)
9937                then
9938                   Inherited_Precond := Grab_PPC (Inherited (J));
9939
9940                   --  No precondition so far, so establish this as the first
9941
9942                   if No (Precond) then
9943                      Precond := Inherited_Precond;
9944
9945                   --  Here we already have a precondition, add inherited one
9946
9947                   else
9948                      --  Add new precondition to old one using OR ELSE
9949
9950                      declare
9951                         New_Expr : constant Node_Id :=
9952                                      Get_Pragma_Arg
9953                                        (Next
9954                                          (First
9955                                            (Pragma_Argument_Associations
9956                                              (Inherited_Precond))));
9957                         Old_Expr : constant Node_Id :=
9958                                      Get_Pragma_Arg
9959                                        (Next
9960                                          (First
9961                                            (Pragma_Argument_Associations
9962                                              (Precond))));
9963
9964                      begin
9965                         if Paren_Count (Old_Expr) = 0 then
9966                            Set_Paren_Count (Old_Expr, 1);
9967                         end if;
9968
9969                         if Paren_Count (New_Expr) = 0 then
9970                            Set_Paren_Count (New_Expr, 1);
9971                         end if;
9972
9973                         Rewrite (Old_Expr,
9974                           Make_Or_Else (Sloc (Old_Expr),
9975                             Left_Opnd  => Relocate_Node (Old_Expr),
9976                             Right_Opnd => New_Expr));
9977                      end;
9978
9979                      --  Add new message in the form:
9980
9981                      --     failed precondition from bla
9982                      --       also failed inherited precondition from bla
9983                      --       ...
9984
9985                      --  Skip this if exception locations are suppressed
9986
9987                      if not Exception_Locations_Suppressed then
9988                         declare
9989                            New_Msg : constant Node_Id :=
9990                                        Get_Pragma_Arg
9991                                          (Last
9992                                             (Pragma_Argument_Associations
9993                                                (Inherited_Precond)));
9994                            Old_Msg : constant Node_Id :=
9995                                        Get_Pragma_Arg
9996                                          (Last
9997                                             (Pragma_Argument_Associations
9998                                                (Precond)));
9999                         begin
10000                            Start_String (Strval (Old_Msg));
10001                            Store_String_Chars (ASCII.LF & "  also ");
10002                            Store_String_Chars (Strval (New_Msg));
10003                            Set_Strval (Old_Msg, End_String);
10004                         end;
10005                      end if;
10006                   end if;
10007                end if;
10008
10009                Prag := Next_Pragma (Prag);
10010             end loop;
10011          end loop;
10012
10013          --  If we have built a precondition for Pre'Class (including any
10014          --  Pre'Class aspects inherited from parent subprograms), then we
10015          --  insert this composite precondition at this stage.
10016
10017          if Present (Precond) then
10018             Prepend (Precond, Declarations (N));
10019          end if;
10020       end if;
10021
10022       --  Build postconditions procedure if needed and prepend the following
10023       --  declaration to the start of the declarations for the subprogram.
10024
10025       --     procedure _postconditions [(_Result : resulttype)] is
10026       --     begin
10027       --        pragma Check (Postcondition, condition [,message]);
10028       --        pragma Check (Postcondition, condition [,message]);
10029       --        ...
10030       --        Invariant_Procedure (_Result) ...
10031       --        Invariant_Procedure (Arg1)
10032       --        ...
10033       --     end;
10034
10035       --  First we deal with the postconditions in the body
10036
10037       if Is_Non_Empty_List (Declarations (N)) then
10038
10039          --  Loop through declarations
10040
10041          Prag := First (Declarations (N));
10042          while Present (Prag) loop
10043             if Nkind (Prag) = N_Pragma then
10044
10045                --  If pragma, capture if enabled postcondition, else ignore
10046
10047                if Pragma_Name (Prag) = Name_Postcondition
10048                  and then Check_Enabled (Name_Postcondition)
10049                then
10050                   if Plist = No_List then
10051                      Plist := Empty_List;
10052                   end if;
10053
10054                   Analyze (Prag);
10055
10056                   --  If expansion is disabled, as in a generic unit, save
10057                   --  pragma for later expansion.
10058
10059                   if not Expander_Active then
10060                      Prepend (Grab_PPC, Declarations (N));
10061                   else
10062                      Append (Grab_PPC, Plist);
10063                   end if;
10064                end if;
10065
10066                Next (Prag);
10067
10068             --  Not a pragma, if comes from source, then end scan
10069
10070             elsif Comes_From_Source (Prag) then
10071                exit;
10072
10073             --  Skip stuff not coming from source
10074
10075             else
10076                Next (Prag);
10077             end if;
10078          end loop;
10079       end if;
10080
10081       --  Now deal with any postconditions from the spec
10082
10083       if Present (Spec_Id) then
10084          Spec_Postconditions : declare
10085             procedure Process_Post_Conditions
10086               (Spec  : Node_Id;
10087                Class : Boolean);
10088             --  This processes the Spec_PPC_List from Spec, processing any
10089             --  postconditions from the list. If Class is True, then only
10090             --  postconditions marked with Class_Present are considered.
10091             --  The caller has checked that Spec_PPC_List is non-Empty.
10092
10093             -----------------------------
10094             -- Process_Post_Conditions --
10095             -----------------------------
10096
10097             procedure Process_Post_Conditions
10098               (Spec  : Node_Id;
10099                Class : Boolean)
10100             is
10101                Pspec : Node_Id;
10102
10103             begin
10104                if Class then
10105                   Pspec := Spec;
10106                else
10107                   Pspec := Empty;
10108                end if;
10109
10110                --  Loop through PPC pragmas from spec
10111
10112                Prag := Spec_PPC_List (Contract (Spec));
10113                loop
10114                   if Pragma_Name (Prag) = Name_Postcondition
10115                     and then (not Class or else Class_Present (Prag))
10116                   then
10117                      if Plist = No_List then
10118                         Plist := Empty_List;
10119                      end if;
10120
10121                      if not Expander_Active then
10122                         Prepend
10123                           (Grab_PPC (Pspec), Declarations (N));
10124                      else
10125                         Append (Grab_PPC (Pspec), Plist);
10126                      end if;
10127                   end if;
10128
10129                   Prag := Next_Pragma (Prag);
10130                   exit when No (Prag);
10131                end loop;
10132             end Process_Post_Conditions;
10133
10134          --  Start of processing for Spec_Postconditions
10135
10136          begin
10137             if Present (Spec_PPC_List (Contract (Spec_Id))) then
10138                Process_Post_Conditions (Spec_Id, Class => False);
10139             end if;
10140
10141             --  Process inherited postconditions
10142
10143             for J in Inherited'Range loop
10144                if Present (Spec_PPC_List (Contract (Inherited (J)))) then
10145                   Process_Post_Conditions (Inherited (J), Class => True);
10146                end if;
10147             end loop;
10148          end Spec_Postconditions;
10149       end if;
10150
10151       --  If we had any postconditions and expansion is enabled, or if the
10152       --  procedure has invariants, then build the _Postconditions procedure.
10153
10154       if (Present (Plist) or else Invariants_Or_Predicates_Present)
10155         and then Expander_Active
10156       then
10157          if No (Plist) then
10158             Plist := Empty_List;
10159          end if;
10160
10161          --  Special processing for function case
10162
10163          if Ekind (Designator) /= E_Procedure then
10164             declare
10165                Rent : constant Entity_Id :=
10166                         Make_Defining_Identifier (Loc, Name_uResult);
10167                Ftyp : constant Entity_Id := Etype (Designator);
10168
10169             begin
10170                Set_Etype (Rent, Ftyp);
10171
10172                --  Add argument for return
10173
10174                Parms :=
10175                  New_List (
10176                    Make_Parameter_Specification (Loc,
10177                      Parameter_Type      => New_Occurrence_Of (Ftyp, Loc),
10178                      Defining_Identifier => Rent));
10179
10180                --  Add invariant call if returning type with invariants and
10181                --  this is a public function, i.e. a function declared in the
10182                --  visible part of the package defining the private type.
10183
10184                if Has_Invariants (Etype (Rent))
10185                  and then Present (Invariant_Procedure (Etype (Rent)))
10186                  and then Is_Public_Subprogram_For (Etype (Rent))
10187                then
10188                   Append_To (Plist,
10189                     Make_Invariant_Call (New_Occurrence_Of (Rent, Loc)));
10190                end if;
10191             end;
10192
10193          --  Procedure rather than a function
10194
10195          else
10196             Parms := No_List;
10197          end if;
10198
10199          --  Add invariant calls and predicate calls for parameters. Note that
10200          --  this is done for functions as well, since in Ada 2012 they can
10201          --  have IN OUT args.
10202
10203          declare
10204             Formal : Entity_Id;
10205             Ftype  : Entity_Id;
10206
10207          begin
10208             Formal := First_Formal (Designator);
10209             while Present (Formal) loop
10210                if Ekind (Formal) /= E_In_Parameter then
10211                   Ftype := Etype (Formal);
10212
10213                   if Has_Invariants (Ftype)
10214                     and then Present (Invariant_Procedure (Ftype))
10215                     and then Is_Public_Subprogram_For (Ftype)
10216                   then
10217                      Append_To (Plist,
10218                        Make_Invariant_Call
10219                          (New_Occurrence_Of (Formal, Loc)));
10220                   end if;
10221
10222                   if Present (Predicate_Function (Ftype)) then
10223                      Append_To (Plist,
10224                        Make_Predicate_Check
10225                          (Ftype, New_Occurrence_Of (Formal, Loc)));
10226                   end if;
10227                end if;
10228
10229                Next_Formal (Formal);
10230             end loop;
10231          end;
10232
10233          --  Build and insert postcondition procedure
10234
10235          declare
10236             Post_Proc : constant Entity_Id :=
10237                           Make_Defining_Identifier (Loc,
10238                             Chars => Name_uPostconditions);
10239             --  The entity for the _Postconditions procedure
10240
10241          begin
10242             Prepend_To (Declarations (N),
10243               Make_Subprogram_Body (Loc,
10244                 Specification =>
10245                   Make_Procedure_Specification (Loc,
10246                     Defining_Unit_Name => Post_Proc,
10247                     Parameter_Specifications => Parms),
10248
10249                 Declarations => Empty_List,
10250
10251                 Handled_Statement_Sequence =>
10252                   Make_Handled_Sequence_Of_Statements (Loc,
10253                     Statements => Plist)));
10254
10255             Set_Ekind (Post_Proc, E_Procedure);
10256
10257             --  If this is a procedure, set the Postcondition_Proc attribute on
10258             --  the proper defining entity for the subprogram.
10259
10260             if Ekind (Designator) = E_Procedure then
10261                Set_Postcondition_Proc (Designator, Post_Proc);
10262             end if;
10263          end;
10264
10265          Set_Has_Postconditions (Designator);
10266       end if;
10267    end Process_PPCs;
10268
10269    ----------------------------
10270    -- Reference_Body_Formals --
10271    ----------------------------
10272
10273    procedure Reference_Body_Formals (Spec : Entity_Id; Bod : Entity_Id) is
10274       Fs : Entity_Id;
10275       Fb : Entity_Id;
10276
10277    begin
10278       if Error_Posted (Spec) then
10279          return;
10280       end if;
10281
10282       --  Iterate over both lists. They may be of different lengths if the two
10283       --  specs are not conformant.
10284
10285       Fs := First_Formal (Spec);
10286       Fb := First_Formal (Bod);
10287       while Present (Fs) and then Present (Fb) loop
10288          Generate_Reference (Fs, Fb, 'b');
10289
10290          if Style_Check then
10291             Style.Check_Identifier (Fb, Fs);
10292          end if;
10293
10294          Set_Spec_Entity (Fb, Fs);
10295          Set_Referenced (Fs, False);
10296          Next_Formal (Fs);
10297          Next_Formal (Fb);
10298       end loop;
10299    end Reference_Body_Formals;
10300
10301    -------------------------
10302    -- Set_Actual_Subtypes --
10303    -------------------------
10304
10305    procedure Set_Actual_Subtypes (N : Node_Id; Subp : Entity_Id) is
10306       Decl           : Node_Id;
10307       Formal         : Entity_Id;
10308       T              : Entity_Id;
10309       First_Stmt     : Node_Id := Empty;
10310       AS_Needed      : Boolean;
10311
10312    begin
10313       --  If this is an empty initialization procedure, no need to create
10314       --  actual subtypes (small optimization).
10315
10316       if Ekind (Subp) = E_Procedure
10317         and then Is_Null_Init_Proc (Subp)
10318       then
10319          return;
10320       end if;
10321
10322       Formal := First_Formal (Subp);
10323       while Present (Formal) loop
10324          T := Etype (Formal);
10325
10326          --  We never need an actual subtype for a constrained formal
10327
10328          if Is_Constrained (T) then
10329             AS_Needed := False;
10330
10331          --  If we have unknown discriminants, then we do not need an actual
10332          --  subtype, or more accurately we cannot figure it out! Note that
10333          --  all class-wide types have unknown discriminants.
10334
10335          elsif Has_Unknown_Discriminants (T) then
10336             AS_Needed := False;
10337
10338          --  At this stage we have an unconstrained type that may need an
10339          --  actual subtype. For sure the actual subtype is needed if we have
10340          --  an unconstrained array type.
10341
10342          elsif Is_Array_Type (T) then
10343             AS_Needed := True;
10344
10345          --  The only other case needing an actual subtype is an unconstrained
10346          --  record type which is an IN parameter (we cannot generate actual
10347          --  subtypes for the OUT or IN OUT case, since an assignment can
10348          --  change the discriminant values. However we exclude the case of
10349          --  initialization procedures, since discriminants are handled very
10350          --  specially in this context, see the section entitled "Handling of
10351          --  Discriminants" in Einfo.
10352
10353          --  We also exclude the case of Discrim_SO_Functions (functions used
10354          --  in front end layout mode for size/offset values), since in such
10355          --  functions only discriminants are referenced, and not only are such
10356          --  subtypes not needed, but they cannot always be generated, because
10357          --  of order of elaboration issues.
10358
10359          elsif Is_Record_Type (T)
10360            and then Ekind (Formal) = E_In_Parameter
10361            and then Chars (Formal) /= Name_uInit
10362            and then not Is_Unchecked_Union (T)
10363            and then not Is_Discrim_SO_Function (Subp)
10364          then
10365             AS_Needed := True;
10366
10367          --  All other cases do not need an actual subtype
10368
10369          else
10370             AS_Needed := False;
10371          end if;
10372
10373          --  Generate actual subtypes for unconstrained arrays and
10374          --  unconstrained discriminated records.
10375
10376          if AS_Needed then
10377             if Nkind (N) = N_Accept_Statement then
10378
10379                --  If expansion is active, the formal is replaced by a local
10380                --  variable that renames the corresponding entry of the
10381                --  parameter block, and it is this local variable that may
10382                --  require an actual subtype.
10383
10384                if Full_Expander_Active then
10385                   Decl := Build_Actual_Subtype (T, Renamed_Object (Formal));
10386                else
10387                   Decl := Build_Actual_Subtype (T, Formal);
10388                end if;
10389
10390                if Present (Handled_Statement_Sequence (N)) then
10391                   First_Stmt :=
10392                     First (Statements (Handled_Statement_Sequence (N)));
10393                   Prepend (Decl, Statements (Handled_Statement_Sequence (N)));
10394                   Mark_Rewrite_Insertion (Decl);
10395                else
10396                   --  If the accept statement has no body, there will be no
10397                   --  reference to the actuals, so no need to compute actual
10398                   --  subtypes.
10399
10400                   return;
10401                end if;
10402
10403             else
10404                Decl := Build_Actual_Subtype (T, Formal);
10405                Prepend (Decl, Declarations (N));
10406                Mark_Rewrite_Insertion (Decl);
10407             end if;
10408
10409             --  The declaration uses the bounds of an existing object, and
10410             --  therefore needs no constraint checks.
10411
10412             Analyze (Decl, Suppress => All_Checks);
10413
10414             --  We need to freeze manually the generated type when it is
10415             --  inserted anywhere else than in a declarative part.
10416
10417             if Present (First_Stmt) then
10418                Insert_List_Before_And_Analyze (First_Stmt,
10419                  Freeze_Entity (Defining_Identifier (Decl), N));
10420             end if;
10421
10422             if Nkind (N) = N_Accept_Statement
10423               and then Full_Expander_Active
10424             then
10425                Set_Actual_Subtype (Renamed_Object (Formal),
10426                  Defining_Identifier (Decl));
10427             else
10428                Set_Actual_Subtype (Formal, Defining_Identifier (Decl));
10429             end if;
10430          end if;
10431
10432          Next_Formal (Formal);
10433       end loop;
10434    end Set_Actual_Subtypes;
10435
10436    ---------------------
10437    -- Set_Formal_Mode --
10438    ---------------------
10439
10440    procedure Set_Formal_Mode (Formal_Id : Entity_Id) is
10441       Spec : constant Node_Id := Parent (Formal_Id);
10442
10443    begin
10444       --  Note: we set Is_Known_Valid for IN parameters and IN OUT parameters
10445       --  since we ensure that corresponding actuals are always valid at the
10446       --  point of the call.
10447
10448       if Out_Present (Spec) then
10449          if Ekind (Scope (Formal_Id)) = E_Function
10450            or else Ekind (Scope (Formal_Id)) = E_Generic_Function
10451          then
10452             --  [IN] OUT parameters allowed for functions in Ada 2012
10453
10454             if Ada_Version >= Ada_2012 then
10455                if In_Present (Spec) then
10456                   Set_Ekind (Formal_Id, E_In_Out_Parameter);
10457                else
10458                   Set_Ekind (Formal_Id, E_Out_Parameter);
10459                end if;
10460
10461             --  But not in earlier versions of Ada
10462
10463             else
10464                Error_Msg_N ("functions can only have IN parameters", Spec);
10465                Set_Ekind (Formal_Id, E_In_Parameter);
10466             end if;
10467
10468          elsif In_Present (Spec) then
10469             Set_Ekind (Formal_Id, E_In_Out_Parameter);
10470
10471          else
10472             Set_Ekind               (Formal_Id, E_Out_Parameter);
10473             Set_Never_Set_In_Source (Formal_Id, True);
10474             Set_Is_True_Constant    (Formal_Id, False);
10475             Set_Current_Value       (Formal_Id, Empty);
10476          end if;
10477
10478       else
10479          Set_Ekind (Formal_Id, E_In_Parameter);
10480       end if;
10481
10482       --  Set Is_Known_Non_Null for access parameters since the language
10483       --  guarantees that access parameters are always non-null. We also set
10484       --  Can_Never_Be_Null, since there is no way to change the value.
10485
10486       if Nkind (Parameter_Type (Spec)) = N_Access_Definition then
10487
10488          --  Ada 2005 (AI-231): In Ada 95, access parameters are always non-
10489          --  null; In Ada 2005, only if then null_exclusion is explicit.
10490
10491          if Ada_Version < Ada_2005
10492            or else Can_Never_Be_Null (Etype (Formal_Id))
10493          then
10494             Set_Is_Known_Non_Null (Formal_Id);
10495             Set_Can_Never_Be_Null (Formal_Id);
10496          end if;
10497
10498       --  Ada 2005 (AI-231): Null-exclusion access subtype
10499
10500       elsif Is_Access_Type (Etype (Formal_Id))
10501         and then Can_Never_Be_Null (Etype (Formal_Id))
10502       then
10503          Set_Is_Known_Non_Null (Formal_Id);
10504
10505          --  We can also set Can_Never_Be_Null (thus preventing some junk
10506          --  access checks) for the case of an IN parameter, which cannot
10507          --  be changed, or for an IN OUT parameter, which can be changed but
10508          --  not to a null value. But for an OUT parameter, the initial value
10509          --  passed in can be null, so we can't set this flag in that case.
10510
10511          if Ekind (Formal_Id) /= E_Out_Parameter then
10512             Set_Can_Never_Be_Null (Formal_Id);
10513          end if;
10514       end if;
10515
10516       Set_Mechanism (Formal_Id, Default_Mechanism);
10517       Set_Formal_Validity (Formal_Id);
10518    end Set_Formal_Mode;
10519
10520    -------------------------
10521    -- Set_Formal_Validity --
10522    -------------------------
10523
10524    procedure Set_Formal_Validity (Formal_Id : Entity_Id) is
10525    begin
10526       --  If no validity checking, then we cannot assume anything about the
10527       --  validity of parameters, since we do not know there is any checking
10528       --  of the validity on the call side.
10529
10530       if not Validity_Checks_On then
10531          return;
10532
10533       --  If validity checking for parameters is enabled, this means we are
10534       --  not supposed to make any assumptions about argument values.
10535
10536       elsif Validity_Check_Parameters then
10537          return;
10538
10539       --  If we are checking in parameters, we will assume that the caller is
10540       --  also checking parameters, so we can assume the parameter is valid.
10541
10542       elsif Ekind (Formal_Id) = E_In_Parameter
10543         and then Validity_Check_In_Params
10544       then
10545          Set_Is_Known_Valid (Formal_Id, True);
10546
10547       --  Similar treatment for IN OUT parameters
10548
10549       elsif Ekind (Formal_Id) = E_In_Out_Parameter
10550         and then Validity_Check_In_Out_Params
10551       then
10552          Set_Is_Known_Valid (Formal_Id, True);
10553       end if;
10554    end Set_Formal_Validity;
10555
10556    ------------------------
10557    -- Subtype_Conformant --
10558    ------------------------
10559
10560    function Subtype_Conformant
10561      (New_Id                   : Entity_Id;
10562       Old_Id                   : Entity_Id;
10563       Skip_Controlling_Formals : Boolean := False) return Boolean
10564    is
10565       Result : Boolean;
10566    begin
10567       Check_Conformance (New_Id, Old_Id, Subtype_Conformant, False, Result,
10568         Skip_Controlling_Formals => Skip_Controlling_Formals);
10569       return Result;
10570    end Subtype_Conformant;
10571
10572    ---------------------
10573    -- Type_Conformant --
10574    ---------------------
10575
10576    function Type_Conformant
10577      (New_Id                   : Entity_Id;
10578       Old_Id                   : Entity_Id;
10579       Skip_Controlling_Formals : Boolean := False) return Boolean
10580    is
10581       Result : Boolean;
10582    begin
10583       May_Hide_Profile := False;
10584
10585       Check_Conformance
10586         (New_Id, Old_Id, Type_Conformant, False, Result,
10587          Skip_Controlling_Formals => Skip_Controlling_Formals);
10588       return Result;
10589    end Type_Conformant;
10590
10591    -------------------------------
10592    -- Valid_Operator_Definition --
10593    -------------------------------
10594
10595    procedure Valid_Operator_Definition (Designator : Entity_Id) is
10596       N    : Integer := 0;
10597       F    : Entity_Id;
10598       Id   : constant Name_Id := Chars (Designator);
10599       N_OK : Boolean;
10600
10601    begin
10602       F := First_Formal (Designator);
10603       while Present (F) loop
10604          N := N + 1;
10605
10606          if Present (Default_Value (F)) then
10607             Error_Msg_N
10608               ("default values not allowed for operator parameters",
10609                Parent (F));
10610          end if;
10611
10612          Next_Formal (F);
10613       end loop;
10614
10615       --  Verify that user-defined operators have proper number of arguments
10616       --  First case of operators which can only be unary
10617
10618       if Id = Name_Op_Not
10619         or else Id = Name_Op_Abs
10620       then
10621          N_OK := (N = 1);
10622
10623       --  Case of operators which can be unary or binary
10624
10625       elsif Id = Name_Op_Add
10626         or Id = Name_Op_Subtract
10627       then
10628          N_OK := (N in 1 .. 2);
10629
10630       --  All other operators can only be binary
10631
10632       else
10633          N_OK := (N = 2);
10634       end if;
10635
10636       if not N_OK then
10637          Error_Msg_N
10638            ("incorrect number of arguments for operator", Designator);
10639       end if;
10640
10641       if Id = Name_Op_Ne
10642         and then Base_Type (Etype (Designator)) = Standard_Boolean
10643         and then not Is_Intrinsic_Subprogram (Designator)
10644       then
10645          Error_Msg_N
10646             ("explicit definition of inequality not allowed", Designator);
10647       end if;
10648    end Valid_Operator_Definition;
10649
10650 end Sem_Ch6;