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