OSDN Git Service

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